[Haskell-cafe] compilation question

Mitchell, Neil neil.mitchell.2 at credit-suisse.com
Tue Nov 11 12:54:29 EST 2008


Hi

The one way to test this is to benchmark, everything else will just be
peoples random guesses.

As for my random guess, eval should be significantly faster than peval
in Hugs, and probably slightly faster than peval in GHC. I don't see why
you think peval is efficient - monads /= efficiency, they merely are an
extra layer over standard evaluation. If you use the IO monad and some
careful annotations you could hope to draw with eval, but just accept
the beauty that is pure functional programming and smile :-)

Thanks

Neil

> -----Original Message-----
> From: haskell-cafe-bounces at haskell.org 
> [mailto:haskell-cafe-bounces at haskell.org] On Behalf Of Peter Padawitz
> Sent: 11 November 2008 5:49 pm
> To: haskell-cafe at haskell.org
> Cc: Hubert Wagner
> Subject: [Haskell-cafe] compilation question
> 
> At first a type of arithmetic expressions and its generic evaluator:
> 
> data Expr = Con Int | Var String | Sum [Expr] | Prod [Expr] | Expr :- 
> Expr |
>         Int :* Expr | Expr :^ Int
> 
> data ExprAlg a = ExprAlg {con :: Int -> a, var :: String -> 
> a, sum_ :: 
> [a] -> a,
>               prod :: [a] -> a, sub :: a -> a -> a,
>               scal :: Int -> a -> a, expo :: a -> Int -> a}
>                 
> eval :: ExprAlg a -> Expr -> a
> eval alg (Con i)   = con alg i
> eval alg (Var x)   = var alg x
> eval alg (Sum es)  = sum_ alg (map (eval alg) es)
> eval alg (Prod es) = prod alg (map (eval alg) es)
> eval alg (e :- e') = sub alg (eval alg e) (eval alg e')
> eval alg (n :* e)  = scal alg n (eval alg e)
> eval alg (e :^ n)  = expo alg (eval alg e) n
> 
> Secondly, a procedural version of eval (in fact based on 
> continuations):
> 
> data Id a = Id {out :: a} deriving Show
> 
> instance Monad Id where (>>=) m = ($ out m); return = Id
> 
> peval :: ExprAlg a -> Expr -> Id a
> peval alg (Con i)   = return (con alg i)
> peval alg (Var x)   = return (var alg x)
> peval alg (Sum es)  = do as <- mapM (peval alg) es; return 
> (sum_ alg as)
> peval alg (Prod es) = do as <- mapM (peval alg) es; return 
> (prod alg as)
> peval alg (e :- e') = do a <- peval alg e; b <- peval alg e'; return 
> (sub alg a b)
> peval alg (n :* e)  = do a <- peval alg e; return (scal alg n a)
> peval alg (e :^ n)  = do a <- peval alg e; return (expo alg a n)
> 
> My question: Is peval less time- or space-consuming than 
> eval? Or would 
> ghc, hugs et al. optimize eval towards peval by themselves?
> 
> Peter
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
> 
> 

==============================================================================
Please access the attached hyperlink for an important electronic communications disclaimer: 

http://www.credit-suisse.com/legal/en/disclaimer_email_ib.html
==============================================================================



More information about the Haskell-Cafe mailing list