I have written the following module that uses deriving to make X an instance
of Show and Read but uses a custom instance for type A.

\begin{code}
module Test where

data X = X{a :: A} deriving (Show,Read)
data A = A | AA

instance Show A where
   showsPrec _ a = case a of { A  -> shows 1 ; AA -> shows 2}

instance Read A where
   readsPrec _ s = case s of  { "1" -> [(A,"")]; "2" -> [(AA,"")] ;  _  ->
[]}
\end{code}

Now the strange thing, eventhough for type A we have that (read.show) = id
:: A -> A, i.e.

Test> read (show A) :: A
1
Test> read (show AA) :: A
2

It is NOT the case that (read.show) = id :: X -> X!!!, i.e.

Test> read (show X{a=A}) :: X

Program error: PreludeText.read: no parse

I find this behavior very annoying; I lost a lot of time trying to find a
bug, of course assuming that the example above would work :-(. If
(read.show) is the identity for all component types, then I expect that
(read.show) = id for the combined type as well.

What does the Haskell report say?

page 124:

* The result of show is readable by read if all component types are
readable. (This is true for all instances defined in the Prelude BUT MAY NOT
BE TRUE FOR USER-DEFINED INSTANCES.) (capitalization by Erik)

Boooooooooooooooooooooooooooh, Booooooooooooooooooooooooooh!




Reply via email to