FMonad.State.Day
newtype StateT s mm x a Source #
Constructors
Fields
Defined in FMonad.State.Day
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 #
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 #
fmap :: (a -> b) -> StateT s mm x a -> StateT s mm x b #
(<$) :: a -> StateT s mm x b -> StateT s mm x a #
flift :: (Functor s, FStrong mm, Functor x) => mm x ~> StateT s mm x Source #
toOuter :: (Functor x, FFunctor mm) => StateT ((,) s0) mm x ~> StateT s0 mm x Source #
fromOuter :: (Functor x, FFunctor mm) => StateT s0 mm x ~> StateT ((,) s0) mm x Source #
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 #
type State s = StateT s IdentityT Source #
state :: FMonad mm => (forall r. s (a -> r) -> Day s x r) -> StateT s mm x a Source #
state_ :: (Functor s, FMonad mm) => (forall b. s b -> (s b, x a)) -> StateT s mm x a Source #
get :: (Comonoid s, FMonad mm) => StateT s mm s () Source #
put :: (Comonad s, FMonad mm) => s a -> StateT s mm Identity a Source #
runState :: State s x a -> s (a -> r) -> Day s x r Source #