Bug in library report

Simon Peyton-Jones simonpj@microsoft.com
Tue, 23 Jul 2002 13:56:13 +0100


Folks,

Another small but long-standing bug in the Haskell Library report:
the recursive calls to 'reads' and 'shows' in the Read and Show
instances for Ratio and Array should be calls to readsPrec and showsPrec
respectively.  The corrected defintions are below.
(c.f. the example of derived instances in Appendix D of the language
report.)

Anyone disagree?   (How do these bugs last so long?)

Simon

=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D Page 5 =
=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D
  instance  (Read a, Integral a)  =3D> Read (Ratio a)  where
    readsPrec p  =3D  readParen (p > prec)
                              (\r -> [(x%y,u) | (x,s)   <- readsPrec
(prec+1) r,
                                                ("%",t) <- lex s,
                                                (y,u)   <- readsPrec
(prec+1) t ])

  instance  (Integral a)  =3D> Show (Ratio a)  where
    showsPrec p (x:%y)  =3D  showParen (p > prec)
                               (showsPrec (prec+1) x .=20
			        showString " % " .=20
				showsPrec (prec+1) y)


=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D Page 24 =
=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D=3D
  instance  (Ix a, Show a, Show b) =3D> Show (Array a b)  where
    showsPrec p a =3D showParen (p > arrPrec) (
                    showString "array " .
                    showsPrec (arrPrec+1) (bounds a) . showChar ' ' .
                    showsPrec (arrPrec+1) (assocs a)                  )

  instance  (Ix a, Read a, Read b) =3D> Read (Array a b)  where
    readsPrec p =3D readParen (p > arrPrec)
           (\r -> [ (array b as, u)=20
                  | ("array",s) <- lex r,
                    (b,t)       <- readsPrec (arrPrec+1) s,
                    (as,u)      <- readsPrec (arrPrec+1) t ])

  -- Precedence of the 'array' function is that of application itself
  arrPrec =3D 10