[GHC] #13799: -ddump-splices prints out declarations in the wrong order

#13799: -ddump-splices prints out declarations in the wrong order -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template | Version: 8.0.1 Haskell | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Debugging Unknown/Multiple | information is incorrect Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- {{{#!hs {-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE TemplateHaskell #-} {-# OPTIONS_GHC -ddump-splices #-} module Bug where $([d| data A = A data B = B |]) $([d| deriving instance Eq A deriving instance Eq B |]) }}} {{{ GHCi, version 8.0.2: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Bug ( Bug.hs, interpreted ) Bug.hs:(6,3)-(8,6): Splicing declarations [d| data A_a13D = A_a13E data B_a13B = B_a13C |] ======> data A_a3IA = A_a3IB data B_a3IC = B_a3ID Bug.hs:(10,3)-(12,6): Splicing declarations [d| deriving instance Eq B deriving instance Eq A |] ======> deriving instance Eq A deriving instance Eq B }}} Notice that it printed {{{#!hs [d| deriving instance Eq B deriving instance Eq A |] }}} instead of {{{#!hs [d| deriving instance Eq A deriving instance Eq B |] }}} which is what I originally wrote. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13799 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13799: -ddump-splices prints out declarations in the wrong order -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Debugging | Unknown/Multiple information is incorrect | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): More generally, GHC seems to be pretty cavalier in modifying the quasiquoted declarations before pretty-printing them. Here's another example: {{{#!hs {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TypeOperators #-} {-# OPTIONS_GHC -ddump-splices #-} module Bug where $([d| infixr 5 :*: data a :*: b = a :*: b |]) }}} {{{ $ /opt/ghc/8.2.1/bin/runghc Bug.hs Bug.hs:(6,3)-(8,6): Splicing declarations [d| infixr 5 :*:_a1pB, :*:_a1pA data a_a1pC :*:_a1pA b_a1pD = a_a1pC :*:_a1pB b_a1pD |] ======> infixr 5 :*:_a4aj infixr 5 :*:_a4ai data (:*:_a4ai) a_a4ak b_a4al = a_a4ak :*:_a4aj b_a4al Bug.hs:6:3: error: Multiple fixity declarations for ‘:*:_a4aj’ also at Bug.hs:(6,3)-(8,6) | 6 | $([d| infixr 5 :*: | ^^^^^^^^^^^^^^^^... }}} Because `(:*:)` is used in both the type and value namespace, GHC seems to be creating //two// `newName`s for `:*:` behind the hood, and changing the data/fixity declarations accordingly. (Notice that the fixity declaration has two identifiers now!) It then proceeds to fail to compile due to #13054, but that's a separate issue. The issue at hand is that `-ddump- splices` is printing out internal details in the quasiquoted `[d| ... |]` declarations, when it really needn't. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13799#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13799: -ddump-splices prints out declarations in the wrong order -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: wontfix | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Debugging | Unknown/Multiple information is incorrect | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => closed * resolution: => wontfix Comment: Upon further thought, I don't think this is a feasible thing to do. The problem is that by the time we have enough info for `-ddump-splices` to print out anything, the source has long since been renamed, and with renaming comes dependency analysis, which possibly results in declaration reordering as seen above. We could consider plumbing through the pre- renamed source to be printed as well, but that's a lot of wiring for very little gain. On the other hand, the fact that you can't splice a quoted thing with an `infix` declaration for two names in different namespaces is a very real, but separate bug. I've opened #14032 for this. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13799#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC