mirror of
https://github.com/haskell-effectful/effectful.git
synced 2024-11-22 22:14:21 +03:00
Document dynamic variants of basic effects
This commit is contained in:
parent
da73cb6e54
commit
6451445e77
2
LICENSE
2
LICENSE
@ -1,4 +1,4 @@
|
||||
Copyright (c) 2021, Andrzej Rybczak
|
||||
Copyright (c) 2021-2022, Andrzej Rybczak
|
||||
|
||||
All rights reserved.
|
||||
|
||||
|
@ -1,4 +1,4 @@
|
||||
Copyright (c) 2021, Andrzej Rybczak
|
||||
Copyright (c) 2021-2022, Andrzej Rybczak
|
||||
|
||||
All rights reserved.
|
||||
|
||||
|
@ -1,24 +1,27 @@
|
||||
module Effectful
|
||||
( -- * The 'Eff' monad
|
||||
( -- * Introduction
|
||||
-- $intro
|
||||
|
||||
-- * The 'Eff' monad
|
||||
Eff
|
||||
|
||||
-- ** Effect constraints
|
||||
-- ** Effect constraints
|
||||
, Effect
|
||||
, Dispatch(..)
|
||||
, DispatchOf
|
||||
, (:>)
|
||||
, (:>>)
|
||||
|
||||
-- * Running the 'Eff' monad
|
||||
-- * Running the 'Eff' monad
|
||||
|
||||
-- ** Pure computations
|
||||
-- ** Pure computations
|
||||
, runPureEff
|
||||
|
||||
-- ** Computations with side effects
|
||||
-- ** Computations with side effects
|
||||
, IOE
|
||||
, runEff
|
||||
|
||||
-- ** Unlift strategies
|
||||
-- ** Unlift strategies
|
||||
, UnliftStrategy(..)
|
||||
, Persistence(..)
|
||||
, Limit(..)
|
||||
@ -26,7 +29,7 @@ module Effectful
|
||||
, withUnliftStrategy
|
||||
, withEffToIO
|
||||
|
||||
-- * Re-exports
|
||||
-- * Re-exports
|
||||
, MonadIO(..)
|
||||
, MonadUnliftIO(..)
|
||||
) where
|
||||
@ -36,3 +39,8 @@ import Control.Monad.IO.Unlift
|
||||
|
||||
import Effectful.Internal.Effect
|
||||
import Effectful.Internal.Monad
|
||||
|
||||
-- $intro
|
||||
--
|
||||
-- TODO
|
||||
--
|
||||
|
@ -131,7 +131,8 @@ import Effectful.Internal.Monad
|
||||
-- unsafeEff_ $ logMessage logger msg
|
||||
-- :}
|
||||
--
|
||||
-- However, in order for this approach to be sound, the function that introduces the @Log@ effect needs to require 'IOE':
|
||||
-- However, in order for this approach to be sound, the function that introduces
|
||||
-- the @Log@ effect needs to require 'IOE':
|
||||
--
|
||||
-- >>> :{
|
||||
-- runLog :: IOE :> es => Logger -> Eff (Log : es) a -> Eff es a
|
||||
|
@ -1,22 +1,41 @@
|
||||
-- | The dynamically dispatched variant of the 'Error' effect.
|
||||
--
|
||||
-- /Note:/ unless you plan to change interpretations at runtime, it's
|
||||
-- recommended to use the statically dispatched variant,
|
||||
-- i.e. "Effectful.Error.Static".
|
||||
module Effectful.Error.Dynamic
|
||||
( Error(..)
|
||||
( -- * Effect
|
||||
Error(..)
|
||||
|
||||
-- ** Handlers
|
||||
, runError
|
||||
, runErrorNoCallStack
|
||||
|
||||
-- ** Operations
|
||||
, throwError
|
||||
, catchError
|
||||
, handleError
|
||||
, tryError
|
||||
|
||||
-- * Re-exports
|
||||
, E.HasCallStack
|
||||
, E.CallStack
|
||||
, E.getCallStack
|
||||
, E.prettyCallStack
|
||||
) where
|
||||
|
||||
import Effectful
|
||||
import Effectful.Dispatch.Dynamic
|
||||
import qualified Effectful.Error.Static as E
|
||||
|
||||
-- | Provide the ability to handle errors of type @e@.
|
||||
data Error e :: Effect where
|
||||
ThrowError :: e -> Error e m a
|
||||
CatchError :: m a -> (E.CallStack -> e -> m a) -> Error e m a
|
||||
|
||||
type instance DispatchOf (Error e) = 'Dynamic
|
||||
|
||||
-- | Handle errors of type @e@ (via "Effectful.Error.Static").
|
||||
runError
|
||||
:: Eff (Error e : es) a
|
||||
-> Eff es (Either (E.CallStack, e) a)
|
||||
@ -25,26 +44,47 @@ runError = reinterpret E.runError $ \env -> \case
|
||||
CatchError m h -> localSeqUnlift env $ \unlift -> do
|
||||
E.catchError (unlift m) (\cs -> unlift . h cs)
|
||||
|
||||
-- | Handle errors of type @e@ (via "Effectful.Error.Static"). In case of an
|
||||
-- error discard the 'E.CallStack'.
|
||||
runErrorNoCallStack
|
||||
:: Eff (Error e : es) a
|
||||
-> Eff es (Either e a)
|
||||
runErrorNoCallStack = fmap (either (Left . snd) Right) . runError
|
||||
|
||||
-- | Throw an error of type @e@.
|
||||
throwError
|
||||
:: (HasCallStack, Error e :> es)
|
||||
=> e
|
||||
-- ^ The error.
|
||||
-> Eff es a
|
||||
throwError = send . ThrowError
|
||||
|
||||
-- | Handle an error of type @e@.
|
||||
catchError
|
||||
:: (HasCallStack, Error e :> es)
|
||||
=> Eff es a
|
||||
-- ^ The inner computation.
|
||||
-> (E.CallStack -> e -> Eff es a)
|
||||
-- ^ A handler for errors in the inner computation.
|
||||
-> Eff es a
|
||||
catchError m = send . CatchError m
|
||||
|
||||
-- | The same as @'flip' 'catchError'@, which is useful in situations where the
|
||||
-- code for the handler is shorter.
|
||||
handleError
|
||||
:: Error e :> es
|
||||
=> (E.CallStack -> e -> Eff es a)
|
||||
-- ^ A handler for errors in the inner computation.
|
||||
-> Eff es a
|
||||
-- ^ The inner computation.
|
||||
-> Eff es a
|
||||
handleError = flip catchError
|
||||
|
||||
-- | Similar to 'catchError', but returns an 'Either' result which is a 'Right'
|
||||
-- if no error was thrown and a 'Left' otherwise.
|
||||
tryError
|
||||
:: (HasCallStack, Error e :> es)
|
||||
=> Eff es a
|
||||
-- ^ The inner computation.
|
||||
-> Eff es (Either (E.CallStack, e) a)
|
||||
tryError m = (Right <$> m) `catchError` \es e -> pure $ Left (es, e)
|
||||
|
@ -54,7 +54,7 @@
|
||||
-- >>> T.runExceptT . (`T.runStateT` "Hi") $ m1
|
||||
-- Right ((),"Hi")
|
||||
--
|
||||
-- Here, whether state modifications within the @catchError@ block are lost or
|
||||
-- Here, whether state updates within the 'catchError' block are discarded or
|
||||
-- not depends on the shape of the monad transformer stack, which is surprising
|
||||
-- and can be a source of subtle bugs. On the other hand:
|
||||
--
|
||||
@ -68,23 +68,33 @@
|
||||
-- >>> runEff . runError @String . runState "Hi" $ m2
|
||||
-- Right ((),"Hi there!")
|
||||
--
|
||||
-- Here, no matter the order of effects, state modifications within the
|
||||
-- @catchError@ block always persist, giving predictable behavior.
|
||||
-- Here, no matter the order of effects, state updates made within the
|
||||
-- @catchError@ block before the error happens always persist, giving
|
||||
-- predictable behavior.
|
||||
--
|
||||
-- /Hint:/ if you'd like to reproduce the transactional behavior with the
|
||||
-- 'Effectful.State.Static.Local.State' effect, appropriate usage of
|
||||
-- 'Control.Monad.Catch.bracketOnError' will do the trick.
|
||||
module Effectful.Error.Static
|
||||
( Error
|
||||
, runError
|
||||
, runErrorNoCallStack
|
||||
, throwError
|
||||
, catchError
|
||||
, handleError
|
||||
, tryError
|
||||
( -- * Effect
|
||||
Error
|
||||
|
||||
-- * Re-exports
|
||||
, HasCallStack
|
||||
, CallStack
|
||||
, getCallStack
|
||||
, prettyCallStack
|
||||
) where
|
||||
-- ** Handlers
|
||||
, runError
|
||||
, runErrorNoCallStack
|
||||
|
||||
-- ** Operations
|
||||
, throwError
|
||||
, catchError
|
||||
, handleError
|
||||
, tryError
|
||||
|
||||
-- * Re-exports
|
||||
, HasCallStack
|
||||
, CallStack
|
||||
, getCallStack
|
||||
, prettyCallStack
|
||||
) where
|
||||
|
||||
import Control.Exception
|
||||
import Data.Unique
|
||||
@ -118,7 +128,7 @@ runError m = unsafeEff $ \es0 -> mask $ \release -> do
|
||||
Left ex -> tryHandler ex eid (\cs e -> Left (cs, e))
|
||||
$ throwIO ex
|
||||
|
||||
-- | Handle errors of type @e@. In case of error discard the 'CallStack'.
|
||||
-- | Handle errors of type @e@. In case of an error discard the 'CallStack'.
|
||||
runErrorNoCallStack
|
||||
:: forall e es a
|
||||
. Eff (Error e : es) a
|
||||
|
@ -1,6 +1,9 @@
|
||||
-- | Provider of the 'MonadFail' instance for 'Eff'.
|
||||
module Effectful.Fail
|
||||
( Fail(..)
|
||||
( -- * Effect
|
||||
Fail(..)
|
||||
|
||||
-- ** Handlers
|
||||
, runFail
|
||||
, runFailIO
|
||||
) where
|
||||
|
@ -1,6 +1,9 @@
|
||||
-- | Provider of the 'MonadPrim' instance for 'Eff'.
|
||||
module Effectful.Prim
|
||||
( Prim
|
||||
( -- * Effect
|
||||
Prim
|
||||
|
||||
-- ** Handlers
|
||||
, runPrim
|
||||
) where
|
||||
|
||||
|
@ -1,6 +1,16 @@
|
||||
-- | The dynamically dispatched variant of the 'Reader' effect.
|
||||
--
|
||||
-- /Note:/ unless you plan to change interpretations at runtime, it's
|
||||
-- recommended to use the statically dispatched variant,
|
||||
-- i.e. "Effectful.Reader.Static".
|
||||
module Effectful.Reader.Dynamic
|
||||
( Reader(..)
|
||||
( -- * Effect
|
||||
Reader(..)
|
||||
|
||||
-- ** Handlers
|
||||
, runReader
|
||||
|
||||
-- ** Operations
|
||||
, ask
|
||||
, asks
|
||||
, local
|
||||
@ -16,7 +26,12 @@ data Reader r :: Effect where
|
||||
|
||||
type instance DispatchOf (Reader r) = 'Dynamic
|
||||
|
||||
runReader :: r -> Eff (Reader r : es) a -> Eff es a
|
||||
-- | Run the 'Reader' effect with the given initial environment (via
|
||||
-- "Effectful.Reader.Static").
|
||||
runReader
|
||||
:: r -- ^ The initial environment.
|
||||
-> Eff (Reader r : es) a
|
||||
-> Eff es a
|
||||
runReader r = reinterpret (R.runReader r) $ \env -> \case
|
||||
Ask -> R.ask
|
||||
Local f m -> localSeqUnlift env $ \unlift -> R.local f (unlift m)
|
||||
@ -24,11 +39,26 @@ runReader r = reinterpret (R.runReader r) $ \env -> \case
|
||||
----------------------------------------
|
||||
-- Operations
|
||||
|
||||
-- | Fetch the value of the environment.
|
||||
ask :: (HasCallStack, Reader r :> es) => Eff es r
|
||||
ask = send Ask
|
||||
|
||||
asks :: (HasCallStack, Reader r :> es) => (r -> a) -> Eff es a
|
||||
-- | Retrieve a function of the current environment.
|
||||
--
|
||||
-- @'asks' f ≡ f '<$>' 'ask'@
|
||||
asks
|
||||
:: (HasCallStack, Reader r :> es)
|
||||
=> (r -> a) -- ^ The function to apply to the environment.
|
||||
-> Eff es a
|
||||
asks f = f <$> ask
|
||||
|
||||
local :: (HasCallStack, Reader r :> es ) => (r -> r) -> Eff es a -> Eff es a
|
||||
-- | Execute a computation in a modified environment.
|
||||
--
|
||||
-- @'runReader' r ('local' f m) ≡ 'runReader' (f r) m@
|
||||
--
|
||||
local
|
||||
:: (HasCallStack, Reader r :> es)
|
||||
=> (r -> r) -- ^ The function to modify the environment.
|
||||
-> Eff es a
|
||||
-> Eff es a
|
||||
local f = send . Local f
|
||||
|
@ -1,7 +1,12 @@
|
||||
-- | Support for access to a read only value of a particular type.
|
||||
module Effectful.Reader.Static
|
||||
( Reader
|
||||
( -- * Effect
|
||||
Reader
|
||||
|
||||
-- ** Handlers
|
||||
, runReader
|
||||
|
||||
-- ** Operations
|
||||
, ask
|
||||
, asks
|
||||
, local
|
||||
@ -19,7 +24,7 @@ newtype instance StaticRep (Reader r) = Reader r
|
||||
|
||||
-- | Run a 'Reader' effect with the given initial environment.
|
||||
runReader
|
||||
:: r -- ^ An initial environment.
|
||||
:: r -- ^ The initial environment.
|
||||
-> Eff (Reader r : es) a
|
||||
-> Eff es a
|
||||
runReader r = evalStaticRep (Reader r)
|
||||
|
@ -1,18 +1,25 @@
|
||||
-- | The 'State' effect with dynamic dispatch.
|
||||
-- | The dynamically dispatched variant of the 'State' effect.
|
||||
--
|
||||
-- /Note:/ unless you plan to change interpretations at runtime, it's
|
||||
-- recommended to use one of the statically dispatched variants,
|
||||
-- i.e. "Effectful.State.Static.Local" or "Effectful.State.Static.Shared".
|
||||
module Effectful.State.Dynamic
|
||||
( State(..)
|
||||
( -- * Effect
|
||||
State(..)
|
||||
|
||||
-- * Local
|
||||
-- ** Handlers
|
||||
|
||||
-- *** Local
|
||||
, runLocalState
|
||||
, evalLocalState
|
||||
, execLocalState
|
||||
|
||||
-- * Shared
|
||||
-- *** Shared
|
||||
, runSharedState
|
||||
, evalSharedState
|
||||
, execSharedState
|
||||
|
||||
-- * Operations
|
||||
-- ** Operations
|
||||
, get
|
||||
, gets
|
||||
, put
|
||||
@ -39,12 +46,18 @@ type instance DispatchOf (State s) = 'Dynamic
|
||||
----------------------------------------
|
||||
-- Local
|
||||
|
||||
-- | 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
|
||||
|
||||
-- | 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
|
||||
|
||||
-- | 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
|
||||
|
||||
@ -62,12 +75,18 @@ localState env = \case
|
||||
----------------------------------------
|
||||
-- Shared
|
||||
|
||||
-- | 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
|
||||
|
||||
-- | 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
|
||||
|
||||
-- | 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
|
||||
|
||||
@ -85,41 +104,54 @@ sharedState env = \case
|
||||
----------------------------------------
|
||||
-- Operations
|
||||
|
||||
-- | Fetch the current value of the state.
|
||||
get
|
||||
:: (HasCallStack, State s :> es)
|
||||
=> Eff es s
|
||||
get = send Get
|
||||
|
||||
-- | Get a function of the current state.
|
||||
--
|
||||
-- @'gets' f ≡ f '<$>' 'get'@
|
||||
gets
|
||||
:: (HasCallStack, State s :> es)
|
||||
=> (s -> a)
|
||||
-> Eff es a
|
||||
gets f = f <$> get
|
||||
|
||||
-- | Set the current state to the given value.
|
||||
put
|
||||
:: (HasCallStack, State s :> es)
|
||||
=> s
|
||||
-> Eff es ()
|
||||
put = send . Put
|
||||
|
||||
-- | Apply the function to the current state and return a value.
|
||||
state
|
||||
:: (HasCallStack, State s :> es)
|
||||
=> (s -> (a, s))
|
||||
-> Eff es a
|
||||
state = send . State
|
||||
|
||||
-- | Apply the function to the current state.
|
||||
--
|
||||
-- @'modify' f ≡ 'state' (\\s -> ((), f s))@
|
||||
modify
|
||||
:: (HasCallStack, State s :> es)
|
||||
=> (s -> s)
|
||||
-> Eff es ()
|
||||
modify f = state (\s -> ((), f s))
|
||||
|
||||
-- | Apply the monadic function to the current state and return a value.
|
||||
stateM
|
||||
:: (HasCallStack, State s :> es)
|
||||
=> (s -> Eff es (a, s))
|
||||
-> Eff es a
|
||||
stateM = send . StateM
|
||||
|
||||
-- | Apply the monadic function to the current state.
|
||||
--
|
||||
-- @'modifyM' f ≡ 'stateM' (\\s -> ((), ) '<$>' f s)@
|
||||
modifyM
|
||||
:: (HasCallStack, State s :> es)
|
||||
=> (s -> Eff es s)
|
||||
|
@ -4,8 +4,8 @@
|
||||
-- "Effectful.State.Static.Shared".
|
||||
--
|
||||
-- /Note:/ unlike the 'Control.Monad.Trans.State.StateT' monad transformer from
|
||||
-- the @transformers@ library, the 'State' effect doesn't lose state
|
||||
-- modifications when an exception is received:
|
||||
-- the @transformers@ library, the 'State' effect doesn't discard state updates
|
||||
-- when an exception is received:
|
||||
--
|
||||
-- >>> import qualified Control.Monad.Trans.State.Strict as S
|
||||
--
|
||||
@ -23,10 +23,15 @@
|
||||
-- :}
|
||||
-- "Hi there!"
|
||||
module Effectful.State.Static.Local
|
||||
( State
|
||||
( -- * Effect
|
||||
State
|
||||
|
||||
-- ** Handlers
|
||||
, runState
|
||||
, evalState
|
||||
, execState
|
||||
|
||||
-- ** Operations
|
||||
, get
|
||||
, gets
|
||||
, put
|
||||
@ -45,28 +50,28 @@ data State s :: Effect
|
||||
type instance DispatchOf (State s) = 'Static
|
||||
newtype instance StaticRep (State s) = State s
|
||||
|
||||
-- | Run a 'State' effect with the given initial state and return the final
|
||||
-- | Run the 'State' effect with the given initial state and return the final
|
||||
-- value along with the final state.
|
||||
runState
|
||||
:: s -- ^ An initial state.
|
||||
:: s -- ^ The initial state.
|
||||
-> Eff (State s : es) a
|
||||
-> Eff es (a, s)
|
||||
runState s0 m = do
|
||||
(a, State s) <- runStaticRep (State s0) m
|
||||
pure (a, s)
|
||||
|
||||
-- | Run a 'State' effect with the given initial state and return the final
|
||||
-- | Run the 'State' effect with the given initial state and return the final
|
||||
-- value, discarding the final state.
|
||||
evalState
|
||||
:: s -- ^ An initial state.
|
||||
:: s -- ^ The initial state.
|
||||
-> Eff (State s : es) a
|
||||
-> Eff es a -- ^ A return value.
|
||||
-> Eff es a
|
||||
evalState s = evalStaticRep (State s)
|
||||
|
||||
-- | Run a 'State' effect with the given initial state and return the final
|
||||
-- | Run the 'State' effect with the given initial state and return the final
|
||||
-- state, discarding the final value.
|
||||
execState
|
||||
:: s -- ^ An initial state.
|
||||
:: s -- ^ The initial state.
|
||||
-> Eff (State s : es) a
|
||||
-> Eff es s
|
||||
execState s0 m = do
|
||||
|
@ -4,8 +4,8 @@
|
||||
-- manage its own version of the value, use "Effectful.State.Static.Local".
|
||||
--
|
||||
-- /Note:/ unlike the 'Control.Monad.Trans.State.StateT' monad transformer from
|
||||
-- the @transformers@ library, the 'State' effect doesn't lose state
|
||||
-- modifications when an exception is received:
|
||||
-- the @transformers@ library, the 'State' effect doesn't discard state updates
|
||||
-- when an exception is received:
|
||||
--
|
||||
-- >>> import qualified Control.Monad.Trans.State.Strict as S
|
||||
--
|
||||
@ -23,10 +23,15 @@
|
||||
-- :}
|
||||
-- "Hi there!"
|
||||
module Effectful.State.Static.Shared
|
||||
( State
|
||||
( -- * Effect
|
||||
State
|
||||
|
||||
-- ** Handlers
|
||||
, runState
|
||||
, evalState
|
||||
, execState
|
||||
|
||||
-- ** Operations
|
||||
, get
|
||||
, gets
|
||||
, put
|
||||
@ -47,7 +52,7 @@ data State s :: Effect
|
||||
type instance DispatchOf (State s) = 'Static
|
||||
newtype instance StaticRep (State s) = State (MVar s)
|
||||
|
||||
-- | Run a 'State' effect with the given initial state and return the final
|
||||
-- | Run the 'State' effect with the given initial state and return the final
|
||||
-- value along with the final state.
|
||||
runState :: s -> Eff (State s : es) a -> Eff es (a, s)
|
||||
runState s m = do
|
||||
@ -55,14 +60,14 @@ runState s m = do
|
||||
a <- evalStaticRep (State v) m
|
||||
(a, ) <$> unsafeEff_ (readMVar v)
|
||||
|
||||
-- | Run a 'State' effect with the given initial state and return the final
|
||||
-- | Run the 'State' effect with the given initial state and return the final
|
||||
-- value, discarding the final state.
|
||||
evalState :: s -> Eff (State s : es) a -> Eff es a
|
||||
evalState s m = do
|
||||
v <- unsafeEff_ $ newMVar s
|
||||
evalStaticRep (State v) m
|
||||
|
||||
-- | Run a 'State' effect with the given initial state and return the final
|
||||
-- | Run the 'State' effect with the given initial state and return the final
|
||||
-- state, discarding the final value.
|
||||
execState :: s -> Eff (State s : es) a -> Eff es s
|
||||
execState s m = do
|
||||
|
@ -1,15 +1,23 @@
|
||||
-- | The dynamically dispatched variant of the 'State' effect.
|
||||
--
|
||||
-- /Note:/ unless you plan to change interpretations at runtime, it's
|
||||
-- recommended to use one of the statically dispatched variants,
|
||||
-- i.e. "Effectful.Writer.Static.Local" or "Effectful.Writer.Static.Shared".
|
||||
module Effectful.Writer.Dynamic
|
||||
( Writer(..)
|
||||
( -- * Effect
|
||||
Writer(..)
|
||||
|
||||
-- * Local
|
||||
-- ** Handlers
|
||||
|
||||
-- *** Local
|
||||
, runLocalWriter
|
||||
, execLocalWriter
|
||||
|
||||
-- * Shared
|
||||
-- *** Shared
|
||||
, runSharedWriter
|
||||
, execSharedWriter
|
||||
|
||||
-- * Operations
|
||||
-- * Operations
|
||||
, tell
|
||||
, listen
|
||||
, listens
|
||||
@ -20,6 +28,7 @@ import Effectful.Dispatch.Dynamic
|
||||
import qualified Effectful.Writer.Static.Local as L
|
||||
import qualified Effectful.Writer.Static.Shared as S
|
||||
|
||||
-- | Provide access to a write only value of type @w@.
|
||||
data Writer w :: Effect where
|
||||
Tell :: w -> Writer w m ()
|
||||
Listen :: m a -> Writer w m (a, w)
|
||||
@ -29,9 +38,13 @@ type instance DispatchOf (Writer w) = 'Dynamic
|
||||
----------------------------------------
|
||||
-- Local
|
||||
|
||||
-- | Run the 'Writer' effect and return the final value along with the final
|
||||
-- output (via "Effectful.Writer.Static.Local").
|
||||
runLocalWriter :: Monoid w => Eff (Writer w : es) a -> Eff es (a, w)
|
||||
runLocalWriter = reinterpret L.runWriter localWriter
|
||||
|
||||
-- | Run a 'Writer' effect and return the final output, discarding the final
|
||||
-- value (via "Effectful.Writer.Static.Local").
|
||||
execLocalWriter :: Monoid w => Eff (Writer w : es) a -> Eff es w
|
||||
execLocalWriter = reinterpret L.execWriter localWriter
|
||||
|
||||
@ -47,9 +60,13 @@ localWriter env = \case
|
||||
----------------------------------------
|
||||
-- Shared
|
||||
|
||||
-- | Run the 'Writer' effect and return the final value along with the final
|
||||
-- output (via "Effectful.Writer.Static.Shared").
|
||||
runSharedWriter :: Monoid w => Eff (Writer w : es) a -> Eff es (a, w)
|
||||
runSharedWriter = reinterpret S.runWriter sharedWriter
|
||||
|
||||
-- | Run the 'Writer' effect and return the final output, discarding the final
|
||||
-- value (via "Effectful.Writer.Static.Shared").
|
||||
execSharedWriter :: Monoid w => Eff (Writer w : es) a -> Eff es w
|
||||
execSharedWriter = reinterpret S.execWriter sharedWriter
|
||||
|
||||
@ -65,18 +82,26 @@ sharedWriter env = \case
|
||||
----------------------------------------
|
||||
-- Operations
|
||||
|
||||
-- | Append the given output to the overall output of the 'Writer'.
|
||||
tell
|
||||
:: (HasCallStack, Writer w :> es)
|
||||
=> w
|
||||
-> Eff es ()
|
||||
tell = send . Tell
|
||||
|
||||
-- | Execute an action and append its output to the overall output of the
|
||||
-- 'Writer'.
|
||||
listen
|
||||
:: (HasCallStack, Writer w :> es)
|
||||
=> Eff es a
|
||||
-> Eff es (a, w)
|
||||
listen = send . Listen
|
||||
|
||||
-- | Execute an action and append its output to the overall output of the
|
||||
-- 'Writer', then return the final value along with a function of the recorded
|
||||
-- output.
|
||||
--
|
||||
-- @'listens' f m ≡ 'Data.Bifunctor.second' f '<$>' 'listen' m@
|
||||
listens
|
||||
:: (HasCallStack, Writer w :> es)
|
||||
=> (w -> b)
|
||||
|
@ -14,9 +14,14 @@
|
||||
-- 'Control.Monad.Trans.Writer.Strict.censor', they don't cooperate with runtime
|
||||
-- exceptions very well, so they're deliberately omitted here.
|
||||
module Effectful.Writer.Static.Local
|
||||
( Writer
|
||||
( -- * Effect
|
||||
Writer
|
||||
|
||||
-- ** Handlers
|
||||
, runWriter
|
||||
, execWriter
|
||||
|
||||
-- ** Operations
|
||||
, tell
|
||||
, listen
|
||||
, listens
|
||||
|
@ -14,9 +14,14 @@
|
||||
-- 'Control.Monad.Trans.Writer.Strict.censor', they don't cooperate with runtime
|
||||
-- exceptions very well, so they're deliberately omitted here.
|
||||
module Effectful.Writer.Static.Shared
|
||||
( Writer
|
||||
( -- * Effect
|
||||
Writer
|
||||
|
||||
-- ** Handlers
|
||||
, runWriter
|
||||
, execWriter
|
||||
|
||||
-- ** Operations
|
||||
, tell
|
||||
, listen
|
||||
, listens
|
||||
|
@ -1,4 +1,4 @@
|
||||
Copyright (c) 2021, Andrzej Rybczak
|
||||
Copyright (c) 2021-2022, Andrzej Rybczak
|
||||
|
||||
All rights reserved.
|
||||
|
||||
|
@ -65,9 +65,9 @@ import Effectful.Dispatch.Static
|
||||
-- :}
|
||||
-- "Hi!!!"
|
||||
--
|
||||
-- In the first example state modification made concurrently are not reflected
|
||||
-- in the parent thread because the value is thread local, but in the second
|
||||
-- example they are, because the value is shared.
|
||||
-- In the first example state updates made concurrently are not reflected in the
|
||||
-- parent thread because the value is thread local, but in the second example
|
||||
-- they are, because the value is shared.
|
||||
--
|
||||
data Concurrent :: Effect
|
||||
|
||||
|
Loading…
Reference in New Issue
Block a user