
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. So maybe make the types instances of typeclasses? This would be Num for (+) I guess. For the first example above it will not work however, alone for it is not of type a -> a -> a. 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). 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) ? 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 ? Thanks a lot Peter

On Mar 10, 2013, at 12:33 AM, Peter Caspers
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.
So maybe make the types instances of typeclasses? This would be Num for (+) I guess. For the first example above it will not work however, alone for it is not of type a -> a -> a. 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).
If you really want that, you can stop ghc from importing Prelude. I haven't tested it yet, but I think import Prelude hiding (Num) should work. Of course, in this case you would lose all predefined instances of Num, including the ability to add integers, but you can get them back through another module. But I would strongly suggest that you define another operator instead. Unlike C++, Haskell allows you to define as many operators as you like.
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) ?
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.
Well, it's the way it is usually done. This is called a "smart constructor" pattern.
Also again, taking this way I can not provide several constructors taking inputs of different types, can I ?
Sorry, didn't get what you mean here.

Thank you all for your answers, this helps a lot. To clarify my last point ...
Also again, taking this way I can not provide several constructors taking inputs of different types, can I ? Sorry, didn't get what you mean here.
In C++ it is perfectly normal to have overloaded functions like f : Int -> Int -> Int f : Int -> Char -> Int in coexistence, because the compiler can infer (at compile time) what function to call by looking at the arguments types. In Haskell I think this is not possible simply due to the flexibility given by partial function application, i.e. f 5 would not be well defined any more, it could be Int -> Int or Char -> Int. Thanks again and kind regards Peter

On Mar 10, 2013, at 11:47 AM, Peter Caspers
Thank you all for your answers, this helps a lot. To clarify my last point ...
Also again, taking this way I can not provide several constructors taking inputs of different types, can I ? Sorry, didn't get what you mean here.
In C++ it is perfectly normal to have overloaded functions like
f : Int -> Int -> Int f : Int -> Char -> Int
in coexistence, because the compiler can infer (at compile time) what function to call by looking at the arguments types.
In Haskell I think this is not possible simply due to the flexibility given by partial function application, i.e.
f 5
would not be well defined any more, it could be Int -> Int or Char -> Int.
Well, that's what typeclasses are for. class F a where f :: Int -> a -> Int instance F Int where f = ... instance F Char where f = ... ghci> :t f 5 ghci> f 5 :: (F a) => a -> Int

In C++ it is perfectly normal to have overloaded functions like
f : Int -> Int -> Int f : Int -> Char -> Int
Something that may not be obvious about Haskell is that Haskell does NOT have overloaded functions/operators at all. More precisely, for any identifier and any point in a Haskell module, there is at most ONE definition of that identifier that is in scope at that point. More precisely, we can think of a function has having two parts: an *interface* which specifies its type and zero or more *implementations* which specify its behaviour, all of which must have types that match or are special cases of that interface. For any identfier and any point in a Haskell module, there is at most one INTERFACE for that identifier that is in scope at that point, so there is no possible doubt about the type of that identifier. As an example, the standard Prelude has *one* interface for +, namely (+) :: Num t => t -> t -> t and it offers a number of implementations of + (in 'instance' declarations) for various types. There are additional implementations in other modules, but they all must have types that are instances of this one. I don't believe that partial (Curried) application has anything to do with it. Torsors would need multiparameter type classes so that g + t :: t t - t :: g and so on, but Haskell originally didn't have multiparameter type classes.

