[GHC] #11628: Unexpected results with Read/Show

#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

#11628: Unexpected results with Read/Show -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | 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: | -------------------------------------+------------------------------------- Comment (by simonpj): What exactly is the bug here? What does not work that you expect to work? What does "does not work" mean? (Compile time error? Run time crash? Run time success but data printed does not look right?) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11628#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11628: Unexpected results with Read/Show -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | 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: | -------------------------------------+------------------------------------- Comment (by rwbarton): Lots of distractions here. Here is the crux of the matter: {{{ newtype X u = X u instance Show u => Show (X u) where show (X u) = show u main = print (Just (X (Just 1))) -- prints "Just Just 1" }}} Of course, you should just define `showsPrec` like you mentioned. Just defining `show` should be okay if (either you don't care about compatibility with Read or) the output is a single token, like a number or a quoted string. Otherwise you need to define `showsPrec`. Agree that the docs should be clearer on this point. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11628#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11628: Unexpected results with Read/Show -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | 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: | -------------------------------------+------------------------------------- Comment (by simonpj): Great, thanks. Nothing to do with GADTs then. Documentation patches would be v welcome. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11628#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11628: Unexpected results with Read/Show -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | 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: | -------------------------------------+------------------------------------- Comment (by crockeea): Replying to [comment:2 rwbarton]:
Lots of distractions here. Here is the crux of the matter: {{{ newtype X u = X u instance Show u => Show (X u) where show (X u) = show u main = print (Just (X (Just 1))) -- prints "Just Just 1" }}} Of course, you should just define `showsPrec` like you mentioned.
Just defining `show` should be okay if (either you don't care about compatibility with Read or) the output is a single token, like a number or a quoted string. Otherwise you need to define `showsPrec`. Agree that the docs should be clearer on this point.
Thanks for clarifying. So it seems like this is just a documentation problem. For SPJ or future visitors: the problem as I see it is that the second print statement results in a runtime exception (`Prelude.read: no parse`). I believe it should run without exception. Apparently, based on my `Show` instances, this is non unexpected behavior. However, the documentation for show/read doesn't make it clear that I should define `showsPrec` rather than `show`. Given that rwbarton thinks the behavior is expected, then this ticket is about updated the documentation for Text.Read and Text.Show. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11628#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11628: Unexpected results with Read/Show -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Documentation | Unknown/Multiple bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by crockeea): * failure: Incorrect result at runtime => Documentation bug -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11628#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC