#4429: Ability to specify the namespace in mkName
---------------------------------+------------------------------------------
Reporter: reinerp | Owner: reinerp
Type: feature request | Status: new
Priority: normal | Milestone: 7.4.1
Component: Template Haskell | Version: 6.12.3
Keywords: | Testcase:
Blockedby: | Difficulty:
Os: Unknown/Multiple | Blocking:
Architecture: Unknown/Multiple | Failure: None/Unknown
---------------------------------+------------------------------------------
Comment(by reinerp):
I've got a similar question, this time about {{{TyVarI}}}. Consider this
example:
{{{
{-# LANGUAGE TemplateHaskell, ScopedTypeVariables, TypeFamilies #-}
module ReifyTyVar where
import Language.Haskell.TH
f :: forall a. a -> a
f x = $( do { inf <- reify (mkName "a"); runIO (print inf); [| x |] })
g :: forall b. (b ~ Int) => b -> b
g x = $( do { inf <- reify (mkName "b"); runIO (print inf); [| x |] })
}}}
The following is printed at compile time:
{{{
TyVarI b_1627390992 (VarT b_1627391179)
TyVarI a_1627390993 (VarT a_1627393676)
}}}
In both of these cases, the {{{Type}}} field of {{{TyVarI}}} is just a
{{{VarT}}} of the {{{Name}}} field.
Are there any examples where this is not the case? I thought that {{{g}}}
might be such an example, because the type coercion {{{b ~ Int}}} is
available, but apparently not.
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/4429#comment:23>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs