hw-polysemy-0.2.5.0: Opinionated polysemy library
Safe HaskellSafe-Inferred
LanguageGHC2021

HaskellWorks.Polysemy

Synopsis

Documentation

class Member (t :: Effect) (r :: EffectRow) #

This class indicates that an effect must be present in the caller's stack. It is the main mechanism by which a program defines its effect dependencies.

Minimal complete definition

membership'

Instances

Instances details
Member t z => Member t (_1 ': z) 
Instance details

Defined in Polysemy.Internal.Union

Methods

membership' :: ElemOf t (_1 ': z)

Member t (t ': z) 
Instance details

Defined in Polysemy.Internal.Union

Methods

membership' :: ElemOf t (t ': z)

type family Members (es :: [Effect]) (r :: EffectRow) where ... #

Makes constraints of functions that use multiple effects shorter by translating single list of effects into multiple Member constraints:

foo :: Members '[ Output Int
                , Output Bool
                , State String
                ] r
    => Sem r ()

translates into:

foo :: ( Member (Output Int) r
       , Member (Output Bool) r
       , Member (State String) r
       )
    => Sem r ()

Since: polysemy-0.1.2.0

Equations

Members ('[] :: [Effect]) r = () 
Members (e ': es) r = (Member e r, Members es r) 

data Sem (r :: EffectRow) a #

The Sem monad handles computations of arbitrary extensible effects. A value of type Sem r describes a program with the capabilities of r. For best results, r should always be kept polymorphic, but you can add capabilities via the Member constraint.

The value of the Sem monad is that it allows you to write programs against a set of effects without a predefined meaning, and provide that meaning later. For example, unlike with mtl, you can decide to interpret an Error effect traditionally as an Either, or instead as (a significantly faster) IO Exception. These interpretations (and others that you might add) may be used interchangeably without needing to write any newtypes or Monad instances. The only change needed to swap interpretations is to change a call from runError to errorToIOFinal.

The effect stack r can contain arbitrary other monads inside of it. These monads are lifted into effects via the Embed effect. Monadic values can be lifted into a Sem via embed.

Higher-order actions of another monad can be lifted into higher-order actions of Sem via the Final effect, which is more powerful than Embed, but also less flexible to interpret.

A Sem can be interpreted as a pure value (via run) or as any traditional Monad (via runM or runFinal). Each effect E comes equipped with some interpreters of the form:

runE :: Sem (E ': r) a -> Sem r a

which is responsible for removing the effect E from the effect stack. It is the order in which you call the interpreters that determines the monomorphic representation of the r parameter.

Order of interpreters can be important - it determines behaviour of effects that manipulate state or change control flow. For example, when interpreting this action:

>>> :{
  example :: Members '[State String, Error String] r => Sem r String
  example = do
    put "start"
    let throwing, catching :: Members '[State String, Error String] r => Sem r String
        throwing = do
          modify (++"-throw")
          throw "error"
          get
        catching = do
          modify (++"-catch")
          get
    catch @String throwing (\ _ -> catching)
:}

when handling Error first, state is preserved after error occurs:

>>> :{
  example
    & runError
    & fmap (either id id)
    & evalState ""
    & runM
    & (print =<<)
:}
"start-throw-catch"

while handling State first discards state in such cases:

>>> :{
  example
    & evalState ""
    & runError
    & fmap (either id id)
    & runM
    & (print =<<)
:}
"start-catch"

A good rule of thumb is to handle effects which should have "global" behaviour over other effects later in the chain.

After all of your effects are handled, you'll be left with either a Sem '[] a, a Sem '[ Embed m ] a, or a Sem '[ Final m ] a value, which can be consumed respectively by run, runM, and runFinal.

Examples

As an example of keeping r polymorphic, we can consider the type

Member (State String) r => Sem r ()

to be a program with access to

get :: Sem r String
put :: String -> Sem r ()

methods.

By also adding a

Member (Error Bool) r

constraint on r, we gain access to the

throw :: Bool -> Sem r a
catch :: Sem r a -> (Bool -> Sem r a) -> Sem r a

functions as well.

In this sense, a Member (State s) r constraint is analogous to mtl's MonadState s m and should be thought of as such. However, unlike mtl, a Sem monad may have an arbitrary number of the same effect.

For example, we can write a Sem program which can output either Ints or Bools:

foo :: ( Member (Output Int) r
       , Member (Output Bool) r
       )
    => Sem r ()
foo = do
  output @Int  5
  output True

Notice that we must use -XTypeApplications to specify that we'd like to use the (Output Int) effect.

Since: polysemy-0.1.2.0

Instances

Instances details
Member (Fail :: (Type -> Type) -> Type -> Type) r => MonadFail (Sem r)

Since: polysemy-1.1.0.0

Instance details

Defined in Polysemy.Internal

Methods

fail :: String -> Sem r a #

Member Fixpoint r => MonadFix (Sem r) 
Instance details

Defined in Polysemy.Internal

Methods

mfix :: (a -> Sem r a) -> Sem r a #

Member (Embed IO) r => MonadIO (Sem r)

This instance will only lift IO actions. If you want to lift into some other MonadIO type, use this instance, and handle it via the embedToMonadIO interpretation.

Instance details

Defined in Polysemy.Internal

Methods

liftIO :: IO a -> Sem r a #

Member NonDet r => Alternative (Sem r) 
Instance details

Defined in Polysemy.Internal

Methods

empty :: Sem r a #

(<|>) :: Sem r a -> Sem r a -> Sem r a #

some :: Sem r a -> Sem r [a] #

many :: Sem r a -> Sem r [a] #

Applicative (Sem f) 
Instance details

Defined in Polysemy.Internal

Methods

pure :: a -> Sem f a #

(<*>) :: Sem f (a -> b) -> Sem f a -> Sem f b #

liftA2 :: (a -> b -> c) -> Sem f a -> Sem f b -> Sem f c #

(*>) :: Sem f a -> Sem f b -> Sem f b #

(<*) :: Sem f a -> Sem f b -> Sem f a #

Functor (Sem f) 
Instance details

Defined in Polysemy.Internal

Methods

fmap :: (a -> b) -> Sem f a -> Sem f b #

(<$) :: a -> Sem f b -> Sem f a #

Monad (Sem f) 
Instance details

Defined in Polysemy.Internal

Methods

(>>=) :: Sem f a -> (a -> Sem f b) -> Sem f b #

(>>) :: Sem f a -> Sem f b -> Sem f b #

return :: a -> Sem f a #

Member NonDet r => MonadPlus (Sem r)

Since: polysemy-0.2.1.0

Instance details

Defined in Polysemy.Internal

Methods

mzero :: Sem r a #

mplus :: Sem r a -> Sem r a -> Sem r a #

Monoid a => Monoid (Sem f a)

Since: polysemy-1.6.0.0

Instance details

Defined in Polysemy.Internal

Methods

mempty :: Sem f a #

mappend :: Sem f a -> Sem f a -> Sem f a #

mconcat :: [Sem f a] -> Sem f a #

Semigroup a => Semigroup (Sem f a)

Since: polysemy-1.6.0.0

Instance details

Defined in Polysemy.Internal

Methods

(<>) :: Sem f a -> Sem f a -> Sem f a #

sconcat :: NonEmpty (Sem f a) -> Sem f a #

stimes :: Integral b => b -> Sem f a -> Sem f a #

send :: forall e (r :: EffectRow) a. Member e r => e (Sem r) a -> Sem r a #

Execute an action of an effect.

This is primarily used to create methods for actions of effects:

data FooBar m a where
  Foo :: String -> m a -> FooBar m a
  Bar :: FooBar m Int

foo :: Member FooBar r => String -> Sem r a -> Sem r a
foo s m = send (Foo s m)

bar :: Member FooBar r => Sem r Int
bar = send Bar

makeSem allows you to eliminate this boilerplate.

@since TODO

makeSem :: Name -> Q [Dec] #

If T is a GADT representing an effect algebra, as described in the module documentation for Polysemy, $(makeSem ''T) automatically generates a smart constructor for every data constructor of T. This also works for data family instances. Names of smart constructors are created by changing first letter to lowercase or removing prefix : in case of operators. Fixity declaration is preserved for both normal names and operators.

Since: polysemy-0.1.2.0

makeSem_ :: Name -> Q [Dec] #

Like makeSem, but does not provide type signatures and fixities. This can be used to attach Haddock comments to individual arguments for each generated function.

data Output o m a where
  Output :: o -> Output o m ()

makeSem_ ''Output

-- | Output the value @o@.
output :: forall o r
       .  Member (Output o) r
       => o         -- ^ Value to output.
       -> Sem r ()  -- ^ No result.

Because of limitations in Template Haskell, signatures have to follow some rules to work properly:

  • makeSem_ must be used before the explicit type signatures
  • signatures have to specify argument of Sem representing union of effects as r (e.g. Sem r ())
  • all arguments in effect's type constructor have to follow naming scheme from data constructor's declaration:
data Foo e m a where
  FooC1 :: Foo x m ()
  FooC2 :: Foo (Maybe x) m ()

should have x in type signature of fooC1:

fooC1 :: forall x r. Member (Foo x) r => Sem r ()

and Maybe x in signature of fooC2:

fooC2 :: forall x r. Member (Foo (Maybe x)) r => Sem r ()
  • all effect's type variables and r have to be explicitly quantified using forall (order is not important)

These restrictions may be removed in the future, depending on changes to the compiler.

Change in (TODO(Sandy): version): in case of GADTs, signatures now only use names from data constructor's type and not from type constructor declaration.

Since: polysemy-0.1.2.0

data Final (m :: Type -> Type) (z :: Type -> Type) a #

An effect for embedding higher-order actions in the final target monad of the effect stack.

This is very useful for writing interpreters that interpret higher-order effects in terms of the final monad.

Final is more powerful than Embed, but is also less flexible to interpret (compare runEmbedded with finalToFinal). If you only need the power of embed, then you should use Embed instead.

Beware: Final actions are interpreted as actions of the final monad, and the effectful state visible to withWeavingToFinal / withStrategicToFinal / interpretFinal is that of all interpreters run in order to produce the final monad.

This means that any interpreter built using Final will not respect local/global state semantics based on the order of interpreters run. You should signal interpreters that make use of Final by adding a -Final suffix to the names of these.

State semantics of effects that are not interpreted in terms of the final monad will always appear local to effects that are interpreted in terms of the final monad.

State semantics between effects that are interpreted in terms of the final monad depend on the final monad. For example, if the final monad is a monad transformer stack, then state semantics will depend on the order monad transformers are stacked.

Since: polysemy-1.2.0.0

runFinal :: Monad m => Sem '[Final m] a -> m a #

Lower a Sem containing only a single lifted, final Monad into that monad.

If you also need to process an Embed m effect, use this together with embedToFinal.

Since: polysemy-1.2.0.0

data Async (m :: Type -> Type) a #

An effect for spawning asynchronous computations.

The Maybe returned by async is due to the fact that we can't be sure an Error effect didn't fail locally.

Since: polysemy-0.5.0.0

async :: forall (r :: EffectRow) a. Member Async r => Sem r a -> Sem r (Async (Maybe a)) #

Run the given action asynchronously and return a thread handle.

await :: forall (r :: EffectRow) a. Member Async r => Async a -> Sem r a #

Wait for the thread referenced by the given handle to terminate.

cancel :: forall (r :: EffectRow) a. Member Async r => Async a -> Sem r () #

Cancel the thread referenced by the given handle.

sequenceConcurrently :: forall t (r :: EffectRow) a. (Traversable t, Member Async r) => t (Sem r a) -> Sem r (t (Maybe a)) #

Perform a sequence of effectful actions concurrently.

Since: polysemy-1.2.2.0

data DataLog a (b :: Type -> Type) c #

Structural logs, used as a backend for the simpler Text log effect, Log.

Can also be used on its own, or reinterpreted into an effect like those from co-log or di.

data Log (a :: Type -> Type) b #

The default high-level effect for simple text messages. To be used with the severity constructors:

import qualified Polysemy.Log as Log

prog = do
  Log.debug "debugging…"
  Log.warn "warning!"

Interpreters should preprocess and relay the message to DataLog.

data LogEntry a #

Metadata wrapper for a log message.

Instances

Instances details
Show a => Show (LogEntry a) 
Instance details

Defined in Polysemy.Log.Data.LogEntry

Methods

showsPrec :: Int -> LogEntry a -> ShowS #

show :: LogEntry a -> String #

showList :: [LogEntry a] -> ShowS #

type Logger = DataLog (LogEntry LogMessage) #

Alias for the logger with the default message type used by Log.

data LogMessage #

User-specified part of the default logging data, consisting of a severity level like warning, error, debug, and a plain text message.

Instances

Instances details
Show LogMessage 
Instance details

Defined in Polysemy.Log.Data.LogMessage

Eq LogMessage 
Instance details

Defined in Polysemy.Log.Data.LogMessage

data Severity #

A log message's severity, or log level.

dataLog :: forall a (r :: EffectRow). Member (DataLog a) r => a -> Sem r () #

Schedule an arbitrary value for logging.

log :: forall (r :: EffectRow). (HasCallStack, Member Log r) => Severity -> Text -> Sem r () #

Log a message with the given severity. Basic Sem constructor.

trace :: forall (r :: EffectRow). (HasCallStack, Member Log r) => Text -> Sem r () #

Log a message with the Trace severity.

debug :: forall (r :: EffectRow). (HasCallStack, Member Log r) => Text -> Sem r () #

Log a message with the Debug severity.

info :: forall (r :: EffectRow). (HasCallStack, Member Log r) => Text -> Sem r () #

Log a message with the Info severity.

warn :: forall (r :: EffectRow). (HasCallStack, Member Log r) => Text -> Sem r () #

Log a message with the Warn severity.

error :: forall (r :: EffectRow). (HasCallStack, Member Log r) => Text -> Sem r () #

Log a message with the Error severity.

crit :: forall (r :: EffectRow). (HasCallStack, Member Log r) => Text -> Sem r () #

Log a message with the Crit severity.

formatLogEntry :: LogEntry LogMessage -> Text #

Default formatter for the default message type.

setLogLevel :: forall (r :: EffectRow) a. Member (DataLog (LogEntry LogMessage)) r => Maybe Severity -> Sem r a -> Sem r a #

Set the minimum severity for messages to be handled, with Nothing meaning no messages are logged.

setLogLevelWith :: forall msg (r :: EffectRow) a. Member (DataLog msg) r => (msg -> Severity) -> Maybe Severity -> Sem r a -> Sem r a #

Set the minimum severity for messages to be handled, with Nothing meaning no messages are logged. This can be used with arbitrary message types, using the ex argument to extract the severity from the message.

data Embed (m :: Type -> Type) (z :: Type -> Type) a #

An effect which allows a regular Monad m into the Sem ecosystem. Monadic actions in m can be lifted into Sem via embed.

For example, you can use this effect to lift IO actions directly into Sem:

embed (putStrLn "hello") :: Member (Embed IO) r => Sem r ()

That being said, you lose out on a significant amount of the benefits of Sem by using embed directly in application code; doing so will tie your application code directly to the underlying monad, and prevent you from interpreting it differently. For best results, only use Embed in your effect interpreters.

Consider using trace and traceToIO as a substitute for using putStrLn directly.

Since: polysemy-1.0.0.0

embed :: forall m (r :: EffectRow) a. Member (Embed m) r => m a -> Sem r a #

Embed a monadic action m in Sem.

Since: polysemy-1.0.0.0

embedToFinal :: forall (m :: Type -> Type) (r :: EffectRow) a. (Member (Final m) r, Functor m) => Sem (Embed m ': r) a -> Sem r a #

Transform an Embed m effect into a Final m effect

Since: polysemy-1.2.0.0

runEmbedded :: forall m1 m2 (r :: EffectRow) a. Member (Embed m2) r => (forall x. m1 x -> m2 x) -> Sem (Embed m1 ': r) a -> Sem r a #

Given a natural transform from m1 to m2 run a Embed m1 effect by transforming it into a Embed m2 effect.

Since: polysemy-1.0.0.0

data Error e (m :: k -> Type) (a :: k) #

This effect abstracts the throwing and catching of errors, leaving it up to the interpreter whether to use exceptions or monad transformers like ExceptT to perform the short-circuiting mechanism.

throw :: forall e (r :: EffectRow) a. Member (Error e :: (Type -> Type) -> Type -> Type) r => e -> Sem r a #

Short-circuit the current program using the given error value.

catch :: forall e (r :: EffectRow) a. Member (Error e :: (Type -> Type) -> Type -> Type) r => Sem r a -> (e -> Sem r a) -> Sem r a #

Recover from an error that might have been thrown in the higher-order action given by the first argument by passing the error to the handler given by the second argument.

trap :: forall e r a. (e -> Sem r a) -> Sem (Error e ': r) a -> Sem r a Source #

Run a computation that may fail, and handle the error case. Unlike catch from Error this function removes the Error effect from the stack.

trap_ :: forall e r a. Sem r a -> Sem (Error e ': r) a -> Sem r a Source #

Like trap, but the error is not passed to the handler.

fromEither :: forall e (r :: EffectRow) a. Member (Error e :: (Type -> Type) -> Type -> Type) r => Either e a -> Sem r a #

Upgrade an Either into an Error effect.

Since: polysemy-0.5.1.0

fromEitherM :: forall e m (r :: EffectRow) a. (Member (Error e :: (Type -> Type) -> Type -> Type) r, Member (Embed m) r) => m (Either e a) -> Sem r a #

A combinator doing embed and fromEither at the same time. Useful for interoperating with IO.

Since: polysemy-0.5.1.0

fromException :: forall e (r :: EffectRow) a. (Exception e, Member (Error e :: (Type -> Type) -> Type -> Type) r, Member (Embed IO) r) => IO a -> Sem r a #

Lift an exception generated from an IO action into an Error.

fromExceptionVia :: forall exc err (r :: EffectRow) a. (Exception exc, Member (Error err :: (Type -> Type) -> Type -> Type) r, Member (Embed IO) r) => (exc -> err) -> IO a -> Sem r a #

Like fromException, but with the ability to transform the exception before turning it into an Error.

note :: forall e (r :: EffectRow) a. Member (Error e :: (Type -> Type) -> Type -> Type) r => e -> Maybe a -> Sem r a #

Attempt to extract a Just a from a Maybe a, throwing the provided exception upon Nothing.

try :: forall e (r :: EffectRow) a. Member (Error e :: (Type -> Type) -> Type -> Type) r => Sem r a -> Sem r (Either e a) #

Similar to catch, but returns an Either result which is (Right a) if no exception of type e was thrown, or (Left ex) if an exception of type e was thrown and its value is ex.

tryJust :: forall e (r :: EffectRow) b a. Member (Error e :: (Type -> Type) -> Type -> Type) r => (e -> Maybe b) -> Sem r a -> Sem r (Either b a) #

A variant of try that takes an exception predicate to select which exceptions are caught (c.f. catchJust). If the exception does not match the predicate, it is re-thrown.

catchJust #

Arguments

:: forall e (r :: EffectRow) b a. Member (Error e :: (Type -> Type) -> Type -> Type) r 
=> (e -> Maybe b)

Predicate to select exceptions

-> Sem r a

Computation to run

-> (b -> Sem r a)

Handler

-> Sem r a 

The function catchJust is like catch, but it takes an extra argument which is an exception predicate, a function which selects which type of exceptions we're interested in.

mapError :: forall e1 e2 (r :: EffectRow) a. Member (Error e2 :: (Type -> Type) -> Type -> Type) r => (e1 -> e2) -> Sem ((Error e1 :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a #

Transform one Error into another. This function can be used to aggregate multiple errors into a single type.

Since: polysemy-1.0.0.0

onLeft :: forall e m a. Monad m => (e -> m a) -> Either e a -> m a Source #

onNothing :: forall a m. Monad m => m a -> Maybe a -> m a Source #

onLeftM :: forall e m a. Monad m => (e -> m a) -> m (Either e a) -> m a Source #

onNothingM :: forall a m. Monad m => m a -> m (Maybe a) -> m a Source #

runError :: forall e (r :: [(Type -> Type) -> Type -> Type]) a. Sem ((Error e :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r (Either e a) #

Run an Error effect in the style of ExceptT.

data Reader i (m :: Type -> Type) a #

An effect corresponding to ReaderT.

ask :: forall i (r :: EffectRow). Member (Reader i) r => Sem r i #

Get the environment.

asks :: forall i j (r :: EffectRow). Member (Reader i) r => (i -> j) -> Sem r j #

Apply a function to the environment and return the result.

inputToReader :: forall i (r :: EffectRow) a. Member (Reader i) r => Sem ((Input i :: (Type -> Type) -> Type -> Type) ': r) a -> Sem r a #

Transform an Input effect into a Reader effect.

Since: polysemy-1.0.0.0

runReader :: forall i (r :: [(Type -> Type) -> Type -> Type]) a. i -> Sem (Reader i ': r) a -> Sem r a #

Run a Reader effect with a constant value.

data Resource (m :: Type -> Type) a #

An effect capable of providing bracket semantics. Interpreters for this will successfully run the deallocation action even in the presence of other short-circuiting effects.

bracket :: forall (r :: EffectRow) a c b. Member Resource r => Sem r a -> (a -> Sem r c) -> (a -> Sem r b) -> Sem r b #

Allocate a resource, use it, and clean it up afterwards.

bracket_ #

Arguments

:: forall (r :: EffectRow) a b c. Member Resource r 
=> Sem r a

computation to run first

-> Sem r b

computation to run last (even if an exception was raised)

-> Sem r c

computation to run in-between

-> Sem r c 

A variant of bracket where the return value from the first computation is not required.

cf. bracket and bracket_

Since: polysemy-1.5.0.0

bracketOnError :: forall (r :: EffectRow) a c b. Member Resource r => Sem r a -> (a -> Sem r c) -> (a -> Sem r b) -> Sem r b #

Allocate a resource, use it, and clean it up afterwards if an error occurred.

finally #

Arguments

:: forall (r :: EffectRow) a b. Member Resource r 
=> Sem r a

computation to run first

-> Sem r b

computation to run afterward (even if an exception was raised)

-> Sem r a 

Like bracket, but for the simple case of one computation to run afterward.

Since: polysemy-0.4.0.0

onException #

Arguments

:: forall (r :: EffectRow) a b. Member Resource r 
=> Sem r a

computation to run first

-> Sem r b

computation to run afterward if an exception was raised

-> Sem r a 

Like bracketOnError, but for the simple case of one computation to run afterward.

Since: polysemy-0.4.0.0

runResource :: forall (r :: [(Type -> Type) -> Type -> Type]) a. Sem (Resource ': r) a -> Sem r a #

Run a Resource effect purely.

Since: polysemy-1.0.0.0