In C++ it is perfectly normal to have overloaded functions like
f : Int -> Int -> Int f : Int -> Char -> Int Something that may not be obvious about Haskell is that Haskell does NOT have overloaded functions/operators at all.
thanks, this was the core of my question. So by example, if I define a Date type as data Date = Date Int deriving Show representing a date by its serial number and want two constructors (conditions are only examples here) -- smart constructor with serialNumber date serialNumber | serialNumber > 0 = Date serialNumber | otherwise = error ("invalid serialNumber " ++ show serialNumber) -- smart constructor with day month year date2 day month year | month >= 1 && month <=12 = undefined | otherwise = error ("invalid month " ++ show month) there is no way of naming both functions date (instead of date2 above, which compiles), right ? I still think the basic reason is that date 5 would then either refer to the first constructor (i.e. representing a date with serial number 5) or a partial application of the second constructor (i.e. representing a function taking month and year and returning the date "5th month, year"). If this is the case, what would be the natural Haskell way of organizing the smart constructors ? Just number them as above ? Or naming them dateFromSerialNumber, dateFromDayMonthYear ? Or would you do it differently from the start ? Thank you Peter

Hi Peter,
-- smart constructor with serialNumber date serialNumber | serialNumber > 0 = Date serialNumber | otherwise = error ("invalid serialNumber " ++ show serialNumber)
Instead of raising an error it's more secure to return a Maybe value. date :: Int -> Maybe Date date serialNumber | serialNumber > 0 = Just $ Date serialNumber | otherwise = Nothing
-- smart constructor with day month year date2 day month year | month >= 1 && month <=12 = undefined | otherwise = error ("invalid month " ++ show month)
To increase type safety it's a good idea to use as much explicit data types instead of Int values as possible: data Month = January | ...
If this is the case, what would be the natural Haskell way of organizing the smart constructors ? Just number them as above ? Or naming them dateFromSerialNumber, dateFromDayMonthYear ?
I would use the descriptive names but leave out the 'date', because you could still have: import qualified Date Date.fromSerialNumber Greetings, Daniel

Hi Daniel,
Instead of raising an error it's more secure to return a Maybe value.
date :: Int -> Maybe Date date serialNumber | serialNumber > 0 = Just $ Date serialNumber | otherwise = Nothing
yes, I understand (Maybe seems the equivalent of c++'s boost::optional<T>).
-- smart constructor with day month year date2 day month year | month >= 1 && month <=12 = undefined | otherwise = error ("invalid month " ++ show month) To increase type safety it's a good idea to use as much explicit data types instead of Int values as possible:
data Month = January | ...
ok, I will try to change my code in that direction. The idea is clear.
I would use the descriptive names but leave out the 'date', because you could still have:
import qualified Date
Date.fromSerialNumber
also clear, yes. I think I have a better starting point now. Not impossible that I will come back later with further questions :-) Thank you for your help Peter

On 11/03/2013, at 12:10 AM, Peter Caspers wrote:
thanks, this was the core of my question. So by example, if I define a Date type as
data Date = Date Int deriving Show
representing a date by its serial number and want two constructors (conditions are only examples here)
-- smart constructor with serialNumber date serialNumber | serialNumber > 0 = Date serialNumber | otherwise = error ("invalid serialNumber " ++ show serialNumber)
-- smart constructor with day month year date2 day month year | month >= 1 && month <=12 = undefined | otherwise = error ("invalid month " ++ show month)
there is no way of naming both functions date (instead of date2 above, which compiles), right ?
Right.
I still think the basic reason is that
date 5
would then either refer to the first constructor (i.e. representing a date with serial number 5) or a partial application of the second constructor (i.e. representing a function taking month and year and returning the date "5th month, year").
I am having real trouble understanding why you think this. Yes, for an *untyped* language, "date 27" would not know whether to return a date or a closure. But Haskell is *not* an untyped language. The one-identifier-one-visible-interface rule is about making a practical type inference algorithm. I'm also having some trouble understanding why negative serial numbers would be illegal. Dates are a Z-torsor; to convert integers to dates you have to choose an arbitrary origin. My Dershowitz-and-Reingold-inspired Smalltalk calendar library lets you use Julian day number (shifted by 0.5), modified Julian day number, rata die, and ahargana. I've been thinking of allowing a fifth origin: COBOL's 0=31-Dec-1600. "serialNumber" is a bad name because the origin is arbitrary and the name does not reveal what the origin is. You can easily write date :: Either Int (Int Int Int) -> Date date (Left days_since_epoch) = Date days_since_epoch date (Right (year,month,day)) | 1 <= month && month <= 12 && 1 <= day && day <= days_in_month year month = … | otherwise = error ("bad date") Or even set up your own interface type: import System.Time -- to get Month; pity Data.Time doesn't offer that. data Date_Presentation = Julian_Day_Number Int | Modified_Julian_Day_Number Int | Rata_Die Int | Ahargana Int | Days_Since_COBOL_Epoch Int | Gregorian Int Month Int | Julian Int Month Int | Revised_Julian Int Month Int -- more accurate than Gregorian date :: Date_Presentation -> Date date (Julian_Day_Number j) = … … date (Revised_Julian y m d) = … You will notice that this list offers 5 date presentations that use a single number and three that use two numbers and a month name. Overloading is no help with that!
If this is the case, what would be the natural Haskell way of organizing the smart constructors ? Just number them as above ? Or naming them dateFromSerialNumber, dateFromDayMonthYear ?
As noted above, there is NO unique "serial number" for a date and NO unique day/month/year representation either. Smalltalk-80 introduced baStudlyCaps namesThatIsNamesWithInternalCapitals because it was implemented on a machine that used the ASCII 63 left arrow and up arrow instead of the ASCII 67 underscore and caret. So it used the codepoint we associate with underscore for the assignment symbol. In C and C++ and SML and Haskell, we are allowed to use underscores. ThereisnoneedtorunyourwordstogetherOrUseInternalCaps. Nobody_will_shoot_you_for_writing_readably. You should probably take advantage of the module name and call your functions Date.from_julian_day_number :: Int -> Date Date.from_gregorian :: Int -> Month -> Int -> Date
Or would you do it differently from the start ?
One question is support for different calendars. I would probably have a My_Date module that just offers julian day number, modified julian day number, ahagarna, rata die, and maybe a couple of other epochs. I would create nested modules My_Date.Gregorian, My_Date.Julian, My_Date.Revised_Julian, My_Date.Mayan, and so on, so that a new calendar could be supported by just plugging in a new module, not by changing anything. For something without so many alternatives, I might make a different choice.

On Mar 9, 2013, at 3:33 PM, Peter Caspers
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).
So maybe make the types instances of typeclasses? This would be Num for (+) I guess. For the first example above it will not work however, alone for it is not of type a -> a -> a. 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).
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) ?
Take a look at affine spaces and additive groups in the vector-space package. There may be other treatments of torsors on hackage, but vector-space has a fairly straightforward approach.
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 ?
This approach -- hiding data constructors and exporting functions that perform validation -- is called "smart constructors," and is accepted practice. It isn't entirely satisfying due to interfering with pattern matching in client code, so you either need to work with projection functions for your data type, or use ViewPatterns to provide a more transparent record type at use sites. Anthony
Thanks a lot Peter
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Sat, Mar 9, 2013 at 5:33 PM, Peter Caspers

On 12/03/2013, at 3:15 AM, Carlos Camarao wrote:
On Sat, Mar 9, 2013 at 5:33 PM, Peter Caspers
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.
Stop right there. Overloading in the C++ sense is "ad hoc polymorphism" where the signatures of the various definitions need not resemble each other in any way. Haskell just plain does not have anything like that. (+) in Haskell is *not* overloaded; it has several implementations and allows you to define as many more as you want. But they all conform to the *SAME* interface. This is much more like OO inheritance. In particular, C++ will let you define versions of + where the arguments are of two different types and the result is a third. You cannot provide such an implementation for Haskell's predefined (+).
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.
Ada has had this since Ada 81. The design goal that forced it was the wish to allow the same identifier to be used as an enumeral in more than one enumerated type, so that you could do type Colour is (Red, Green, Blue); type Fruit_State is (Green, Ripe, Rotten); X : Colour := Green; Y : Fruit_State := Green; and in particular, since character literals like 'X' are allowed as enumerals in Ada, they wished to be able to write A: EBCDIC_Character := 'X'; B: ASCII_Character := 'X'; and have A and B be different bytes. The difference is that Ada *does* do this sort of thing using overload resolution and Haskell *doesn't*.
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…
Prelude> :type (+) (+) :: Num a => a -> a -> a The predefined (+) in Haskell requires its arguments and its result to be precisely the same type. I think you had better justify the claim that Date+Period -> Date and Date+Period -> Period are possible at the same time by showing us actual code.

