
Mark P Jones writes:
[...]
Defaulting only kicks in if (a) at least one class is numeric, and (b) all classes are standard. [...] Defaulting was designed to work in this way so that (i) it would catch and deal with the most common problems occurring with numeric literals, and (ii) it would not be used too often; defaulting is in general undesirable because it can silently change the semantics. Again, defaulting is an example of a compromise in the design of Haskell. Ideally, you'd do without it all together, but if you went that way, you'd end up having to write more type information in your programs. And again, I don't suppose there is a universally satisfactory point on this spectrum.
A language extension for subtyping would be of some use there. For example, if Int is set up as a subtype of Integer, meaning that an Int value is acceptable anywhere an Integer value is expected (with the typechecker inserting the conversion code), the literal 42 can unambiguously be assigned the type Int. (This is a reprise of an airy suggestion I've posted before, hence the move to the haskell-cafe list. I'm still at the reading-about- related-work stage of doing something more thorough about it.) Regards, Tom

Thu, 19 Oct 2000 16:25:02 +1300 (NZDT), Tom Pledger
A language extension for subtyping would be of some use there. For example, if Int is set up as a subtype of Integer, meaning that an Int value is acceptable anywhere an Integer value is expected (with the typechecker inserting the conversion code), the literal 42 can unambiguously be assigned the type Int.
This disallows literals of a non-standard type Int8. Not good. -- __("< Marcin Kowalczyk * qrczak@knm.org.pl http://qrczak.ids.net.pl/ \__/ ^^ SYGNATURA ZASTÊPCZA QRCZAK

Marcin 'Qrczak' Kowalczyk writes:
Thu, 19 Oct 2000 16:25:02 +1300 (NZDT), Tom Pledger
pisze: A language extension for subtyping would be of some use there. For example, if Int is set up as a subtype of Integer, meaning that an Int value is acceptable anywhere an Integer value is expected (with the typechecker inserting the conversion code), the literal 42 can unambiguously be assigned the type Int.
This disallows literals of a non-standard type Int8. Not good.
If you had such a non-standard type, I imagine you'd also declare something like this: instance Subtype Int8 Int16 where ... instance Subtype Int16 Int24 where ... instance Subtype Int24 Int where ... and hence literals in the range -128 to 127 would be typed Int8, etc. Regards, Tom

On Thu, 19 Oct 2000, Tom Pledger wrote:
If you had such a non-standard type, I imagine you'd also declare something like this:
instance Subtype Int8 Int16 where ... instance Subtype Int16 Int24 where ... instance Subtype Int24 Int where ...
and hence literals in the range -128 to 127 would be typed Int8, etc.
What would be the rule for typing integer literals? Currently it's simple: fromIntegral (number::Integer), and Int8 is a completely non-magical type. With your proposal, assume that the programmer makes a bunch of subtype declarations for his own types... What now? (Assuming that subtyping can be reasonably embedded in the Haskell's type system at all.) A more concrete example. Does 10 have type Int8 or Word8? Is Int8 a subtype of Word8, or the reverse? How could 10 be used as both Int8 and Word8? Current Haskell rules and not perfect: 12345::Int8 is legal. Conversions are explicit and there is no distinction between always safe conversions and those that may take an out of range parameter. But I'm happy with it; conversions are rarely used anyway, rules are simple, and there is no need of asking a question like: is every Int representable as Double (the answer may depend on the implementation). -- Marcin 'Qrczak' Kowalczyk

Marcin 'Qrczak' Kowalczyk writes:
On Thu, 19 Oct 2000, Tom Pledger wrote:
If you had such a non-standard type, I imagine you'd also declare something like this:
instance Subtype Int8 Int16 where ... instance Subtype Int16 Int24 where ... instance Subtype Int24 Int where ...
and hence literals in the range -128 to 127 would be typed Int8, etc.
What would be the rule for typing integer literals? Currently it's simple: fromIntegral (number::Integer), and Int8 is a completely non-magical type.
With your proposal, assume that the programmer makes a bunch of subtype declarations for his own types... What now?
(Assuming that subtyping can be reasonably embedded in the Haskell's type system at all.)
Of course! There's nothing quite like a nice flight of fancy. :-) A possible rule for typing integer literals is: intLitType x = tryToBeMoreSpecific (x `belongsTo`) IntegerT tryToBeMoreSpecific p t = case filter p (subtypes t) of [] -> t [t'] -> tryToBeMoreSpecific p t' ts -> case filter p (leastSpecificCommonSubtypes ts) of [t''] -> tryToBeMoreSpecific p t'' _ -> --ambiguity It's more complicated for the implementer, but makes things simpler for the programmer because we can then remove the Integral class and some unintuitive dualities like length/genericLength.
A more concrete example. Does 10 have type Int8 or Word8? Is Int8 a subtype of Word8, or the reverse? How could 10 be used as both Int8 and Word8?
There should be no subtype relationship between Int8 and Word8 in either direction, because they denote different things: numbers and encodings respectively. We can say that every Int8 value *is* an Int16 value, but there is no reasonable corresponding statement about Int8 and Word8. Faced with the choice, I'd say that 10 looks like a number, and make it an Int8. If Word8 literals are required, as opposed to terms like fromEnum 10, they should have some other appearance like 10W.
Current Haskell rules and not perfect: 12345::Int8 is legal. Conversions are explicit and there is no distinction between always safe conversions and those that may take an out of range parameter. But I'm happy with it; conversions are rarely used anyway, rules are simple, and there is no need of asking a question like: is every Int representable as Double (the answer may depend on the implementation).
I'd be very cautious about putting Double into any subtype relationship at all, because its meaning is tied back into its representation. If you can't explain that "every X is a Y" without referring to representation issues, you shouldn't be declaring X as a subtype of Y! Admittedly I dodged your general comment and focussed on your example. I need to be more certain that subtyping is a feasible language extension, before I try to tell you what you should be happy with. :-) Regards, Tom

