On 19-May-2000, S.D.Mechveliani <[EMAIL PROTECTED]> wrote:
> I wonder how to make the user prelude  BPrelude  to replace
>                          2 + x  :: T
> 
> with          (Additive.fromInteger 2 :: T) + x
> rather than   (Num.fromInteger      2 :: T) + x
> ?

That seems like a quite reasonable request to me.

The Haskell 98 Report says the following:

 |    The integer literal i is equivalent to fromInteger i, where
 |    fromInteger is a method in class Num (see Section 6.4.1).

Hugs and ghc seem to interpret that as meaning

      The integer literal i is equivalent to Prelude.fromInteger i.

For the next version of Haskell, I propose changing the wording to

      The integer literal i is equivalent to fromInteger i.  Normally
      fromInteger is a method in the standard Prelude class Num (see Section
      6.4.1), but it is also possible for modules to use `import qualified
      Prelude' and then define their own fromInteger function or method,
      or import fromInteger from another module.

Likewise for fromRational.

I suppose this change would not be backwards compatible with the current Hugs/ghc
interpretation, since it would break code such as

      import qualified Prelude
      main = Prelude.print 42

However, the fix would be straightforward -- just add `import Prelude (fromInteger)'.

On the other hand, this treatment of integer literals would be
inconsistent with the treatment of some other Haskell constructs,
such as unary negation.  I guess a design decision has been made
that these constructs should always refer to the identifiers from the
standard Prelude.  But this design decision makes it very difficult
if, like S.D.Mechveliani, you want to define an alternative prelude.

For unary negation, the report effectively defines `- a' to mean
`Prelude.negate a'.  [It does so in a fairly round-about manner:

 |    The special form -e denotes prefix negation, the only prefix operator in Haskell 
 |, and is
 |    syntax for negate (e). The binary - operator does not necessarily refer to the 
 |definition
 |    of - in the Prelude; it may be rebound by the module system. However, unary - 
 |will always
 |    refer to the negate function defined in the Prelude.
 ...
 | Translation:
 | 
 |    The following identities hold:
 | 
 |    -e = negate (e)

This is somewhat ambiguous; if it is really intended that unary -
always refer to the negate function define in the Prelude, it really
ought to be written as

      The special form -e denotes prefix negation, the only prefix operator in Haskell 
, and is
      syntax for Prelude.negate (e).
                 ^^^^^^^^
 ...
   Translation:
   
      The following identities hold:
   
      -e = Prelude.negate (e)
           ^^^^^^^^

I would propose that clarification as "Haskell 98 typo", except that
to be consistent, there are a lot of other places for which similar
changes would be required.]

There is a similar issue for the treatment of if-then-else,
which is defined by the translation

 |    if e1 then e2 else e3 = case e1 of { True -> e2 ; False -> e3 }
 | 
 |    where True and False are the two nullary constructors from the type Bool,
 |    as defined in the Prelude.

Here again it is effectively defined in terms of `Prelude.True' and `Prelude.False'.
I guess in this case there is much less reason to allow this syntax to refer
to `SomeOtherModule.True' or `SomeOtherModule.False'; unlike negate and fromInteger,
there are no type classes involved, so I can't see any good reason for wanting
to redefine True and False.

There is also a similar issue for arithmetic sequences.

 |    Arithmetic sequences satisfy these identities:
 | 
 |    [ e1.. ] = enumFrom e1
 |    [ e1,e2.. ] = enumFromThen e1 e2
 |    [ e1..e3 ] = enumFromTo e1 e3
 |    [ e1,e2..e3 ] = enumFromThenTo e1 e2 e3
 | 
 |    where enumFrom, enumFromThen, enumFromTo, and enumFromThenTo are class methods in 
 |the
 |    class Enum as defined in the Prelude (see Figure 5).

Here a type class is involved, and there are some quite good reasons why one
might want to replace the Enum class when designing an alternate standard Prelude.
In particular, Double and Float are instances of Prelude.Enum, which is arguably
bad design.  Also Prelude.Enum has a method fromEnum

         fromEnum :: Enum a => a -> Int

which converts an arbitrary enumerated type to an Int.  This method is
dangerous, since for types such as Integer it might easily overflow.
So here too I would propose that the wording be changed to make it
clear that enumFrom, etc. need not be defined in the Prelude but can
instead refer to user-defined functions or methods from some other module.

Likewise there is a similar issue for the monad syntax.
One might well want to define a new monad class using advanced type
system features not present in standard Haskell in order to allow e.g.
set types with some constraint (e.g. `Ord') on the arguments to be
monads.  As Haskell currently stands there is no way to use the monad
syntax for such types, even though it would make good sense to do so.
So again, for the next version of Haskell I propose the wording
be changed to make it clear that the `>>' and `>>=' in the translation
for `do' expressions need not refer to the methods defined in the
standard Prelude.

Comments?

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

Reply via email to