| There's simply no valid syntax in Haskell 98 for naming
| the list type constructor (`[]') in a module import or
| export list!
| 
| Is there any particular reason for this, or is this
| just a defect in the Haskell 98 report?

First thought
~~~~~~~~~~~~~
As Malcolm pointed out:
Section 2.4, Identifiers and Operators, says (:) is a reservedop.

    Note that a colon by itself, ":", is reserved solely for use as the
    Haskell list constructor; this makes its treatment uniform with other
    parts of list syntax, such as "[]" and "[a,b]".

On reflection I think this makes sense.  Consider the type

        [Int]

The H98 report is pretty clear that this means (Prelude.[] Int)
where 'Int' means whatever 'Int' is bound to in the current scope,
but 'Prelude.[]' means 'the [] type constructor from the Standard Prelude,
regardless of whether '[]' itself is in scope, or whether plain '[]'
is actually bound to 'MyPrelude.[]' in the present scope.

Now give, that, it would be a bit odd if

        [] Int

meant something entirely different.  Similarly for tuples and suchlike.
(Int,Int) and (,) Int Int should mean the same.

So on this point, GHC is wrong, and we should fix it.  The Report says that
':' is special too.  One may argue with that, but that's what it says, and
it's consistent with treating the rest of list syntax specially.

Similarly (->) always means Prelude.->

Assuming that this position doesn't seem wholly unreasonable, can anyone
suggest a location for clarification in the H98 report, since clarification
is
clearly needed?

Second thought
~~~~~~~~~~~~~~
Of course, that doesn't solve the problem!  Sergey essentially wants to
replace the entire prelude, special syntax and all.  There are lots
of small but important things under the heading of special syntax:

        Explicit lists [a,b,c]
        List comprehensions
        Numeric constants (1 means 'fromInteger 1')
        do notation

Here is an idea for an extension to Haskell 98 to support this.  Suppose
we added a pragma, or compiler flag, that let us say where the special
syntax should come from:

        module M where
        import Prelude ()
        import {-# SYNTAX #-} MyPrelude

Here, I've expressed it as a pragma.  The idea is that wherever we have
a special syntax think, like [Int], it means 'S.[] Int', where S is
either 'Prelude' or, if there's a SYNTAX pragma, the module specified
in the pragma.  That module had jolly well better export all the things
needed
to support special syntax (which we'd need to enumerate). 

Note that if we chose to do this, we'd want the ability to have '[]' in
export lists, so that MyPrelude was able to explicitly export '[]', so that
the SYNTAX lookup would find it.  So we'd also have to extend the syntax of
import and export lists as Fergus suggests.  But this facility would only
be useful for (the) module intended to be imported with {-# SYNTAX #-}

I don't think this would be too hard to implement in GHC.  Now I think
about it, it's rather attractive. I wonder what other people think?
Perhaps {-# SYNTAX #-} is a bit noisy -- but Haskell's philosophy is
to signal very clearly when something non-Prelude is going on.

Simon

Reply via email to