polysemy-1.0.0.0: Higher-order, low-boilerplate, zero-cost free monads.

Safe HaskellNone
LanguageHaskell2010

Polysemy.Internal

Synopsis

Documentation

newtype Sem r a Source #

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 tradtionally as an Either, or instead significantly faster as an IO Exception. These interpretations (and others that you might add) may be used interchangably without needing to write any newtypes or Monad instances. The only change needed to swap interpretations is to change a call from runError to lowerError.

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.

A Sem can be interpreted as a pure value (via run) or as any traditional Monad (via runM). 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 or a Sem '[ Embed m ] a value, which can be consumed respectively by run and runM.

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: 0.1.2.0

Constructors

Sem 

Fields

Instances
Monad (Sem f) Source # 
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 #

fail :: String -> Sem f a #

Functor (Sem f) Source # 
Instance details

Defined in Polysemy.Internal

Methods

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

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

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

Defined in Polysemy.Internal

Methods

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

Member NonDet r => MonadFail (Sem r) Source #

Since: 0.2.1.0

Instance details

Defined in Polysemy.Internal

Methods

fail :: String -> Sem r a #

Applicative (Sem f) Source # 
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 #

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

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) Source # 
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] #

Member NonDet r => MonadPlus (Sem r) Source #

Since: 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 #

type Member e r = MemberNoError e r Source #

A proof that the effect e is available somewhere inside of the effect stack r.

type family Members es r :: Constraint where ... Source #

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: 0.1.2.0

Equations

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

send :: Member e r => e (Sem r) a -> Sem r a Source #

Embed an effect into a Sem. This is used primarily via makeSem to implement smart constructors.

embed :: Member (Embed m) r => m a -> Sem r a Source #

Embed a monadic action m in Sem.

Since: 1.0.0.0

run :: Sem '[] a -> a Source #

Run a Sem containing no effects as a pure value.

runM :: Monad m => Sem '[Embed m] a -> m a Source #

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

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

Introduce an effect into Sem. Analogous to lift in the mtl ecosystem

raiseUnder :: forall e2 e1 r a. Sem (e1 ': r) a -> Sem (e1 ': (e2 ': r)) a Source #

Like raise, but introduces a new effect underneath the head of the list.

raiseUnder2 :: forall e2 e3 e1 r a. Sem (e1 ': r) a -> Sem (e1 ': (e2 ': (e3 ': r))) a Source #

Like raise, but introduces two new effects underneath the head of the list.

raiseUnder3 :: forall e2 e3 e4 e1 r a. Sem (e1 ': r) a -> Sem (e1 ': (e2 ': (e3 ': (e4 ': r)))) a Source #

Like raise, but introduces two new effects underneath the head of the list.

newtype Embed m (z :: Type -> Type) a where Source #

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: 1.0.0.0

Constructors

Embed 

Fields

usingSem :: Monad m => (forall x. Union r (Sem r) x -> m x) -> Sem r a -> m a Source #

Like runSem but flipped for better ergonomics sometimes.

liftSem :: Union r (Sem r) a -> Sem r a Source #

hoistSem :: (forall x. Union r (Sem r) x -> Union r' (Sem r') x) -> Sem r a -> Sem r' a Source #

(.@) infixl 8 Source #

Arguments

:: Monad m 
=> (forall x. Sem r x -> m x)

The lowering function, likely runM.

-> (forall y. (forall x. Sem r x -> m x) -> Sem (e ': r) y -> Sem r y) 
-> Sem (e ': r) z 
-> m z 

Some interpreters need to be able to lower down to the base monad (often IO) in order to function properly --- some good examples of this are lowerError and lowerResource.

However, these interpreters don't compose particularly nicely; for example, to run lowerResource, you must write:

runM . lowerError runM

Notice that runM is duplicated in two places here. The situation gets exponentially worse the more intepreters you have that need to run in this pattern.

Instead, .@ performs the composition we'd like. The above can be written as

(runM .@ lowerError)

The parentheses here are important; without them you'll run into operator precedence errors.

Warning: This combinator will duplicate work that is intended to be just for initialization. This can result in rather surprising behavior. For a version of .@ that won't duplicate work, see the .@! operator in polysemy-zoo.

(.@@) infixl 8 Source #

Arguments

:: Monad m 
=> (forall x. Sem r x -> m x)

The lowering function, likely runM.

-> (forall y. (forall x. Sem r x -> m x) -> Sem (e ': r) y -> Sem r (f y)) 
-> Sem (e ': r) z 
-> m (f z) 

Like .@, but for interpreters which change the resulting type --- eg. lowerError.