[Haskell-cafe] Overloading

Carlos Camarao carlos.camarao at gmail.com
Mon Mar 11 15:15:14 CET 2013


On Sat, Mar 9, 2013 at 5:33 PM, Peter Caspers <pcaspers1973 at gmail.com>
wrote:

    Hi,

    I just started playing around a bit with Haskell, so sorry in
    advance for very basic (and maybe stupid) questions. Coming from
    the C++ world one thing I would like to do is overloading
    operators. For example I want to write (Date 6 6 1973) + (Period 2
    Months) for some self defined types Date and Period. Another
    example would be (Period 1 Years) + (Period 3 Months).

    Just defining the operator (+) does not work because it collides
    with Prelude.+. I assume using fully qualified names would work,
    but that is not what I want.


Hi. To define (+) as an overloaded operator in Haskell, you have to define
and use a type class.  Since (+) is already a member of type class Num
in the Prelude, you would have to define instances of Num (i.e. define
instance Num Date and instance Num Period), but, since (+) has type
a->a->a in class Num, and you want to use (+) with type a->b->a (or
even a->b->c), you have to import the Prelude hiding class Num, and
define a new type class with (+) as member, like, say:

{-# LANGUAGE MultiParamTypeClasses, TypeSynonymInstances #-}
module Date where

import Prelude hiding (Num)

type Day   = Int
type Year  = Int
data Month = Jan | Feb | Mar | Apr | Mai | Jun | Jul | Aug | Sep | Oct |
Nov | Dec
newtype Date  = Date Day Month Year

type NumDays    = Int
type NumMonths = Int
newtype Period   = Period NumDays NumMonths

class Sum a b where
  (+):: a -> b -> a

instance Sum Day Period where
  (+) = ...
instance Sum Day Day where
  (+) = ...
instance Sum Period Period where
  (+) = ...


    So maybe make the types instances of typeclasses?

Yes: overloading in Haskell is done with type classes.

    This would be Num for (+) I guess.

(+) has type a->a->a in Num so that does not allow
Date->Period->... and Date->Date->...

    For the first example above it will not work however, alone for it
    is not of type a -> a -> a.

Yes. You have to define another type class that gives (+) type a->b->a
(even a->b->c, if you wish).

    Also the second example does not fit, because I would have to make
    Period an instance of Num, which does not make sense, because I
    can not multiply Periods (for example).

Well, you could define multiplication as, say, an error: this is a
consequence
of using type classes: you have to give definitions for all class members.

    Am I missing something or is that what I am trying here just
    impossible by the language design (and then probably for a good
    reason) ?

You have to use type classes to overload names (and operators). If the
type of a member in a type class is not general enough, you have to define
and use another type class.

    A second question concerns the constructors in own datatypes like
    Date above. Is it possible to restrict the construction of objects
    to sensible inputs, i.e. reject something like Date 50 23 2013 ?
    My workaround would be to provide a function say

    date :: Int->Int->Int->Date

    checking the input and returning a Date object or throw an error
    if the input does not correspond to a real date. I could then hide
    the Date constructor itself (by not exporting it). However this
    seems not really elegant. Also again, taking this way I can not
    provide several constructors taking inputs of different types, can
    I ?

You can. The constructor has to be a member of a type class.

Furthermore, Haskell supports a more powerful form of overloading than
(any other language I know, including) C++: context-dependent
overloading. This means that the type of an expression (f e), and thus
of f, can be determined at compile-time (inferred) based on the
context where (f e) occurs, not only on the type of the
argument (e) of the function's call.

For example, you _could_ in principle use (d+p==d) and (d+p==p),
with d::Date, p::Period, and instances of (+) with types
Date->Period->Date and Date->Period->Period, if you wish...

Cheers,

Carlos
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20130311/566baeef/attachment.htm>


More information about the Haskell-Cafe mailing list