Syntax extensions (was: RE: The Future of Haskelldiscussionatthe Haskell Workshop)

nilsson at cs.yale.edu nilsson at cs.yale.edu
Wed Sep 17 12:52:09 EDT 2003


> Looks fine to me.  A few things to think about:
> 
>   - Some of the keywords specify an entire language (eg. Haskell98),
>     whereas some are language modifiers (eg. FFI).  We might want
>    to make a distinction.  Currently GHC supports only Haskell98 +
>     modifiers.

Yes.

>   - Are extensions always additive?

Presumably not.

> Are there any extensions which are incompatible?

Presumably yes. That's what I menat by "if compatible".
Thiese issues needs to be clearly specified and agreed upon, of course.

>  - There are features you might want to *disable*.  eg.
>    GHC lets you turn off the monomorphism restriction.
> 
> Perhaps something like this:
>
>  {-# LANGUAGE Haskell98 +FFI -MonomorphismRestriction #-}

Nice!

Hopefully, a common extended Haskell, supported by all major Haskell
systems and including features that are very commonly used, can then be
understood (for example) as follows:

    Haskell03 = Haskell98 +MPTC +FunctionalDependences +RankNPolymorphism
                          -MonomorphismRestriction

Thus,

    {-# LANGUAGE Haskell03 #-}

would mean the same as

    {-# LANGUAGE Haskell98 +MPTC +FunctionalDependences +RankNPolymorphism
                           -MonomorphismRestriction #-}

saving typing in the common case.

/Henrik

-- 
Henrik Nilsson
Yale University
Department of Computer Science
nilsson at cs.yale.edu


More information about the Haskell mailing list