[Haskell-cafe] Unresolved overloading error

Henning Thielemann lemming at henning-thielemann.de
Mon May 21 06:17:34 EDT 2007


On Sat, 31 Mar 2007, Jacques Carette wrote:

> Bryan Burgers wrote:
> > On 3/31/07, Scott Brown <doolagarl2002 at yahoo.com.au> wrote:
> >>
> >> It's working now, thank you.
> >> I changed the definition to
> >>
> >> > binom n j = div (fac n) ((fac j)*(fac (n - j)))
> >>
> >> > bernoulli n p j = fromIntegral(binom n j)*(p ^ j) * ((1 - p)^(n - j))
> >
> > As a matter of style suggestion, it might make 'binom' more clear if
> > you use 'div' as an infix operator:
> >
> >> binom n j = (fac n) `div` ( fac j * fac (n - j) )
> And as a matter of efficiency, no one would write binom using factorial,
> but would rather write at least
> binom u k = (product [(u-i+1)  | i <- [1..k]]) `div` (product [1..k])
> and even better would be to do it this way
> -- bb u k = toInteger $ product [ (u-i+1) / i | i <- [1..k]]
> but that does not type (for a good reason).

How about

binomialSeq :: Integral a => a -> [a]
binomialSeq n =
   scanl (\acc (num,den) -> div (acc*num) den) 1
         (zip [n, pred n ..] [1..n])

and the use of (!!) ?


http://darcs.haskell.org/htam/src/Combinatorics.hs


More information about the Haskell-Cafe mailing list