[GHC] #8753: Import constructor but not the data type
GHC
ghc-devs at haskell.org
Sun Feb 9 09:20:15 UTC 2014
#8753: Import constructor but not the data type
-------------------------------------+------------------------------------
Reporter: andreas.abel | Owner:
Type: feature request | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.6.3
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture: Unknown/Multiple
Type of failure: None/Unknown | Difficulty: Unknown
Test Case: | Blocked By:
Blocking: | Related Tickets:
-------------------------------------+------------------------------------
Old description:
> How do I import a constructor but not its data type? The constructor
> might have the name of a data type which I do not want to bring into
> scope.
>
> Use case: Library (A) defines a parametrized data type (D a) which I
> want to use in my code (B) in instantiated form (D Int) but with the same
> name (D). I want to pattern match against inhabitants of type D, so I
> need the constructor(s) in scope.
>
> Here is how it could look like if import lists let me specify whether I
> want to import a type or a constructor with name "D".
>
> module A where
>
> data D a = D a
>
> module B where
>
> import A (constructor D)
> import qualified A
> D = A.D Int
>
> f :: D -> Int
> f (D x) = x
>
> Haskell has different name spaces for type and constructors, but does not
> let the user talk about these name spaces where it matters, namely in
> import/export lists. At least I found no documentation instructing me
> how to do this.
New description:
How do I import a constructor but not its data type? The constructor
might have the name of a data type which I do not want to bring into
scope.
Use case: Library (`A`) defines a parametrized data type (`D a`) which I
want to use in my code (`B`) in instantiated form (`D Int`) but with the
same name (`D`). I want to pattern match against inhabitants of type `D`,
so I need the constructor(s) in scope.
Here is how it could look like if import lists let me specify whether I
want to import a type or a constructor with name "`D`".
{{{#!haskell
module A where
data D a = D a
}}}
{{{#!haskell
module B where
import A (constructor D)
import qualified A
D = A.D Int
f :: D -> Int
f (D x) = x
}}}
Haskell has different name spaces for type and constructors, but does not
let the user talk about these name spaces where it matters, namely in
import/export lists. At least I found no documentation instructing me how
to do this.
--
Comment (by hvr):
(fixed-up wiki markup in ticket description)
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/8753#comment:2>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list