[Hugs-users] overloading operators

Daniel Fischer daniel.is.fischer at web.de
Wed Apr 13 05:43:34 EDT 2005


Am Mittwoch, 13. April 2005 06:04 schrieb Alfredo Paz-Valderrama:
> Ok
> but whe the Thompson's book says:
>
> --------------------------------------------
> Literals are not overloaded, there is no automatic conversion from Int to
> Float. .. we will receive an error message if we type
>
> (floor 5.6) + 6.7
>
> since we are trying to add quantities of two different types. We have to
> convert the Int to a Float to perform the addtion, thus:
>
> fromIntegral (floor 5.6) + 6.7
>
> where fromInt takes int to corresponding Float.
> --------------------------------------------
> pag. 45 "The Craft of Functional Programming" second edition
>

In my copy, the passage reads:

Although literals are overloaded, there is no automatic conversion ...

and 'floor 5.6' is not a literal, it's the result of a function application - 
and it can have any Integral type.

Prelude> :i floor
floor :: (RealFrac a, Integral b) => a -> b  -- class member

Floating Point literals are overloaded, too:

Prelude> :t 5.6
5.6 :: Fractional a => a,

5.6 means the same as 'fromRational 5.6'.

Feel free to argue against the decision to overload literals but not provide 
automatic conversion of numeric types, but there are good reasons for it and 
you'll get used to it pretty fast.

>
> sadly, if I use a integer number it's work!
>
> 5 + 6.7
>
> WHY?????
>
> 5 is don't Integer like (floor 5.6)?
>

It works with _literals_, the type is irrelevant:
Prelude> 5.6 + 4%5
32 % 5

The following refers to type classes, take a look at chapter 12.
Now if you try to evaluate

floor 5.6 + 6.7,

floor 5.6 has type Integral b => b - though my hugs gives
Prelude> :t floor 5.6
floor 5.6 :: (RealFrac a, Integral b) => b,
the appearance of 'RealFrac a' in the context is irritating to say the least -

and 6.7 has type Fractional a => a.
For the expression to be well typed, you'd need a simultaneous instance of 
Integral and Fractional. You can provide such:

module FracInt where

import Data.Ratio

default (Integer,Rational,Double)

instance Integral a => Integral (Ratio a) where
   quotRem x y = (q,r)
                 where
		    q = fromIntegral . floor $ x / y
		    r = x - q*y
   toInteger = floor

and then, hey presto:

FracInt> floor 5.6 + 6.7
117 % 10

if you leave out the default declaration, hugs will complain about an 
unresolved overloading (read section 10 of the 'Gentle Introduction' or 
section 4.3.4 of the report to learn about default declarations).

Don't expect to feel at home with all this in half an hour, but it's quite 
easily absorbed.
>
>
> --
> Alfredo Paz-Valderrama
> Sociedad Peruana de Computacion
>
> Mensaje citado por Scott Turner <p.turner at computer.org>:
> > On 2005 April 12 Tuesday 23:12, Alfredo Paz-Valderrama wrote:
> > > If i write this in hugs:
> > >
> > > 1 / 2
> > >
> > > I get 0.5 by answer, but the / operator signature is:
> > >
> > > float -> float -> float
> >
> > 1 and 2 are overloaded. They can be Integer, Float, etc.
> >
> > You can think of 2 as meaning (fromInteger 2). FromInteger is defined in
> > the Prelude to convert an Integer to any numeric type.
> >
> > Haskell organizes overloading using type classes. The type class called
> > Num contains fromInteger, +, -, and *.  So these operators along with the
> > integer literals 1,2, etc. can be used with any numeric type. You can
> > define your own numeric type (for example polynomials) and use 1,2, and +
> > with that.
> >
> > Actually, the / operator is not limited to Float, either. It is
> > overloaded for
> > the type class "Fractional", which includes Double and Rational.  Hugs
> > will tell you the type is
> >    Float -> Float -> Float

actually, hugs (November 2003) gives
FracInt> :t (/)
(/) :: Fractional a => a -> a -> a.

> > because there's a defaulting mechanism so that if multiple types are
> > possible,
> > Hugs can choose one and give you an answer.
>
Hope, I haven't spread too much confusion,
Daniel


More information about the Hugs-Users mailing list