TH.reify can be ambiguous when giving a name that's in multiple namespaces
What should this program do?
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeOperators #-}
module Bug where
import Language.Haskell.TH
(***) :: Bool -> Bool -> Bool
(***) _ _ = True
type (***) a b = Bool
$(return [])
main :: IO ()
main = putStrLn $(reify (mkName "***") >>= stringE . show)
The issue is that reify (mkName "***")
could conceivable look up the Info
of two different things: the value-level (***)
or the type-level (***)
. In this case, it happens to pick the value-level one:
$ /opt/ghc/8.2.1/bin/runghc Bug.hs
VarI Bug.*** (AppT (AppT ArrowT (ConT GHC.Types.Bool)) (AppT (AppT ArrowT (ConT GHC.Types.Bool)) (ConT GHC.Types.Bool))) Nothing
So if you want to look up the type-level (***)
's info in this way, you're hosed.
If the above scenario seems contrived, and you find yourself thinking "but RyanGlScott, why don't you just use '(***)
and ''(***)
?", keep in mind that there are times I need to look up //unqualified// names, and in those situations, mkName
is all I have at my disposal for creating the Name
to look up.
There has to be a better way to go about business here. Perhaps we should introduce another function
reifyAll :: Name -> [Info]
That finds all possible Info
s in all the namespaces the argument Name
can be found in?
Trac metadata
Trac field | Value |
---|---|
Version | 8.0.1 |
Type | Bug |
TypeOfFailure | OtherFailure |
Priority | normal |
Resolution | Unresolved |
Component | Template Haskell |
Test case | |
Differential revisions | |
BlockedBy | |
Related | |
Blocking | |
CC | |
Operating system | |
Architecture |