pandora-0.4.5: A box of patterns and paradigms
Safe HaskellSafe-Inferred
LanguageHaskell2010

Pandora.Paradigm.Primary.Transformer.Continuation

Synopsis

Documentation

newtype Continuation r t a Source #

Constructors

Continuation ((((->) ::|:. a) :. t) := r) 

Instances

Instances details
(forall (u :: Type -> Type). Bindable u ((->) :: Type -> Type -> Type)) => Liftable (Continuation r) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Continuation

Methods

lift :: forall (u :: Type -> Type). Covariant u (->) (->) => u ~> Continuation r u Source #

Monad t => Monad (Continuation r t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Continuation

Interpreted (Continuation r t) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Continuation

Associated Types

type Primary (Continuation r t) a Source #

Methods

run :: Continuation r t a -> Primary (Continuation r t) a Source #

unite :: Primary (Continuation r t) a -> Continuation r t a Source #

(||=) :: Interpreted u => (Primary (Continuation r t) a -> Primary u b) -> Continuation r t a -> u b Source #

(=||) :: Interpreted u => (Continuation r t a -> u b) -> Primary (Continuation r t) a -> Primary u b Source #

(<$||=) :: (Covariant j (->) (->), Interpreted u) => (Primary (Continuation r t) a -> Primary u b) -> (j := Continuation r t a) -> j := u b Source #

(<$$||=) :: (Covariant j (->) (->), Covariant k (->) (->), Interpreted u) => (Primary (Continuation r t) a -> Primary u b) -> ((j :. k) := Continuation r t a) -> (j :. k) := u b Source #

(<$$$||=) :: (Covariant j (->) (->), Covariant k (->) (->), Covariant l (->) (->), Interpreted u) => (Primary (Continuation r t) a -> Primary u b) -> ((j :. (k :. l)) := Continuation r t a) -> (j :. (k :. l)) := u b Source #

(<$$$$||=) :: (Covariant j (->) (->), Covariant k (->) (->), Covariant l (->) (->), Covariant m (->) (->), Interpreted u) => (Primary (Continuation r t) a -> Primary u b) -> ((j :. (k :. (l :. m))) := Continuation r t a) -> (j :. (k :. (l :. m))) := u b Source #

(=||$>) :: (Covariant j (->) (->), Interpreted u) => (Continuation r t a -> u b) -> (j := Primary (Continuation r t) a) -> j := Primary u b Source #

(=||$$>) :: (Covariant j (->) (->), Covariant k (->) (->), Interpreted u) => (Continuation r t a -> u b) -> ((j :. k) := Primary (Continuation r t) a) -> (j :. k) := Primary u b Source #

(=||$$$>) :: (Covariant j (->) (->), Covariant k (->) (->), Covariant l (->) (->), Interpreted u) => (Continuation r t a -> u b) -> ((j :. (k :. l)) := Primary (Continuation r t) a) -> (j :. (k :. l)) := Primary u b Source #

(=||$$$$>) :: (Covariant j (->) (->), Covariant k (->) (->), Covariant l (->) (->), Covariant m (->) (->), Interpreted u) => (Continuation r t a -> u b) -> ((j :. (k :. (l :. m))) := Primary (Continuation r t) a) -> (j :. (k :. (l :. m))) := Primary u b Source #

Covariant t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) => Pointable (Continuation r t) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Continuation

Methods

point :: a -> Continuation r t a Source #

Covariant t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) => Bindable (Continuation r t) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Continuation

Methods

(=<<) :: (a -> Continuation r t b) -> Continuation r t a -> Continuation r t b Source #

Covariant t ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) => Covariant (Continuation r t) ((->) :: Type -> Type -> Type) ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Continuation

Methods

(-<$>-) :: (a -> b) -> Continuation r t a -> Continuation r t b Source #

type Primary (Continuation r t) a Source # 
Instance details

Defined in Pandora.Paradigm.Primary.Transformer.Continuation

type Primary (Continuation r t) a = ((((->) :: Type -> Type -> Type) ::|:. a) :. t) := r

cwcc :: ((a -> Continuation r t b) -> Continuation r t a) -> Continuation r t a Source #

Call with current continuation

reset :: (forall u. Bindable u (->), Monad t) => Continuation r t r -> Continuation s t r Source #

Delimit the continuation of any shift

shift :: Pointable t (->) => ((a -> t r) -> Continuation r t r) -> Continuation r t a Source #

Capture the continuation up to the nearest enclosing reset and pass it

interruptable :: Pointable t (->) => ((a -> Continuation a t a) -> Continuation a t a) -> t a Source #