[Haskell-cafe] benchmarking pure code

Paul Brauner paul.brauner at loria.fr
Wed Mar 31 07:12:44 EDT 2010


Thank you, I will look at that. But it seems that criterion uses NFData
no?

Paul

On Wed, Mar 31, 2010 at 12:57:20PM +0200, Bas van Dijk wrote:
> On Wed, Mar 31, 2010 at 11:06 AM, Paul Brauner <paul.brauner at loria.fr> wrote:
> > data Term = Lam Term | App Term Term | Var Int
> >
> > instance NFData where
> >  rnf (Lam t)     = rnf t
> >  rnf (App t1 t2) = rnf t1 `seq` rnf t2
> >  rnf (Var x)     = rnf x
> >
> > the actual datatype doesn't have fancy stuff like higher-order
> > types for constructors, it's really similar. The only difference
> > is that it is a GADT, but this souldn't change anything right?
> >
> > Did I make some mistake in instancing NFData ?
> 
> No, your NFData instance is correct. You first pattern match on the
> term followed by recursively calling rnf on the sub-terms. This will
> correctly force the entire term.
> 
> Maybe you could try using criterion[1] for your benchmark and see if
> that makes any difference. Something like:
> 
> {-# LANGUAGE BangPatterns #-}
> 
> import Criterion.Main
> 
> main :: IO ()
> main = let !t = genterm in defaultMain [bench "subst" $ nf (subst u) t]
> 
> regards,
> 
> Bas
> 
> [1] http://hackage.haskell.org/package/criterion


More information about the Haskell-Cafe mailing list