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

Language.CBAny

Contents

Description

  • Almost Haskell98. See CB98,hs for the genuine Haskell98 version Here we use a few extensions to make the code prettier
  • 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

Synopsis

Documentation

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

The (higher-order abstract) syntax of our DSL

class EDSL exp whereSource

Methods

int :: Int -> exp IntSource

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

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

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

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

Instances

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

We use IO to print out the evaluation trace, so to observe the difference in evaluation orders

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

A convenient abbreviation (could've been called bind)

t :: EDSL exp => exp IntSource

A sample EDSL term

Write a term once, evaluate many times (with different orders)

Embedding of the DSL into Haskell

newtype S l m a Source

Constructors

S 

Fields

unS :: m a
 

Instances

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

We use IO to print out the evaluation trace, so to observe the difference in evaluation orders

Call-by-name

data Name Source

Instances

MonadIO m => EDSL (S Name m)

We use IO to print out the evaluation trace, so to observe the difference in evaluation orders

runName :: S Name m a -> m aSource

t1 :: EDSL exp => exp IntSource

A more elaborate example

t2 :: EDSL exp => exp IntSource

Call-by-value

The only difference is the interpretation of lam:

before evaluating the body, _always_ evaluate the argument

data Value Source

Instances

MonadIO m => EDSL (S Value m) 

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

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

runValue :: S Value m a -> m aSource

Call-by-need

The only difference is the interpretation of lam:

before evaluating the body, share the argument

The argument is evaluated _at most_ once

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

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

runLazy :: S Lazy m a -> m aSource