[GHC] #10027: Importing constructor of associated data type fails

GHC ghc-devs at haskell.org
Tue Jan 27 10:01:35 UTC 2015


#10027: Importing constructor of associated data type fails
-------------------------------------+-------------------------------------
        Reporter:  lspitzner         |                   Owner:
            Type:  bug               |                  Status:  new
        Priority:  normal            |               Milestone:
       Component:  Compiler          |                 Version:  7.8.4
      Resolution:                    |                Keywords:
Operating System:  Unknown/Multiple  |  constructor import associated data
 Type of failure:  None/Unknown      |  type
      Blocked By:                    |            Architecture:
 Related Tickets:                    |  Unknown/Multiple
                                     |               Test Case:
                                     |                Blocking:
                                     |  Differential Revisions:
-------------------------------------+-------------------------------------

Comment (by simonpj):

 Very good point. The same happens with this simpler test case:
 {{{
 module A where
   data family D a

 module B where
   import A
   data Foo = Foo
   data instance D Foo = DCon

 module C where
   import B( D( DCon ) )  -- This import is rejected
 }}}
 Compilation of `C` fails because the `import` is rejected.

 It's rejected because (GHC considers that) `B` really doesn't export `D`:
 the family `D` is defined in module `A`.  So module `B` exports only
 `Foo(Foo)` and the data constructor `DCon`, but not the data family `D`.

 Alas, that means that there is simply no way to import `DCon` explicitly.
 Not very clever, but that's the way it is.

 This does seem wrong.  The issue is: what is exported if you omit an
 explicit export list, and just say `module M where ...`?  The
 [https://www.haskell.org/onlinereport/haskell2010/haskellch5.html#x11-1000005.2
 Haskell Report] says "If the export list is omitted, all values, types and
 classes defined in the module are exported, but not those that are
 imported".  But it was written without thinking of type families.

 So I suppose we could agree that, for the purposes of an omitted export
 list, a `data instance` is considered as defining the data family too, so
 that the data family is exported as well as the data constructors.
 Otherwise there is literally no way to import the data constructor by
 name.  And really it is odd to have data constructors in scope without
 their type constructor also being in scope.

 An alterantive would be to extend the use of `-XExplicitNamespaces` (see
 [https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/syntax-
 extns.html#explicit-namespaces user manual]) to allow an import to specify
 data constructor.  Thus
 {{{
 import B( datacon DCon )
 }}}
 That could become tiresome for data types with lots of constructors.

 Any opinions?

 Simon

--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/10027#comment:1>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list