Consider operator fixity when deriving Show or Read

Oleg Grenrus oleg.grenrus at iki.fi
Sun Jan 6 10:34:50 UTC 2019


Report says explicitly "ignoring associativity". Yet, I have written manual Show/Read to make Show of list-like data prettier: I don't know any problem with that. Would be good to know, why report is written as it is.

- Oleg

The result of show is a syntactically correct Haskell expression containing only constants, given the fixity declarations in force at the point where the type is declared. It contains only the constructor names defined in the data type, parentheses, and spaces. When labelled constructor fields are used, braces, commas, field names, and equal signs are also used. Parentheses are only added where needed, ignoring associativity. No line breaks are added. The result of showis 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.)

Sent from my iPhone

> On 6 Jan 2019, at 3.53, Dannyu NDos <ndospark320 at gmail.com> wrote:
> 
> 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)
>>             )
>> 
> _______________________________________________
> Libraries mailing list
> Libraries at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/libraries/attachments/20190106/739703f1/attachment.html>


More information about the Libraries mailing list