RE: Primitive types and Prelude shenanigans

2001-02-28 Thread Simon Peyton-Jones

| Why not just let
| 
|   if x then y else z
| 
| be syntactic sugar for
| 
|   Prelude.ifThenElse x y z

The burden of my original message was that
a) this is reasonable, but
b) it would have to become the *defined behaviour*

As you say, the "defined behaviour" would have to cover
guards as well, and I'm not absolutely certain what else.

The way GHC is set up now, it's relatively easy to make such
changes (this wasn't true before).  But it takes some design work.  

If someone cares enough
to do the design work, and actively wants the result, I'll see how
hard it is to implement.

Simon


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Primitive types and Prelude shenanigans

2001-02-27 Thread Dylan Thurston

On Fri, Feb 16, 2001 at 05:13:10PM +, Marcin 'Qrczak' Kowalczyk wrote:
 Fri, 16 Feb 2001 04:14:24 -0800, Simon Peyton-Jones [EMAIL PROTECTED] pisze:
  Here I think the right thing is to say that desugaring for boolean
  constructs uses a function 'if' assumed to have type
  if :: forall b. Bool - b - b - b
 
 What if somebody wants to make 'if' overloaded on more types than
 some constant type called Bool?
 
 class Condition a where
 if :: a - b - b - b

(Note that Hawk does almost exactly this.)

 Generally I don't feel the need of allowing to replace if, Bool and
 everything else with custom definitions, especially when there is no
 single obvious way.

Why not just let

  if x then y else z

be syntactic sugar for

  Prelude.ifThenElse x y z

when some flag is given?  That allows a Prelude hacker to do whatever
she wants, from the standard

  ifThenElse :: Bool - x - x - x
  ifThenElse True x _ = x
  ifThenElse True _ y = y

to something like

  class (Boolean a) = Condition a b where
 ifThenElse :: a - b - b - b

("if" is a keyword, so cannot be used as a function name.  Hawk uses
"mux" for this operation.)

Compilers are good enough to inline the standard definition (and
compile it away when appropriate), right?

Pattern guards can be turned into "ifThenElse" as specified in section
3.17.3 of the Haskell Report.  Or maybe there should be a separate
function "evalGuard", which is ordinarily of type
  evalGuard :: [(Bool, a)] - a - a
(taking the list of guards and RHS, together with the default case).

It's less clear that compilers would be able to produce good code in
this case.

But this would have to be changed:

  An alternative of the form

pat - exp where decls

  is treated as shorthand for:

pat | True - exp where decls

Best,
Dylan Thurston

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Primitive types and Prelude shenanigans

2001-02-21 Thread Fergus Henderson

On 21-Feb-2001, Marcin 'Qrczak' Kowalczyk [EMAIL PROTECTED] wrote:
 Wed, 21 Feb 2001 12:55:37 +1100, Fergus Henderson [EMAIL PROTECTED] pisze:
 
  The documentation in the Haskell report does not say what
  `fromInteger' should do for `Int', but the Hugs behaviour definitely
  seems preferable, IMHO.
 
 Sometimes yes. But for playing with Word8, Int8, CChar etc. it's
 sometimes needed to just cast bits without overflow checking, to
 convert between "signed bytes" and "unsigned bytes".

Both are desirable in different situations.  But if you want to ignore
overflow, you should have to say so explicitly.  `fromInteger' is
implicitly applied to literals, and implicit truncation is dangerous,
so `fromInteger' should not truncate.

There should be a different function for conversions that silently
truncate.  You can implement such a function yourself, of course,
e.g. as follows:

trunc :: (Bounded a, Integral a) = Integer - a
trunc x = res
   where min, max, size, modulus, result :: Integer
 min = toInteger (minBound `asTypeOf` res)
 max = toInteger (maxBound `asTypeOf` res)
 size = max - min + 1
 modulus = x `mod` size
 result = if modulus  max then modulus - size else modulus
 res = fromInteger result

But it is probably worth including something like this in the standard
library, perhaps as a type class method.

-- 
Fergus Henderson [EMAIL PROTECTED]  |  "I have always known that the pursuit
|  of excellence is a lethal habit"
WWW: http://www.cs.mu.oz.au/~fjh  | -- the last words of T. S. Garp.

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Primitive types and Prelude shenanigans

2001-02-16 Thread William Lee Irwin III

William Lee Irwin III [EMAIL PROTECTED] pisze:
  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 +, 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 [EMAIL PROTECTED] pisze:
 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 +, 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 +, 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 +, 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

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Primitive types and Prelude shenanigans

2001-02-16 Thread Marcin 'Qrczak' Kowalczyk

Fri, 16 Feb 2001 04:14:24 -0800, Simon Peyton-Jones [EMAIL PROTECTED] pisze:

 [Incidentally, if this is nhc's behaviour, it's not H98.
 The Report (tries to) stress that you get the "fromInt from the actual
 standard Prelude" regardless of what is in scope.  That's why I'm not
 going to make it the default behaviour.]

But is mere -fglasgow-exts enough to enable it?

BTW: fromInt is not H98. However when a compiler uses fromInt instead
of fromInteger where the number fits, with a suitable default method
for fromInt which is not exported from Prelude, then no program can
tell the difference, so it's OK. Unfortunately integer literals cannot
expand to Prelude.fromInt, because Prelude does not export fromInt!

Currently ghc extension flags can have no effect on module imports,
so if fromInt is not visible in standard mode, it will not visible
in extended mode either. In such case these two extensions (Prelude
substitution and using fromInt for integer literals) are incompatible.

 Marcin suggests that 'if' is just syntactic sugar.  But that would
 be a disaster if the new Bool type didn't have constructors True
 and False.

Correction: it would be a disaster when there are no Prelude.True
and Prelude.False constructors of the same type. It needs not to be
called Bool if the desugaring rule does not say so.

 Here I think the right thing is to say that desugaring for boolean
 constructs uses a function 'if' assumed to have type
 if :: forall b. Bool - b - b - b

What if somebody wants to make 'if' overloaded on more types than
some constant type called Bool?

class Condition a where
if :: a - b - b - b

Generally I don't feel the need of allowing to replace if, Bool and
everything else with custom definitions, especially when there is no
single obvious way.

-- 
 __("  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTPCZA
QRCZAK


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Primitive types and Prelude shenanigans

2001-02-16 Thread Marcin 'Qrczak' Kowalczyk

Thu, 15 Feb 2001 20:56:20 -0800, William Lee Irwin III [EMAIL PROTECTED] pisze:

   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 * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTPCZA
QRCZAK


___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Primitive types and Prelude shenanigans

2001-02-16 Thread William Lee Irwin III

William Lee Irwin III [EMAIL PROTECTED] pisze:
  literal "5" gets mapped to (fromPositiveInteger 5)
  literal "-9" gets mapped to (fromNonZeroInteger -9)

On Fri, Feb 16, 2001 at 05:42:17PM +, 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

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Primitive types and Prelude shenanigans

2001-02-15 Thread William Lee Irwin III

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 

Re: Primitive types and Prelude shenanigans

2001-02-15 Thread Fergus Henderson

On 15-Feb-2001, William Lee Irwin III [EMAIL PROTECTED] wrote:
 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 [EMAIL PROTECTED]  |  "I have always known that the pursuit
|  of excellence is a lethal habit"
WWW: http://www.cs.mu.oz.au/~fjh  | -- the last words of T. S. Garp.

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



RE: Primitive types and Prelude shenanigans

2001-02-14 Thread Simon Peyton-Jones

| 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

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe