[Haskell] URLs in haskell module namespace
Simon Marlow
simonmar at microsoft.com
Thu Mar 24 11:40:53 EST 2005
On 23 March 2005 13:11, Malcolm Wallace wrote:
> I think this will be trivially possible once the compilers support
> multiple versioning of packages. (Ghc may even support it already.):
>
> {-# OPTIONS -package foo-1.0 #-}
> module Old (module Foo) where
> import Foo
>
> {-# OPTIONS -package foo-2.2 #-}
> module New (module Foo) where
> import Foo
>
> module Convert where
> import qualified Old
> import qualified New
> convert (Old.Foo x y) = New.Foo y x
We're not going to support this, at least for the forseeable future.
It's a pretty big change: every entity in the program becomes
parameterised by the package name as well as the module name, because
module names can overlap.
This means a change to the language: there might be multiple types
called M.T in the program, which are not compatible (they might have
different representations). You can't pass a value of type M.T that you
got from version 1.0 of the package to a function expecting M.T in
version 2.
This issue came up in the thread about grafting from late 2003 on the
libraries list (sorry don't have a link to hand).
Cheers,
Simon
More information about the Haskell
mailing list