#3615: GHCi doesn't allow the use of imported data contructors
---------------------+------------------------------------------------------
Reporter:  blamario  |          Owner:          
    Type:  bug       |         Status:  new     
Priority:  normal    |      Component:  Compiler
 Version:  6.10.4    |       Severity:  normal  
Keywords:            |       Testcase:          
      Os:  Linux     |   Architecture:  x86     
---------------------+------------------------------------------------------
 There are two modules in this simplified scenario. The main module is
 Main.hs and contains the following three lines of code.

 {{{
 module Main where
 import Imp (D(..))
 main = print D1
 }}}

 Module Imp contains a single data type definition:

 {{{
 module Imp where
 data D = D1 | D2 deriving Show
 }}}

 Now, when I compile Main everything works. GHCi doesn't complain when it
 loads the main module either, but it doesn't allow me to construct D on
 its command line. This makes no sense to me.

 {{{
 $ ghc --make Main.hs
 [1 of 2] Compiling Imp              ( Imp.hs, Imp.o )
 [2 of 2] Compiling Main             ( Main.hs, Main.o )
 Linking Main ...
 $ ./Main
 D1
 $ ghci Main.hs
 GHCi, version 6.10.4: http://www.haskell.org/ghc/  :? for help
 Loading package ghc-prim ... linking ... done.
 Loading package integer ... linking ... done.
 Loading package base ... linking ... done.
 Ok, modules loaded: Main, Imp.
 Prelude Main> D1

 <interactive>:1:0: Not in scope: data constructor `D1'
 Prelude Main>
 }}}

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/3615>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to