[Haskell-cafe] Define variable types
Daniel Fischer
daniel.is.fischer at web.de
Thu Feb 5 07:16:00 EST 2009
Am Donnerstag, 5. Februar 2009 12:37 schrieb Tsunkiet Man:
> Hello,
>
> I'm new to Haskell and it seems like a very nice language to learn. However
> I'm not really familiar with the errormessages it produces. I am using a
> Helium interpreter. I've created the following module (however it is just a
> small sketch). I've written the following code:
>
> fac :: Int -> Int
> fac n = product[1..n]
>
> boven :: Int -> Int -> Int
> boven n k = (fac n) `div` fac k * fac (n-k)
You want parentheses there:
boven n k = fac n `div` (fac k * fac (n-k))
>
> bin :: Int -> Int -> Int -> Int
> bin n k p |(n-k)>0 && k>0 = (boven n k) * (p^k) * (1-p)^(n-k)
>
> |(n-k)<0 && k>0 = (boven n k) * (p^k) * (1/((1-p)^(-(n-k))))
> |(n-k)<0 && k<0 = (boven n k) * (1/(p^(-k))) *
>
> (1/((1-p)^(-(n-k))))
>
> When I load this into my interpreter it says:
>
> Compiling ./Test.hs
> (11,55): Type error in infix application
> expression : 1 / ((1 - p) ^ (-(n - k)))
> operator : /
> type : Float -> Float -> Float
> does not match : Int -> Int -> Int
> (12,47): Type error in infix application
> expression : 1 / (p ^ (-k))
> operator : /
> type : Float -> Float -> Float
> does not match : Int -> Int -> a
> (12,62): Type error in infix application
> expression : 1 / ((1 - p) ^ (-(n - k)))
> operator : /
> type : Float -> Float -> Float
> does not match : Int -> Int -> a
> Compilation failed with 3 errors
>
> Some details that might be usefull:
>
> Line 11 is |(n-k)<0 && k>0 = (boven n k) * (p^k) * (1/((1-p)^(-(n-k))))
> Line 12 is |(n-k)<0 && k<0 = (boven n k) * (1/(p^(-k))) *
> (1/((1-p)^(-(n-k))))
>
> So my question is: how can I fix these errors?
Haskell doesn't do automatic type conversion, so you have to explicitly
convert from one numerical type to another.
Ints can only be divided using div (or quot), not by (/) which is the division
operator of Fractional types (Float, Double, Rational...).
However, I'm rather convinced the type signature you gave for bin is not what
you want, I think p should be a floating point number, as should the
resulting probability. That would give the type signature
bin :: Int -> Int -> Float -> Float
and the use of (/) is then legitimate. But you then must convert the binomial
coefficient to a floating point number to be able to multiply it:
bin n k p = fromIntegral (boven n k) * p^^k * (1-p)^^(n-k)
Note I've used a different exponentiation operator, (^^), which supports
negative exponents, thus avoid the branches. Since (^^) is Haskell98, Helium
should have it.
Another thing is the fact that the factorials will soon overflow using Int, so
you should better use Integer and Double instead of Int and Float.
>
> (I used these lines of codes because it is not possible to use a negative
> exponent in the Helium interpreter.)
>
> Thank you for answering my question!
>
> Greetings JTKM
HTH,
Daniel
More information about the Haskell-Cafe
mailing list