On 20-May-2000, Simon Peyton-Jones <[EMAIL PROTECTED]> wrote:
> 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.
...
> 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?

I like this proposal.  I'm not rapt about the particular syntax you've
chosen for it, though.  I think I'd prefer something that was part
of the language syntax proper, rather than a pragma.  Perhaps

        module M where
        import Prelude ()
        import syntax MyPrelude

where `syntax' here would be treated as a special-id (like `qualified')?

Or how about just

        module M where
        import prelude MyPrelude

?

> That module had jolly well better export all the things
> needed to support special syntax (which we'd need to enumerate). 

It may be best to check that requirement lazily: the module would only
be _required_ to export the things needed for those parts of the
syntax which the importing module actually uses.  This would make it
easier to develop an alternative prelude in a step-by-step manner.

> 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 #-}

Another alternative to this would be to simply define the `[]' and
`:' constructors as syntactic sugar for `ListNil' and `ListCons', and to
define the `[]' list type constructor as just syntactic sugar for `ListType'.
The list type could then by defined in the Prelude using ordinary Haskell
syntax:
        data ListType t = ListNil | ListCons t (ListType t)
Then these symbols could be mentioned in import and export lists using
the existing syntax.

I don't have any particular preference as to which of those two solutions
is adopted, but I thought the alternative worth mentioning.

-- 
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