RE: Primitive types and Prelude shenanigans

| On Mon, Feb 12, 2001 at 02:38:25PM -0800, William Lee Irwin III wrote: | > I had in mind looking within the compiler, actually. Where in the | > compiler? It's a big program, it might take me a while to do an | > uninformed search. I've peeked around a little bit and not gotten | > anywhere. | | If anyone else is pursuing thoughts along the same lines as I | am (and I | have suspicions), TysWiredIn.lhs appears quite relevant to the set of | primitive data types, though there is no obvious connection to the | module issue (PrelBase.Bool vs. Foo.Bool). PrelMods.lhs | appears to shed | more light on that issue in particular. $TOP/ghc/compiler/prelude/ was | the gold mine I encountered. Perhaps I should add something here. I'm very sympathetic to the idea of making it possible to do entirely without the standard Prelude, and to substitute a Prelude of one's own. The most immediate and painful stumbling block in Haskell 98 is that numeric literals, like 3, turn into (Prelude.fromInt 3), where "Prelude.fromInt" really means "the fromInt from the standard Prelude" regardless of whether the standard Prelude is imported scope. Some while ago I modified GHC to have an extra runtime flag to let you change this behaviour. The effect was that 3 turns into simply (fromInt 3), and the "fromInt" means "whatever fromInt is in scope". The same thing happens for - numeric patterns - n+k patterns (the subtraction is whatever is in scope) - negation (you get whatever "negate" is in scope, not Prelude.negate) (Of course, this is not Haskell 98 behaviour.) I think I managed to forget to tell anyone of this flag. And to my surprise I can't find it any more! But several changes I made to make it easy are still there, so I'll reinstate it shortly. That should make it easy to define a new numeric class structure. So much for numerics. It's much less obvious what to do about booleans. Of course, you can always define your own Bool type. But we're going to have to change the type that if-then-else uses, and presumably guards too. Take if-then-else. Currently it desugars to case e of True -> then-expr False -> else-expr but your new boolean might not have two constructors. So maybe we should simply assume a function if :: Bool -> a -> a -> a and use that for both if-then-else and guards.... I wonder what else? For example, can we assume that f x | otherwise = e is equivalent to f x = e That is, "otherwise" is a guard that is equivalent to the boolean "true" value. ("otherwise" might be bound to something else if you import a non-std Prelude.) If we don't assume this, we may generate rather bizarre code: f x y | x==y = e1 | otherwise = e2 ===> f x y = if (x==y) e1 (if otherwise e2 (error "non-exhaustive patterns for f")) And we'll get warnings from the pattern-match compiler. So perhaps we should guarantee that (if otherwise e1 e2) = e1. You may say that's obvious, but the point is that we have to specify what can be assumed about an alien Prelude. Matters get even more tricky if you want to define your own lists. There's quite a lot of built-in syntax for lists, and type checking that goes with it. Last time I thought about it, it made my head hurt. Tuples are even worse, because they constitute an infinite family. The bottom line is this. a) It's desirable to be able to substitute a new prelude b) It's not obvious exactly what that should mean c) And it may not be straightforward to implement It's always hard to know how to deploy finite design-and-implementation resources. Is this stuff important to a lot of people? If you guys can come up with a precise specification for (b), I'll think hard about how hard (c) really is. Simon

