
#11628: Unexpected results with Read/Show -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Keywords: | 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: -------------------------------------+------------------------------------- In the following simplified example, `Foo` and `U` correspond to GADTs that GHC will not derive `Read`/`Show` for. I attempted to work around that by using newtypes for each GADT constructor, and letting GHC derive the `Show`/`Read` instances for those instead. However, I get a runtime error (`Prelude.read: no parse`) on the second print statement in `main`: {{{ {-# LANGUAGE FlexibleContexts, FlexibleInstances, GADTs, ScopedTypeVariables #-} import Text.Read (Read(readPrec)) newtype Bar r = Bar r deriving (Show, Read) newtype Foo r = Foo (Bar r) -- use the GHC-derived Show/Read for Bar instance (Show r) => Show (Foo r) where show (Foo x) = show x instance (Read r) => Read (Foo r) where readPrec = Foo <$> readPrec data U t rep r where U1 :: t r -> U t Int r U2 :: t r -> U t Char r -- use the Read/Show instances for U1Wrap and U2Wrap newtype U1Wrap t r = U1Wrap {unU1Wrap :: t r} deriving (Show, Read) newtype U2Wrap t r = U2Wrap (t r) deriving (Show, Read) instance (Read (t r)) => Read (U t Int r) where readPrec = (U1 . unU1Wrap) <$> readPrec instance (Read (U2Wrap t r)) => Read (U t Char r) where readPrec = do x <- readPrec return $ case x of (U2Wrap y) -> U2 y instance (Show (t r)) => Show (U t Int r) where show (U1 x) = show $ U1Wrap x instance (Show (t r)) => Show (U t Char r) where show (U2 x) = show (U2Wrap x :: U2Wrap t r) main :: IO () main = do let x = U1 $ Foo $ Bar 3 y = U2 $ Foo $ Bar 3 print $ show (read (show x) `asTypeOf` x) print $ show (read (show y) `asTypeOf` y) }}} Someone mentioned that I should define `showsPrec` rather than `show`, but these are listed as alternatives in [https://downloads.haskell.org/~ghc/latest/docs/html/libraries/base-4.8.2.0 /Text-Show.html the docs]. It's not clear to me if GHCs derived instances are invalid, or if I'm doing something illegal. In the latter case, the docs need some improvement. (Verified this behavior in 7.10.2 and HEAD.) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11628 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler