Consider operator fixity when deriving Show or Read

Dannyu NDos ndospark320 at gmail.com
Sun Jan 6 01:53:20 UTC 2019


Sorry for the mix-up. I mean associativity, not fixity!

2019년 1월 6일 (일) 오전 9:06, Dannyu NDos <ndospark320 at gmail.com>님이 작성:

> 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/ee9bbbef/attachment.html>


More information about the Libraries mailing list