
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) )

Sorry for the mix-up. I mean associativity, not fixity!
2019년 1월 6일 (일) 오전 9:06, Dannyu NDos
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) )

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
wrote: Sorry for the mix-up. I mean associativity, not fixity!
2019년 1월 6일 (일) 오전 9:06, Dannyu NDos
님이 작성: 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@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

The current GHC implementation constructs Read instances out of other Read instances. In order to make this work some restictions are necessary. Given that a top-down paring strategy is used we cannot easily construct parsers for left-recursive data types. To cope with this problem, and to make sure that at least Read instances can read data written by Show instances, data is written out by Show instances with a sufficjently large number of parentheses. Unfortunately this may make reading data back extremely show. A solution for this problem is described in out Haskell 2008 Workshop paper: @inproceedings{1411296, Address = {New York, NY, USA}, Author = {Viera, Marcos and Swierstra, S. Doaitse and Lempsink, Eelco}, Booktitle = {Haskell Symposium}, Date-Added = {2009-06-06 22:24:07 +0200}, Date-Modified = {2009-06-06 22:24:07 +0200}, Doi = {http://doi.acm.org/10.1145/1411286.1411296}, Isbn = {978-1-60558-064-7}, Location = {Victoria, BC, Canada}, Pages = {63--74}, Publisher = {ACM}, Read = {Yes}, Title = {Haskell, do you read me?: constructing and composing efficient top-down parsers at runtime}, Year = {2008}, }} which I am attaching. Unfortunately the solution to solve all problems is rather involved. The code you can find in the package ChristmasTree: "ChristmasTree (Changing Haskell's Read Implementation Such That by Manipulating ASTs it Reads Expressions Efficiently) is an alternative approach of read that composes grammars instead of parsers. It reads data in linear time, while the function read has an exponential behavior in some cases of data types with infix operators.” Hope this helps answering your question, Doaitse
Op 6 jan. 2019, om 11:34 heeft Oleg Grenrus
het volgende geschreven: 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
wrote: Sorry for the mix-up. I mean associativity, not fixity!
2019년 1월 6일 (일) 오전 9:06, Dannyu NDos
님이 작성: 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@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
participants (3)
-
Dannyu NDos
-
Doaitse Swierstra
-
Oleg Grenrus