Consider operator fixity when deriving Show or Read

Dannyu NDos ndospark320 at gmail.com
Sun Jan 6 00:06:02 UTC 2019


For the following code as an example:

{-# LANGUAGE TypeOperators #-}

infixr 5 :.

data List a = Null | a :. List a deriving (Eq, Ord, Show, Read)


The Show instance and the Read instance are inaware of the fixity of (:.):

*Main> 2 :. 3 :. Null
2 :. (3 :. Null)
*Main> read "2 :. 3 :. Null" :: List Int
*** Exception: Prelude.read: no parse
*Main> read "2 :. (3 :. Null)" :: List Int
2 :. (3 :. Null)

The derived instances should be:

instance Show a => Show (List a) where
showsPrec p Null = showParen (11 <= p) (showString "Null")
showsPrec p (x :. xs) = showParen (5 <= p) (go p (x :. xs)) where
go _ Null = showString "Null"
go p (x :. xs) = showsPrec p x . showString " :. " . go p xs

instance Read a => Read (List a) where
readPrec = parens $ do
Ident "Null" <- lexP
return Null
+++ (do
x <- readPrec
Symbol ":." <- lexP
xs <- readPrec
return (x :. xs)
)
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/libraries/attachments/20190106/261c006d/attachment.html>


More information about the Libraries mailing list