[GHC] #14918: GHC 8.4.1 regression: derived Read instances with field names containing # no longer parse
GHC
ghc-devs at haskell.org
Wed Mar 14 01:32:53 UTC 2018
#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
More information about the ghc-tickets
mailing list