[Haskell-cafe] Define variable types
Miguel Mitrofanov
miguelimo38 at yandex.ru
Thu Feb 5 07:21:27 EST 2009
Note also that Helium ISN'T Haskell; it lacks hell of a lot of Haskell98 features (not to mention common extensions).
05.02.09, 14:57, "Roman Cheplyaka" <roma at ro-che.info>:
> * Tsunkiet Man <temp.tsun at gmail.com> [2009-02-05 12:37:22+0100]
> > 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)
> >
> > 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
> You can't use fractional division (/) with integers. You can convert
> integers to fractions using fromIntegral. E.g.:
> 1 / fromIntegral ((1 - p) ^ (-(n - k)))
> (literals like 1 doesn't need to be converted because they are
> polymorphic)
> --
> Roman I. Cheplyaka :: http://ro-che.info/
> "Don't let school get in the way of your education." - Mark Twain
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
More information about the Haskell-Cafe
mailing list