On Mar 12, 2013, at 12:44 AM, "Richard A. O'Keefe"
Prelude> :type (+) (+) :: Num a => a -> a -> a
The predefined (+) in Haskell requires its arguments and its result to be precisely the same type.
I think you had better justify the claim that Date+Period -> Date and Date+Period -> Period are possible at the same time by showing us actual code.
Ehm...
import Prelude hiding (Num)
class SumDP a where (+) :: Date -> Period -> a
instance SumDP Date where date + period =

On 12/03/2013, at 10:00 AM, MigMit wrote:
On Mar 12, 2013, at 12:44 AM, "Richard A. O'Keefe"
wrote: Prelude> :type (+) (+) :: Num a => a -> a -> a
The predefined (+) in Haskell requires its arguments and its result to be precisely the same type.
I think you had better justify the claim that Date+Period -> Date and Date+Period -> Period are possible at the same time by showing us actual code.
Ehm...
import Prelude hiding (Num) class SumDP a where (+) :: Date -> Period -> a instance SumDP Date where date + period =
instance SumDP Period where date + period =
Notice the difference? I said that THE PREDEFINED (+) in Haskell requires its arguments and its result to be precisely the same type. This example is not the predefined (+); it's another variable entirely that happens to have the same short name and cannot also add integers.

12.03.2013, 02:53, "Richard A. O'Keefe"
On 12/03/2013, at 10:00 AM, MigMit wrote:
On Mar 12, 2013, at 12:44 AM, "Richard A. O'Keefe"
wrote: Prelude> :type (+) (+) :: Num a => a -> a -> a
The predefined (+) in Haskell requires its arguments and its result to be precisely the same type.
I think you had better justify the claim that Date+Period -> Date and Date+Period -> Period are possible at the same time by showing us actual code. Ehm...
import Prelude hiding (Num) class SumDP a where (+) :: Date -> Period -> a instance SumDP Date where date + period =
instance SumDP Period where date + period = Notice the difference? I said that THE PREDEFINED (+) in Haskell requires its arguments and its result to be precisely the same type.
This example is not the predefined (+); it's another variable entirely that happens to have the same short name and cannot also add integers.
So? You've said:
I think you had better justify the claim that Date+Period -> Date and Date+Period -> Period are possible at the same time by showing us actual code.
You didn't say THIS (+) should be the "predefined" one. And, since you were replying to what Carlos said, and he didn't say it either, my code is still a valid example. Of course, you can refine your request so that it would mention the "predefined" (+), but that would be off-topic here.

