[GHC] #13776: -ddump-splices produces unnecessarily qualified names for tuple and list types

#13776: -ddump-splices produces unnecessarily qualified names for tuple and list types -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template | Version: 8.0.1 Haskell | Keywords: newcomer | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- If you compile this: {{{#!hs {-# LANGUAGE TemplateHaskell #-} {-# OPTIONS_GHC -ddump-splices #-} module Bug where import Language.Haskell.TH f :: $(conT ''(,) `appT` conT ''Int `appT` conT ''Int) f = (1,2) g :: $(conT ''[] `appT` conT ''Int) g = [] }}} You'll get some unsavory output: {{{ Bug.hs:10:8-34: Splicing type conT ''[] `appT` conT ''Int ======> GHC.Types.[] Int Bug.hs:7:8-53: Splicing type conT ''(,) `appT` conT ''Int `appT` conT ''Int ======> GHC.Tuple.(,) Int Int }}} It's unsavory because if you actually try to use the spliced output in Haskell code: {{{#!hs module Bug2 where f :: GHC.Tuple.(,) Int Int f = (1,2) g :: GHC.Types.[] Int g = [] }}} Then it won't parse. Expressions have the same problem: {{{#!hs {-# LANGUAGE TemplateHaskell #-} {-# OPTIONS_GHC -ddump-splices #-} module Bug3 where import Language.Haskell.TH f :: (Int, Int) f = $(conE '(,) `appE` litE (integerL 1) `appE` litE (integerL 1)) g :: [Int] g = $(conE '[]) }}} {{{ Bug3.hs:8:7-65: Splicing expression conE '(,) `appE` litE (integerL 1) `appE` litE (integerL 1) ======> (GHC.Tuple.(,) 1) 1 Bug3.hs:11:7-14: Splicing expression conE '[] ======> GHC.Types.[] }}} And patterns: {{{#!hs {-# LANGUAGE TemplateHaskell #-} {-# OPTIONS_GHC -ddump-splices #-} module Bug4 where import Language.Haskell.TH f :: (Int, Int) -> () f $(conP '(,) [litP (integerL 1), litP (integerL 1)]) = () g :: [Int] -> () g $(conP '[] []) = () }}} {{{ Bug4.hs:8:5-52: Splicing pattern conP '(,) [litP (integerL 1), litP (integerL 1)] ======> GHC.Tuple.(,) 1 1 Bug4.hs:11:5-15: Splicing pattern conP '[] [] ======> GHC.Types.[] }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13776 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13776: -ddump-splices produces unnecessarily qualified names for tuple and list types -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): How would you like it to behave? Should the pretty-printer look under `ConT` constructors for certain names (tuples, lists, etc) and print out the right thing? I suppose so. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13776#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13776: -ddump-splices produces unnecessarily qualified names for tuple and list types -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Replying to [comment:1 goldfire]:
Should the pretty-printer look under `ConT` constructors for certain names (tuples, lists, etc) and print out the right thing?
Even better, one might envision changing the `Ppr Name` instance so that special constructors like `[]`, `(,)`, etc. are never printed qualified. After all, they don't make sense to print qualified! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13776#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13776: -ddump-splices produces unnecessarily qualified names for tuple and list types -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mrkgnao): I'd like to work on this. Anything I should know? I'm looking at the `template-haskell` source, and it looks fairly understandable, -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13776#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13776: -ddump-splices produces unnecessarily qualified names for tuple and list types -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: mrkgnao Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: newcomer 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 RyanGlScott): * owner: (none) => mrkgnao Comment: Thanks, mrkgnao! You're on the right track by looking at the `template- haskell` source code. In particular, I think `showName'` is what needs to change, since that's what is responsible for printing out qualified `Name`s. It might be a simple matter of checking if a `Name` is in a set of special names (like `[]`, `(,)`, etc.) and printing it out unqualified if there's a match. If you have any other questions, feel free to ask on this ticket. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13776#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13776: -ddump-splices produces unnecessarily qualified names for tuple and list types -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: mrkgnao Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ckoparkar): I'd like to work on this, if that's OK with @mrkgnao. I have a patch on my local machine that does the right thing for the examples posted in the description (and some tests: `th/T3319`, `th/T5700`, `th/TH_foreignInterruptible`). While I work on submitting that on Phabricator, I wanted to post a summary here and get some early feedback. (1) It seems that `showName` doesn't play a role in pretty-printing the splices with `-ddump-splices`. Instead, the `Outputable` instances in GHC do most of the work. Specifically, `Outputable RdrName` is responsible for printing out the fully qualified names in question. (2) When the Renamer typechecks & runs a splice (`RnSplice.runRnSplice`), it converts the splice to `HsSyn RdrName` (hence the `Outputable RdrName`). `TcSplice.lookupThName` is involved in the process, which converts a `TH.Name` to `Name` via `Convert.thRdrNameGuesses`. (3) For primitives like `[]`, `(:)` etc. `TH.dataToQa` generates a fully qualified global name, i.e `NameG NameSpace PkgName ModName`. And the corresponding `RdrName` generated by `thRdrNameGuesses` is also fully qualified (`Orig Module OccName`). But this is not what we want for built- in syntax. (4) So the "patch" is a simple change to modify this behavior. If `thOrigRdrName` is dealing with built-in syntax, it returns an `Exact Name` instead. {{{#!haskell thOrigRdrName :: String -> TH.NameSpace -> PkgName -> ModName -> RdrName thOrigRdrName occ th_ns pkg mod = let occ' = mk_occ (mk_ghc_ns th_ns) occ in case isBuiltInOcc_maybe occ' of Just name -> nameRdrName name Nothing -> (mkOrig $! (mkModule (mk_pkg pkg) (mk_mod mod))) $! occ' }}} I ran the testsuite, and apart from some `perf` tests, almost everything else worked. These tests fail: {{{ ghci/linking/ghcilink003.run ghcilink003 [bad exit code] (normal) ghci/linking/ghcilink006.run ghcilink006 [bad exit code] (normal) th/T13366.run -- (gcc: error trying to exec 'cc1plus': execvp: -- No such file or directory) }}} but there's a good chance that this is unrelated to the patch. Does the overall approach seem reasonable ? I'll submit a patch soon. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13776#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13776: -ddump-splices produces unnecessarily qualified names for tuple and list types -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: mrkgnao Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): That approach looks promising to me! All of the test failures seem to be C++-related—do you have `g++` installed? In any case, I'd go ahead and just submit your patch to Phabricator. If the CI fails on those tests //there//, then we can puzzle it over :) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13776#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13776: -ddump-splices produces unnecessarily qualified names for tuple and list types -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: mrkgnao Type: bug | Status: patch Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4506 Wiki Page: | -------------------------------------+------------------------------------- Changes (by ckoparkar): * status: new => patch * differential: => Phab:D4506 Comment: Great! Submitted a patch to Phabricator :) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13776#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13776: -ddump-splices produces unnecessarily qualified names for tuple and list
types
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: mrkgnao
Type: bug | Status: patch
Priority: normal | Milestone:
Component: Template Haskell | Version: 8.0.1
Resolution: | Keywords: newcomer
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D4506
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#13776: -ddump-splices produces unnecessarily qualified names for tuple and list types -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: mrkgnao Type: bug | Status: closed Priority: normal | Milestone: 8.6.1 Component: Template Haskell | Version: 8.0.1 Resolution: fixed | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4506 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed * milestone: => 8.6.1 Comment: Thanks for the patch! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13776#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC