TypeData constructor names confusion when checking exports
Given these two modules:
module A(Foo(..)) where
data Foo = Foo1 | Foo2 | Foo3
{-# LANGUAGE DataKinds, TypeData #-}
module B(Foo(Foo1, Foo2)) where
import qualified A
type data Foo = Foo1 | Foo2 | Foo3
There should be no confusion in what the Foo1
and Foo2
refers to in the export spec of B
, since A
is imported qualified. And yet as of b8ebf876 GHC produces the following error message:
input/type-data-export/B.hs:2:10: error: [GHC-88993]
• The type constructor ‘Foo’ is not the parent of the data constructor ‘Foo2’.
Data constructors can only be exported with their parent type constructor.
Parent: A.Foo
• In the export: Foo(Foo1, Foo2)
|
2 | module B(Foo(Foo1, Foo2)) where
| ^^^^^^^^^^^^^^^
input/type-data-export/B.hs:2:10: error: [GHC-88993]
• The type constructor ‘Foo’ is not the parent of the data constructor ‘Foo1’.
Data constructors can only be exported with their parent type constructor.
Parent: A.Foo
• In the export: Foo(Foo1, Foo2)
|
2 | module B(Foo(Foo1, Foo2)) where
| ^^^^^^^^^^^^^^^
Edited by sheaf