[GHC] #9066: Template Haskell cannot splice an infix declaration for a data constructor
GHC
ghc-devs at haskell.org
Mon Nov 3 15:43:03 UTC 2014
#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
More information about the ghc-tickets
mailing list