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

Language.CB98

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 This is the Haskell98 version of the code CB.hs located in the same directory as this file

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

Synopsis

Documentation

type Arr exp a b = exp a -> exp bSource

The (higher-order abstract) syntax of our DSL

class EDSL exp whereSource

Methods

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

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

int :: Int -> exp IntSource

add :: exp Int -> exp Int -> exp IntSource

sub :: exp Int -> exp Int -> exp IntSource

Instances

MonadIO m => EDSL (SLazy m) 
MonadIO m => EDSL (SValue m) 
MonadIO m => EDSL (SName m)

Call-by-name

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

A convenient abbreviation

t :: EDSL exp => exp IntSource

A sample EDSL term

newtype SName m a Source

Interpretation of EDSL expressions as values of the host language (Haskell) An EDSL expression of type a is interpreted as a Haskell value of the type SName m a, SValue m a or SLazy m a, where m is a Monad (the parameter of the interpretation).

Constructors

SN 

Fields

unSN :: m a
 

Instances

Monad m => Monad (SName m)

Could be automatically derived by GHC. But we stick to Haskell98

MonadIO m => MonadIO (SName m) 
MonadIO m => EDSL (SName m)

Call-by-name

runName :: SName m a -> m aSource

t1 :: EDSL exp => exp IntSource

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

A more elaborate example

t2 :: EDSL exp => exp IntSource

A better example

newtype SValue m a Source

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

Call-by-value

Constructors

SV 

Fields

unSV :: m a
 

Instances

Monad m => Monad (SValue m)

Could be automatically derived by GHC.

MonadIO m => MonadIO (SValue m) 
MonadIO m => EDSL (SValue m) 

vn :: SValue m x -> SName m xSource

We reuse most of EDSL (SName) except for lam

nv :: SName m x -> SValue m xSource

runValue :: SValue m a -> m aSource

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

We now evaluate the previously written tests t, t1, t2 under the new interpretation

Call-by-need

newtype SLazy m a Source

Constructors

SL 

Fields

unSL :: m a
 

Instances

Monad m => Monad (SLazy m)

Could be automatically derived by GHC.

MonadIO m => MonadIO (SLazy m) 
MonadIO m => EDSL (SLazy m) 

ln :: SLazy m x -> SName m xSource

nl :: SName m x -> SLazy m xSource

runLazy :: SLazy m a -> m aSource