On 12/03/2013, at 3:15 AM, Carlos Camarao 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.
Stop right there. Overloading in the C++ sense is "ad hoc polymorphism" where the signatures of the various definitions need not resemble each other in any way. Haskell just plain does not have anything like that. (+) in Haskell is *not* overloaded; it has several implementations and allows you to define as many more as you want. But they all conform to the *SAME* interface. This is much more like OO inheritance.
Sorry, I think my sentence: "To define (+) as an overloaded operator in Haskell, you have to define and use a type class." is not quite correct. I meant that to define any operator in Haskell you have to have a type class defined with that operator as member. Then, if there is already a type class defined, a programmer can either use it (if that is suitable/adequate) or hide it and define another one. Sorry, that's what I meant.
In particular, C++ will let you define versions of + where the arguments are of two different types and the result is a third. You cannot provide such an implementation for Haskell's predefined (+).
Yes, but the requirement of using the "predefined" (+) is an extra requirement (I would call (+) in Haskell not a predefined operator, but an operator whose type is defined in a class (Num) which is in the Prelude). A Haskell programmer can still define versions of (+) where the arguments are of two different types and the result is a third (he cannot though use the two type classes, and thus neither instances of these two type classes, in a program). The suitability/adequacy of the type defined in a class means that the type of all names/operators in an instance of the class must be an instance-type of the type specified in the class. And unsuitability/inadequacy requires the definition and use of another type class (sorry to repeat that, just reinforcing).
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.
Ada has had this since Ada 81. The design goal that forced it was the wish to allow the same identifier to be used as an enumeral in more than one enumerated type, so that you could do type Colour is (Red, Green, Blue); type Fruit_State is (Green, Ripe, Rotten); X : Colour := Green; Y : Fruit_State := Green;
and in particular, since character literals like 'X' are allowed as enumerals in Ada, they wished to be able to write A: EBCDIC_Character := 'X'; B: ASCII_Character := 'X'; and have A and B be different bytes. The difference is that Ada *does* do this sort of thing using overload resolution and Haskell *doesn't*.
Ok. I will have a look at Ada's overloading mechanism. Thanks! I am trying to emphasize the constrained *polymorphism* that is possible in Haskell, which allows overloading resolution not to be required in an use of an operator or constant. I believe that this is a significant new contribution of the language. (I think Green and 'X' are not polymorphic, and any use of them required thus that overloading be resolved).
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… Prelude> :type (+) (+) :: Num a => a -> a -> a The predefined (+) in Haskell requires its arguments and its result to be precisely the same type.
I think you had better justify the claim that Date+Period -> Date and Date+Period -> Period are possible at the same time by showing us actual code.
I think I have shown it (see previous message): as Miguel Mitrofanov, hiding and redefining Num. Kind regards, Carlos

On Tue, Mar 12, 2013 at 1:52 PM, Carlos Camarao
Sorry, I think my sentence: "To define (+) as an overloaded operator in Haskell, you have to define and use a type class." is not quite correct. I meant that to define any operator in Haskell you have to have a type class defined with that operator as member.
What? An operator is just an infix function, taken from the set of symbols. Any function can be an operator (and is, via `func` syntax). No typeclass is required to define a random operator. What did you really mean to say there? -- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

On Tue, Mar 12, 2013 at 3:21 PM, Brandon Allbery
On Tue, Mar 12, 2013 at 1:52 PM, Carlos Camarao
wrote: Sorry, I think my sentence: "To define (+) as an overloaded operator in Haskell, you have to define and use a type class." is not quite correct. I meant that to define any operator in Haskell you have to have a type class defined with that operator as member.
What? An operator is just an infix function, taken from the set of symbols. Any function can be an operator (and is, via `func` syntax). No typeclass is required to define a random operator.
What did you really mean to say there?
Sorry, I meant: "To define any _overloaded_ name or operator (i.e. any name/operator that can be overloaded) in Haskell you have to have a type class defined with that name/operator as member. Cheers, Carlos

