[GHC] #9066: Template Haskell cannot splice an infix declaration for a data constructor

#9066: Template Haskell cannot splice an infix declaration for a data constructor ------------------------------------+------------------------------------- Reporter: goldfire | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.8.2 Keywords: | Operating System: Unknown/Multiple Architecture: Unknown/Multiple | Type of failure: None/Unknown Difficulty: Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | ------------------------------------+------------------------------------- When I say {{{ $([d| data Blargh = (:<=>) Int Int infix 4 :<=> |]) }}} I get {{{ Illegal variable name: ‘:<=>’ When splicing a TH declaration: infix 4 :<=>_0 }}} The code inside the TH quote works when not used with TH. I will fix in due course. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9066 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9066: Template Haskell cannot splice an infix declaration for a data constructor -------------------------------------+------------------------------------- Reporter: goldfire | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: Component: Template | Version: 7.8.2 Haskell | Keywords: Resolution: | Architecture: Unknown/Multiple Operating System: | Difficulty: Unknown Unknown/Multiple | Blocked By: Type of failure: | Related Tickets: None/Unknown | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by goldfire): This also fails for type constructors: {{{ $( [d| type Foo a b = Either a b infix 5 `Foo` |]) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9066#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9066: Template Haskell cannot splice an infix declaration for a data constructor -------------------------------------+------------------------------------- Reporter: goldfire | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: Component: Template | Version: 7.8.2 Haskell | Keywords: Resolution: | Architecture: Unknown/Multiple Operating System: | Difficulty: Unknown Unknown/Multiple | Blocked By: Type of failure: | Related Tickets: None/Unknown | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by goldfire): Harrumph. In that second case, {{{[d| infix 5 `Foo` |]}}} produces an `Exact` `RdrName` for `Foo` that names a ''data'' constructor, not a ''type'' constructor, even when only the type constructor is in scope. Then, according to `Note [dataTcOccs and Exact Names]` in !RnEnv, the `Exact` `RdrName`s are trusted to have the right namespace and, so a naive fix for this bug fails the `Foo` case. There are two possible ways forward that I see: 1. Don't trust `Exact` `RdrName`s in `dataTcOccs`. That is, when we have an `Exact` constructor name, also look for the type with same spelling. 2. Duplicate the `dataTcOccs` logic in !DsMeta. I favor (2), because code that consumes the TH AST will want the `TH.Name`s to have the right namespaces. It's really a bug that the fixity declaration above refers to a data constructor `Foo`. Going to implement (2). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9066#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9066: Template Haskell cannot splice an infix declaration for a data constructor -------------------------------------+------------------------------------- Reporter: goldfire | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: Component: Template | Version: 7.8.2 Haskell | Keywords: Resolution: | Architecture: Unknown/Multiple Operating System: | Difficulty: Unknown Unknown/Multiple | Blocked By: Type of failure: | Related Tickets: None/Unknown | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by goldfire): Well, option (2) is infeasible. This is because desugaring a quoted fixity declaration produces `TH.Name`s that do ''not'' have namespace information attached. This is a consequence of the fact that namespace information is available only with `TH.Name`'s `NameG` constructor, which also has package and module information. Of course, when processing a quote, we have no idea what package/module the declaration will eventually end up in, so `NameG` is a non-starter. Thus, we have no namespace information here, and instead must be liberal when processing `Exact` `RdrName`s. I suppose the Right Way to fix this is to add namespace information to TH's `NameU` and `NameL` constructors, but that probably has farther- reaching implications than need to be dealt with at this moment. Going to implement (1). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9066#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9066: Template Haskell cannot splice an infix declaration for a data constructor -------------------------------------+------------------------------------- Reporter: goldfire | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: Component: Template | Version: 7.8.2 Haskell | Keywords: Resolution: | Architecture: Unknown/Multiple Operating System: | Difficulty: Unknown Unknown/Multiple | Blocked By: Type of failure: | Related Tickets: None/Unknown | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by simonpj): I'm a bit confused. * What does the TH syntax look like? Presumably `InfixD fixity name` where `name :: TH.Name`. * What is the flavour of that `name`? Presumably not a `NameG`? So `NameS` or `NameL`? * If `NameS`, we never generate an `Exact` `RdrName`, so I guess `NameL`? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9066#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9066: Template Haskell cannot splice an infix declaration for a data constructor -------------------------------------+------------------------------------- Reporter: goldfire | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: Component: Template | Version: 7.8.2 Haskell | Keywords: Resolution: | Architecture: Unknown/Multiple Operating System: | Difficulty: Unknown Unknown/Multiple | Blocked By: Type of failure: | Related Tickets: None/Unknown | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by goldfire): This sample program was educational for me: {{{ import Language.Haskell.TH.Syntax import GHC.Exts ( Int(I#) ) import Data.Generics ( listify ) $( do let getNames = listify (const True :: Name -> Bool) showNS VarName = "VarName" showNS DataName = "DataName" showNS TcClsName = "TcClsName" showFlav NameS = "NameS" showFlav (NameQ mod) = "NameQ " ++ show mod showFlav (NameU i) = "NameU " ++ show (I# i) showFlav (NameL i) = "NameL " ++ show (I# i) showFlav (NameG ns pkg mod) = "NameG " ++ showNS ns ++ " " ++ show pkg ++ " " ++ show mod toString (Name occ flav) = show occ ++ " (" ++ showFlav flav ++ ")" decs <- [d| type Foo a b = Either a b infix 5 `Foo` data Blargh = Foo |] runIO $ do putStr $ unlines $ map show decs putStrLn "" putStr $ unlines $ map toString $ getNames decs return [] ) }}} The goal here is to learn more about the `Name`s used in the desugaring. Here is my output: {{{ TySynD Foo_1627434972 [PlainTV a_1627434975,PlainTV b_1627434976] (AppT (AppT (ConT Data.Either.Either) (VarT a_1627434975)) (VarT b_1627434976)) InfixD (Fixity 5 InfixN) Foo_1627434974 InfixD (Fixity 5 InfixN) Foo_1627434972 DataD [] Blargh_1627434973 [] [NormalC Foo_1627434974 []] [] OccName "Foo" (NameU 1627434972) OccName "a" (NameU 1627434975) OccName "b" (NameU 1627434976) OccName "Either" (NameG TcClsName PkgName "base" ModName "Data.Either") OccName "a" (NameU 1627434975) OccName "b" (NameU 1627434976) OccName "Foo" (NameU 1627434974) OccName "Foo" (NameU 1627434972) OccName "Blargh" (NameU 1627434973) OccName "Foo" (NameU 1627434974) }}} We see here a few things: - My solution (2) above is already somewhat implemented. Note that the quote has only '''1''' fixity declaration, but the desugared TH AST has '''2'''! This was the essence of my idea (2) above. - GHC correctly notices the difference between the type `Foo` and the data constructor `Foo` in a quote. - All of the local names are `NameU`s. These `NameU`s indeed become `Exact`s during splicing. But, the round trip from quote to TH AST to splice loses the namespace information, because `NameU`s do not carry namespace info. So, we either add namespace information to `NameU` or implement (1), above. Adding namespace info to `NameU` is slightly annoying, because fixity declarations are the ''only'' place that the namespace isn't apparent from a usage site. Another possible solution is to add namespace info to the `InfixD` TH constructor. This is dissatisfactory because TH should model concrete syntax, and concrete syntax doesn't have a namespace marker there. I'm happy to take suggestions, but my tendency is toward (1). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9066#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9066: Template Haskell cannot splice an infix declaration for a data constructor -------------------------------------+------------------------------------- Reporter: goldfire | Owner: goldfire Type: bug | Status: patch Priority: normal | Milestone: Component: Template | Version: 7.8.2 Haskell | Keywords: Resolution: | Architecture: Unknown/Multiple Operating System: | Difficulty: Unknown Unknown/Multiple | Blocked By: Type of failure: | Related Tickets: None/Unknown | Test Case: | Blocking: | Differential Revisions: Phab:D424 | -------------------------------------+------------------------------------- Changes (by goldfire): * status: new => patch * differential: => Phab:D424 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9066#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9066: Template Haskell cannot splice an infix declaration for a data constructor
-------------------------------------+-------------------------------------
Reporter: goldfire | Owner: goldfire
Type: bug | Status: patch
Priority: normal | Milestone:
Component: Template | Version: 7.8.2
Haskell | Keywords:
Resolution: | Architecture: Unknown/Multiple
Operating System: | Difficulty: Unknown
Unknown/Multiple | Blocked By:
Type of failure: | Related Tickets:
None/Unknown |
Test Case: |
Blocking: |
Differential Revisions: Phab:D424 |
-------------------------------------+-------------------------------------
Comment (by Richard Eisenberg

#9066: Template Haskell cannot splice an infix declaration for a data constructor
-------------------------------------+-------------------------------------
Reporter: goldfire | Owner: goldfire
Type: bug | Status: patch
Priority: normal | Milestone:
Component: Template | Version: 7.8.2
Haskell | Keywords:
Resolution: | Architecture: Unknown/Multiple
Operating System: | Difficulty: Unknown
Unknown/Multiple | Blocked By:
Type of failure: | Related Tickets:
None/Unknown |
Test Case: |
Blocking: |
Differential Revisions: Phab:D424 |
-------------------------------------+-------------------------------------
Comment (by Richard Eisenberg

#9066: Template Haskell cannot splice an infix declaration for a data constructor -------------------------------------+------------------------------------- Reporter: goldfire | Owner: goldfire Type: bug | Status: closed Priority: normal | Milestone: Component: Template | Version: 7.8.2 Haskell | Keywords: Resolution: fixed | Architecture: Unknown/Multiple Operating System: | Difficulty: Unknown Unknown/Multiple | Blocked By: Type of failure: | Related Tickets: None/Unknown | Test Case: th/T9066 | Blocking: | Differential Revisions: Phab:D424 | -------------------------------------+------------------------------------- Changes (by goldfire): * status: patch => closed * testcase: => th/T9066 * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9066#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9066: Template Haskell cannot splice an infix declaration for a data constructor -------------------------------------+------------------------------------- Reporter: goldfire | Owner: goldfire Type: bug | Status: closed Priority: normal | Milestone: Component: Template Haskell | Version: 7.8.2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: th/T9066 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D424 Wiki Page: | -------------------------------------+------------------------------------- Comment (by mpickering): I don't think this was every really fixed properly and the wrinkle still exists in `RnEnv`. It seems that requiring namespace information on the `InfixD` constructor is the best way forward. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9066#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC