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

FMonad.State.Simple.Inner

Documentation

newtype StateT s1 mm x a Source #

Constructors

StateT 

Fields

Instances

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

Defined in FMonad.State.Simple.Inner

Methods

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

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

Defined in FMonad.State.Simple.Inner

Methods

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

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

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

Defined in FMonad.State.Simple.Inner

Methods

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

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

flift :: (FStrong mm, Functor x) => mm x ~> StateT s1 mm x Source #

toAdjointT :: StateT s1 mm x ~> AdjointT (TracedT s1) (WriterT s1) mm x Source #

fromAdjointT :: AdjointT (TracedT s1) (WriterT s1) mm x ~> StateT s1 mm x Source #

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

runState :: State s1 x a -> x (s1 -> (a, s1)) Source #