Carlos Camarao wrote:
Sorry, I think my sentence: "To define (+) as an overloaded operator in Haskell, you have to define and use a type class." is not quite correct. I meant that to define any operator in Haskell you have to have a type class defined with that operator as member.
No. Operators and type classes are entirely orthogonal in Haskell. For example, the list concatenation operator (++) is not defined in any type class. It could be. Either the `mplus` of MonadPlus or the `mappend` of Monoid would make sense. But it happens not to be.
Yes, but the requirement of using the "predefined" (+) is an extra requirement (I would call (+) in Haskell not a predefined operator, but an operator whose type is defined in a class (Num) which is in the Prelude). A Haskell programmer can still define versions of (+) where the arguments are of two different types and the result is a third (he cannot though use the two type classes, and thus neither instances of these two type classes, in a program).
I wish we could argue over semantics instead of vocabulary. By calling the (+) of Num "predefined" I meant nothing other than "it is _defined_ in the Haskell report before (_pre_) you or I add any code of our own". We agree on the facts. I don't call it an "extra" requirement. The original context was very clearly that in C++ where you have int+int, int+double, double+int, double+double, char*+int, int+char* and so on all predefined, you can *also* add your own date+period *without* hiding the predefined versions. And _that_ is overloading. If the question is whether Haskell can do overloading, _that_ is what has to be achieved: you can add a *new* interface date+period *without* hiding the ones that were already defined before you started coding. The interesting challenge here is that we should have Date + Period -> Date Date - Period -> Date Period + Date -> Date Period - Date -> ILLEGAL Period + Period -> Deriod Period - Period -> Period Date + Date -> ILLEGAL Date - Date -> Date and _also_ (remember we are trying to beat C++ here) Int +/- Int -> Int. I suspect that this can be done using type-level programming (so that Date + Date and Period - Date _begin_ to type check but then violate a type constraint) but that's where my Haskell skills are most risible.

On Mar 13, 2013, at 12:54 AM, "Richard A. O'Keefe"
The interesting challenge here is that we should have
Date + Period -> Date Date - Period -> Date Period + Date -> Date Period - Date -> ILLEGAL Period + Period -> Deriod Period - Period -> Period Date + Date -> ILLEGAL Date - Date -> Date
and _also_ (remember we are trying to beat C++ here) Int +/- Int -> Int.
Well, an obvious suggestion would be to use MultiParamTypeClasses and TypeFamilies: {- LANGUAGE MultiParamTypeClasses, TypeFamilies -} module Date where import Prelude hiding (Num, (+)) data Date = Date data Period = Period class Plus a b where type PlusResult a b (+) :: a -> b -> PlusResult a b instance Plus Date Period where type PlusResult Date Period = Date Date + Period = Date instance Plus Period Date where type PlusResult Period Date = Date Period + Date = Date instance Plus Period Period where type PlusResult Period Period = Period Period + Period = Period But I suppose you've been thinking about Haskell98. That, I'm afraid, doesn't seem possible.

If you add NoImplicitPrelude, I think you should also be able to do:
import Prelude hiding (Num)
import qualified Prelude (Num)
instance Num a => Plus a a where
type PlusResult a a = a
a + b = a Prelude.+ b
On Tue, Mar 12, 2013 at 2:24 PM, MigMit
On Mar 13, 2013, at 12:54 AM, "Richard A. O'Keefe"
wrote: The interesting challenge here is that we should have
Date + Period -> Date Date - Period -> Date Period + Date -> Date Period - Date -> ILLEGAL Period + Period -> Deriod Period - Period -> Period Date + Date -> ILLEGAL Date - Date -> Date
and _also_ (remember we are trying to beat C++ here) Int +/- Int -> Int.
Well, an obvious suggestion would be to use MultiParamTypeClasses and TypeFamilies:
{- LANGUAGE MultiParamTypeClasses, TypeFamilies -} module Date where import Prelude hiding (Num, (+)) data Date = Date data Period = Period class Plus a b where type PlusResult a b (+) :: a -> b -> PlusResult a b instance Plus Date Period where type PlusResult Date Period = Date Date + Period = Date instance Plus Period Date where type PlusResult Period Date = Date Period + Date = Date instance Plus Period Period where type PlusResult Period Period = Period Period + Period = Period
But I suppose you've been thinking about Haskell98. That, I'm afraid, doesn't seem possible. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Mar 13, 2013, at 12:54 AM, "Richard A. O'Keefe"
The interesting challenge here is that we should have
Date + Period -> Date Date - Period -> Date Period + Date -> Date Period - Date -> ILLEGAL Period + Period -> Deriod Period - Period -> Period Date + Date -> ILLEGAL Date - Date -> Date
and _also_ (remember we are trying to beat C++ here) Int +/- Int -> Int.
I think I would also want Period * Int -> Period Period * Period -> ILLEGAL Donn

