Safe Haskell | None |
---|---|
Language | Haskell2010 |
Control.Monad.Indexed.Trans.State
Description
The indexed state transformer: each
term takes an input of type StateT
_ i ji
and gives an output of type j
.
Documentation
newtype StateT f i j a Source #
Instances
Monad m => Bind (StateT m :: Type -> Type -> Type -> Type) Source # | |
Monad m => Apply (StateT m :: Type -> Type -> Type -> Type) Source # | |
Defined in Control.Monad.Indexed.Trans.State Methods (<*>) :: forall (i :: k) (j :: k) a b (k :: k). StateT m i j (a -> b) -> StateT m j k a -> StateT m i k b Source # (*>) :: forall (i :: k) (j :: k) a (k :: k) b. StateT m i j a -> StateT m j k b -> StateT m i k b Source # (<*) :: forall (i :: k) (j :: k) a (k :: k) b. StateT m i j a -> StateT m j k b -> StateT m i k a Source # liftA2 :: forall a b c (i :: k) (j :: k) (k :: k). (a -> b -> c) -> StateT m i j a -> StateT m j k b -> StateT m i k c Source # | |
Monad m => Monad (StateT m k k) Source # | |
Functor f => Functor (StateT f i j) Source # | |
MonadFix m => MonadFix (StateT m k k) Source # | |
Defined in Control.Monad.Indexed.Trans.State | |
Monad m => Applicative (StateT m k k) Source # | |
Defined in Control.Monad.Indexed.Trans.State | |
MonadPlus m => Alternative (StateT m k k) Source # | |
MonadPlus m => MonadPlus (StateT m k k) Source # | |
modify :: Applicative p => (i -> j) -> StateT p i j i Source #
get :: Applicative p => StateT p k k k Source #
put :: Applicative p => j -> StateT p i j () Source #
liftCallCC :: CallCC f g h (a, i) (b, j) (c, k) (d, l) -> CallCC (StateT f e j) (StateT g i k) (StateT h i l) a b c d Source #