[GHC] #14918: GHC 8.4.1 regression: derived Read instances with field names containing # no longer parse

#14918: GHC 8.4.1 regression: derived Read instances with field names containing # no longer parse -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.2 Component: Compiler | Version: 8.4.1 Keywords: deriving | Operating System: Unknown/Multiple Architecture: | Type of failure: Incorrect result Unknown/Multiple | at runtime Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- (Originally noticed [here](https://github.com/ekmett/transformers- compat/issues/32).) Consider the following program: {{{#!hs {-# LANGUAGE MagicHash #-} module Bug where data T a = MkT { runT# :: a } deriving (Read, Show) t1, t2 :: T Int t1 = MkT 1 t2 = read $ show t1 main :: IO () main = print t2 }}} In GHC 8.2.1, this runs without issue: {{{ $ /opt/ghc/8.2.2/bin/runghc Bug.hs MkT {runT# = 1} }}} In GHC 8.4.1, however, this produces a runtime error: {{{ $ ~/Software/ghc-8.4.1/bin/runghc Bug.hs Bug.hs: Prelude.read: no parse }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14918 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14918: GHC 8.4.1 regression: derived Read instances with field names containing # no longer parse -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.2 Component: Compiler | Version: 8.4.1 Resolution: | Keywords: deriving Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by RyanGlScott: Old description:
(Originally noticed [here](https://github.com/ekmett/transformers- compat/issues/32).)
Consider the following program:
{{{#!hs {-# LANGUAGE MagicHash #-} module Bug where
data T a = MkT { runT# :: a } deriving (Read, Show)
t1, t2 :: T Int t1 = MkT 1 t2 = read $ show t1
main :: IO () main = print t2 }}}
In GHC 8.2.1, this runs without issue:
{{{ $ /opt/ghc/8.2.2/bin/runghc Bug.hs MkT {runT# = 1} }}}
In GHC 8.4.1, however, this produces a runtime error:
{{{ $ ~/Software/ghc-8.4.1/bin/runghc Bug.hs Bug.hs: Prelude.read: no parse }}}
New description: (Originally noticed [https://github.com/ekmett/transformers- compat/issues/32 here].) Consider the following program: {{{#!hs {-# LANGUAGE MagicHash #-} module Bug where data T a = MkT { runT# :: a } deriving (Read, Show) t1, t2 :: T Int t1 = MkT 1 t2 = read $ show t1 main :: IO () main = print t2 }}} In GHC 8.2.1, this runs without issue: {{{ $ /opt/ghc/8.2.2/bin/runghc Bug.hs MkT {runT# = 1} }}} In GHC 8.4.1, however, this produces a runtime error: {{{ $ ~/Software/ghc-8.4.1/bin/runghc Bug.hs Bug.hs: Prelude.read: no parse }}} -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14918#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14918: GHC 8.4.1 regression: derived Read instances with field names containing # no longer parse -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.2 Component: Compiler | Version: 8.4.1 Resolution: | Keywords: deriving Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: #14364 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: tdammers (added) * related: => #14364 Comment: Comparing the results of `-ddump-deriv` between GHC 8.2.1 and 8.4.1 is interesting. In GHC 8.2.1, we have: {{{ instance GHC.Read.Read a => GHC.Read.Read (Bug.T a) where GHC.Read.readPrec = GHC.Read.parens (Text.ParserCombinators.ReadPrec.prec 11 (do GHC.Read.expectP (Text.Read.Lex.Ident "MkT") GHC.Read.expectP (Text.Read.Lex.Punc "{") GHC.Read.expectP (Text.Read.Lex.Ident "runT") GHC.Read.expectP (Text.Read.Lex.Symbol "#") GHC.Read.expectP (Text.Read.Lex.Punc "=") a1_a2wO <- Text.ParserCombinators.ReadPrec.reset GHC.Read.readPrec GHC.Read.expectP (Text.Read.Lex.Punc "}") GHC.Base.return (Bug.MkT a1_a2wO))) GHC.Read.readList = GHC.Read.readListDefault GHC.Read.readListPrec = GHC.Read.readListPrecDefault }}} But in GHC 8.4.1, we have: {{{ instance GHC.Read.Read a => GHC.Read.Read (Bug.T a) where GHC.Read.readPrec = GHC.Read.parens (Text.ParserCombinators.ReadPrec.prec 11 (do GHC.Read.expectP (Text.Read.Lex.Ident "MkT") GHC.Read.expectP (Text.Read.Lex.Punc "{") a1_a2Tm <- GHC.Read.readField "runT#" (Text.ParserCombinators.ReadPrec.reset GHC.Read.readPrec) GHC.Read.expectP (Text.Read.Lex.Punc "}") GHC.Base.return (Bug.MkT a1_a2Tm))) GHC.Read.readList = GHC.Read.readListDefault GHC.Read.readListPrec = GHC.Read.readListPrecDefault }}} This likely has something to do with commit dbd81f7e86514498218572b9d978373b1699cc5b (Factor out readField (#14364)). tdammers, do you know what is going on here? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14918#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14918: GHC 8.4.1 regression: derived Read instances with field names containing # no longer parse -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.2 Component: Compiler | Version: 8.4.1 Resolution: | Keywords: deriving Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: #5041, #14364 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * related: #14364 => #5041, #14364 Comment: Ah, I know what is happening here. #5041 is quite relevant, as is [http://git.haskell.org/ghc.git/blob/152055a19cf368439c8450040b68142f8e7d0346... this comment] from the GHC source: {{{#!hs -- For constructors and field labels ending in '#', we hackily -- let the lexer generate two tokens, and look for both in sequence -- Thus [Ident "I"; Symbol "#"]. See Trac #5041 }}} Now let's look at [http://git.haskell.org/ghc.git/blob/152055a19cf368439c8450040b68142f8e7d0346... what readField does]: {{{#!hs readField :: String -> ReadPrec a -> ReadPrec a readField fieldName readVal = do expectP (L.Ident fieldName) expectP (L.Punc "=") readVal }}} Alas, it attempts to treat the field name as a single `Ident`. But if that field name contains a `#` (e.g., `runT#`, as in the original example), then this will fail. It looks like we'll need a variant of `readField` that takes hashes into account. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14918#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14918: GHC 8.4.1 regression: derived Read instances with field names containing # no longer parse -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: patch Priority: high | Milestone: 8.4.2 Component: Compiler | Version: 8.4.1 Resolution: | Keywords: deriving Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: #5041, #14364 | Differential Rev(s): Phab:D4502 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => patch * differential: => Phab:D4502 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14918#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14918: GHC 8.4.1 regression: derived Read instances with field names containing #
no longer parse
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: patch
Priority: high | Milestone: 8.4.2
Component: Compiler | Version: 8.4.1
Resolution: | Keywords: deriving
Operating System: Unknown/Multiple | Architecture:
Type of failure: Incorrect result | Unknown/Multiple
at runtime | Test Case:
Blocked By: | Blocking:
Related Tickets: #5041, #14364 | Differential Rev(s): Phab:D4502
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ryan Scott

#14918: GHC 8.4.1 regression: derived Read instances with field names containing # no longer parse -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: merge Priority: high | Milestone: 8.4.2 Component: Compiler | Version: 8.4.1 Resolution: | Keywords: deriving Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Incorrect result | Test Case: at runtime | deriving/should_run/T14918 Blocked By: | Blocking: Related Tickets: #5041, #14364 | Differential Rev(s): Phab:D4502 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: patch => merge * testcase: => deriving/should_run/T14918 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14918#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14918: GHC 8.4.1 regression: derived Read instances with field names containing # no longer parse -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: high | Milestone: 8.4.2 Component: Compiler | Version: 8.4.1 Resolution: fixed | Keywords: deriving Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Incorrect result | Test Case: at runtime | deriving/should_run/T14918 Blocked By: | Blocking: Related Tickets: #5041, #14364 | Differential Rev(s): Phab:D4502 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged to `master` and `ghc-8.4`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14918#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC