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

FMonad.State.Simple.Outer

Documentation

newtype StateT s0 mm x a Source #

Constructors

StateT 

Fields

Instances

Instances details
FFunctor mm => FFunctor (StateT s0 mm) Source # 
Instance details

Defined in FMonad.State.Simple.Outer

Methods

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

FMonad mm => FMonad (StateT s0 mm) Source # 
Instance details

Defined in FMonad.State.Simple.Outer

Methods

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

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

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

Defined in FMonad.State.Simple.Outer

Methods

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

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

flift :: (FFunctor mm, Functor x) => mm x ~> StateT s0 mm x Source #

fromAdjointT :: AdjointT (EnvT s0) (ReaderT s0) mm x ~> StateT s0 mm x Source #

toAdjointT :: StateT s0 mm x ~> AdjointT (EnvT s0) (ReaderT s0) mm x Source #

state :: forall s0 x mm a. (FMonad mm, Functor x) => (s0 -> (x a, s0)) -> StateT s0 mm x a Source #

runState :: forall s0 x a. State s0 x a -> s0 -> (x a, s0) Source #