On Wed, May 14, 2008 at 10:11:17AM +0100, Edsko de Vries wrote:
> Suppose we have some data structure that uses HOAS; typically, a DSL
> with explicit sharing. For example:
> 
> > data Expr = One | Add Expr Expr | Let Expr (Expr -> Expr)
> 
> When I use such a data structure, I find myself writing expressions such
> as
> 
> > Let foo $ \a -> 
> > Let bar $ \b ->
> > Add a b
> 
> It seems to me that there should be a monad here somewhere, so that I
> can write this approximately like
> 
> do a <- foo
>    b <- bar
>       return (Add a b)

Neat idea, but the monad can't work exactly as you propose, because
it'd break the monad laws: do { a <- foo; return a } should be equal
to foo, but in your example it'd result in Let foo id.

However, with an explicit binding marker the continuation monad does
what you want:

import Control.Monad.Cont

data Expr = One | Add Expr Expr | Let Expr (Expr -> Expr)

type ExprM = Cont Expr

bind :: Expr -> ExprM Expr
bind e = Cont (Let e)

runExprM :: ExprM Expr -> Expr
runExprM e = runCont e id

Now you'd write your example as

do a <- bind foo
   b <- bind bar
   return (Add a b)

HTH.


Lauri
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to