[GHC] #13307: Record pattern synonym fields have to be manually exported
GHC
ghc-devs at haskell.org
Mon Feb 20 14:53:57 UTC 2017
#13307: Record pattern synonym fields have to be manually exported
-------------------------------------+-------------------------------------
Reporter: ocharles | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.2
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Old description:
> The following currently fails to compile:
>
> {{{#!hs
> {-# LANGUAGE PatternSynonyms #-}
> module A
> ( T(T)
> ) where
>
> data Impl = Impl Int
>
> newtype T = MkT Impl
>
> pattern T {x} = MkT (Impl x)
>
> {-# LANGUAGE RecordWildCards #-}
> module B where
>
> import A
>
> foo :: T -> Int
> foo T{x} = x
> }}}
>
> As far as GHC can see, in module `B`, `T` does not have a field `x`. The
> fix is to manually export `x` from `A`:
>
> {{{#!hs
> module A (T(T, x)) where
> }}}
>
> But this is tedious for records with a large amount of fields
New description:
The following currently fails to compile:
{{{#!hs
{-# LANGUAGE PatternSynonyms #-}
module A( T( MkT2 ) ) where
data Impl = Impl Int
newtype T = MkT Impl
pattern MkT2 {x} = MkT (Impl x)
{-# LANGUAGE RecordWildCards #-}
module B where
import A
foo :: T -> Int
foo MkT2{x} = x
}}}
As far as GHC can see, in module `B`, `MkT2` does not have a field `x`.
The fix is to manually export `x` from `A`:
{{{#!hs
module A (T(MkT2, x)) where
}}}
But this is tedious for records with a large amount of fields
--
Comment (by simonpj):
Yes, with plain old `newtype T` you could say
[{{
module A( T(..) ) where
newtype T = MkT { x :: Impl }
}}}
to export both `MkT` and `x` along with `T`.
But in the example ocharles wants to bundle the pattern synonym data
constructor `MkT2` in with the type constructor `T`. Maybe you would like
to say
{{{
module A( T( MkT, MkT2(..) ) where ...
}}}
to mean the same as `T( MkT, MkT2, x )`. But we don't currently support
that.
I suppose you could say that the notation `T( MkT, MkT2, .. )` means "T
together with data constructor/pattern synonyms `MkT` and `MkT2`, plus
their field names. But that would be a (modest) design change.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13307#comment:2>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list