diff --git a/effectful-core/src/Effectful/State/Dynamic.hs b/effectful-core/src/Effectful/State/Dynamic.hs index a592459..3904d4c 100644 --- a/effectful-core/src/Effectful/State/Dynamic.hs +++ b/effectful-core/src/Effectful/State/Dynamic.hs @@ -10,14 +10,14 @@ module Effectful.State.Dynamic -- ** Handlers -- *** Local - , runLocalState - , evalLocalState - , execLocalState + , runStateLocal + , evalStateLocal + , execStateLocal -- *** Shared - , runSharedState - , evalSharedState - , execSharedState + , runStateShared + , evalStateShared + , execStateShared -- ** Operations , get @@ -48,18 +48,18 @@ type instance DispatchOf (State s) = Dynamic -- | Run the 'State' effect with the given initial state and return the final -- value along with the final state (via "Effectful.State.Static.Local"). -runLocalState :: s -> Eff (State s : es) a -> Eff es (a, s) -runLocalState s0 = reinterpret (L.runState s0) localState +runStateLocal :: s -> Eff (State s : es) a -> Eff es (a, s) +runStateLocal s0 = reinterpret (L.runState s0) localState -- | Run the 'State' effect with the given initial state and return the final -- value, discarding the final state (via "Effectful.State.Static.Local"). -evalLocalState :: s -> Eff (State s : es) a -> Eff es a -evalLocalState s0 = reinterpret (L.evalState s0) localState +evalStateLocal :: s -> Eff (State s : es) a -> Eff es a +evalStateLocal s0 = reinterpret (L.evalState s0) localState -- | Run the 'State' effect with the given initial state and return the final -- state, discarding the final value (via "Effectful.State.Static.Local"). -execLocalState :: s -> Eff (State s : es) a -> Eff es s -execLocalState s0 = reinterpret (L.execState s0) localState +execStateLocal :: s -> Eff (State s : es) a -> Eff es s +execStateLocal s0 = reinterpret (L.execState s0) localState localState :: L.State s :> es @@ -77,18 +77,18 @@ localState env = \case -- | Run the 'State' effect with the given initial state and return the final -- value along with the final state (via "Effectful.State.Static.Shared"). -runSharedState :: s -> Eff (State s : es) a -> Eff es (a, s) -runSharedState s0 = reinterpret (S.runState s0) sharedState +runStateShared :: s -> Eff (State s : es) a -> Eff es (a, s) +runStateShared s0 = reinterpret (S.runState s0) sharedState -- | Run the 'State' effect with the given initial state and return the final -- value, discarding the final state (via "Effectful.State.Static.Shared"). -evalSharedState :: s -> Eff (State s : es) a -> Eff es a -evalSharedState s0 = reinterpret (S.evalState s0) sharedState +evalStateShared :: s -> Eff (State s : es) a -> Eff es a +evalStateShared s0 = reinterpret (S.evalState s0) sharedState -- | Run the 'State' effect with the given initial state and return the final -- state, discarding the final value (via "Effectful.State.Static.Shared"). -execSharedState :: s -> Eff (State s : es) a -> Eff es s -execSharedState s0 = reinterpret (S.execState s0) sharedState +execStateShared :: s -> Eff (State s : es) a -> Eff es s +execStateShared s0 = reinterpret (S.execState s0) sharedState sharedState :: S.State s :> es diff --git a/effectful/bench/Countdown.hs b/effectful/bench/Countdown.hs index da64225..78b7f2d 100644 --- a/effectful/bench/Countdown.hs +++ b/effectful/bench/Countdown.hs @@ -173,16 +173,16 @@ programEffectfulDynamic = do countdownEffectfulDynLocal :: Integer -> (Integer, Integer) countdownEffectfulDynLocal n = - E.runPureEff . ED.runLocalState n $ programEffectfulDynamic + E.runPureEff . ED.runStateLocal n $ programEffectfulDynamic countdownEffectfulDynShared :: Integer -> (Integer, Integer) countdownEffectfulDynShared n = - E.runPureEff . ED.runSharedState n $ programEffectfulDynamic + E.runPureEff . ED.runStateShared n $ programEffectfulDynamic countdownEffectfulDynLocalDeep :: Integer -> (Integer, Integer) countdownEffectfulDynLocalDeep n = E.runPureEff . runR . runR . runR . runR . runR - . ED.runLocalState n + . ED.runStateLocal n . runR . runR . runR . runR . runR $ programEffectfulDynamic where @@ -191,7 +191,7 @@ countdownEffectfulDynLocalDeep n = E.runPureEff countdownEffectfulDynSharedDeep :: Integer -> (Integer, Integer) countdownEffectfulDynSharedDeep n = E.runPureEff . runR . runR . runR . runR . runR - . ED.runSharedState n + . ED.runStateShared n . runR . runR . runR . runR . runR $ programEffectfulDynamic where @@ -200,8 +200,8 @@ countdownEffectfulDynSharedDeep n = E.runPureEff ---------------------------------------- -- efectful (double-dynamic) -runDoubleLocalState :: s -> E.Eff (ED.State s : es) a -> E.Eff es (a, s) -runDoubleLocalState s0 = E.reinterpret (ED.runLocalState s0) $ \env -> \case +runDoubleStateLocal :: s -> E.Eff (ED.State s : es) a -> E.Eff es (a, s) +runDoubleStateLocal s0 = E.reinterpret (ED.runStateLocal s0) $ \env -> \case ED.Get -> ED.get ED.Put s -> ED.put s ED.State f -> ED.state f @@ -209,19 +209,19 @@ runDoubleLocalState s0 = E.reinterpret (ED.runLocalState s0) $ \env -> \case countdownEffectfulDoubleDynLocal :: Integer -> (Integer, Integer) countdownEffectfulDoubleDynLocal n = - E.runPureEff . runDoubleLocalState n $ programEffectfulDynamic + E.runPureEff . runDoubleStateLocal n $ programEffectfulDynamic countdownEffectfulDoubleDynLocalDeep :: Integer -> (Integer, Integer) countdownEffectfulDoubleDynLocalDeep n = E.runPureEff . runR . runR . runR . runR . runR - . runDoubleLocalState n + . runDoubleStateLocal n . runR . runR . runR . runR . runR $ programEffectfulDynamic where runR = E.runReader () -runDoubleSharedState :: s -> E.Eff (ED.State s : es) a -> E.Eff es (a, s) -runDoubleSharedState s0 = E.reinterpret (ED.runSharedState s0) $ \env -> \case +runDoubleStateShared :: s -> E.Eff (ED.State s : es) a -> E.Eff es (a, s) +runDoubleStateShared s0 = E.reinterpret (ED.runStateShared s0) $ \env -> \case ED.Get -> ED.get ED.Put s -> ED.put s ED.State f -> ED.state f @@ -229,12 +229,12 @@ runDoubleSharedState s0 = E.reinterpret (ED.runSharedState s0) $ \env -> \case countdownEffectfulDoubleDynShared :: Integer -> (Integer, Integer) countdownEffectfulDoubleDynShared n = - E.runPureEff . runDoubleSharedState n $ programEffectfulDynamic + E.runPureEff . runDoubleStateShared n $ programEffectfulDynamic countdownEffectfulDoubleDynSharedDeep :: Integer -> (Integer, Integer) countdownEffectfulDoubleDynSharedDeep n = E.runPureEff . runR . runR . runR . runR . runR - . runDoubleSharedState n + . runDoubleStateShared n . runR . runR . runR . runR . runR $ programEffectfulDynamic where diff --git a/effectful/bench/Utils.hs b/effectful/bench/Utils.hs index 8ffb7a9..41c9bc1 100644 --- a/effectful/bench/Utils.hs +++ b/effectful/bench/Utils.hs @@ -16,6 +16,6 @@ runDeep ] a -> IO a runDeep = runEff - . evalLocalState () . evalLocalState () . evalLocalState () . evalLocalState () - . evalLocalState () . evalLocalState () . evalLocalState () . evalLocalState () - . evalLocalState () . evalLocalState () + . evalStateLocal () . evalStateLocal () . evalStateLocal () . evalStateLocal () + . evalStateLocal () . evalStateLocal () . evalStateLocal () . evalStateLocal () + . evalStateLocal () . evalStateLocal () diff --git a/effectful/tests/AsyncTests.hs b/effectful/tests/AsyncTests.hs index 35f33d9..ed3d5f3 100644 --- a/effectful/tests/AsyncTests.hs +++ b/effectful/tests/AsyncTests.hs @@ -23,7 +23,7 @@ asyncTests = testGroup "Async" ] test_localState :: Assertion -test_localState = runEff . runConcurrent . evalLocalState x $ do +test_localState = runEff . runConcurrent . evalStateLocal x $ do replicateConcurrently_ 2 $ do r <- goDownward 0 U.assertEqual "expected result" x r @@ -41,7 +41,7 @@ test_localState = runEff . runConcurrent . evalLocalState x $ do else goDownward $ acc + 1 test_sharedState :: Assertion -test_sharedState = runEff . runConcurrent . evalSharedState (S.empty @Int) $ do +test_sharedState = runEff . runConcurrent . evalStateShared (S.empty @Int) $ do concurrently_ (addWhen even x) (addWhen odd x) U.assertEqual "expected result" (S.fromList [1..x]) =<< get where @@ -57,7 +57,7 @@ test_sharedState = runEff . runConcurrent . evalSharedState (S.empty @Int) $ do addWhen f $ n - 1 test_errorHandling :: Assertion -test_errorHandling = runEff . runConcurrent . evalSharedState (0::Int) $ do +test_errorHandling = runEff . runConcurrent . evalStateShared (0::Int) $ do r <- runError $ concurrently_ (liftIO (threadDelay 10000) >> throwError err) (modify (+x)) @@ -73,7 +73,7 @@ test_errorHandling = runEff . runConcurrent . evalSharedState (0::Int) $ do err = "thrown from async" test_asyncWithUnmask :: Assertion -test_asyncWithUnmask = runEff . runConcurrent . evalLocalState "initial" $ do +test_asyncWithUnmask = runEff . runConcurrent . evalStateLocal "initial" $ do x <- asyncWithUnmask $ \unmask -> do liftIO $ threadDelay 10000 r1 <- get @String -- 2 @@ -88,7 +88,7 @@ test_asyncWithUnmask = runEff . runConcurrent . evalLocalState "initial" $ do (inner1, inner2, outer) test_pooledWorkers :: Assertion -test_pooledWorkers = runEff . runConcurrent . evalLocalState (0::Int) $ do +test_pooledWorkers = runEff . runConcurrent . evalStateLocal (0::Int) $ do x <- pooledForConcurrentlyN threads [1..n] $ \k -> do r <- get @Int modify @Int (+1) diff --git a/effectful/tests/ConcurrencyTests.hs b/effectful/tests/ConcurrencyTests.hs index 60a9675..f9073e2 100644 --- a/effectful/tests/ConcurrencyTests.hs +++ b/effectful/tests/ConcurrencyTests.hs @@ -23,7 +23,7 @@ concurrencyTests = testGroup "Concurrency" ] test_localState :: Assertion -test_localState = runEff . evalLocalState x $ do +test_localState = runEff . evalStateLocal x $ do withUnliftStrategy (ConcUnlift Ephemeral $ Limited 2) $ do replicateConcurrently_ 2 $ do r <- goDownward 0 @@ -42,7 +42,7 @@ test_localState = runEff . evalLocalState x $ do else goDownward $ acc + 1 test_sharedState :: Assertion -test_sharedState = runEff . evalSharedState (S.empty @Int) $ do +test_sharedState = runEff . evalStateShared (S.empty @Int) $ do withUnliftStrategy (ConcUnlift Ephemeral $ Limited 2) $ do concurrently_ (addWhen even x) (addWhen odd x) U.assertEqual "expected result" (S.fromList [1..x]) =<< get @@ -59,7 +59,7 @@ test_sharedState = runEff . evalSharedState (S.empty @Int) $ do addWhen f $ n - 1 test_errorHandling :: Assertion -test_errorHandling = runEff . evalSharedState (0::Int) $ do +test_errorHandling = runEff . evalStateShared (0::Int) $ do withUnliftStrategy (ConcUnlift Ephemeral $ Limited 2) $ do r <- runError $ concurrently_ (liftIO (threadDelay 10000) >> throwError err) @@ -76,7 +76,7 @@ test_errorHandling = runEff . evalSharedState (0::Int) $ do err = "thrown from async" test_unliftMany :: Assertion -test_unliftMany = runEff . evalLocalState "initial value" $ do +test_unliftMany = runEff . evalStateLocal "initial value" $ do withUnliftStrategy (ConcUnlift Persistent $ Limited 1) $ do x <- withRunInIO $ \runInIO -> async $ do v1 <- runInIO $ get @String -- 1 @@ -94,7 +94,7 @@ test_unliftMany = runEff . evalLocalState "initial value" $ do (v1, v2, v3, v4) test_asyncWithUnmask :: Assertion -test_asyncWithUnmask = runEff . evalLocalState "initial" $ do +test_asyncWithUnmask = runEff . evalStateLocal "initial" $ do withUnliftStrategy (ConcUnlift Persistent $ Limited 1) $ do x <- asyncWithUnmask $ \unmask -> do liftIO $ threadDelay 10000 @@ -110,7 +110,7 @@ test_asyncWithUnmask = runEff . evalLocalState "initial" $ do (inner1, inner2, outer) test_pooledWorkers :: Assertion -test_pooledWorkers = runEff . evalLocalState (0::Int) $ do +test_pooledWorkers = runEff . evalStateLocal (0::Int) $ do withUnliftStrategy (ConcUnlift Ephemeral $ Limited n) $ do x <- pooledForConcurrentlyN threads [1..n] $ \k -> do r <- get @Int