| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Control.Monad.Trans.MultiGST.Strict
Description
Alternative multi-valued version of mtl's RWS / RWST. In contrast to
  this version only takes a single list of types as
 parameter, but with additional encoding of the allowed access for each
 element. This supports the MultiRWS(T) notion more succinctly, i.e.
 to pass a "state" element to a function that only requiresexpects readget
 access. This is not possible with MonadMultiGetMultiRWS.
Synopsis
- newtype MultiGSTT ts m a = MultiGSTT {
- runMultiGSTTRaw :: StateT (HListM ts) m a
 
 - type MultiGSTTNull = MultiGSTT '[]
 - type MultiGST r = MultiGSTT r Identity
 - type ContainsReader = HListMContains 'GettableFlag
 - type ContainsState = HListMContains 'SettableFlag
 - type ContainsWriter = HListMContains 'TellableFlag
 - class Monad m => MonadMultiReader a m where
- mAsk :: m a
 
 - class (Monad m, Monoid a) => MonadMultiWriter a m where
- mTell :: a -> m ()
 
 - class Monad m => MonadMultiGet a m where
- mGet :: m a
 
 - data CanReadWrite a
 - runMultiGSTTNil :: Monad m => MultiGSTT '[] m a -> m a
 - runMultiGSTTNil_ :: Monad m => MultiGSTT '[] m a -> m ()
 - withReader :: Monad m => t -> MultiGSTT ('Gettable t ': tr) m a -> MultiGSTT tr m a
 - withReader_ :: Monad m => t -> MultiGSTT ('Gettable t ': tr) m a -> MultiGSTT tr m ()
 - withWriter :: (Monoid t, Monad m) => MultiGSTT ('Tellable t ': tr) m a -> MultiGSTT tr m (a, t)
 - withWriterAW :: (Monoid t, Monad m) => MultiGSTT ('Tellable t ': tr) m a -> MultiGSTT tr m (a, t)
 - withWriterWA :: (Monoid t, Monad m) => MultiGSTT ('Tellable t ': tr) m a -> MultiGSTT tr m (t, a)
 - withWriterW :: (Monoid t, Monad m) => MultiGSTT ('Tellable t ': tr) m a -> MultiGSTT tr m t
 - withState :: Monad m => t -> MultiGSTT ('Settable t ': tr) m a -> MultiGSTT tr m (a, t)
 - withStateAS :: Monad m => t -> MultiGSTT ('Settable t ': tr) m a -> MultiGSTT tr m (a, t)
 - withStateSA :: Monad m => t -> MultiGSTT ('Settable t ': tr) m a -> MultiGSTT tr m (t, a)
 - withStateA :: Monad m => t -> MultiGSTT ('Settable t ': tr) m a -> MultiGSTT tr m a
 - withStateS :: Monad m => t -> MultiGSTT ('Settable t ': tr) m a -> MultiGSTT tr m t
 - withState_ :: Monad m => t -> MultiGSTT ('Settable t ': tr) m a -> MultiGSTT tr m ()
 - without :: Monad m => MultiGSTT tr m a -> MultiGSTT (ct ': tr) m a
 - mGetRaw :: Monad m => MultiGSTT ts m (HListM ts)
 - mSetRaw :: Monad m => HListM ts -> MultiGSTT ts m ()
 - mapMultiGSTT :: ts ~ HListM cts => (m (a, ts) -> m' (a', ts)) -> MultiGSTT cts m a -> MultiGSTT cts m' a'
 
Documentation
newtype MultiGSTT ts m a Source #
Constructors
| MultiGSTT | |
Fields 
  | |
Instances
type MultiGSTTNull = MultiGSTT '[] Source #
MonadMulti classes
type ContainsReader = HListMContains 'GettableFlag Source #
type ContainsState = HListMContains 'SettableFlag Source #
type ContainsWriter = HListMContains 'TellableFlag Source #
class Monad m => MonadMultiReader a m where Source #
All methods must be defined.
The idea is: Any monad stack is instance of MonadMultiReader a, iff
 the stack contains a MultiReaderT x with a element of x.
Instances
| (MonadTrans t, Monad (t m), MonadMultiReader a m) => MonadMultiReader a (t m) Source # | |
Defined in Control.Monad.Trans.MultiReader.Class  | |
| (Monad m, ContainsType a c) => MonadMultiReader a (MultiReaderT c m) Source # | |
Defined in Control.Monad.Trans.MultiReader.Strict Methods mAsk :: MultiReaderT c m a Source #  | |
| (Monad m, ContainsType a c) => MonadMultiReader a (MultiReaderT c m) Source # | |
Defined in Control.Monad.Trans.MultiReader.Lazy Methods mAsk :: MultiReaderT c m a Source #  | |
| (Monad m, ContainsType a r) => MonadMultiReader a (MultiRWST r w s m) Source # | |
Defined in Control.Monad.Trans.MultiRWS.Strict  | |
| (Monad m, ContainsType a r) => MonadMultiReader a (MultiRWST r w s m) Source # | |
Defined in Control.Monad.Trans.MultiRWS.Lazy  | |
class (Monad m, Monoid a) => MonadMultiWriter a m where Source #
Instances
class Monad m => MonadMultiGet a m where Source #
In contrast to MonadMultiReader, MonadMultiGet is defined for State too, so it corresponds to read-access of any kind.
Note however that for MultiRWS, only the values from the state part can
 be accessed via MonadMultiGet, due to limitations of the design of
 MultiRWS and of the type system. This is issue is resolved in the
 MultiGST type.
Instances
run-functions
runMultiGSTTNil :: Monad m => MultiGSTT '[] m a -> m a Source #
runMultiGSTTNil_ :: Monad m => MultiGSTT '[] m a -> m () Source #
with-functions
withWriter :: (Monoid t, Monad m) => MultiGSTT ('Tellable t ': tr) m a -> MultiGSTT tr m (a, t) Source #
withWriterAW :: (Monoid t, Monad m) => MultiGSTT ('Tellable t ': tr) m a -> MultiGSTT tr m (a, t) Source #
withWriterWA :: (Monoid t, Monad m) => MultiGSTT ('Tellable t ': tr) m a -> MultiGSTT tr m (t, a) Source #
withWriterW :: (Monoid t, Monad m) => MultiGSTT ('Tellable t ': tr) m a -> MultiGSTT tr m t Source #
without-functions
other functions
mapMultiGSTT :: ts ~ HListM cts => (m (a, ts) -> m' (a', ts)) -> MultiGSTT cts m a -> MultiGSTT cts m' a' Source #