monad-classes-0.3.2.2: 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 :: Peano) m where Source #

Minimal complete definition

liftN

Associated Types

type Down n m :: * -> * Source #

Methods

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

Instances

MonadLiftN Zero m Source # 

Associated Types

type Down (Zero :: Peano) (m :: * -> *) :: * -> * Source #

Methods

liftN :: Proxy# Peano Zero -> Down Zero m a -> m a Source #

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

Associated Types

type Down (Succ n :: Peano) (t m :: * -> *) :: * -> * Source #

Methods

liftN :: Proxy# Peano (Succ n) -> Down (Succ n) (t m) a -> t m a Source #

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) Source # 
type CanDo * IO (EffExec IO) = True

data EffExcept (e :: *) Source #

Except effect

Instances

type CanDo * IO (EffExcept e) Source # 
type CanDo * IO (EffExcept e) = True

N-classes

data Peano :: * #

Constructors

Zero 
Succ Peano 

Instances

Bounded Peano 
Enum Peano 
Eq Peano 

Methods

(==) :: Peano -> Peano -> Bool #

(/=) :: Peano -> Peano -> Bool #

Integral Peano 
Data Peano 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Peano -> c Peano #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Peano #

toConstr :: Peano -> Constr #

dataTypeOf :: Peano -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Peano) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Peano) #

gmapT :: (forall b. Data b => b -> b) -> Peano -> Peano #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Peano -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Peano -> r #

gmapQ :: (forall d. Data d => d -> u) -> Peano -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Peano -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Peano -> m Peano #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Peano -> m Peano #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Peano -> m Peano #

Num Peano 
Ord Peano 

Methods

compare :: Peano -> Peano -> Ordering #

(<) :: Peano -> Peano -> Bool #

(<=) :: Peano -> Peano -> Bool #

(>) :: Peano -> Peano -> Bool #

(>=) :: Peano -> Peano -> Bool #

max :: Peano -> Peano -> Peano #

min :: Peano -> Peano -> Peano #

Read Peano 
Real Peano 

Methods

toRational :: Peano -> Rational #

Show Peano 

Methods

showsPrec :: Int -> Peano -> ShowS #

show :: Peano -> String #

showList :: [Peano] -> ShowS #

Ix Peano 

class Monad m => MonadStateN (n :: Peano) s m where Source #

Minimal complete definition

stateN

Methods

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

Instances

Monad m => MonadStateN Zero s (StateT s m) Source # 

Methods

stateN :: Proxy# Peano Zero -> (s -> (a, s)) -> StateT s m a Source #

Monad m => MonadStateN Zero s (StateT s m) Source # 

Methods

stateN :: Proxy# Peano Zero -> (s -> (a, s)) -> StateT s m a Source #

MonadState big m => MonadStateN Zero small (ZoomT * big small m) Source # 

Methods

stateN :: Proxy# Peano Zero -> (small -> (a, small)) -> ZoomT * big small m a Source #

(Monad (t m), MonadTrans t, MonadStateN n s m, Monad m) => MonadStateN (Succ n) s (t m) Source # 

Methods

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

class Monad m => MonadReaderN (n :: Peano) r m where Source #

Minimal complete definition

askN

Methods

askN :: Proxy# n -> m r Source #

Instances

Monad m => MonadReaderN Zero r (StateT r m) Source # 

Methods

askN :: Proxy# Peano Zero -> StateT r m r Source #

Monad m => MonadReaderN Zero r (StateT r m) Source # 

Methods

askN :: Proxy# Peano Zero -> StateT r m r Source #

MonadReaderN Zero r ((->) LiftedRep LiftedRep r) Source # 
Monad m => MonadReaderN Zero r (ReaderT * r m) Source # 

Methods

askN :: Proxy# Peano Zero -> ReaderT * r m r Source #

MonadState s m => MonadReaderN Zero s (ReadStateT * * s m) Source # 

Methods

askN :: Proxy# Peano Zero -> ReadStateT * * s m s Source #

MonadReader big m => MonadReaderN Zero small (ZoomT * big small m) Source # 

Methods

askN :: Proxy# Peano Zero -> ZoomT * big small m small Source #

(MonadTrans t, Monad (t m), MonadReaderN n r m, Monad m) => MonadReaderN (Succ n) r (t m) Source # 

Methods

askN :: Proxy# Peano (Succ n) -> t m r Source #

class Monad m => MonadLocalN (n :: Peano) r m where Source #

Minimal complete definition

localN

Methods

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

Instances

Monad m => MonadLocalN Zero r (StateT r m) Source # 

Methods

localN :: Proxy# Peano Zero -> (r -> r) -> StateT r m a -> StateT r m a Source #

Monad m => MonadLocalN Zero r (StateT r m) Source # 

Methods

localN :: Proxy# Peano Zero -> (r -> r) -> StateT r m a -> StateT r m a Source #

MonadLocalN Zero r ((->) LiftedRep LiftedRep r) Source # 

Methods

localN :: Proxy# Peano Zero -> (r -> r) -> (LiftedRep -> LiftedRep) r a -> (LiftedRep -> LiftedRep) r a Source #

Monad m => MonadLocalN Zero r (ReaderT * r m) Source # 

Methods

localN :: Proxy# Peano Zero -> (r -> r) -> ReaderT * r m a -> ReaderT * r m a Source #

(MonadTrans t, Monad (t m), MFunctor * t, MonadLocalN n r m, Monad m) => MonadLocalN (Succ n) r (t m) Source # 

Methods

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

class Monad m => MonadWriterN (n :: Peano) w m where Source #

Minimal complete definition

tellN

Methods

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

Instances

(Monad m, Monoid w) => MonadWriterN Zero w (StateT w m) Source # 

Methods

tellN :: Proxy# Peano Zero -> w -> StateT w m () Source #

(Monad m, Monoid w) => MonadWriterN Zero w (StateT w m) Source # 

Methods

tellN :: Proxy# Peano Zero -> w -> StateT w m () Source #

(Monad m, Monoid w) => MonadWriterN Zero w (WriterT w m) Source # 

Methods

tellN :: Proxy# Peano Zero -> w -> WriterT w m () Source #

(Monad m, Monoid w) => MonadWriterN Zero w (WriterT w m) Source # 

Methods

tellN :: Proxy# Peano Zero -> w -> WriterT w m () Source #

Monad m => MonadWriterN Zero w (CustomWriterT' * w m m) Source # 

Methods

tellN :: Proxy# Peano Zero -> w -> CustomWriterT' * w m m () Source #

(MonadState big m, Monoid small) => MonadWriterN Zero small (ZoomT * big small m) Source # 

Methods

tellN :: Proxy# Peano Zero -> small -> ZoomT * big small m () Source #

(MonadTrans t, Monad (t m), MonadWriterN n w m, Monad m) => MonadWriterN (Succ n) w (t m) Source # 

Methods

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

class Monad m => MonadExceptN (n :: Peano) e m where Source #

Minimal complete definition

throwN

Methods

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

Instances

Exception e => MonadExceptN Zero e IO Source # 

Methods

throwN :: Proxy# Peano Zero -> e -> IO a Source #

Monad m => MonadExceptN Zero () (MaybeT m) Source # 

Methods

throwN :: Proxy# Peano Zero -> () -> MaybeT m a Source #

Monad m => MonadExceptN Zero e (ExceptT e m) Source # 

Methods

throwN :: Proxy# Peano Zero -> e -> ExceptT e m a Source #

(MonadTrans t, Monad (t m), MonadExceptN n e m, Monad m) => MonadExceptN (Succ n) e (t m) Source # 

Methods

throwN :: Proxy# Peano (Succ n) -> e -> t m a Source #

class Monad m => MonadExecN (n :: Peano) w m where Source #

Minimal complete definition

execN

Methods

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

Instances

Monad w => MonadExecN Zero w w Source # 

Methods

execN :: Proxy# Peano Zero -> w a -> w a Source #

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

Methods

execN :: Proxy# Peano (Succ n) -> w a -> t m a Source #

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 :: [Bool]) :: Peano where ... 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 :: k) (stack :: * -> *) :: [Bool] where ... 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 :: k) :: 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) Source # 
type CanDo * IO (EffExcept e) = True
type CanDo * IO (EffExec IO) Source # 
type CanDo * IO (EffExec IO) = True
type CanDo * (MaybeT m) eff Source # 
type CanDo * (MaybeT m) eff
type CanDo * (WriterT w m) eff Source # 
type CanDo * (WriterT w m) eff
type CanDo * (StateT s m) eff Source # 
type CanDo * (StateT s m) eff
type CanDo * (ExceptT e m) eff Source # 
type CanDo * (ExceptT e m) eff
type CanDo * (StateT s m) eff Source # 
type CanDo * (StateT s m) eff
type CanDo * (WriterT w m) eff Source # 
type CanDo * (WriterT w m) eff
type CanDo * ((->) LiftedRep LiftedRep e) eff Source # 
type CanDo * ((->) LiftedRep LiftedRep e) eff
type CanDo * (ReaderT * e m) eff Source # 
type CanDo * (ReaderT * e m) eff
type CanDo * (ReadStateT * * s m) eff Source # 
type CanDo * (ReadStateT * * s m) eff
type CanDo * (CustomWriterT' * w n m) eff Source # 
type CanDo * (CustomWriterT' * w n m) eff
type CanDo * (ZoomT * big small m) eff Source # 
type CanDo * (ZoomT * big small m) eff