[Haskell-cafe] Eval of a syntax tree for reduction

Greg Buchholz haskell at sleepingsquirrel.org
Tue Mar 28 01:50:37 EST 2006


Steve Downey wrote:
] I'm considering changing eval1 to be ArithExpr->Maybe ArithExpr
] 
] If the expression is reducible, then I return Just t, and if it's not
] reducible, then Nothing
] 
] It makes eval1 a bit more complicated, and not as straightforward
] translation from the type system being described, though.
] e.g reducing If looks more like
] 
] eval1 (TmIfExpr t1 t2 t3) =
]     let t1' = eval1 t1
]     in  case t1' of
]             { Just t1'' -> Just $ TmIfExpr t1'' t2 t3
]             ; Nothing -> Nothing
]             }
] 
] I'm looking for some suggestions on the direction to proceed.

    If you are looking to get rid of the noise caused by Maybe, you
could package up all of the "case" and "Just" stuff into a few reusable
functions.  In fact, its already been done for you, since Maybe is a
monad...

    http://www.nomaware.com/monads/html/maybemonad.html

...You could try something like...

> import Control.Monad  -- for liftM3, etc.
>  
> eval1_ :: ArithExpr -> Maybe ArithExpr
> eval1_ (TmIfExpr TmTrue  t _) = return t
> eval1_ (TmIfExpr TmFalse _ t) = return t
> eval1_ (TmIfExpr t1 t2 t3) = liftM3 TmIfExpr (eval1_ t1) (return t2) (return t3)

...and if it turns out you don't like the resulting "Maybeified"
program, you can get the original functionality back by changing the
type signature to use the Identity monad instead of Maybe.

Greg Buchholz



More information about the Haskell-Cafe mailing list