[Haskell-cafe] namespacing?

Jason Bailey azrael at demonlords.net
Wed Dec 8 11:16:35 EST 2004


I'm appreciating the feedback. I discovered where I was going wrong.

The library I was using allowed me to import a module, which in turn
allowed me to use functions from other modules. So even though I could
use func directly I couldn't use B.func because I hadn't explicitly
imported B.

 I find that interesting. I would have thought that if I hadn't
explicitly imported a module I would either be forced to use the
qualified name, not use the function at all, or at the very least be
allowed to qualify the name.

thanks

Jason



> -------- Original Message --------
> Subject: Re: [Haskell-cafe] namespacing?
> From: "Duncan Coutts" <duncan.coutts at worc.ox.ac.uk>
> Date: Wed, December 08, 2004 10:12 am
> To: azrael at demonlords.net
> Cc: haskell-cafe at haskell.org
> 
> On Wed, 2004-12-08 at 07:58 -0700, azrael at demonlords.net wrote:
> > I've got a general new person type question.
> > 
> > I understand that I can hide a function in a module that I am importing
> > if it conflicts with another identical function name.
> > 
> > But if the situation arises that I would like to use two identically
> > named  functions from two different modules is there anyway for me to
> > specify that I want to use the function from module A rather then the
> > function from module B.
> 
> module C where
> 
> import A
> import qualified A (foo)
> 
> import B
> import qualified B (foo)
> 
> 
> ... A.foo ...
> 
> ... B.foo ...
> 
> 
> There are actually several options here, you can import modules only
> qualified, then every value from that module needs to be qualified. Some
> modules are designed to be used this way, see for example Data.HashTable
> http://www.haskell.org/ghc/docs/latest/html/libraries/base/Data.HashTable.html
> (and people are encouraged to write new modules in this style).
> 
> If it's just one or two values that clash then the example above is
> good, ie import the whole thing unqualified and just qualify the one or
> two names that clash.
> 
> You can even give short names to modules you import, eg:
> 
> import qualified System.Gnome.GConf as Config
> 
> now I can say Config.get rather than System.Gnome.GConf.get
> 
> Hope this helps.
> 
> Duncan



More information about the Haskell-Cafe mailing list