[GHC] #14289: Pretty-printing of derived multi-parameter classes omits necessary parentheses

#14289: Pretty-printing of derived multi-parameter classes omits necessary parentheses -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 (Parser) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Take this file: {{{#!hs {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE TemplateHaskell #-} {-# OPTIONS -ddump-splices #-} import Language.Haskell.TH class C a b main :: IO () main = putStrLn $([d| data Foo a = Foo a deriving (C a) |] >>= stringE . show) }}} When this is compiled, `-ddump-splices` does not faithfully print back what was written by the user: {{{ [1 of 1] Compiling Main ( Bug.hs, interpreted ) Bug.hs:10:19-77: Splicing expression [d| data Foo_a4l1 a_a4l3 = Foo_a4l2 a_a4l3 deriving C a_a4l3 |] >>= stringE . show ======> "[DataD [] Foo_6989586621679026555 [PlainTV a_6989586621679026557] Nothing [NormalC Foo_6989586621679026556 [(Bang NoSourceUnpackedness NoSourceStrictness,VarT a_6989586621679026557)]] [DerivClause Nothing [AppT (ConT Main.C) (VarT a_6989586621679026557)]]]" }}} In particular, this pretty-prints `deriving C a_a4l3`, which doesn't even parse correctly. It should print `deriving (C a_a4l3)`. Ultimately, there is an off-by-one error in the number of parentheses being printed, since if you tweak the original example by adding another set of parentheses: {{{#!hs {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE TemplateHaskell #-} {-# OPTIONS -ddump-splices #-} import Language.Haskell.TH class C a b main :: IO () main = putStrLn $([d| data Foo a = Foo a deriving ((C a)) |] >>= stringE . show) }}} Then it pretty-prints exactly one set of parentheses (as opposed to two): {{{ [1 of 1] Compiling Main ( Bug.hs, interpreted ) Bug.hs:10:19-79: Splicing expression [d| data Foo_a1zI a_a1zK = Foo_a1zJ a_a1zK deriving (C a_a1zK) |] >>= stringE . show ======> "[DataD [] Foo_6989586621679026522 [PlainTV a_6989586621679026524] Nothing [NormalC Foo_6989586621679026523 [(Bang NoSourceUnpackedness NoSourceStrictness,VarT a_6989586621679026524)]] [DerivClause Nothing [AppT (ConT Main.C) (VarT a_6989586621679026524)]]]" }}} There are two suspicious parts of the GHC codebase that contribute to this bug: * This parser production: http://git.haskell.org/ghc.git/blob/4364f1e7543b6803cfaef321105d253e0bdf08a4... This recognizes singleton derived classes that are surrounded by a set of parentheses, and "strips off" the parentheses. * This `Outputable` instance: http://git.haskell.org/ghc.git/blob/4364f1e7543b6803cfaef321105d253e0bdf08a4... This code detects lists of two or more derived classes and surrounds them with extra parentheses to make up for the set that was removed during parsing. But this fails to detect the case of `deriving (C a)`, since this only contains a single class. Indeed, trying to distinguish between, say, `deriving T` and `deriving (T)` at this level would be quite tricky. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14289 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14289: Pretty-printing of derived multi-parameter classes omits necessary parentheses -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: alanz Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by alanz): * owner: (none) => alanz -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14289#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14289: Pretty-printing of derived multi-parameter classes omits necessary parentheses -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: alanz Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4056 Wiki Page: | -------------------------------------+------------------------------------- Changes (by alanz): * status: new => patch * differential: => Phab:D4056 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14289#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14289: Pretty-printing of derived multi-parameter classes omits necessary
parentheses
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: alanz
Type: bug | Status: patch
Priority: normal | Milestone:
Component: Compiler | Version: 8.2.1
(Parser) |
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D4056
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Alan Zimmerman

#14289: Pretty-printing of derived multi-parameter classes omits necessary parentheses -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: alanz Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 (Parser) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4056 Wiki Page: | -------------------------------------+------------------------------------- Changes (by alanz): * status: patch => closed * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14289#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC