Primitive types and Prelude shenanigans

William Lee Irwin III wli@holomorphy.com
Thu, 15 Feb 2001 20:56:20 -0800


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