[Haskell-cafe] Why Haskell?

Bertram Felgenhauer bertram.felgenhauer at googlemail.com
Sun Jul 23 01:48:47 EDT 2006


Matthew Bromberg wrote:
> 4)  Hmm, a simple example I tried actually worked, however I have a file 
> that has this header
> module Parsefile where
> import System.IO
> import System.IO.Unsafe
> import Text.ParserCombinators.Parsec
> import Data.HashTable
> ...
> 
> For some reason it requires that I use the fully qualified name 
> Data.HashTable.lookup instead of just lookup to get the correct 
> functionality.

The reason is that the standard Prelude also provides function
called 'lookup'. [*] You could hide it by explicitely importing the
Prelude:

  import Prelude hiding (lookup)

Another solution is to import the HashTable module with a shorter
name to save typing (and avoid noise) in the Code:

  import Data.HashTable as H

allows you to use H.lookup for the lookup. If you make the import
qualified,

  import qualified Data.HashTable as H

you are forced to use that prefix, but you can use the Prelude's
lookup without any prefix again.

By specifying the names to import you can create any mix of
prefixed and non-prefixed functions you want. Another useful
thing to know is that you can import different modules with the
same name (beware of conflicting symbols though). For example,
adding

  import Data.HashTable (HashTable)

to the qualified import allows you to use the type 'HashTable'
without the 'H.' prefix.

regards,

Bertram

[*] it'd be nice if the name resolution could be guided by the
    type checker - but that's probably hard. Has anyone tried that?


More information about the Haskell-Cafe mailing list