liboleg-2010.1.5: An evolving collection of Oleg Kiselyov's Haskell modules

Language.CB

Description

Embedding a higher-order domain-specific language (simply-typed lambda-calculus with constants) with a selectable evaluation order: Call-by-value, call-by-name, call-by-need in the same Final Tagless framework

http://okmij.org/ftp/tagless-final/tagless-typed.html#call-by-any

Synopsis

Documentation

data IntT Source

Our EDSL is typed. EDSL types are built from the following two type constructors:

data a :-> b Source

class EDSL exp whereSource

We could have used Haskell's type Int and the arrow -> constructor. We would like to emphasize however that EDSL types need not be identical to the host language types. To give the type system to EDSL, we merely need labels -- which is what IntT and :-> are

The (higher-order abstract) syntax of our DSL

Methods

lam :: (exp a -> exp b) -> exp (a :-> b)Source

app :: exp (a :-> b) -> exp a -> exp bSource

int :: Int -> exp IntTSource

add :: exp IntT -> exp IntT -> exp IntTSource

sub :: exp IntT -> exp IntT -> exp IntTSource

Instances

MonadIO m => EDSL (S Lazy m) 
MonadIO m => EDSL (S Value m) 
MonadIO m => EDSL (S Name m) 

let_ :: EDSL exp => exp a -> (exp a -> exp b) -> exp bSource

A convenient abbreviation

t :: EDSL exp => exp IntTSource

A sample EDSL term

type family Sem m a :: *Source

Interpretation of EDSL types as host language types The type interpretation function Sem is parameterized by m, which is assumed to be a Monad.

newtype S l m a Source

Interpretation of EDSL expressions as values of the host language (Haskell) An EDSL expression of the type a is interpreted as a Haskell value of the type S l m a, where m is a Monad (the parameter of the interpretation) and l is the label for the evaluation order (one of Name, Value, or Lazy). (S l m) is not quite a monad -- only up to the Sem interpretation

Constructors

S 

Fields

unS :: m (Sem m a)
 

Instances

MonadIO m => EDSL (S Lazy m) 
MonadIO m => EDSL (S Value m) 
MonadIO m => EDSL (S Name m) 

data Name Source

Call-by-name

Instances

MonadIO m => EDSL (S Name m) 

runName :: S Name m a -> m (Sem m a)Source

t1 :: EDSL exp => exp IntTSource

Evaluating:

 t = (lam $ \x -> let_ (x `add` x)
                      $ \y -> y `add` y) `app` int 10

The addition (x add x) is performed twice because y is bound to a computation, and y is evaluated twice

t2 :: EDSL exp => exp IntTSource

A better example

data Value Source

The result of subtraction was not needed, and so it was not performed | OTH, (int 5 add int 5) was computed four times

Instances

MonadIO m => EDSL (S Value m) 

vn :: S Value m x -> S Name m xSource

We reuse most of EDSL (S Name) except for lam

nv :: S Name m x -> S Value m xSource

runValue :: S Value m a -> m (Sem m a)Source

share :: MonadIO m => m a -> m (m a)Source

data Lazy Source

Instances

MonadIO m => EDSL (S Lazy m) 

ln :: S Lazy m x -> S Name m xSource

We reuse most of EDSL (S Name) except for lam

nl :: S Name m x -> S Lazy m xSource

runLazy :: S Lazy m a -> m (Sem m a)Source