Wed, 14 Feb 2001 14:19:39 -0800, Simon Peyton-Jones
Some while ago I modified GHC to have an extra runtime flag to let you change this behaviour. The effect was that 3 turns into simply (fromInt 3), and the "fromInt" means "whatever fromInt is in scope".
Wasn't that still fromInteger?
I think I managed to forget to tell anyone of this flag.
I remember that it has been advertised.
And to my surprise I can't find it any more!
Me neither. But it's still documented. It must have been list during some branch merging I guess. May I propose an alternative way of specifying an alternative Prelude? Instead of having a command line switch, let's say that 3 always means Prelude.fromInteger 3 - for any *module Prelude* which is in scope! That is, one could say: import Prelude () import MyPrelude as Prelude IMHO it's very intuitive, contrary to -fno-implicit-prelude flag. I see only one problem with that: inside the module MyPrelude it is not visible as Prelude yet. But it's easy to fix. Just allow a module to import itself! module MyPrelude where import Prelude as P import MyPrelude as Prelude Now names qualified with Prelude refer to entities defined in this very module, including implicit Prelude.fromInteger. I don't know if such self-import should hide MyPrelude qualification or not. I guess it should, similarly as explicit import of Prelude hides its implicit import. That is, each module implicitly imports itself, unless it imports itself explicitly (possibly under a different name) - same as for Prelude.
So much for numerics. It's much less obvious what to do about booleans.
IMHO a natural generalization (not necessarily useful) is to follow the definition of the 'if' syntactic sugar literally. 'if' expands to the appropriate 'case'. So Prelude.True and Prelude.False must be defined, and they must have the same type (otherwise we get a type error each time we use 'if'). This would allow even data FancyBool a = True | False | DontKnow a The main problem is probably the current implementation: syntactic sugar like 'if' is typechecked prior to desugaring. The same problem is with the 'do' notation. But I don't see conceptual dilemmas.
For example, can we assume that f x | otherwise = e is equivalent to f x = e
We should not need this information except for performance and warnings. Semantically otherwise is just a normal variable. So it does not matter much. Non-standard 'otherwise' is the same as currently would be foo :: Bool foo = True The compiler could be improved by examining the unfolded definition for checking whether to generate warnings, instead of relying on special treatment of the particular qualified name. -- __("< Marcin Kowalczyk * qrczak@knm.org.pl http://qrczak.ids.net.pl/ \__/ ^^ SYGNATURA ZASTÊPCZA QRCZAK

Simon Peyton-Jones wrote: | I'm very sympathetic to the idea of making it possible | to do entirely without the standard Prelude, and to | substitute a Prelude of one's own. I think this is a very good idea. | Some while ago I modified GHC to have an extra runtime | flag to let you change this behaviour. The effect was | that 3 turns into simply (fromInt 3), and the | "fromInt" means "whatever fromInt is in scope". Hmmm... so how about: foo fromInt = 3 Would this translate to: foo f = f 3 ? How about alpha renaming? | [...] guarantee that (if otherwise e1 e2) = e1. I do not understand this. "otherwise" is simply a function name, that can be used, redefined or hidden, by anyone. It is not used in any desugaring. Why change that behaviour? | It's always hard to know how to deploy finite | design-and-implementation resources. Is this stuff | important to a lot of people? I think it is important to define a minimalistic Prelude, so that people at least know what is standard and what is not. Try to put everything else in modules. /Koen. -- Koen Claessen http://www.cs.chalmers.se/~koen phone:+46-31-772 5424 mailto:koen@cs.chalmers.se ----------------------------------------------------- Chalmers University of Technology, Gothenburg, Sweden

On Wed, Feb 14, 2001 at 02:19:39PM -0800, Simon Peyton-Jones wrote:
The most immediate and painful stumbling block in Haskell 98 is that numeric literals, like 3, turn into (Prelude.fromInt 3), where "Prelude.fromInt" really means "the fromInt from the standard Prelude" regardless of whether the standard Prelude is imported scope.
Some while ago I modified GHC to have an extra runtime flag to let you change this behaviour. The effect was that 3 turns into simply (fromInt 3), and the "fromInt" means "whatever fromInt is in scope". The same thing happens for - numeric patterns - n+k patterns (the subtraction is whatever is in scope) - negation (you get whatever "negate" is in scope, not Prelude.negate)
For the idea for numeric literals I had in mind (which is so radical I don't intend to seek much, if any help in implementing it other than general information), even this is insufficient. Some analysis of the value of the literal would need to be incorporated so that something like the following happens: literal "0" gets mapped to zero :: AdditiveMonoid t => t literal "1" gets mapped to one :: MultiplicativeMonoid t => t literal "5" gets mapped to (fromPositiveInteger 5) literal "-9" gets mapped to (fromNonZeroInteger -9) literal "5.0" gets mapped to (fromPositiveReal 5.0) literal "-2.0" gets mapped to (fromNonZeroReal -2.0) literal "0.0" gets mapped to (fromReal 0.0) etc. A single fromInteger or fromIntegral won't suffice here. The motivation behind this is so that some fairly typical mathematical objects (multiplicative monoid of nonzero integers, etc.) can be directly represented by numerical literals (and primitive types). I don't for a minute think this is suitable for general use, but I regard it as an interesting (to me) experiment. On Wed, Feb 14, 2001 at 02:19:39PM -0800, Simon Peyton-Jones wrote:
(Of course, this is not Haskell 98 behaviour.) I think I managed to forget to tell anyone of this flag. And to my surprise I can't find it any more! But several changes I made to make it easy are still there, so I'll reinstate it shortly. That should make it easy to define a new numeric class structure.
It certainly can't hurt; even if the code doesn't help directly with my dastardly plans, examining how the handling of overloaded literals differs will help me understand what's going on. On Wed, Feb 14, 2001 at 02:19:39PM -0800, Simon Peyton-Jones wrote:
So much for numerics. It's much less obvious what to do about booleans. Of course, you can always define your own Bool type. But we're going to have to change the type that if-then-else uses, and presumably guards too. Take if-then-else. Currently it desugars to case e of True -> then-expr False -> else-expr but your new boolean might not have two constructors. So maybe we should simply assume a function if :: Bool -> a -> a -> a and use that for both if-then-else and guards.... I wonder what else?
I had in mind that there might be a class of suitable logical values corresponding to the set of all types suitable for use as such. As far as I know, the only real restriction on subobject classifiers for logical values is that it be a pointed set where the point represents truth. Even if it's not the most general condition, it's unlikely much can be done computationally without that much. So since we must be able to compare logical values to see if they're that distinguished truth value: \begin{pseudocode} class Eq lv => LogicalValue lv where definitelyTrue :: lv \end{pseudocode}
From here, ifThenElse might be something like:
\begin{morepseudocode} ifThenElse :: LogicalValue lv => lv -> a -> a -> a ifThenElse isTrue thenValue elseValue = case isTrue == definitelyTrue of BooleanTrue -> thenValue _ -> elseValue \end{morepseudocode} or something on that order. The if/then/else syntax is really just a combinator like this with a mixfix syntax, and case is the primitive, so quite a bit of flexibility is possible given either some "hook" the mixfix operator will use or perhaps even means for defining arbitrary mixfix operators. (Of course, a hook is far easier.) The gains from something like this are questionable, but it's not about gaining anything for certain, is it? Handling weird logics could be fun. On Wed, Feb 14, 2001 at 02:19:39PM -0800, Simon Peyton-Jones wrote: [interesting example using otherwise in a pattern guard elided]
And we'll get warnings from the pattern-match compiler. So perhaps we should guarantee that (if otherwise e1 e2) = e1.
I'm with you on this, things would probably be too weird otherwise. On Wed, Feb 14, 2001 at 02:19:39PM -0800, Simon Peyton-Jones wrote:
You may say that's obvious, but the point is that we have to specify what can be assumed about an alien Prelude.
There is probably a certain amount of generality that would be desirable to handle, say, Dylan Thurston's prelude vs. the standard prelude. I'm willing to accept compiler hacking as part of ideas as radical as mine. Some reasonable assumptions: (1) lists are largely untouchable (2) numeric monotypes present in the std. prelude will also be present (3) tuples probably won't change (4) I/O libs will probably not be toyed with much (monads are good!) (5) logical values will either be a monotype or a pointed set class (may be too much to support more than a monotype) (6) relations (==), (<), etc. will get instances on primitive monotypes (7) Read and Show probably won't change much (8) Aside from perhaps Arrows, monads probably won't change much (Arrows should be able to provide monad compatibility) (9) probably no one will try to alter application syntax to operate on things like instances of class Applicable (10) the vast majority of the prelude changes desirable to support will have to do with the numeric hierarchy These are perhaps not a terribly useful set of assumptions. On Wed, Feb 14, 2001 at 02:19:39PM -0800, Simon Peyton-Jones wrote:
Matters get even more tricky if you want to define your own lists. There's quite a lot of built-in syntax for lists, and type checking that goes with it. Last time I thought about it, it made my head hurt. Tuples are even worse, because they constitute an infinite family.
The only ideas I have about lists are maybe to reinstate monad comprehensions. As far as tuples go, perhaps a derived or automagically defined Functor (yes, I know it isn't derivable now) instance and other useful instances (e.g. AdditiveMonoid, PointedSet, other instances where distinguished elements etc. cannot be written for the infinite number of instances required) would have interesting consequences if enough were cooked up to bootstrap tuples in a manner polymorphic in the dimension (fillTuple :: Tuple t => (Natural -> a) -> t a ?, existential tuples?) Without polytypism or some other mechanism for defining instances on these infinite families of types, achieving the same effect(s) would be difficult outside of doing it magically in the compiler. Neither looks easy to pull off in any case, so I'm wary of these ideas. On Wed, Feb 14, 2001 at 02:19:39PM -0800, Simon Peyton-Jones wrote:
The bottom line is this. a) It's desirable to be able to substitute a new prelude b) It's not obvious exactly what that should mean c) And it may not be straightforward to implement
It's always hard to know how to deploy finite design-and-implementation resources. Is this stuff important to a lot of people? If you guys can come up with a precise specification for (b), I'll think hard about how hard (c) really is.
I think Dylan Thurston's proposal is probably the best starting point for something that should really get support. If other alternatives in the same vein start going around, I'd think supporting them would also be good, but much of what I have in mind is probably beyond reasonable expectations, and will probably not get broadly used. Cheers, Bill

On 15-Feb-2001, William Lee Irwin III
Some reasonable assumptions:
I disagree about the reasonableness of many of your assumptions ;-)
(1) lists are largely untouchable
I want to be able to write a Prelude that has lists as a strict data type, rather than a lazy data type.
(4) I/O libs will probably not be toyed with much (monads are good!) (5) logical values will either be a monotype or a pointed set class (may be too much to support more than a monotype)
I think that that replacing the I/O libs is likely to be a much more useful and realistic proposition than replacing the boolean type.
(9) probably no one will try to alter application syntax to operate on things like instances of class Applicable
That's a separate issue; you're talking here about a language extension, not just a new Prelude.
(10) the vast majority of the prelude changes desirable to support will have to do with the numeric hierarchy
s/numeric hierarchy/class hierarchy/
--
Fergus Henderson

Thu, 15 Feb 2001 20:56:20 -0800, William Lee Irwin III
literal "0" gets mapped to zero :: AdditiveMonoid t => t literal "1" gets mapped to one :: MultiplicativeMonoid t => t literal "5" gets mapped to (fromPositiveInteger 5) literal "-9" gets mapped to (fromNonZeroInteger -9)
Actually -9 gets mapped to negate (fromInteger 9). At least in theory, because in ghc it's fromInteger (-9) AFAIK.
The motivation behind this is so that some fairly typical mathematical objects (multiplicative monoid of nonzero integers, etc.) can be directly represented by numerical literals (and primitive types).
I am definitely against it, especially the zero and one case. When one can write 1, he should be able to write 2 too obtaining the same type. It's not hard to write zero and one. What next: 0 for nullPtr and []? Moreover, the situation where each integer literal means applied fromInteger is simple to understand, remember and use. I don't want to define a bunch of operations for the same thing. Please keep Prelude's rules simple. -- __("< Marcin Kowalczyk * qrczak@knm.org.pl http://qrczak.ids.net.pl/ \__/ ^^ SYGNATURA ZASTÊPCZA QRCZAK

On Fri, Feb 16, 2001 at 05:14:14PM +1100, Fergus Henderson wrote:
I disagree about the reasonableness of many of your assumptions ;-)
Great! =)
On 15-Feb-2001, William Lee Irwin III
(1) lists are largely untouchable
On Fri, Feb 16, 2001 at 05:14:14PM +1100, Fergus Henderson wrote:
I want to be able to write a Prelude that has lists as a strict data type, rather than a lazy data type.
Hmm, sounds like infinite lists might have trouble there, but I hereby
cast out that assumption.
On 15-Feb-2001, William Lee Irwin III
(4) I/O libs will probably not be toyed with much (monads are good!) (5) logical values will either be a monotype or a pointed set class (may be too much to support more than a monotype)
On Fri, Feb 16, 2001 at 05:14:14PM +1100, Fergus Henderson wrote:
I think that that replacing the I/O libs is likely to be a much more useful and realistic proposition than replacing the boolean type.
I won't pretend for an instant that replacing the Boolean type will
be remotely useful to more than a handful of people.
On 15-Feb-2001, William Lee Irwin III
(9) probably no one will try to alter application syntax to operate on things like instances of class Applicable
On Fri, Feb 16, 2001 at 05:14:14PM +1100, Fergus Henderson wrote:
That's a separate issue; you're talking here about a language extension, not just a new Prelude.
I'm not sure one would have to go that far (though I'm willing to be
convinced), but either way, we need not concern ourselves.
On 15-Feb-2001, William Lee Irwin III
(10) the vast majority of the prelude changes desirable to support will have to do with the numeric hierarchy
On Fri, Feb 16, 2001 at 05:14:14PM +1100, Fergus Henderson wrote:
s/numeric hierarchy/class hierarchy/
I suppose I was trying to narrow it down as far as possible, but if people really are touching every place in the class hierarchy, then I can't do better than that. Cheers, Bill

