[Haskell-cafe] Unresolved overloading error

2007-03-31 Thread Scott Brown
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


Re: [Haskell-cafe] Unresolved overloading error

2007-03-31 Thread Lennart Augustsson
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


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Unresolved overloading error

2007-03-31 Thread 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))


Lennart Augustsson [EMAIL PROTECTED] 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



 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


Re: [Haskell-cafe] Unresolved overloading error

2007-03-31 Thread Bryan Burgers

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

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Unresolved overloading error

2007-03-31 Thread Jacques Carette

Bryan Burgers wrote:

On 3/31/07, Scott Brown [EMAIL PROTECTED] 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 
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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Parsing words with parsec

2007-03-31 Thread Paolo Veronelli
On Friday 30 March 2007 06:59, Stefan O'Rear wrote:

 Anyway, I think parsec is *far* too big a hammer for the nail you're trying
 to hit.

In the end , the big hammer solution has become

parseLine = fmap (map fst. filter snd) $ many parser 
  where parser = do w - option (,False) parseAWord  
anyChar -- skip the separator
return w
parseAWord = try positive | (many1 nonSeparator  return 
(,False)) 
positive = do c - wordChar
  (cs,tn) - option (,True) parseAWord
  return (c:cs,tn)
   
wordChar = letter | oneOf _@ ? a word-character
 
nonSeparator = wordChar | digit ? a non-separator

while your, corrected not parsec solution is

wordsOfLine isNonSeparator isWordChar = (filter (all isWordChar)).
 groupBy (\x y - (isNonSeparator x) == (isNonSeparator y)) 

Still ,I wonder if the parsec solution can be simplified.

Thanks.

(PS. I put an option on the ML software which sends me an ack on posting , so 
at least I know I sent the mail :) )
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] HGL on Mac OS X

2007-03-31 Thread Ruben Zilibowitz

Hi,

Has anyone got the GHC module HGL to work on Mac OS X? If so I'd be  
very interested to know how.


Cheers,

Ruben

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe