composite-base-0.5.2.0: Shared utilities for composite-* packages.

Safe HaskellNone
LanguageHaskell2010

Control.Monad.Composite.Context

Description

Module with a ReaderT style monad specialized to holding a record.

Synopsis

Documentation

newtype ContextT c m a Source #

Monad transformer which adds an implicit environment which is a record. Isomorphic to ReaderT (Record c) m.

Constructors

ContextT 

Fields

Instances

MonadRWS r w s m => MonadRWS r w s (ContextT c m) Source # 
MonadState s m => MonadState s (ContextT c m) Source # 

Methods

get :: ContextT c m s #

put :: s -> ContextT c m () #

state :: (s -> (a, s)) -> ContextT c m a #

MonadReader r m => MonadReader r (ContextT c m) Source # 

Methods

ask :: ContextT c m r #

local :: (r -> r) -> ContextT c m a -> ContextT c m a #

reader :: (r -> a) -> ContextT c m a #

MonadError e m => MonadError e (ContextT c m) Source # 

Methods

throwError :: e -> ContextT c m a #

catchError :: ContextT c m a -> (e -> ContextT c m a) -> ContextT c m a #

MonadWriter w m => MonadWriter w (ContextT c m) Source # 

Methods

writer :: (a, w) -> ContextT c m a #

tell :: w -> ContextT c m () #

listen :: ContextT c m a -> ContextT c m (a, w) #

pass :: ContextT c m (a, w -> w) -> ContextT c m a #

MonadBase b m => MonadBase b (ContextT c m) Source # 

Methods

liftBase :: b α -> ContextT c m α #

MonadBaseControl b m => MonadBaseControl b (ContextT c m) Source # 

Associated Types

type StM (ContextT c m :: * -> *) a :: * #

Methods

liftBaseWith :: (RunInBase (ContextT c m) b -> b a) -> ContextT c m a #

restoreM :: StM (ContextT c m) a -> ContextT c m a #

Monad m => MonadContext c (ContextT c m) Source # 

Methods

askContext :: ContextT c m (Record c) Source #

localContext :: (Record c -> Record c) -> ContextT c m a -> ContextT c m a Source #

MonadTrans (ContextT c) Source # 

Methods

lift :: Monad m => m a -> ContextT c m a #

MonadTransControl (ContextT c) Source # 

Associated Types

type StT (ContextT c :: (* -> *) -> * -> *) a :: * #

Methods

liftWith :: Monad m => (Run (ContextT c) -> m a) -> ContextT c m a #

restoreT :: Monad m => m (StT (ContextT c) a) -> ContextT c m a #

Monad m => Monad (ContextT c m) Source # 

Methods

(>>=) :: ContextT c m a -> (a -> ContextT c m b) -> ContextT c m b #

(>>) :: ContextT c m a -> ContextT c m b -> ContextT c m b #

return :: a -> ContextT c m a #

fail :: String -> ContextT c m a #

Functor m => Functor (ContextT c m) Source # 

Methods

fmap :: (a -> b) -> ContextT c m a -> ContextT c m b #

(<$) :: a -> ContextT c m b -> ContextT c m a #

MonadFix m => MonadFix (ContextT c m) Source # 

Methods

mfix :: (a -> ContextT c m a) -> ContextT c m a #

MonadFail m => MonadFail (ContextT c m) Source # 

Methods

fail :: String -> ContextT c m a #

Applicative m => Applicative (ContextT c m) Source # 

Methods

pure :: a -> ContextT c m a #

(<*>) :: ContextT c m (a -> b) -> ContextT c m a -> ContextT c m b #

(*>) :: ContextT c m a -> ContextT c m b -> ContextT c m b #

(<*) :: ContextT c m a -> ContextT c m b -> ContextT c m a #

MonadIO m => MonadIO (ContextT c m) Source # 

Methods

liftIO :: IO a -> ContextT c m a #

Alternative m => Alternative (ContextT c m) Source # 

Methods

empty :: ContextT c m a #

(<|>) :: ContextT c m a -> ContextT c m a -> ContextT c m a #

some :: ContextT c m a -> ContextT c m [a] #

many :: ContextT c m a -> ContextT c m [a] #

MonadPlus m => MonadPlus (ContextT c m) Source # 

Methods

mzero :: ContextT c m a #

mplus :: ContextT c m a -> ContextT c m a -> ContextT c m a #

MonadThrow m => MonadThrow (ContextT c m) Source # 

Methods

throwM :: Exception e => e -> ContextT c m a #

MonadCatch m => MonadCatch (ContextT c m) Source # 

Methods

catch :: Exception e => ContextT c m a -> (e -> ContextT c m a) -> ContextT c m a #

MonadMask m => MonadMask (ContextT c m) Source # 

Methods

mask :: ((forall a. ContextT c m a -> ContextT c m a) -> ContextT c m b) -> ContextT c m b #

uninterruptibleMask :: ((forall a. ContextT c m a -> ContextT c m a) -> ContextT c m b) -> ContextT c m b #

MonadCont m => MonadCont (ContextT c m) Source # 

Methods

callCC :: ((a -> ContextT c m b) -> ContextT c m a) -> ContextT c m a #

type StT (ContextT c) a Source # 
type StT (ContextT c) a = a
type StM (ContextT c m) a Source # 
type StM (ContextT c m) a = StM m a

runInContext :: Record c -> ContextT c m a -> m a Source #

Run some action in a given context, equivalent to runContextT but with the arguments flipped.

withContext :: (Record c' -> Record c) -> ContextT c m a -> ContextT c' m a Source #

Permute the current context with a function and then run some action with that modified context.

mapContextT :: (m a -> n b) -> ContextT c m a -> ContextT c n b Source #

Transform the monad underlying a ContextT using a natural transform.

class Monad m => MonadContext c m | m -> c where Source #

Class of monad (stacks) which have context reading functionality baked in. Similar to MonadReader but can coexist with a another monad that provides MonadReader and requires the context to be a record.

Minimal complete definition

askContext, localContext

Methods

askContext :: m (Record c) Source #

Fetch the context record from the environment.

localContext :: (Record c -> Record c) -> m a -> m a Source #

Run some action which has the same type of context with the context modified.

Instances

MonadContext c m => MonadContext c (MaybeT m) Source # 

Methods

askContext :: MaybeT m (Record c) Source #

localContext :: (Record c -> Record c) -> MaybeT m a -> MaybeT m a Source #

MonadContext c ((->) (Record c)) Source # 

Methods

askContext :: Record c -> Record c Source #

localContext :: (Record c -> Record c) -> (Record c -> a) -> Record c -> a Source #

Monad m => MonadContext c (ContextT c m) Source # 

Methods

askContext :: ContextT c m (Record c) Source #

localContext :: (Record c -> Record c) -> ContextT c m a -> ContextT c m a Source #

MonadContext c m => MonadContext c (ExceptT e m) Source # 

Methods

askContext :: ExceptT e m (Record c) Source #

localContext :: (Record c -> Record c) -> ExceptT e m a -> ExceptT e m a Source #

MonadContext c m => MonadContext c (IdentityT * m) Source # 
MonadContext c m => MonadContext c (StateT s m) Source # 

Methods

askContext :: StateT s m (Record c) Source #

localContext :: (Record c -> Record c) -> StateT s m a -> StateT s m a Source #

MonadContext c m => MonadContext c (StateT s m) Source # 

Methods

askContext :: StateT s m (Record c) Source #

localContext :: (Record c -> Record c) -> StateT s m a -> StateT s m a Source #

(MonadContext c m, Monoid w) => MonadContext c (WriterT w m) Source # 

Methods

askContext :: WriterT w m (Record c) Source #

localContext :: (Record c -> Record c) -> WriterT w m a -> WriterT w m a Source #

(MonadContext c m, Monoid w) => MonadContext c (WriterT w m) Source # 

Methods

askContext :: WriterT w m (Record c) Source #

localContext :: (Record c -> Record c) -> WriterT w m a -> WriterT w m a Source #

MonadContext c m => MonadContext c (ContT * r m) Source # 

Methods

askContext :: ContT * r m (Record c) Source #

localContext :: (Record c -> Record c) -> ContT * r m a -> ContT * r m a Source #

MonadContext c m => MonadContext c (ReaderT * r m) Source # 

Methods

askContext :: ReaderT * r m (Record c) Source #

localContext :: (Record c -> Record c) -> ReaderT * r m a -> ReaderT * r m a Source #

(MonadContext c m, Monoid w) => MonadContext c (RWST r w s m) Source # 

Methods

askContext :: RWST r w s m (Record c) Source #

localContext :: (Record c -> Record c) -> RWST r w s m a -> RWST r w s m a Source #

(MonadContext c m, Monoid w) => MonadContext c (RWST r w s m) Source # 

Methods

askContext :: RWST r w s m (Record c) Source #

localContext :: (Record c -> Record c) -> RWST r w s m a -> RWST r w s m a Source #

asksContext :: MonadContext c m => (Record c -> a) -> m a Source #

Project some value out of the context using a function.

askField :: MonadContext c m => Getter (Record c) a -> m a Source #

Project some value out of the context using a lens (typically a field lens).