indexed-state-0.0.5: Indexed State
Safe HaskellSafe-Inferred
LanguageHaskell2010

Control.Monad.State.Profunctor.Class

Documentation

class IxFunctor f where Source #

Methods

($.$) :: (a -> b) -> f j k a -> f j k b infixl 4 Source #

Instances

Instances details
Functor f => IxFunctor (IxStateT f) Source # 
Instance details

Defined in Control.Monad.State.Profunctor.IxState

Methods

($.$) :: (a -> b) -> IxStateT f j k a -> IxStateT f j k b Source #

class IxFunctor f => IxApply f where Source #

Methods

(<*.*>) :: f j k (a -> b) -> f i j a -> f i k b infixl 4 Source #

Instances

Instances details
Monad f => IxApply (IxStateT f) Source # 
Instance details

Defined in Control.Monad.State.Profunctor.IxState

Methods

(<*.*>) :: IxStateT f j k (a -> b) -> IxStateT f i j a -> IxStateT f i k b Source #

class IxApply f => IxApplicative f where Source #

Methods

ipure :: a -> f i i a Source #

Instances

Instances details
Monad f => IxApplicative (IxStateT f) Source # 
Instance details

Defined in Control.Monad.State.Profunctor.IxState

Methods

ipure :: a -> IxStateT f i i a Source #

class IxApply f => IxBind f where Source #

Minimal complete definition

(-<<<) | (>>>-)

Methods

(-<<<) :: (a -> f i j b) -> f j k a -> f i k b infixr 1 Source #

(>>>-) :: f j k a -> (a -> f i j b) -> f i k b infixr 1 Source #

Instances

Instances details
Monad f => IxBind (IxStateT f) Source # 
Instance details

Defined in Control.Monad.State.Profunctor.IxState

Methods

(-<<<) :: (a -> IxStateT f i j b) -> IxStateT f j k a -> IxStateT f i k b Source #

(>>>-) :: IxStateT f j k a -> (a -> IxStateT f i j b) -> IxStateT f i k b Source #

class (IxApplicative f, IxBind f) => IxMonad f Source #

Instances

Instances details
Monad f => IxMonad (IxStateT f) Source # 
Instance details

Defined in Control.Monad.State.Profunctor.IxState

class IxFunctor f => IxAlt f where Source #

Methods

(<|.|>) :: f i j a -> f i j a -> f i j a infixl 3 Source #

Instances

Instances details
Alt f => IxAlt (IxStateT f) Source # 
Instance details

Defined in Control.Monad.State.Profunctor.IxState

Methods

(<|.|>) :: IxStateT f i j a -> IxStateT f i j a -> IxStateT f i j a Source #

class IxAlt f => IxAlternative f where Source #

Methods

iempty :: f i j a Source #

Instances

Instances details
(Alt f, Alternative f) => IxAlternative (IxStateT f) Source # 
Instance details

Defined in Control.Monad.State.Profunctor.IxState

Methods

iempty :: IxStateT f i j a Source #

class IxMonad f => IxMonadState f where Source #

Minimal complete definition

istate | iget, iput

Methods

iget :: f t t t Source #

iput :: t -> f t s () Source #

istate :: (s -> (a, t)) -> f t s a Source #

imodify :: (s -> t) -> f t s () Source #

igets :: (s -> t) -> f s s t Source #

Instances

Instances details
Monad f => IxMonadState (IxStateT f) Source # 
Instance details

Defined in Control.Monad.State.Profunctor.IxState

Methods

iget :: IxStateT f t t t Source #

iput :: t -> IxStateT f t s () Source #

istate :: (s -> (a, t)) -> IxStateT f t s a Source #

imodify :: (s -> t) -> IxStateT f t s () Source #

igets :: (s -> t) -> IxStateT f s s t Source #

class IxMonadFix f where Source #

Methods

imfix :: (a -> f t s a) -> f t s a Source #

Instances

Instances details
MonadFix f => IxMonadFix (IxStateT f) Source # 
Instance details

Defined in Control.Monad.State.Profunctor.IxState

Methods

imfix :: (a -> IxStateT f t s a) -> IxStateT f t s a Source #

class IxMonadCont f where Source #

Methods

icallCC :: ((a -> f t r b) -> f r s a) -> f r s a Source #

Instances

Instances details
MonadCont f => IxMonadCont (IxStateT f) Source # 
Instance details

Defined in Control.Monad.State.Profunctor.IxState

Methods

icallCC :: ((a -> IxStateT f t r b) -> IxStateT f r s a) -> IxStateT f r s a Source #

class IxBindTrans g where Source #

Methods

iliftB :: Bind f => f a -> g f s s a Source #

Instances

Instances details
IxBindTrans IxStateT Source # 
Instance details

Defined in Control.Monad.State.Profunctor.IxState

Methods

iliftB :: Bind f => f a -> IxStateT f s s a Source #

class IxMonadTrans g where Source #

Methods

ilift :: Monad f => f a -> g f s s a Source #

Instances

Instances details
IxMonadTrans IxStateT Source # 
Instance details

Defined in Control.Monad.State.Profunctor.IxState

Methods

ilift :: Monad f => f a -> IxStateT f s s a Source #