speedup help

Hal Daume III hdaume@ISI.EDU
Mon, 3 Mar 2003 16:59:21 -0800 (PST)


I think you would get a big speed-up if you got rid of all the rational
stuff and just used:

comb m n = fact m `div` (fact n * fact (m-n))

If that doesn't speed it up enouch, you can of course cache fact m in your
computation and do something like:

sumbn n = sum [ bournoulli i * fm `div` (fn * fact (m-n)) | i <- [0..n-1]]
  where fm = fact m
        fn = fact n

it is possible that the compiler is inlining the call the comb, in which
case this has already been done for you.  hard to say for sure.  putting
'{-# INLINE comb #-}' might help a lot.

>From there, you should probably look at arrays if you can bound n.

--
 Hal Daume III                                   | hdaume@isi.edu
 "Arrest this man, he talks in maths."           | www.isi.edu/~hdaume

On Mon, 3 Mar 2003, Damien R. Sullivan wrote:

> So, I'm having to calculate 'n choose k' an awful lot.  At the moment I've got
> this:
> 
> comb :: Integer -> Integer -> Integer
> comb m 0 = 1
> comb m n = (numerator(toRational (fact m) / toRational (fact n * fact (m-n))))
>          
> where fact is a memoized factorial function.  It's not perfectly memoized,
> though; I use lists, since that's easier by default.  They should be arrays,
> and possibly just changing that would speed comb up a lot.  (Comb is currently
> 40% of runtime, fact is 23%.)  But I think it should be possible to speed up
> comb itself, too.
> 
> comb is only called from here:
> sumbn n = sum [ bernoulli i * fromIntegral(comb (n+1) i) | i <- [0 .. n-1] ]
> 
> 
> Here was one try:
> 
> fcomb :: Integer -> Integer -> Integer
> fcomb m 0 = 1
> fcomb m n = res 
>     where
>     res = last * (m-n+1) `div` n 
>     last = res
> 
> except, obviously, this doesn't work.  I hope it's clear what I'm trying to
> do, or what I would be in a more imperative language -- in C I'd probably have
> some static variable in fcomb.  I figure monads are needed, but I've been
> unable to figure them out enough to apply them here.  Will the monadism
> propagate all the way up and require changing lots of function types?  Bleah.
> I'm using ghc, can I sneak some mutable in here instead?
> 
> Any advice?  Also on using arrays, where my parameters come off the command
> line.  I imagine in C++ I'd just precompute a bunch of tables and then just
> use those values in the actual algorithm.
> 
> Thanks!
> 
> -xx- Damien X-) 
> 
> (if you're curious, this is for a class, but not a class on using Haskell.  I
> chose to use Haskell for this assignment after ghc -O, to my surprise,
> outperformed ocaml.  I suspect GMP deserves the real credit, but hey.)
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>