On Tue, Mar 12, 2013 at 5:54 PM, Richard A. O'Keefe
wrote: Carlos Camarao wrote:
>> Sorry, I think my sentence: >> "To define (+) as an overloaded operator in Haskell, >> you have to define and use a type class." >>is not quite correct. I meant that to define any operator in Haskell you have to >> have a type class defined with that operator as member.
> No. Operators and type classes are entirely orthogonal in Haskell. > For example, the list concatenation operator (++) is not defined in > any type class. It could be. Either the `mplus` of > MonadPlus or the `mappend` of Monoid would make sense. But it > happens not to be.
I have already corrected myself (repeating, I meant: "To define an _overloaded_ name or operator in Haskell you have to have a type class defined with that name/operator as member").
>> Yes, but the requirement of using the "predefined" (+) is an extra >> requirement (I would call (+) in Haskell not a predefined operator, >> but an operator whose type is defined in a class (Num) which is in the >> Prelude). A Haskell programmer can still define versions of (+) where >> the arguments are of two different types and the result is a third >> (he cannot though use the two type classes, and thus neither instances >> of these two type classes, in a program).
> I wish we could argue over semantics instead of vocabulary. > By calling the (+) of Num "predefined" I meant nothing other than > "it is _defined_ in the Haskell report before (_pre_) you or I add > any code of our own". We agree on the facts.
Ok. But the fact that (+) has type a->a->a is a matter (design decision) related to the definition of class Num in the Haskell Prelude. If (+) had type a->b->c, the fact that
"A Haskell programmer can still define versions of (+) where the arguments are of two different types and the result is a third"
would _not_ depend on hiding and redefining a type class. The programmer could then just define the desired instances.
> I don't call it an "extra" requirement. The original context > was very clearly that in C++ where you have int+int, int+double, > double+int, double+double, char*+int, int+char* and so on all > predefined, you can *also* add your own date+period *without* > hiding the predefined versions. And _that_ is overloading. > If the question is whether Haskell can do overloading, _that_ is > what has to be achieved: you can add a *new* interface > date+period *without* hiding the ones that were already defined > before you started coding.
See above. In this view redefining the type of (+) in class Num
as a->b->c would be sufficient for Haskell to have overloading.
> The interesting challenge here is that we should have > Date + Period -> Date Date - Period -> Date > Period + Date -> Date Period - Date -> ILLEGAL > Period + Period -> Deriod Period - Period -> Period > Date + Date -> ILLEGAL Date - Date -> Date > and _also_ (remember we are trying to beat C++ here) Int +/- Int -> Int. > > I suspect that this can be done using type-level programming (so that > Date + Date and Period - Date _begin_ to type check but then violate > a type constraint) but that's where my Haskell skills are most risible.
Without redefining the type of (+) in the Prelude, the challenge can be met by redefining (+) in another type class (and, yes, if Prelude.(+) is also needed, hiding and importing it qualified). Note though that in this case _polymorphic_ uses of (+), whose instantiation could be for instances of both classes (Prelude.Num and the other one) are not possible. Kind regards, Carlos
participants (12)
-
Amy de Buitléir
-
Anthony Cowley
-
Brandon Allbery
-
Carlos Camarao
-
Daniel Trstenjak
-
David Thomas
-
Donn Cave
-
MigMit
-
Miguel Mitrofanov
-
ok@cs.otago.ac.nz
-
Peter Caspers
-
Richard A. O'Keefe