monad-classes-0.3.1.0: more flexible mtl

Safe HaskellNone
LanguageHaskell2010

Control.Monad.Classes

Contents

Synopsis

State

type MonadState s m = MonadStateN (Find (EffState s) m) s m Source

The MonadState s m constraint asserts that m is a monad stack that supports state operations on type s

state :: forall s m a. MonadState s m => (s -> (a, s)) -> m a Source

Construct a state monad computation from a function

get :: MonadState a m => m a Source

Fetch the current value of the state within the monad

put :: MonadState s m => s -> m () Source

put s sets the state within the monad to s

modify :: MonadState s m => (s -> s) -> m () Source

Maps an old state to a new state inside a state monad layer

modify' :: MonadState s m => (s -> s) -> m () Source

A variant of modify in which the computation is strict in the new state

gets :: MonadState s m => (s -> a) -> m a Source

Gets specific component of the state, using a projection function supplied.

Reader

type MonadReader e m = MonadReaderN (Find (EffReader e) m) e m Source

The MonadReader r m constraint asserts that m is a monad stack that supports a fixed environment of type r

type MonadLocal e m = MonadLocalN (Find (EffLocal e) m) e m Source

The MonadLocal r m constraint asserts that m is a monad stack that supports a fixed environment of type r that can be changed externally to the monad

ask :: forall m r. MonadReader r m => m r Source

Fetch the environment passed through the reader monad

local Source

Arguments

:: MonadLocal r m 
=> (r -> r)

The function to modify the environment.

-> m a

Reader to run in the modified environment.

-> m a 

Executes a computation in a modified environment.

Writer

type MonadWriter w m = MonadWriterN (Find (EffWriter w) m) w m Source

The MonadWriter w m constraint asserts that m is a monad stack that supports outputting values of type w

tell :: forall w m. MonadWriter w m => w -> m () Source

tell w is an action that produces the output w

Exceptions

type MonadExcept e m = MonadExceptN (Find (EffExcept e) m) e m Source

The MonadExcept e m constraint asserts that m is a monad stack that supports throwing exceptions of type e

throw :: forall a e m. MonadExcept e m => e -> m a Source

Throw an exception

Exec

type MonadExec w m = MonadExecN (Find (EffExec w) m) w m Source

exec :: forall w m a. MonadExec w m => w a -> m a Source

Lift an IO action

Core classes and types

Generic lifting

class MonadLiftN n m where Source

Associated Types

type Down n m :: * -> * Source

Methods

liftN :: Proxy# n -> Down n m a -> m a Source

Instances

MonadLiftN Zero m 
(MonadLiftN n m, MonadTrans t, Monad m) => MonadLiftN (Succ n) (t m) 

Effects

data EffWriter w Source

Writer effect

data EffReader e Source

Reader effect

data EffLocal e Source

Local state change effect

data EffState s Source

State effect

data EffExec w Source

Arbitrary monadic effect

Instances

type CanDo * IO (EffExec IO) = True 

data EffExcept e Source

Except effect

Instances

type CanDo * IO (EffExcept e) = True 

N-classes

class Monad m => MonadStateN n s m where Source

Methods

stateN :: Proxy# n -> (s -> (a, s)) -> m a Source

Instances

Monad m => MonadStateN Zero s (StateT s m) 
Monad m => MonadStateN Zero s (StateT s m) 
MonadState big m => MonadStateN Zero small (ZoomT * big small m) 
(Monad (t m), MonadTrans t, MonadStateN n s m, Monad m) => MonadStateN (Succ n) s (t m) 

class Monad m => MonadReaderN n r m where Source

Methods

askN :: Proxy# n -> m r Source

Instances

Monad m => MonadReaderN Zero r (StateT r m) 
Monad m => MonadReaderN Zero r (StateT r m) 
Monad m => MonadReaderN Zero r (ReaderT r m) 
MonadReader big m => MonadReaderN Zero small (ZoomT * big small m) 
(MonadTrans t, Monad (t m), MonadReaderN n r m, Monad m) => MonadReaderN (Succ n) r (t m) 

class Monad m => MonadLocalN n r m where Source

Methods

localN :: Proxy# n -> (r -> r) -> m a -> m a Source

Instances

Monad m => MonadLocalN Zero r (StateT r m) 
Monad m => MonadLocalN Zero r (StateT r m) 
Monad m => MonadLocalN Zero r (ReaderT r m) 
(MonadTrans t, Monad (t m), MFunctor t, MonadLocalN n r m, Monad m) => MonadLocalN (Succ n) r (t m) 

class Monad m => MonadWriterN n w m where Source

Methods

tellN :: Proxy# n -> w -> m () Source

Instances

(Monad m, Monoid w) => MonadWriterN Zero w (StateT w m) 
(Monad m, Monoid w) => MonadWriterN Zero w (StateT w m) 
(Monad m, Monoid w) => MonadWriterN Zero w (WriterT w m) 
(Monad m, Monoid w) => MonadWriterN Zero w (WriterT w m) 
Monad m => MonadWriterN Zero w (CustomWriterT' * w m m) 
(MonadState big m, Monoid small) => MonadWriterN Zero small (ZoomT * big small m) 
(MonadTrans t, Monad (t m), MonadWriterN n w m, Monad m) => MonadWriterN (Succ n) w (t m) 

class Monad m => MonadExceptN n e m where Source

Methods

throwN :: Proxy# n -> e -> m a Source

Instances

Exception e => MonadExceptN Zero e IO 
Monad m => MonadExceptN Zero () (MaybeT m) 
Monad m => MonadExceptN Zero e (ExceptT e m) 
(MonadTrans t, Monad (t m), MonadExceptN n e m, Monad m) => MonadExceptN (Succ n) e (t m) 

class Monad m => MonadExecN n w m where Source

Methods

execN :: Proxy# n -> w a -> m a Source

Instances

Monad w => MonadExecN Zero w w 
(MonadTrans t, Monad (t m), MonadExecN n w m, Monad m) => MonadExecN (Succ n) w (t m) 

Type families

You should rarely need these. They are exported mostly for documentation and pedagogical purposes.

type Find eff m = FindTrue (MapCanDo eff m) Source

Find eff m finds the first transformer in a monad transformer stack that can handle the effect eff

type family FindTrue bs :: Peano Source

FindTrue bs returns a (type-level) index of the first occurrence of True in a list of booleans

Equations

FindTrue (True : t) = Zero 
FindTrue (False : t) = Succ (FindTrue t) 

type family MapCanDo eff stack :: [Bool] Source

MapCanDo eff stack maps the type-level function (m -> CanDo m eff) over all layers that a monad transformer stack stack consists of

Equations

MapCanDo eff (t m) = CanDo (t m) eff : MapCanDo eff m 
MapCanDo eff m = `[CanDo m eff]` 

type family CanDo m eff :: Bool Source

CanDo m eff describes whether the given effect can be performed in the monad m (without any additional lifting)

Instances

type CanDo * IO (EffExcept e) = True 
type CanDo * IO (EffExec IO) = True 
type CanDo * (MaybeT m) eff 
type CanDo * (WriterT w m) eff 
type CanDo * (WriterT w m) eff 
type CanDo * (ExceptT e m) eff 
type CanDo * (StateT s m) eff 
type CanDo * (StateT s m) eff 
type CanDo * (ReaderT e m) eff 
type CanDo * (CustomWriterT' * w n m) eff 
type CanDo * (ZoomT * big small m) eff