On Thu, 19 Oct 2000, Tom Pledger wrote:
= case filter p (subtypes t) of [] -> t [t'] -> tryToBeMoreSpecific p t' ts -> case filter p (leastSpecificCommonSubtypes ts) of [t''] -> tryToBeMoreSpecific p t'' _ -> --ambiguity
Why it is bad: - Adding a subtype elsewhere may make a program ambiguous. (Well, it is so with classes too, but at least it occurs only for overlapping instances, not unrelated subtypes of a generic type.) - Assuming that "more specific" means something like "subtype", types are usually put in some ordered sequences. This means that it is not enough for each type to know a basic framework, but it must also know a type just above or below it. When various types come from unrelated sources, it is unlikely that they will know one another in the right order. For example when we have sized integer types (Int8 etc.) and types that are mirrors of C types (CInt, CLong etc.), the sequence of subtypes is a mix of both families. Should both families know each other? When Posix types (CPid etc.) are added, they are again mixed. I can't imagine where all these subtyping instances would be defined. What is worse, whether CLong is smaller or larger than Int is implementation defined. Currently it does not prevent having an implementation independent set of instances. Conversion in both directions is explicit anyway, and literals just have the right type. With your proposal a type that wants to put itself at the right place in the sequence containing Int and CLong is in trouble. Of course some of these types could be defined as synonyms, but it's not necessarily a good idea in general. It would make correctness of a code dependent on the implementation, by not catching code that makes unportable assumptions about type equivalences. - When Int and CLong are isomorphic and thus declared subtypes of each other, wouldn't your proposal make the compiler loop? It's getting hairier and hairier.
It's more complicated for the implementer, but makes things simpler for the programmer because we can then remove the Integral class and some unintuitive dualities like length/genericLength.
I doubt it's simpler fot the programmer. Certainly not simpler for me: I know how the current rules work but I don't know how subtyping could work :-)
There should be no subtype relationship between Int8 and Word8 in either direction, because they denote different things: numbers and encodings respectively.
I hope we are not misunderstood. Word8 in GHC is an integer type representing values 0..255. It is definitely a number, in the same sense as Int8. Only their ranges are not contained in one another.
If Word8 literals are required, as opposed to terms like fromEnum 10, they should have some other appearance like 10W.
And you are saying that your proposal is less ugly than the current state? :-)
I'd be very cautious about putting Double into any subtype relationship at all, because its meaning is tied back into its representation.
But people need to use floating point literals! Each Double is representable as Rational. Your proposal thus lets 0.125 be typed as Double, which can be implicitly coerced to Rational when needed. What about 0.1? It would lose precision when going to Rational through Double. OTOH it should definitely be allowed as a Double value too. How would you allow 0.1 to be used as either Rational or Double?
If you can't explain that "every X is a Y" without referring to representation issues, you shouldn't be declaring X as a subtype of Y!
That's why subtypes are not a right tool for typing numeric literals :-) (Assuming that they can fit Haskell at all.) -- Marcin 'Qrczak' Kowalczyk

On Thu, 19 Oct 2000, Marcin 'Qrczak' Kowalczyk wrote:
- Adding a subtype elsewhere may make a program ambiguous. (Well, it is so with classes too, but at least it occurs only for overlapping instances, not unrelated subtypes of a generic type.)
For example adding two unrelated subtypes of Int16 disallows using 1234 as a value of type Integer! -- Marcin 'Qrczak' Kowalczyk

Marcin 'Qrczak' Kowalczyk writes:
[...]
Why it is bad:
I appreciate your objections, and will bear them in mind, but if my hopes are going to be dashed, I'd rather it were done by one of the issues I see as bigger: - How can we infer types like `(0==) :: Subtype Int a => a -> Bool' ? - What is F^{omega}_{<=} and am I trying to reinvent it and what makes it so hard to implement? Feel free to call me a chicken for not answering your individual points... yet. :-)
[...]
There should be no subtype relationship between Int8 and Word8 in either direction, because they denote different things: numbers and encodings respectively.
I hope we are not misunderstood. Word8 in GHC is an integer type representing values 0..255. It is definitely a number, in the same sense as Int8. Only their ranges are not contained in one another.
My mistake. Thanks for the clarification.
If Word8 literals are required, as opposed to terms like fromEnum 10, they should have some other appearance like 10W.
And you are saying that your proposal is less ugly than the current state? :-)
Joking aside, yes, it may make the overall state even more beautiful. Regards, Tom
participants (3)
-
Marcin 'Qrczak' Kowalczyk
-
qrczak@knm.org.pl
-
Tom Pledger