Export lists in modules

Malcolm Wallace Malcolm.Wallace at cs.york.ac.uk
Thu Feb 23 08:53:17 EST 2006


Bulat Ziganshin <bulat.ziganshin at gmail.com> wrote:

> MW> With my proposal, you would simply replace the
> MW> implicit "import Prelude" with an explicit "import
> MW> Prelude.Standard"
> 
> import Prelude ($)
> can't solve this problem?

One of the problems with the current mechanism for overriding Prelude
definitions, is that every module that /uses/ such an entity must
also explicitly hide the original Prelude:

    module NewMap (map) where
    import Prelude ()
    map = ...

    module User where
    import Prelude hiding (map)
    import NewMap

By forcing the H' Prelude to be explicit by default, it removes this
nuisance.  Instead, you just change which Prelude you import.

    module Prelude.NewMap (module Prelude.Haskell98, map) where
    import Prelude.Haskell98 hiding (map)
    map = ...

    module User where
    import Prelude.NewMap

Note that, my suggestion is that compilers which continue to support the
Haskell'98 language will continue to give you the original implicit
Prelude in that mode.  It is only Haskell-prime programs that would be
affected.  Yes, many trivial programs would acquire one extra import
decl - is that such a big deal?

Especially for beginners, I'm thinking that some teachers might /prefer/
to remove lots of the current Prelude, and build up students' knowledge
gradually, by allowing them to write map, fold, curry, etc for
themselves, without name clashes.  Later, they could "switch on" more
of the language, like numeric classes, by need.

Regards,
    Malcolm


More information about the Haskell-prime mailing list