control-dsl-0.2.1.3: An alternative to monads for control flow DSLs

Safe HaskellSafe
LanguageHaskell2010

Control.Dsl.Cont

Synopsis

Documentation

type (!!) = Cont Source #

A type alias to Cont for a deeply nested delimited continuation.

Examples

Expand
>>> :set -XTypeOperators
>>> :set -XRebindableSyntax
>>> import Prelude hiding ((>>), (>>=), return, fail)
>>> import Control.Dsl
>>> import Control.Dsl.Yield
>>> import Control.Dsl.Empty
>>> import Control.Dsl.Monadic
>>> :{
f :: IO () !! [Integer] !! [String] !! [Double]
f = do
  Yield "foo"
  Yield 0.5
  Yield "bar"
  Yield 42
  Yield "baz"
  return ([] :: [Double])
:}
>>> :{
f >>= (\d -> do { Monadic $ putStrLn $ "double list: " ++ show d
                ; return ([] :: [String]) })
  >>= (\s -> do { Monadic $ putStrLn $ "string list: " ++ show s
                ; return ([] :: [Integer]) })
  >>= (\i -> do { Monadic $ putStrLn $ "integer list: " ++ show i
                ; return () })
:}
double list: [0.5]
string list: ["foo","bar","baz"]
integer list: [42]

newtype Cont r a Source #

A delimited continuation that can be used in a do block.

Constructors

Cont 

Fields

Instances
Dsl Cont r a Source #

Statements based on monomorphic delimited continuations.

Instance details

Defined in Control.Dsl.Dsl

Methods

cpsApply :: Cont r a -> (a -> r) -> r

PolyCont k r a => PolyCont k (Cont r a') a Source #

The PolyCont derivation rule for any keywords in a Cont do block.

This derivated instance provide the ability similar to ContT monad transformers.

Instance details

Defined in Control.Dsl.Cont

Methods

runPolyCont :: k r' a -> (a -> Cont r a') -> Cont r a' Source #

PolyCont Empty r Void => PolyCont Empty (Cont r a) Void Source # 
Instance details

Defined in Control.Dsl.Cont

Methods

runPolyCont :: Empty r' Void -> (Void -> Cont r a) -> Cont r a Source #

PolyCont (Return r) (Cont r' r) Void Source # 
Instance details

Defined in Control.Dsl.Cont

Methods

runPolyCont :: Return r r'0 Void -> (Void -> Cont r' r) -> Cont r' r Source #

PolyCont (Yield x) (Cont r [x]) () Source # 
Instance details

Defined in Control.Dsl.Yield

Methods

runPolyCont :: Yield x r' () -> (() -> Cont r [x]) -> Cont r [x] Source #

toCont :: PolyCont k r a => k r' a -> Cont r a Source #

Convert a PolyCont to a Cont.

when :: Bool -> Cont r () -> Cont r () Source #

unless :: Bool -> Cont r () -> Cont r () Source #