William Lee Irwin III
literal "0" gets mapped to zero :: AdditiveMonoid t => t literal "1" gets mapped to one :: MultiplicativeMonoid t => t literal "5" gets mapped to (fromPositiveInteger 5) literal "-9" gets mapped to (fromNonZeroInteger -9)
On Fri, Feb 16, 2001 at 08:09:58AM +0000, Marcin 'Qrczak' Kowalczyk wrote:
Actually -9 gets mapped to negate (fromInteger 9). At least in theory, because in ghc it's fromInteger (-9) AFAIK.
Sorry I was unclear about this, I had in mind that in the scheme I was
going to implement that the sign of the literal value would be discerned
and negative literals carried to fromNonZeroInteger (-9) etc.
William Lee Irwin III
The motivation behind this is so that some fairly typical mathematical objects (multiplicative monoid of nonzero integers, etc.) can be directly represented by numerical literals (and primitive types).
On Fri, Feb 16, 2001 at 08:09:58AM +0000, Marcin 'Qrczak' Kowalczyk wrote:
I am definitely against it, especially the zero and one case. When one can write 1, he should be able to write 2 too obtaining the same type. It's not hard to write zero and one.
The real hope here is to get the distinct zero and one for things that are already traditionally written that way, like the multiplicative monoid of nonzero integers or the additive monoid of natural numbers. Another implication I view as beneficial is that the 0 (and 1) symbols can be used in vector (and perhaps matrix) contexts without the possibility that other integer literals might be used inadvertantly. On Fri, Feb 16, 2001 at 08:09:58AM +0000, Marcin 'Qrczak' Kowalczyk wrote:
What next: 0 for nullPtr and []?
It's probably good to point out that this scheme is "permissive" enough, or more specifically, allows enough fine-grained expressiveness to allow the symbol to be overloaded for address types on which arithmetic is permitted, and lists under their natural monoid structure, which I agree is aesthetically displeasing at the very least, and probably undesirable to allow by default. On Fri, Feb 16, 2001 at 08:09:58AM +0000, Marcin 'Qrczak' Kowalczyk wrote:
Moreover, the situation where each integer literal means applied fromInteger is simple to understand, remember and use. I don't want to define a bunch of operations for the same thing. Please keep Prelude's rules simple.
I don't think this sort of scheme is appropriate for a standard Prelude either, though I do think it's interesting to me, and perhaps others. I don't mean to give the impression that I'm proposing this for inclusion in any sort of standard Prelude. It's a more radical point in the design space that I am personally interested in exploring both to discover its implications for programming (what's really awkward, what things become convenient, etc.), and to acquaint myself with the aspects of the compiler pertinent to the handling of primitive types. Cheers, Bill

Thu, 15 Feb 2001 20:56:20 -0800, William Lee Irwin III
literal "5" gets mapped to (fromPositiveInteger 5) literal "-9" gets mapped to (fromNonZeroInteger -9)
Note that when a discussed generic Prelude replacement framework is done, and ghc's rules are changed to expand -9 to negate (fromInteger 9) instead of fromInteger (-9), then you don't need uglification of the fromInteger function to be able to define types with only nonnegative numeric values. Just define your negate in an appropriate class, different from the fromInteger's class. -- __("< Marcin Kowalczyk * qrczak@knm.org.pl http://qrczak.ids.net.pl/ \__/ ^^ SYGNATURA ZASTÊPCZA QRCZAK

William Lee Irwin III
literal "5" gets mapped to (fromPositiveInteger 5) literal "-9" gets mapped to (fromNonZeroInteger -9)
On Fri, Feb 16, 2001 at 05:42:17PM +0000, Marcin 'Qrczak' Kowalczyk wrote:
Note that when a discussed generic Prelude replacement framework is done, and ghc's rules are changed to expand -9 to negate (fromInteger 9) instead of fromInteger (-9), then you don't need uglification of the fromInteger function to be able to define types with only nonnegative numeric values. Just define your negate in an appropriate class, different from the fromInteger's class.
Good point, the canonical injection from the positive integers into the various supersets (with structure) thereof handles it nicely. I foresee: fromPositiveInteger :: ContainsPositiveIntegers t => PositiveInteger -> t instance ContainsPositiveIntegers Integer where ... instance AdditiveGroup Integer where ... negate :: AdditiveGroup t => t -> t {- this seems natural, but see below -} fromPositiveInteger 5 :: ContainsPositiveIntegers t => t negate $ fromPositiveInteger 5 :: (AdditiveGroup t, ContainsPositiveIntegers t) => t which is not exactly what I want (and could probably use some aesthetic tweaking); I had in mind that negative integers would somehow imply a ContainsNonZeroIntegers or ContainsAllIntegers instance or the like. The solution actually imposes a rather natural instance (though one which could cause overlaps): instance (AdditiveGroup t, ContainsPositiveIntegers t) => ContainsAllIntegers t where ... I suppose one big wrinkle comes in when I try to discuss negation in the multiplicative monoid of nonzero integers. That question already exists without the Prelude's altered handling of negative literals. negate . fromInteger $ n just brings it immediately to the surface. 0 and 1 will still take some work, but I don't expect help with them. Thanks for the simplification! Cheers, Bill
participants (5)
-
Fergus Henderson
-
Koen Claessen
-
qrczak@knm.org.pl
-
Simon Peyton-Jones
-
William Lee Irwin III