[GHC] #14848: -XDuplicateRecordFields breaks record expression splices
GHC
ghc-devs at haskell.org
Sat Feb 9 22:15:21 UTC 2019
#14848: -XDuplicateRecordFields breaks record expression splices
-------------------------------------+-------------------------------------
Reporter: dailectic | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.2.2
Resolution: | Keywords: ORF
Operating System: Linux | Architecture: x86_64
Type of failure: GHC rejects | (amd64)
valid program | Test Case:
Blocked By: | Blocking:
Related Tickets: #11103 | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Changes (by adamgundry):
* related: => #11103
Comment:
I've just rediscovered this issue, and the interaction between
`DuplicateRecordFields` and `TemplateHaskell` definitely needs to be
addressed more carefully.
The problem here is the case for `HsRecFld` in `DsMeta.repE`, which simply
replaces the field occurrence with the selector function (which has an
internal name that cannot be spliced in, namely `Name "$sel:x:A" (NameG
VarName pkg "Lib")`). There are other related problems in `DsMeta` for
representing fields in record definition, construction and pattern
matching.
The way #11103 dealt with a similar problem in reification was to
represent field names using a specially-crafted `NameQ`, rather than a
`NameG`. In this example that approach would give `Name "x" (NameQ "Lib")`
instead. Note that `NameG` cannot be used with the field label in place of
the selector, because that leads to looking up an Orig name that doesn't
exist.
However, while using `NameQ` should fix this example, it doesn't work in
general: it means the name is dynamically bound, but of course the field
might not be in scope when the splice is run. For a concrete example of
this, consider a tiny variant of the test case from #12993:
{{{#!hs
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE TemplateHaskell #-}
module T12993_Lib (q) where
data X = X { x :: Int }
q = [|x|]
}}}
{{{#!hs
{-# LANGUAGE TemplateHaskell #-}
module T12993 where
import T12993_Lib
f = $(q)
}}}
This currently fails with an "Illegal variable name" error similar to the
original report from this ticket. With the `NameQ` approach, it would
still fail because `x` is not in scope in `T12993`.
It seems fairly clear to me that dealing with this properly requires
extending the TH AST in some way. The least invasive option might be to
extend `NameFlavour` with a new constructor for field names, which would
be rather like `NameG` but would carry the selector name. I'm not sure if
there are better designs, however. What is the process for
proposing/discussing such changes to TH?
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14848#comment:4>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list