haskus-utils-variant-2.4: Variant and EADT

Safe HaskellSafe
LanguageHaskell2010

Haskus.Utils.ContFlow

Description

Continuation based control-flow

Synopsis

Documentation

newtype ContFlow (xs :: [*]) r Source #

A continuation based control-flow

Constructors

ContFlow (ContListToTuple xs r -> r) 

(>::>) :: ContFlow xs r -> ContListToTuple xs r -> r infixl 0 Source #

Bind a flow to a tuple of continuations

(>:-:>) :: ContFlow '[a] r -> (a -> r) -> r infixl 0 Source #

Bind a flow to a 1-tuple of continuations

(>:%:>) :: forall ts xs r. ReorderTuple ts (ContListToTuple xs r) => ContFlow xs r -> ts -> r infixl 0 Source #

Bind a flow to a tuple of continuations and reorder fields if necessary

type family ContListToTuple (xs :: [*]) r where ... Source #

Convert a list of types into the actual data type representing the continuations.

Equations

ContListToTuple xs r = ListToTuple (AddR xs r) 

type family ContTupleToList t r :: [*] where ... Source #

Convert a tuple of continuations into a list of types

Equations

ContTupleToList t r = StripR (TupleToList t) r 

type family StripR f r where ... Source #

Equations

StripR '[] r = '[] 
StripR ((x -> r) ': xs) r = x ': StripR xs r 
StripR ((x -> w) ': xs) r = TypeError ((((Text "Invalid continuation return type `" :<>: ShowType w) :<>: Text "', expecting `") :<>: ShowType r) :<>: Text "'") 

type family AddR f r where ... Source #

Equations

AddR '[] r = '[] 
AddR (x ': xs) r = (x -> r) ': AddR xs r 

class MultiCont a where Source #

Associated Types

type MultiContTypes a :: [*] Source #

Methods

toCont :: a -> ContFlow (MultiContTypes a) r Source #

Convert a data into a multi-continuation

toContM :: Monad m => m a -> ContFlow (MultiContTypes a) (m r) Source #

Convert a data into a multi-continuation (monadic)

Instances
ContVariant xs => MultiCont (V xs) Source # 
Instance details

Defined in Haskus.Utils.Variant

Associated Types

type MultiContTypes (V xs) :: [Type] Source #

Methods

toCont :: V xs -> ContFlow (MultiContTypes (V xs)) r Source #

toContM :: Monad m => m (V xs) -> ContFlow (MultiContTypes (V xs)) (m r) Source #

ContVariant (ApplyAll e xs) => MultiCont (VariantF xs e) Source # 
Instance details

Defined in Haskus.Utils.VariantF

Associated Types

type MultiContTypes (VariantF xs e) :: [Type] Source #

Methods

toCont :: VariantF xs e -> ContFlow (MultiContTypes (VariantF xs e)) r Source #

toContM :: Monad m => m (VariantF xs e) -> ContFlow (MultiContTypes (VariantF xs e)) (m r) Source #