extensible-effects-4.0.0.0: An Alternative to Monad Transformers

Safe HaskellSafe
LanguageHaskell2010

Control.Eff.Reader.Lazy

Description

Lazy read-only state

Synopsis

Documentation

data Reader e v where Source #

The Reader monad

The request for a value of type e from the current environment This can be expressed as a GADT because the type of values returned in response to a (Reader e a) request is not any a; we expect in reply the value of type e, the value from the environment. So, the return type is restricted: 'a ~ e'

One can also define this as

data Reader e v = (e ~ v) => Reader

^ without GADTs, using explicit coercion as is done here.

newtype Reader e v = Reader (e->v)

^ In the latter case, when we make the request, we make it as Reader id. So, strictly speaking, GADTs are not really necessary.

Constructors

Ask :: Reader e e 
Instances
(MonadBase m m, LiftedBase m s) => MonadBaseControl m (Eff (Reader e ': s)) Source # 
Instance details

Defined in Control.Eff.Reader.Lazy

Associated Types

type StM (Eff (Reader e ': s)) a :: Type #

Methods

liftBaseWith :: (RunInBase (Eff (Reader e ': s)) m -> m a) -> Eff (Reader e ': s) a #

restoreM :: StM (Eff (Reader e ': s)) a -> Eff (Reader e ': s) a #

Handle (Reader e) (e -> r) Source #

Given a value to read, and a callback, how to respond to requests.

Instance details

Defined in Control.Eff.Reader.Lazy

Methods

handle :: (v -> e -> r) -> Reader e v -> e -> r Source #

type StM (Eff (Reader e ': s)) a Source # 
Instance details

Defined in Control.Eff.Reader.Lazy

type StM (Eff (Reader e ': s)) a = StM (Eff s) a

withReader :: Monad m => a -> e -> m a Source #

How to interpret a pure value in a reader context

ask :: Member (Reader e) r => Eff r e Source #

Get the current value from a Reader. The signature is inferred (when using NoMonomorphismRestriction).

local :: forall e a r. Member (Reader e) r => (e -> e) -> Eff r a -> Eff r a Source #

Locally rebind the value in the dynamic environment This function is like a relay; it is both an admin for Reader requests, and a requestor of them.

reader :: Member (Reader e) r => (e -> a) -> Eff r a Source #

Request the environment value using a transformation function.

runReader :: forall e r w. e -> Eff (Reader e ': r) w -> Eff r w Source #

The handler of Reader requests. The return type shows that all Reader requests are fully handled.