Document static and dynamic dispatch

This commit is contained in:
Andrzej Rybczak 2022-01-22 17:33:26 +01:00
parent 938550b784
commit df9190d3b0
15 changed files with 411 additions and 97 deletions

View File

@ -1,61 +1,26 @@
module Effectful
( -- * The 'Eff' monad
Eff
( -- * Overview
-- $overview
-- ** Effect constraints
, Effect
, Dispatch(..)
, DispatchOf
, (:>)
, (:>>)
-- * The 'Eff' monad
module Effectful.Monad
-- * Running the 'Eff' monad
-- * Effects
-- ** Pure computations
, runPureEff
-- ** Dynamic dispatch
, module Effectful.Dispatch.Dynamic
-- ** Computations with side effects
, IOE
, runEff
-- *** Unlift strategies
, UnliftStrategy(..)
, Persistence(..)
, Limit(..)
, unliftStrategy
, withUnliftStrategy
, withEffToIO
-- * 'Effect' handlers
-- ** Sending operations to the handler
, send
-- ** Basic handlers
, interpret
, reinterpret
-- ** Handling local 'Eff' computations
, LocalEnv
-- *** Unlifts
, localSeqUnlift
, localSeqUnliftIO
, localUnlift
, localUnliftIO
-- *** Lifts
, withLiftMap
, withLiftMapIO
-- *** Bidirectional lifts
, localLiftUnlift
, localLiftUnliftIO
-- * Re-exports
, MonadIO(..)
, MonadUnliftIO(..)
-- ** Static dispatch
-- $static
) where
import Effectful.Dispatch.Dynamic
import Effectful.Monad
-- $overview
-- TODO
-- $static
--
-- Documentation for statically dispatched effects and the API for defining them
-- is available in "Effectful.Dispatch.Static".

View File

@ -1,5 +1,13 @@
-- | Dynamically dispatched effects.
module Effectful.Dispatch.Dynamic
( -- * Sending operations to the handler
( -- * Introduction
-- ** An example
-- $example
-- ** First order and higher order effects
-- $order
-- * Sending operations to the handler
send
-- * Handling effects
@ -39,6 +47,207 @@ import Effectful.Internal.Effect
import Effectful.Internal.Env
import Effectful.Internal.Monad
-- $example
--
-- Let's create an effect for basic file access, i.e. writing and reading files.
--
-- First, we need to define a generalized algebraic data type of kind 'Effect',
-- where each constructor corresponds to a specific operation of the effect in
-- question.
--
-- >>> :{
-- data FileSystem :: Effect where
-- ReadFile :: FilePath -> FileSystem m String
-- WriteFile :: FilePath -> String -> FileSystem m ()
-- :}
--
-- >>> type instance DispatchOf FileSystem = 'Dynamic
--
-- The @FileSystem@ effect has two operations:
--
-- - @ReadFile@, which takes a @FilePath@ and returns a @String@ in the monadic
-- context.
--
-- - @WriteFile@, which takes a @FilePath@, a @String@ and returns a @()@ in the
-- monadic context.
--
-- For people familiar with the @mtl@ style effects, note that the syntax looks
-- very similar to defining an appropriate type class:
--
-- @
-- class FileSystem m where
-- readFile :: FilePath -> m String
-- writeFile :: FilePath -> String -> m ()
-- @
--
-- The biggest difference between these two is that the definition of a type
-- class gives us operations as functions, while the definition of an effect
-- gives us operations as data constructors. They can be turned into functions
-- with the help of 'send':
--
-- >>> :{
-- readFile :: (HasCallStack, FileSystem :> es) => FilePath -> Eff es String
-- readFile path = send (ReadFile path)
-- :}
--
-- >>> :{
-- writeFile :: (HasCallStack, FileSystem :> es) => FilePath -> String -> Eff es ()
-- writeFile path content = send (WriteFile path content)
-- :}
--
-- The following defines an 'EffectHandler' that reads and writes files from the
-- drive:
--
-- >>> import Control.Exception (IOException)
-- >>> import Control.Monad.Catch (catch)
-- >>> import qualified System.IO as IO
--
-- >>> import Effectful.Error.Static
--
-- >>> newtype FsError = FsError String deriving Show
--
-- >>> :{
-- runFileSystemIO
-- :: (IOE :> es, Error FsError :> es)
-- => Eff (FileSystem : es) a
-- -> Eff es a
-- runFileSystemIO = interpret $ \_ -> \case
-- ReadFile path -> adapt $ IO.readFile path
-- WriteFile path contents -> adapt $ IO.writeFile path contents
-- where
-- adapt m = liftIO m `catch` \(e::IOException) -> throwError . FsError $ show e
-- :}
--
-- Here, we use 'interpret' and simply execute corresponding 'IO' actions for
-- each operation, additionally doing a bit of error management.
--
-- On the other hand, maybe there is a situation in which instead of interacting
-- with the outside world, a pure, in-memory storage is preferred:
--
-- >>> import qualified Data.Map.Strict as M
--
-- >>> import Effectful.State.Static.Local
--
-- >>> :{
-- runFileSystemPure
-- :: Error FsError :> es
-- => M.Map FilePath String
-- -> Eff (FileSystem : es) a
-- -> Eff es a
-- runFileSystemPure fs0 = reinterpret (evalState fs0) $ \_ -> \case
-- ReadFile path -> gets (M.lookup path) >>= \case
-- Just contents -> pure contents
-- Nothing -> throwError . FsError $ "File not found: " ++ show path
-- WriteFile path contents -> modify $ M.insert path contents
-- :}
--
-- Here, we use 'reinterpret' and introduce a 'State' effect for the storage
-- that is private to the effect handler and cannot be accessed outside of it.
--
-- Let's compare how these differ.
--
-- >>> :{
-- action = do
-- file <- readFile "effectful-core.cabal"
-- pure $ length file > 0
-- :}
--
-- >>> :t action
-- action :: (FileSystem :> es) => Eff es Bool
--
-- >>> runEff . runError @FsError . runFileSystemIO $ action
-- Right True
--
-- >>> runPureEff . runErrorNoCallStack @FsError . runFileSystemPure M.empty $ action
-- Left (FsError "File not found: \"effectful-core.cabal\"")
--
-- $order
--
-- Note that the definition of the @FileSystem@ effect from the previous section
-- doesn't use the @m@ type parameter. What is more, when the effect is
-- interpreted, the 'LocalEnv' argument of the 'EffectHandler' is also not
-- used. Such effects are /first order/.
--
-- If an effect makes use of the @m@ parameter, i.e. it takes a monadic action
-- as an argument, it is a /higher order effect/.
--
-- Interpretation of higher order effects is slightly more involved. To see why,
-- let's consider the @Profiling@ effect for logging how much time a specific
-- action took to run:
--
-- >>> :{
-- data Profiling :: Effect where
-- Profile :: String -> m a -> Profiling m a
-- :}
--
-- >>> type instance DispatchOf Profiling = 'Dynamic
--
-- >>> :{
-- profile :: (HasCallStack, Profiling :> es) => String -> Eff es a -> Eff es a
-- profile label action = send (Profile label action)
-- :}
--
-- If we naively try to interpret it, we will run into trouble:
--
-- >>> import GHC.Clock (getMonotonicTime)
--
-- >>> :{
-- runProfiling :: IOE :> es => Eff (Profiling : es) a -> Eff es a
-- runProfiling = interpret $ \_ -> \case
-- Profile label action -> do
-- t1 <- liftIO getMonotonicTime
-- r <- action
-- t2 <- liftIO getMonotonicTime
-- liftIO . putStrLn $ label ++ "' took " ++ show (t2 - t1) ++ " seconds"
-- pure r
-- :}
-- ...
-- ... Couldn't match type localEs with es
-- ...
--
-- The problem is that @action@ has a type @Eff localEs a@, while the monad of
-- the effect handler is @Eff es@. @localEs@ represents the /local environment/
-- in which the @Profile@ operation was called, which is opaque as the effect
-- handler cannot possibly know how it looks like.
--
-- The solution is to use the 'LocalEnv' that an 'EffectHandler' is given to run
-- the action using one of the functions from the 'localUnlift' family:
--
-- >>> :{
-- runProfiling :: IOE :> es => Eff (Profiling : es) a -> Eff es a
-- runProfiling = interpret $ \env -> \case
-- Profile label action -> localSeqUnliftIO env $ \unlift -> do
-- t1 <- getMonotonicTime
-- r <- unlift action
-- t2 <- getMonotonicTime
-- putStrLn $ "Action '" ++ label ++ "' took " ++ show (t2 - t1) ++ " seconds."
-- pure r
-- :}
--
-- In a similar way we can define a dummy interpreter that does no profiling:
--
-- >>> :{
-- runNoProfiling :: Eff (Profiling : es) a -> Eff es a
-- runNoProfiling = interpret $ \env -> \case
-- Profile label action -> localSeqUnlift env $ \unlift -> unlift action
-- :}
--
-- ...and it's done.
--
-- >>> action = profile "greet" . liftIO $ putStrLn "Hello!"
--
-- >>> :t action
-- action :: (Profiling :> es, IOE :> es) => Eff es ()
--
-- >>> runEff . runProfiling $ action
-- Hello!
-- Action 'greet' took ... seconds.
--
-- >>> runEff . runNoProfiling $ action
-- Hello!
--
----------------------------------------
-- Handling effects
@ -246,4 +455,4 @@ type family SuffixOf (es :: [Effect]) (baseEs :: [Effect]) :: Constraint where
SuffixOf (e : es) baseEs = SuffixOf es baseEs
-- $setup
-- >>> import Control.Concurrent
-- >>> import Control.Concurrent (ThreadId, forkIOWithUnmask)

View File

@ -1,5 +1,12 @@
-- | Statically dispatched effects.
module Effectful.Dispatch.Static
( -- * Low level API
( -- * Introduction
-- $intro
-- ** An example
-- $example
-- * Low level API
StaticRep
-- ** Extending the environment
@ -54,6 +61,116 @@ module Effectful.Dispatch.Static
import Effectful.Internal.Env
import Effectful.Internal.Monad
-- $intro
--
-- Unlike dynamically dispatched effects, statically dispatched effects have a
-- single, set interpretation that cannot be changed at runtime. It's worth
-- noting that this doesn't make them worse, just applicable in different
-- scenarios. For example:
--
-- * If you'd like to ensure that a specific effect will behave in a certain way
-- at all times, using a statically dispatched version is the only way to
-- ensure that.
--
-- * If the effect you're about to define has only one reasonable implemenation,
-- it makes a lot of sense to make it statically dispatched.
--
-- Statically dispatched effects also perform better than dynamically dispatched
-- ones, because their operations are implemented as standard top level
-- functions, so they can be inlined by the compiler if appropriate.
--
-- $example
--
-- Let's say that there exists a logging library whose functionality we'd like
-- to turn into an effect. Its @Logger@ data type (after simplification) is
-- represented in the following way:
--
-- >>> data Logger = Logger { logMessage :: String -> IO () }
--
-- Because the @Logger@ type itself allows customization of how messages are
-- logged, it is an excellent candidate to be turned into a statically
-- dispatched effect.
--
-- Such effect is represented by an empty data type of kind 'Effectful.Effect':
--
-- >>> data Log :: Effect
--
-- >>> type instance DispatchOf Log = 'Static
--
-- The environment of 'Eff' will hold the data type that represents the
-- effect. It is defined by the appropriate instance of the 'StaticRep' data
-- family:
--
-- >>> newtype instance StaticRep Log = Log Logger
--
-- /Note:/ all operations of a statically dispatched effect will have a
-- read/write access to this data type as long as they can see its constructors,
-- hence it's best not to export them from the module that defines the effect.
--
-- The logging operation can be defined as follows:
--
-- >>> :{
-- log :: (IOE :> es, Log :> es) => String -> Eff es ()
-- log msg = do
-- Log logger <- getStaticRep
-- liftIO $ logMessage logger msg
-- :}
--
-- That works, but has an unfortunate consequence: in order to use the @log@
-- operation the 'IOE' effect needs to be in scope! This is bad, because we're
-- trying to limit (ideally, fully eliminate) the need to have the full power of
-- 'IO' available in the application code. The solution is to use one of the
-- escape hatches that allow unrestricted access to the internal representation
-- of 'Eff':
--
-- >>> :{
-- log :: Log :> es => String -> Eff es ()
-- log msg = do
-- Log logger <- getStaticRep
-- unsafeEff_ $ logMessage logger msg
-- :}
--
-- 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
-- runLog logger = evalStaticRep (Log logger)
-- :}
--
-- In general, whenever any operation of a static effect introduces potential
-- side effects using one of the unsafe functions, all functions that introduce
-- this effect need to require the 'IOE' effect.
--
-- __If you forget, that's on you, the compiler will not complain.__
--
-- Now we can use the newly defined effect to log messages:
--
-- >>> dummyLogger = Logger { logMessage = \_ -> pure () }
--
-- >>> stdoutLogger = Logger { logMessage = putStrLn }
--
-- >>> :{
-- action = do
-- log "Computing things..."
-- log "Sleeping..."
-- log "Computing more things..."
-- pure "Done"
-- :}
--
-- >>> :t action
-- action :: (Log :> es) => Eff es [Char]
--
-- >>> runEff . runLog stdoutLogger $ action
-- Computing things...
-- Sleeping...
-- Computing more things...
-- "Done"
--
-- >>> runEff . runLog dummyLogger $ action
-- "Done"
--
-- | Utility for lifting 'IO' computations of type
--
-- @'IO' a -> 'IO' b@
@ -83,3 +200,6 @@ unsafeLiftMapIO f m = unsafeEff $ \es -> f (unEff m es)
-- caller of 'unsafeUnliftIO', but it's not checked anywhere.
unsafeUnliftIO :: ((forall r. Eff es r -> IO r) -> IO a) -> Eff es a
unsafeUnliftIO k = unsafeEff $ \es -> k (`unEff` es)
-- $setup
-- >>> import Effectful

View File

@ -1,6 +1,7 @@
module Effectful.Error.Dynamic
( Error(..)
, runError
, runErrorNoCallStack
, throwError
, catchError
, tryError
@ -27,6 +28,12 @@ runError = reinterpret E.runError $ \env -> \case
CatchError m h -> localSeqUnlift env $ \unlift -> do
E.catchError (unlift m) (\cs -> unlift . h cs)
runErrorNoCallStack
:: forall e es a. Typeable e
=> Eff (Error e : es) a
-> Eff es (Either e a)
runErrorNoCallStack = fmap (either (Left . snd) Right) . runError
throwError
:: (HasCallStack, Error e :> es)
=> e

View File

@ -8,7 +8,9 @@
-- type @e@ and will __not__ be caught by functions from this module:
--
-- >>> import qualified Control.Monad.Catch as E
-- >>> let boom = error "BOOM!"
--
-- >>> boom = error "BOOM!"
--
-- >>> runEff . runError @ErrorCall $ boom `catchError` \_ (_::ErrorCall) -> pure "caught"
-- *** Exception: BOOM!
-- ...
@ -23,9 +25,10 @@
-- resources such as 'Control.Monad.Catch.finally' and
-- 'Control.Monad.Catch.bracket' work as expected:
--
-- >>> let msg = liftIO . putStrLn
-- >>> msg = liftIO . putStrLn
--
-- >>> :{
-- runEff . fmap (either (Left . snd) Right) . runError @String $ do
-- runEff . runErrorNoCallStack @String $ do
-- E.bracket_ (msg "Beginning.")
-- (msg "Cleaning up.")
-- (msg "Computing." >> throwError "oops" >> msg "More.")
@ -43,7 +46,7 @@
-- >>> import qualified Control.Monad.State.Strict as T
-- >>> import qualified Control.Monad.Except as T
--
-- >>> let m1 = (T.modify (++ " there!") >> T.throwError "oops") `T.catchError` \_ -> pure ()
-- >>> m1 = (T.modify (++ " there!") >> T.throwError "oops") `T.catchError` \_ -> pure ()
--
-- >>> (`T.runStateT` "Hi") . T.runExceptT $ m1
-- (Right (),"Hi there!")
@ -57,7 +60,7 @@
--
-- >>> import Effectful.State.Static.Local
--
-- >>> let m2 = (modify (++ " there!") >> throwError "oops") `catchError` \_ (_::String) -> pure ()
-- >>> m2 = (modify (++ " there!") >> throwError "oops") `catchError` \_ (_::String) -> pure ()
--
-- >>> runEff . runState "Hi" . runError @String $ m2
-- (Right (),"Hi there!")
@ -70,6 +73,7 @@
module Effectful.Error.Static
( Error
, runError
, runErrorNoCallStack
, throwError
, catchError
, handleError
@ -114,6 +118,13 @@ 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'.
runErrorNoCallStack
:: forall e es a. Typeable e
=> Eff (Error e : es) a
-> Eff es (Either e a)
runErrorNoCallStack = fmap (either (Left . snd) Right) . runError
-- | Throw an error of type @e@.
throwError
:: forall e es a. (HasCallStack, Typeable e, Error e :> es)

View File

@ -12,12 +12,10 @@ import Effectful.Monad
-- | Run the 'Fail' effect via 'Error'.
runFail :: Eff (Fail : es) a -> Eff es (Either String a)
runFail = reinterpret eff $ \_ -> \case
runFail = reinterpret runErrorNoCallStack $ \_ -> \case
Fail msg -> throwError msg
where
eff = fmap (either (Left . snd) Right) . runError
-- | Run the 'Fail' effect by using the 'MonadFail' instance for 'IO'.
-- | Run the 'Fail' effect via the 'MonadFail' instance for 'IO'.
runFailIO :: IOE :> es => Eff (Fail : es) a -> Eff es a
runFailIO = interpret $ \_ -> \case
Fail msg -> liftIO $ fail msg

View File

@ -26,7 +26,7 @@ type Effect = (Type -> Type) -> Type -> Type
-- in the list.
--
-- For example, a computation that only needs access to a mutable value of type
-- 'Integer' would likely use the following type:
-- 'Integer' would have the following type:
--
-- @
-- 'Effectful.State.Static.Local.State' 'Integer' ':>' es => 'Effectful.Monad.Eff' es ()
@ -59,6 +59,6 @@ instance e :> es => e :> (x : es) where
-- in a more concise way than enumerating them all with '(:>)'.
--
-- @[E1, E2, ..., En] ':>>' es ≡ (E1 ':>' es, E2 ':>' es, ..., En :> es)@
type family effs :>> es :: Constraint where
type family xs :>> es :: Constraint where
'[] :>> es = ()
(e : effs) :>> es = (e :> es, effs :>> es)
(x : xs) :>> es = (x :> es, xs :>> es)

View File

@ -100,21 +100,15 @@ type role Eff nominal representational
-- would have the following type:
--
-- @
-- 'Eff' '['Effectful.Reader.Static.Reader' 'String', 'Effectful.State.Static.Local.State' 'Bool'] 'Integer'
-- @
--
-- Normally, a concrete list of effects is not used to parameterize 'Eff'.
-- Instead, the '(:>)' type class is used to express constraints on the list of
-- effects without coupling a computation to a concrete list of effects. For
-- example, the above example would be expressed with the following type:
--
-- @
-- ('Effectful.Reader.Static.Reader' 'String' ':>' es, 'Effectful.State.Static.Local.State' 'Bool' ':>' es) => 'Eff' es 'Integer'
-- @
--
-- This abstraction allows the computation to be used in functions that may
-- perform other effects, and it also allows the effects to be handled in any
-- order.
-- Abstracting over the list of effects with '(:>)':
--
-- - Allows the computation to be used in functions that may perform other
-- effects.
--
-- - Allows the effects to be handled in any order.
newtype Eff (es :: [Effect]) a = Eff (Env es -> IO a)
deriving (Monoid, Semigroup)
@ -273,6 +267,10 @@ instance Fail :> es => MonadFail (Eff es) where
-- IO
-- | Run arbitrary 'IO' computations via 'MonadIO' or 'MonadUnliftIO'.
--
-- /Note:/ it is not recommended to use this effect in application code as it is
-- too liberal. Ideally, this is only used in handlers of more fine-grained
-- effects.
data IOE :: Effect
type instance DispatchOf IOE = 'Static

View File

@ -35,9 +35,9 @@ import Effectful.Internal.Utils
----------------------------------------
-- Unlift strategies
-- | The strategy to use when unlifting 'Eff' computations via 'withRunInIO',
-- 'Effectful.Monad.withEffToIO' or the 'Effectful.Dispatch.Dynamic.localUnlift'
-- family.
-- | The strategy to use when unlifting 'Effectful.Monad.Eff' computations via
-- 'Control.Monad.IO.Unlift.withRunInIO', 'Effectful.Monad.withEffToIO' or the
-- 'Effectful.Dispatch.Dynamic.localUnlift' family.
data UnliftStrategy
= SeqUnlift
-- ^ The fastest strategy and a default setting for 'IOE'. An attempt to call

View File

@ -1,7 +1,6 @@
module Effectful.Monad
( -- * The 'Eff' monad
Eff
, runPureEff
-- ** Effect constraints
, Effect
@ -10,7 +9,12 @@ module Effectful.Monad
, (:>)
, (:>>)
-- * Arbitrary I/O
-- * Running the 'Eff' monad
-- ** Pure computations
, runPureEff
-- ** Computations with side effects
, IOE
, runEff

View File

@ -1,6 +1,6 @@
-- | Support for access to a mutable value of a particular type.
--
-- The value is thread local. If you want it to be shared between threads, see
-- The value is thread local. If you want it to be shared between threads, use
-- "Effectful.State.Static.Shared".
--
-- /Note:/ unlike the 'Control.Monad.Trans.State.StateT' monad transformer from

View File

@ -1,7 +1,7 @@
-- | Support for access to a shared, mutable value of a particular type.
--
-- The value is shared between multiple threads. If you want each thead to
-- manage its own version of the value, see "Effectful.State.Static.Local".
-- 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

View File

@ -1,6 +1,6 @@
-- | Support for access to a write only value of a particular type.
--
-- The value is thread local. If you want it to be shared between threads, see
-- The value is thread local. If you want it to be shared between threads, use
-- "Effectful.Writer.Static.Shared".
--
-- /Warning:/ 'Writer'\'s state will be accumulated via __left-associated__ uses

View File

@ -1,7 +1,7 @@
-- | Support for access to a write only value of a particular type.
--
-- The value is shared between multiple threads. If you want each thead to
-- manage its own version of the value, see "Effectful.Writer.Static.Local".
-- manage its own version of the value, use "Effectful.Writer.Static.Local".
--
-- /Warning:/ 'Writer'\'s state will be accumulated via __left-associated__ uses
-- of '<>', which makes it unsuitable for use with types for which such pattern

View File

@ -15,7 +15,9 @@ import Effectful.Monad
-- following:
--
-- >>> import qualified Effectful.Reader.Static as R
-- >>> let printAsk msg = liftIO . putStrLn . (msg ++) . (": " ++) =<< R.ask
--
-- >>> printAsk msg = liftIO . putStrLn . (msg ++) . (": " ++) =<< R.ask
--
-- >>> :{
-- runEff . R.runReader "GLOBAL" . runConcurrent $ do
-- a <- R.local (const "LOCAL") $ do