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

Control.Monad.Indexed.Cont2

Description

This module defines a 2-continuation flavour of indexed monads. Having two continuation allows unrestricted backtracking (hence the Additive instance for Cont2W below).

Most of this module is focused on using the indexed continuation monads for delimited control, hence adopts its terminology. For instance in `Cont2 w r r'`, r and r' are called the input and output answer types respectively. They are to be thought as a stack (a stack of `a -> b -> r` being a stack whose two first elements are of type a and b).

Cont2W is an indexed monad because the answer type can change along the computation. This is called answer-type modification in the delimited control literature.

Synopsis

Abstract delimited control

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

A type class abstracting over delimited control capability for this 2-continuation flavour of monads.

Methods

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

Instances

Instances details
Comonad w => Shifty (Cont2W w) Source # 
Instance details

Defined in Control.Monad.Indexed.Cont2

Methods

shift :: ((a -> r' -> r') -> r -> Cont2W w r k k) -> Cont2W w r r' a Source #

(Shifty f, Shifty g) => Shifty (f :*: g) Source # 
Instance details

Defined in Control.Monad.Indexed.Cont2

Methods

shift :: ((a -> r' -> r') -> r -> (f :*: g) r k k) -> (f :*: g) r r' a Source #

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

Restricted delimited control where continuations can be captured but can't return values. This is enough for most stack-manipulating functions (the stack, however, cannot influence the control flow anymore). Compared to Shifty it captures the additional case where the stack doesn't actually exist at runtime (IgnoreIndices).

Methods

shift_ :: ((r' -> r') -> r -> m r r'' r'') -> m r r' () Source #

Instances

Instances details
Comonad w => Stacked (Cont2W w) Source # 
Instance details

Defined in Control.Monad.Indexed.Cont2

Methods

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

Applicative m => Stacked (IgnoreIndices m :: Type -> Type -> Type -> Type) Source # 
Instance details

Defined in Control.Monad.Indexed.Cont2

Methods

shift_ :: ((r' -> r') -> r -> IgnoreIndices m r r'' r'') -> IgnoreIndices m r r' () Source #

(Stacked f, Stacked g) => Stacked (f :*: g) Source # 
Instance details

Defined in Control.Monad.Indexed.Cont2

Methods

shift_ :: ((r' -> r') -> r -> (f :*: g) r r'' r'') -> (f :*: g) r r' () Source #

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

stack is a partial mapping operation on the stack.

In a first approximation it can be thought of as a function with type

:: (j -> i) -> m i j ()

The direction of the arrow is explained by the representation of stack types as function. A function with type

((d -> e -> r) -> (a -> b -> c -> r))

actually maps three elements a, b, c to two elements d, e.

The additional parameter of type i is a failure continuation. For instance the following always fails to modify the stack:

stack (\fl _ -> fl)

Finally, the extra function of type (i -> j) is called an “unrolling function” and is tasked with restoring the stack in its original state if a later failure causes backtracking.

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

pop pops and returns the top element of the stack. See also the less expressive pop_ which doesn't require a full Shifty instance.

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

pop_ discards the top element of the stack. It is a less expressive variant of pop, but pop requires a Shifty applicative, whereas pop_ works on any stacked applicative.

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 Cont2W (w :: Type -> Type) r r' a Source #

Constructors

Cont2W 

Fields

Instances

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

Defined in Control.Monad.Indexed.Cont2

Methods

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

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

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

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

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

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

Defined in Control.Monad.Indexed.Cont2

Methods

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

Comonad w => Shifty (Cont2W w) Source # 
Instance details

Defined in Control.Monad.Indexed.Cont2

Methods

shift :: ((a -> r' -> r') -> r -> Cont2W w r k k) -> Cont2W w r r' a Source #

Comonad w => Stacked (Cont2W w) Source # 
Instance details

Defined in Control.Monad.Indexed.Cont2

Methods

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

Comonad w => Alternative (Cont2W w r r) Source # 
Instance details

Defined in Control.Monad.Indexed.Cont2

Methods

empty :: Cont2W w r r a #

(<|>) :: Cont2W w r r a -> Cont2W w r r a -> Cont2W w r r a #

some :: Cont2W w r r a -> Cont2W w r r [a] #

many :: Cont2W w r r a -> Cont2W w r r [a] #

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

Defined in Control.Monad.Indexed.Cont2

Methods

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

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

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

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

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

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

Defined in Control.Monad.Indexed.Cont2

Methods

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

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

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

Defined in Control.Monad.Indexed.Cont2

Methods

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

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

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

Comonad w => MonadPlus (Cont2W w r r) Source # 
Instance details

Defined in Control.Monad.Indexed.Cont2

Methods

mzero :: Cont2W w r r a #

mplus :: Cont2W w r r a -> Cont2W w r r a -> Cont2W w r r a #

Additive (Cont2W w r r' a) Source # 
Instance details

Defined in Control.Monad.Indexed.Cont2

Methods

empty :: Cont2W w r r' a Source #

(<|>) :: Cont2W w r r' a -> Cont2W w r r' a -> Cont2W w r r' a Source #

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

shift0 is the most general delimited control operation on Cont2W.

About the name

Expand

It's named by analogy with the eponymous delimited control operation from the delimited control literature (see A Dynamic Interpretation of the CPS Hierarchy). The traditional shift0 captures all the continuations introduced by nested resets; here we think of the comonad w as carrying the information of additional resets.

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

yield act runs the comonadically effectful action act in the Cont2W monad. See also yield_.

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

yield_ act runs the comonadically effectful action act in the Cont2W monad. This is a variant of yield specialised to the case where the action doesn't return a value.

Bidirectional variants of traditional combinators

some :: (Alternative m, Stacked m) => (forall r'. m (a -> r') r' b) -> m ([a] -> r) r [b] Source #

some act iterates 1 or more times the action act until it fails or run out of input on the stack. See also many which doesn't fail if it can't iterate at least once.

many :: (Alternative m, Stacked m) => (forall r'. m (a -> r') r' b) -> m ([a] -> r) r [b] Source #

many act iterates 0 or more times the action act until it fails or run out of input on the stack. See also some which iterates at least once.

optional :: (Alternative m, Stacked m) => (forall r'. m (a -> r') r' b) -> m (Maybe a -> r) r (Maybe b) Source #

sepBy :: (MonadPlus m, Stacked m) => (forall r'. m (a -> r') r' b) -> (forall r'. m r' r' ()) -> m ([a] -> r) r [b] Source #