simple-effects-0.12.0.0: A simple effect system that integrates with MTL

Safe HaskellNone
LanguageHaskell2010

Control.Effects.Reader

Description

The regular old MonadReader effect with some differences. First, there's no functional dependency limiting your stack to a single environment type. This means less type inference so it might not be enough to just write readEnv. Write 'readEnv @MyEnvType' instead using TypeApplications.

Second, the function has a less generic name and is called readEnv.

Third, since it's a part of this effect framework, you get a implementReadEnv function with which you can provide a different environment implementation _at runtime_.

Synopsis

Documentation

newtype ReadEnv e m Source #

Constructors

ReadEnvMethods 

Fields

Instances

Effect (ReadEnv e) Source # 

Associated Types

type CanLift (ReadEnv e :: (* -> *) -> *) (t :: (* -> *) -> * -> *) :: Constraint Source #

Methods

liftThrough :: (CanLift (ReadEnv e) t, Monad m, Monad (t m)) => ReadEnv e m -> ReadEnv e (t m) Source #

mergeContext :: Monad m => m (ReadEnv e m) -> ReadEnv e m Source #

Generic (ReadEnv e m) Source # 

Associated Types

type Rep (ReadEnv e m) :: * -> * #

Methods

from :: ReadEnv e m -> Rep (ReadEnv e m) x #

to :: Rep (ReadEnv e m) x -> ReadEnv e m #

type CanLift (ReadEnv e) t Source # 
type CanLift (ReadEnv e) t = MonadTrans t
type Rep (ReadEnv e m) Source # 
type Rep (ReadEnv e m) = D1 * (MetaData "ReadEnv" "Control.Effects.Reader" "simple-effects-0.12.0.0-7DU8lieKyuzCHjL9A6aZte" True) (C1 * (MetaCons "ReadEnvMethods" PrefixI True) (S1 * (MetaSel (Just Symbol "_readEnv") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (m e))))

readEnv :: forall e m. MonadEffect (ReadEnv e) m => m e Source #

Read a value of type e. Use with the TypeApplications extension to help with type inference readEnv @Int

implementReadEnv :: Functor m => m e -> RuntimeImplemented (ReadEnv e) m a -> m a Source #

Use the given action in the underlying monad to provide environment values. You can think of implementReadEnv x m as replacing all readEnv calls in m with x.