[GHC] #13307: Record pattern synonym fields have to be manually exported

#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 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- 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 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13307 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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: | -------------------------------------+------------------------------------- Comment (by rwbarton): Well if you had a plain old {{{ newtype T = T { x :: Impl } }}} then this would be the correct, Report-specified behavior. So I think your example is slightly wrong somehow. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13307#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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

#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: | -------------------------------------+------------------------------------- Comment (by ocharles): Specifically, I only want to export the type of the newtype (`T`), and the pattern synonym `MkT2`. The "real" constructor `MkT` for the newtype is internal to the module and not exported. In my actual work, `Impl` is a record with ~10 fields, and I want to have a `newtype` over `Impl` that looks like a record with 10 fields, though they will have different names (proxying to the underlying fields in `Impl`). So yes, what Simon comments with is indeed what I would like to be able to do (though I wouldn't export `MkT`). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13307#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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: | -------------------------------------+------------------------------------- Comment (by rwbarton): Can you write something like {{{ module A( T, pattern MkT2(..) ) where ... }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13307#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by mpickering): * keywords: => PatternSynonyms -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13307#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by rwbarton): The real underlying goal here is to export `T`, `MkT2` and `x`, without having to mention `x`, or export `MkT`. mpickering and I discussed this over IRC and we converged (at least for the moment) on this sketch of a design. * Things can have associated things. Automatically associated to a type are its constructors and record fields. Automatically associated to a pattern synonym are its record fields. (And so on for classes, etc.) * The effect of association is: `Foo(..)` in an export or import list means "Foo and all the things associated to `Foo`". * You can associate a pattern synonym to a type with the `T(P)` export list form (this is the same as "bundling", and maybe I should just use the word "bundled" everywhere). (And it might be useful for other things as well; for example, if you change a class method to a top-level function, by bundling the function with the class, you can preserve the meaning of importing `C(..)`.) * Things being associated is transitive, so then the fields of the pattern synonym are associated with the type, too. This means that in particular > `T( MkT, MkT2, .. )` means "`T` together with data constructor/pattern synonyms `MkT` and `MkT2`, ''plus their field names''". However merely associating a field name `x` of `MkT` with the type `T` ''does not mean'' that exporting `( T( MkT ) )` causes `x` to be exported; because there is no `..` in `T( MkT )`. So, I think that this design is backwards compatible with the Haskell 2010 meaning of `..`. Then, the other thing that is needed is the ability to write either {{{ T( MkT2(..) ) }}} or {{{ T( MkT2 ), pattern MkT2(..) }}} in an export list (or import list) to export (or import) `MkT2` along with all of its associated things. This is already the meaning of the constructions `T(..)` and `C(..)` in Haskell 2010, so this seems like mostly a parser change. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13307#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Generally that seems fine. But Haskell's namespace control system is more complicated than it looks -- see Iavor's [https://web.cecs.pdx.edu/~mpj/pubs/hsmods.pdf 2002 Haskell Symposium paper] -- so I would urge a careful, clear specification before any more implementation happens. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13307#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by mnislaih): * cc: mnislaih (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13307#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC