
I have written this code in Haskell which gives an unresolved overloading error. The function bernoulli should give the probability of j successes occuring in n trials, if each trial has a probability of p.
fac 0 = 1 fac n = n * fac(n - 1)
binom n j = (fac n)/((fac j)*(fac (n - j)))
bernoulli n p j = (binom n j)*(p ^ j) * ((1 - p)^(n - j))
However, bernoulli 6 0.5 3 gives the error: ERROR - Unresolved overloading *** Type : (Fractional a, Integral a) => a *** Expression : bernoulli 6 0.5 3 Why doesn't Haskell infer the types? What kind of type casting or type definition can I use to fix the error? Send instant messages to your online friends http://au.messenger.yahoo.com

The definition of fac forces the result to have the same type as the argument. Then in binom you use / which forces the type to be Fractional. And finally you use ^ which forces the type to be Integral. There is no type that is both Fractional and Integral. I suggest using div instead of / in binom (binomial coefficients are integers after all). And then a fromIntegral applied to the binom call in bernoulli. -- Lennart On Mar 31, 2007, at 10:04 , Scott Brown wrote:
I have written this code in Haskell which gives an unresolved overloading error. The function bernoulli should give the probability of j successes occuring in n trials, if each trial has a probability of p.
fac 0 = 1 fac n = n * fac(n - 1)
binom n j = (fac n)/((fac j)*(fac (n - j)))
bernoulli n p j = (binom n j)*(p ^ j) * ((1 - p)^(n - j))
However, bernoulli 6 0.5 3 gives the error:
ERROR - Unresolved overloading *** Type : (Fractional a, Integral a) => a *** Expression : bernoulli 6 0.5 3
Why doesn't Haskell infer the types? What kind of type casting or type definition can I use to fix the error? Send instant messages to your online friends http:// au.messenger.yahoo.com
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Actually, I don't know what type you want p to be, so you might not need the fromIntegral. On Mar 31, 2007, at 10:21 , Lennart Augustsson wrote:
The definition of fac forces the result to have the same type as the argument. Then in binom you use / which forces the type to be Fractional. And finally you use ^ which forces the type to be Integral. There is no type that is both Fractional and Integral.
I suggest using div instead of / in binom (binomial coefficients are integers after all). And then a fromIntegral applied to the binom call in bernoulli.
-- Lennart
On Mar 31, 2007, at 10:04 , Scott Brown wrote:
I have written this code in Haskell which gives an unresolved overloading error. The function bernoulli should give the probability of j successes occuring in n trials, if each trial has a probability of p.
fac 0 = 1 fac n = n * fac(n - 1)
binom n j = (fac n)/((fac j)*(fac (n - j)))
bernoulli n p j = (binom n j)*(p ^ j) * ((1 - p)^(n - j))
However, bernoulli 6 0.5 3 gives the error:
ERROR - Unresolved overloading *** Type : (Fractional a, Integral a) => a *** Expression : bernoulli 6 0.5 3
Why doesn't Haskell infer the types? What kind of type casting or type definition can I use to fix the error? Send instant messages to your online friends http:// au.messenger.yahoo.com
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

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))
Lennart Augustsson
I have written this code in Haskell which gives an unresolved overloading error. The function bernoulli should give the probability of j successes occuring in n trials, if each trial has a probability of p.
fac 0 = 1 fac n = n * fac(n - 1)
binom n j = (fac n)/((fac j)*(fac (n - j)))
bernoulli n p j = (binom n j)*(p ^ j) * ((1 - p)^(n - j))
However, bernoulli 6 0.5 3 gives the error:
ERROR - Unresolved overloading *** Type : (Fractional a, Integral a) => a *** Expression : bernoulli 6 0.5 3
Why doesn't Haskell infer the types? What kind of type casting or type definition can I use to fix the error? Send instant messages to your online friends http:// au.messenger.yahoo.com
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Send instant messages to your online friends http://au.messenger.yahoo.com

On 3/31/07, Scott Brown
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) )

On 3/31/07, Scott Brown
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). The issue is that it is
Bryan Burgers wrote: possible to prove that the above is an integer, but the compiler can't see that :-( That can be done as import Data.Ratio bb u k = numerator $ product [ (u-i+1) / i | i <- [1..k]] Of course, the above is fast if and only if the gcd operation in Data.Ratio has been well optimized. Jacques

On Sat, 31 Mar 2007, Jacques Carette wrote:
Bryan Burgers wrote:
On 3/31/07, Scott Brown
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

On 31/03/07, Bryan Burgers
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) )
You can even drop the first set of parentheses: binom n r = fac n `div` (fac r * fac (n - r)) Remember that prefix function application has a higher precedence than pretty much anything else. -- -David House, dmhouse@gmail.com
participants (6)
-
Bryan Burgers
-
David House
-
Henning Thielemann
-
Jacques Carette
-
Lennart Augustsson
-
Scott Brown