stacked-0.1.0: A modern indexed monad stack
Safe HaskellNone
LanguageGHC2021

Control.Monad.Indexed.Cont

Synopsis

Abstract delimited control

class Stacked m => Shifty (m :: k -> Type -> Type -> Type) where Source #

Methods

shift :: forall a r' (r :: k) k1. ((a -> r') -> m r k1 k1) -> m r r' a Source #

Instances

Instances details
Comonad w => Shifty (ContW w :: Type -> Type -> Type -> Type) Source # 
Instance details

Defined in Control.Monad.Indexed.Cont

Methods

shift :: ((a -> r') -> ContW w r k1 k1) -> ContW w r r' a Source #

class Stacked (m :: k -> Type -> Type -> Type) where Source #

Methods

shift_ :: forall r' (r :: k) r''. (r' -> m r r'' r'') -> m r r' () Source #

Instances

Instances details
Comonad w => Stacked (ContW w :: Type -> Type -> Type -> Type) Source # 
Instance details

Defined in Control.Monad.Indexed.Cont

Methods

shift_ :: (r' -> ContW w r r'' r'') -> ContW w r r' () Source #

stack :: (Applicative m, Stacked m) => (j -> i) -> m i j () Source #

pop :: (Applicative m, Shifty m) => m (a -> i) i a Source #

pop_ :: (Applicative m, Stacked m) => m (a -> i) i () Source #

push :: (Applicative m, Stacked m) => a -> m i (a -> i) () Source #

(@) :: (Applicative m, Stacked m) => m (a -> i) j b -> a -> m i j b infixl 9 Source #

Comonad-to-indexed-monad transformer

newtype ContW (w :: Type -> Type) r r' a Source #

Constructors

ContW 

Fields

Instances

Instances details
Comonad w => Applicative (ContW w :: Type -> Type -> Type -> Type) Source # 
Instance details

Defined in Control.Monad.Indexed.Cont

Methods

pure :: a -> ContW w i i a Source #

(<*>) :: ContW w i j (a -> b) -> ContW w j k1 a -> ContW w i k1 b Source #

liftA2 :: (a -> b -> c) -> ContW w i j a -> ContW w j k1 b -> ContW w i k1 c Source #

(*>) :: ContW w i j a -> ContW w j k1 b -> ContW w i k1 b Source #

(<*) :: ContW w i j a -> ContW w j k1 b -> ContW w i k1 a Source #

Comonad w => Monad (ContW w :: Type -> Type -> Type -> Type) Source # 
Instance details

Defined in Control.Monad.Indexed.Cont

Methods

(>>=) :: ContW w i j a -> (a -> ContW w j k1 b) -> ContW w i k1 b Source #

Comonad w => Shifty (ContW w :: Type -> Type -> Type -> Type) Source # 
Instance details

Defined in Control.Monad.Indexed.Cont

Methods

shift :: ((a -> r') -> ContW w r k1 k1) -> ContW w r r' a Source #

Comonad w => Stacked (ContW w :: Type -> Type -> Type -> Type) Source # 
Instance details

Defined in Control.Monad.Indexed.Cont

Methods

shift_ :: (r' -> ContW w r r'' r'') -> ContW w r r' () Source #

Comonad w => Applicative (ContW w r r) Source # 
Instance details

Defined in Control.Monad.Indexed.Cont

Methods

pure :: a -> ContW w r r a #

(<*>) :: ContW w r r (a -> b) -> ContW w r r a -> ContW w r r b #

liftA2 :: (a -> b -> c) -> ContW w r r a -> ContW w r r b -> ContW w r r c #

(*>) :: ContW w r r a -> ContW w r r b -> ContW w r r b #

(<*) :: ContW w r r a -> ContW w r r b -> ContW w r r a #

Functor w => Functor (ContW w r r') Source # 
Instance details

Defined in Control.Monad.Indexed.Cont

Methods

fmap :: (a -> b) -> ContW w r r' a -> ContW w r r' b #

(<$) :: a -> ContW w r r' b -> ContW w r r' a #

Comonad w => Monad (ContW w r r) Source # 
Instance details

Defined in Control.Monad.Indexed.Cont

Methods

(>>=) :: ContW w r r a -> (a -> ContW w r r b) -> ContW w r r b #

(>>) :: ContW w r r a -> ContW w r r b -> ContW w r r b #

return :: a -> ContW w r r a #

shift0 :: Comonad w => (w (a -> r') -> ContW w r k k) -> ContW w r r' a Source #

yield :: Comonad w => (w (a -> r) -> r) -> ContW w r r a Source #

yield_ :: Comonad w => (w r -> r) -> ContW w r r () Source #

Experimental combinators (subject to radical change)

abort :: (Applicative m, Shifty m) => r -> m r r' a Source #

capture :: Comonad w => ContW w b r' r' -> ContW w r r (w b) Source #

handle :: forall (w :: Type -> Type) k r r' a. Comonad w => ContW (StoreT k w) r r' a -> ContW w k r' a -> ContW w r r' a Source #

pullback :: Comonad w => (forall x. w x -> v x) -> ContW v r r' a -> ContW w r r' a Source #