[Haskell-cafe] Updating the Haskell Standard

Brian Smith brianlsmith at gmail.com
Thu Jul 21 17:41:20 EDT 2005


On 7/20/05, John Goerzen <jgoerzen at complete.org> wrote:
> There was a brief discussion on #haskell today about the Haskell
> standard.  I'd like to get opinions from more people, and ask if there
> is any effort being done in this direction presently.
> 
> I think an updated standard is overdue.  I find it difficult anymore to
> write any but the most trivial of programs using pure Haskell 98.  Some
> notable, and widely-used, features developed since then include:
> 
>  * Overlapping instances
>  * FFI
>  * Hierarchical namespace
>  * Undecidable instances

Even if "undecidable instances" was standardized, would we want it
turned on by default? I am trying to write "real" programs in Haskell
and I have never even comtemplated using undecidable instances.

My understanding is that they can be unintuitve, and they can cause
typechecking to fail to halt. So, it seems reasonable to require that
undecidable instances require some kind of option to be present. Thus,
there would be a standard "undecidable instances" option or pragma.

Now, it seems reasonable that, if we can standardize the option for
undecidable instances, we could do the same thing for all new features
we wish to add to Haskell 2. This is basically what the Cabal {-#
LANGUAGE UndecidableInstances CPP PatternGuards ... #-} pragma does.

Each implementation would have a set of pragmas that it supports. It
would be best if the implementors agree on a specification for each
feature, so that, e.g.  "-# LANGUAGE UndecidableInstances #-} works
identically wherever it is supported.

Eventually, we would all look around at each other and realize "hey,
GHC, Hugs, and NHC all support pragmas A, B, C, ... and these pragmas
are so useful they should be available by default" Then, we could make
a new option:
    {-# LANGUAGE Haskell 2005 #-}
This would be equivalent to {-# LANGUAGE A B C ... #-}. Then, we would
say that, if {-# LANGUAGE Haskell x #-} is omitted, then x defaults to
"98."

Note that this works for deletions too {-# LANGUAGE No<DeletedFeature> #-}.

I imagine something similar would work for libraries: every
implementation would build up a set of libraries its supports by
default. We would recognize the common set of packages supported and
say "this set of packages is the Haskell 2005 standard library."

The bad thing about this is that "Hellow World, Haskell 2005" would
become kind of ugly:
{-# LANGUAGE Haskell 2005 #-}
main = putStrLn "Hello, World!"

But, of course, Haskell 2005 would be backwards compatible enough to
support the 98 version:
main = putStrLn "Hello, World!"

I guess there must be some reason that this scheme is really horrible
because I don't know of any language that has ever done things this
way. But, it seems to make sense to me...

- Brian


More information about the Haskell-Cafe mailing list