How to use qualified name ModuleName.(.!.) ?

Marc Weber marco-oweber at gmx.de
Wed Jun 20 06:52:16 EDT 2007


Example:

  marc at localhost /tmp/qual $ ls; cat M.hs main.hs; ghc --make main.hs
  M.hi  M.hs  M.o  main.hs

  -- module M ------------------
  module M where
  import Data.List

  infixr 9 .!.

  f = "dummyf"

  (.!.) = (!!)

  -- module Main ------------------
  module Main where
  import qualified M as M

  main = do
    print $ M.f                                      -- (1)
    print $ M.(.!.) [1,2]  1                         -- (2)
  -- -------------------------------

  [2 of 2] Compiling Main             ( main.hs, main.o )

  main.hs:7:10: Not in scope: data constructor `M' (3)

  main.hs:7:12: Not in scope: `.!.'                 (4)

Calling M.f  (1) works fine whereas calling M.(.!.) results in the error
messages.
Is possible somehow? Can I find more information in the ghc docs?

Marc Weber


More information about the Glasgow-haskell-users mailing list