haskus-utils-0.6.0.0: Haskus utility modules

Safe HaskellSafe
LanguageHaskell2010

Haskus.Utils.ContFlow

Contents

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

fret :: forall x r t n xs. (ExtractTuple n t (x -> r), xs ~ ContTupleToList t r, Member x xs, n ~ IndexOf x xs, KnownNat n, CheckNub xs) => t -> x -> r Source #

Call the type-indexed continuation from the tuple passed as first parameter

fretN :: forall n x r t xs. (ExtractTuple n t (x -> r), xs ~ ContTupleToList t r, x ~ Index n xs, KnownNat n) => t -> x -> r Source #

Call the indexed continuation from the tuple passed as first parameter

freturn :: forall x r t n xs. (ExtractTuple n t (x -> r), xs ~ ContTupleToList t r, Member x xs, n ~ IndexOf x xs, KnownNat n, CheckNub xs, ?__cs :: t) => x -> r Source #

Implicitly call the type-indexed continuation in the context

freturnN :: forall n x r t xs. (ExtractTuple n t (x -> r), xs ~ ContTupleToList t r, x ~ Index n xs, KnownNat n, ?__cs :: t) => x -> r Source #

Implicitly call the type-indexed continuation in the context

frec :: forall r xs. (?__cs :: ContListToTuple xs r) => ContFlow xs r -> r Source #

Recursive call

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 

Control-flow

data Then Source #

Constructors

Then 

data Else Source #

Constructors

Else