[Haskell-beginners] Average of numeric list

Nadav Chernin nadavchernin at gmail.com
Tue Apr 5 14:08:59 CEST 2011


Thank you very much

Nadav Chernin

On Tue, Apr 5, 2011 at 2:56 PM, Daniel Fischer <
daniel.is.fischer at googlemail.com> wrote:

> On Tuesday 05 April 2011 11:57:32, Nadav Chernin wrote:
> > How can i know when casting of types maked by compiler and when
> > programmer must to do it?
>
> Generally, there are no implicit type conversions in Haskell, so you always
> have to do it explicitly.
> An exception are numeric literals, an integer literal (in source code or at
> the ghci/hugs prompt) stands for
>
> fromInteger (integerValueParsedFromLiteral)
> -- fromInteger :: Num n => Integer -> n
>
> and a floating-point literal (like 1.234e56) stands for
>
> fromRational (rationalParsedFromLiteral)
> -- fromRational :: Fractional a => Rational -> a
>
> Unless my memory fails, those are the only implicit conversions the
> language report specifies. In GHC (I don't know which other compilers, if
> any, implement it), you can turn on the OverloadedStrings language
> extension to get overloaded string literals (for instances of the IsString
> class), so "this" could be a String , a ByteString or a Text (and some
> others), provided the relevant modules are in scope.
>
> Other language extensions providing compiler-generated conversions may
> exist (now or in future), but I'm not aware of any.
>
> A different, but not unrelated, issue is polymorphism (with type
> inference).
> When you use polymorphic expressions - like [], Nothing, (return True),
> (realToFrac pi) - the compiler uses the context in which the expression
> occurs to infer the type at which the expression is used.
> If that doesn't yield a monomorphic type, under some circumstances the type
> gets defaulted
> (
> http://www.haskell.org/onlinereport/haskell2010/haskellch4.html#x10-790004.3.4
> ),
> or you get a compile error since the compiler couldn't determine what to
> do.
>
> If you don't use any conversion functions,
>
> mean0 xs = sum xs / length xs,
>
> the compiler infers
>
> - xs :: Num n => [n]
> (from sum :: Num n => [n] -> n)
> - sum xs :: Fractional f => f
> (from (/) :: Fractional f => f -> f -> f)
> - combining those : xs :: (Num c, Fractional c) => [c]
> Num is a superclass of Fractional, so the constraint can be simplified,
> giving
> - xs :: Fractional c => [c]
>
> Then (length xs :: Int), inferred from (length :: [a] -> Int), as the
> second argument of (/) forces c = Int, giving the type
>
> mean0 :: Fractional Int => [Int] -> Int
>
> Normally you don't have a Fractional instance for Int in scope, so the
> compilation would fail with a "No instance ..." error. If you had such an
> instance in scope, the superfluous because fulfilled constraint would be
> removed, giving mean0 :: [Int] -> Int.
>
> Now, inserting the fromIntegral conversion in the second argument,
>
> mean1 xs = sum xs / fromIntegral (length xs)
>
> the first part remains unchanged, resulting in
> xs :: Fractional f => [f],
>
> then (sum xs :: f -- for that same, as yet undetermined Fractional type f)
> and fromIntegral's result must have the same type f.
> Since
>
> fromIntegral :: (Integral i, Num n) => i -> n,
>
> length xs :: Int, Int is an instance of Integral and Num is more general
> than Fractional, fromIntegral (length xs) can have that type, enabling the
> compiler to pick the right fromIntegral as soon as it knows f. Overall,
>
> mean1 :: Fractional f => [f] -> f,
>
> the type f can be determined by passing a list of specific type or using
> the result at specific type.
>
> Inserting a conversion for the sum, say realToFrac,
>
> mean2 xs = realToFrac (sum xs) / fromIntegral (length xs)
>
> changes the constraint on the type of xs' elements, now it need no longer
> be a suitable argument for (/) [Fractional], but for realToFrac [Real].
> (realToFrac $ sum xs) has to be the same Fractional type as
> (fromIntegral $ length xs) but can be any Fractional type, giving
>
> mean2 :: (Real r, Fractional f) => [r] -> f
>
> r can only be determined by passing an argument of specific type, f only by
> using the result at a specific type.
>
> >
> > On Tue, Apr 5, 2011 at 12:14 PM, Daniel Fischer <
> >
> > daniel.is.fischer at googlemail.com> wrote:
> > > On Tuesday 05 April 2011 10:38:37, Nadav Chernin wrote:
> > > > Why only  "length as" we must to cast? Why "sum as", that have type
> > > > Integer can be used in (/).
> > > >
> > > > :t (/)
> > > >
> > > > (/) :: (Fractional a) => a -> a -> a
> > >
> > > No, sum as has the type of as's elements,
> > >
> > > sum :: Num a => [a] -> a
> > >
> > > So the use of (/) refines the constraint from (Num a) to (Fractional
> > > a). if you want it to work on Integers too,
> > > you'd get
> > >
> > > mean :: (Real a, Fractional b) => [a] -> b
> > > mean xs = realToFrac (sum xs) / (fromIntegral $ length xs)
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/beginners/attachments/20110405/68e99cc3/attachment.htm>


More information about the Beginners mailing list