functor-monad-0.1.1.0: FFunctor: functors on (the usual) Functors
Safe HaskellSafe-Inferred
LanguageHaskell2010

FMonad.State.Lan

Documentation

newtype StateT s mm x a Source #

Constructors

StateT 

Fields

Instances

Instances details
(FFunctor mm, Functor s) => FFunctor (StateT s mm) Source # 
Instance details

Defined in FMonad.State.Lan

Methods

ffmap :: forall (g :: Type -> Type) (h :: Type -> Type) x. (Functor g, Functor h) => (g ~> h) -> StateT s mm g x -> StateT s mm h x Source #

(Functor s, FMonad mm) => FMonad (StateT s mm) Source # 
Instance details

Defined in FMonad.State.Lan

Methods

fpure :: forall (g :: Type -> Type). Functor g => g ~> StateT s mm g Source #

fbind :: forall (g :: Type -> Type) (h :: Type -> Type) a. (Functor g, Functor h) => (g ~> StateT s mm h) -> StateT s mm g a -> StateT s mm h a Source #

(FFunctor mm, Functor s) => Functor (StateT s mm x) Source # 
Instance details

Defined in FMonad.State.Lan

Methods

fmap :: (a -> b) -> StateT s mm x a -> StateT s mm x b #

(<$) :: a -> StateT s mm x b -> StateT s mm x a #

toInner :: (Functor x, FFunctor mm) => StateT ((,) s1) mm x ~> StateT s1 mm x Source #

fromInner :: (Functor x, FFunctor mm) => StateT s1 mm x ~> StateT ((,) s1) mm x Source #

state :: (Functor s, FMonad mm, Functor x) => (s b -> s a) -> x b -> StateT s mm x a Source #

runState :: State s x a -> Lan s x (s a) Source #