Re: Constructing TH types

Nicolas, thanks for the welcome, and thanks for pointing out the additional 'Type' constructors!
I'd looked over the available constructors, but apparently not very well. The 'ListT', 'TupleT', 'ArrowT', etc., constructors are precisely what I need to make this work in a straightforward fashion.
So I don't actually have a problem making the right 'Name' value, just a problem reading the TH source. Well, that's that. ...
Many thanks,
Eric
On Oct 7, 2012, at 24:22 , Nicolas Frisby
On Sat, Oct 6, 2012 at 2:24 PM, Eric M. Pashman
wrote: Hello,
I'm using Template Haskell (which I've just begun to learn) to do "stanamic" type-checking. Basically I'm just converting 'TypeRep' and 'TyCon' values (from 'Data.Typeable') into Template Haskell's representation (i.e., values of the 'Type' datatype) and splicing them as type signatures in code where compile-time type inference is otherwise impossible.
Hi Eric. I'm going to try to answer each of your questions below, but it's not entirely clear to me what you are trying to do. If you can provide more context, we might be able to give better answers or perhaps suggest alternative approaches.
My first thought was simply to make a TH 'Name' from the 'show' representation of a 'TypeRep', and turn that into a 'Type':
toType :: TypeRep -> Type toType = ConT . mkName . show
This works for simple, atomic types like 'Int', but it chokes on compound types (I mean those with a type parameter, e.g. 'Maybe Int'.), for reasons I don't quite understand.
If I fire up ghci and enter the following
Prelude> :type Language.Haskell.TH.ConT
I get back (roughly) the answer: ConT :: Name -> Type
In particular, note that the argument to ConT is a name. Your code indeed builds a name, but, in your example, it builds the invalid name "Maybe Int". When I splice in the resulting type (ConT (mkName "Maybe Int")), I get the error message
Not in scope: type constructor or class `Maybe Int'
ConT is only for a single named type; it cannot (by itself) represent general types. Does that explanation get the big picture across?
In particular, it cannot (by itself) represent an applications of one named type to another. The type "Maybe Int" can be correctly represented as ConT (mkName "Maybe") `AppT` ConT (mkName "Int"). Or, even better, as ConT ''Maybe `AppT` ConT ''Int. Those ''s are both two occurrences of single quotes — very handy but less known TH syntax.
So I tried this instead:
toType tr = foldr (flip AppT . toType) (tcToType tc) trs where (tc, trs) = splitTyConApp tr
tcToType :: TyCon -> Type tcToType = ConT . mkName . show
This works for both simple types and compound types made from standard prefix type-constructors, but it breaks on sugared constructors like '[]'; a 'TypeRep' for, say, '[Int]' gets turned into an invalid type that spliced in as '[] Int'.
Basically I don't quite understand how 'Name' construction and binding works. Is there a better way to make a 'Name' that will work with sugared type constructors, or do I have to special-case them while doing something like the above? (If so, what are all the special cases? Anything beyond lists and tuples?)
Someone else can surely better explain Name construction and binding. I recall there being subtleties, but instead of internalizing them, I have been fortunate in my needs to be able to avoid mkName altogether (via the ' and '' syntax). It sounds like you might actually require it for you needs though. Hopefully someone else chimes in.
Without more context, I'm not seeing an obviously more robust way that will suite your needs.
One way to see which special cases there are is to fire up ghci and look at the constructors of the Type type.
Prelude> :info Language.Haskell.TH.Type data Type = ForallT [TyVarBndr] Cxt Type | AppT Type Type | SigT Type Kind | VarT Name | ConT Name | PromotedT Name | TupleT Int | UnboxedTupleT Int | ArrowT | ListT | PromotedTupleT Int | PromotedNilT | PromotedConsT | StarT | ConstraintT | LitT TyLit
There are some fancier things in these constructors like support for universal quantification and promotion, but the three constructors that I'm guessing you're most likely to be interested in as special cases are TupleT, ArrowT, and ListT. These are all pretty much pairwise interchangable, eg ArrowT for (ConT ''(GHC.Prim.->)) and ListT for (ConT ''[]). And unless my experience is out-of-date with respect to this now, sometimes TupleT doesn't always show up instead of a type like (ConT ''(GHC.Tuple.(,,,))).
HTH.
Alternative approaches and general tips and hints are welcome as well. I'm fairly new to Haskell in general.
Welcome, enjoy, and good luck!
Regards,
Eric
PS: To compile the code above, you just need these imports:
import Language.Haskell.TH import Data.Typeable (TyCon, TypeRep, splitTyConApp)
Here are some test cases:
import Data.Typeable (typeOf)
tr0 = typeOf (undefined :: Int) -- Simple tr1 = typeOf (undefined :: Maybe Int) -- Compound, infix tr = typeOf (undefined :: [Int]) -- Compound, sugared
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

The issue you had with applications of the [] type seems to be more
insidious than my last email made it out to be. This expression
( $(return $ ConE (mkName "[]")) ::
$(return $ ConT (mkName "[]") `AppT` ConT ''Char)
)
fails with "[] is applied to too many arguments". I'm thinking that
the "[]" in the type is being resolved somehow to the the [] data
constructor, not the [] type constructor.
This seems specific to []; the following works for tuples, even though
the data and type constructor also share a string name.
$(return $ ConE (mkName "(,)") `AppE` LitE (CharL 'c') `AppE` LitE
(CharL 'a')) ::
$(return $ ConT (mkName "(,)") `AppT` ConT ''Char `AppT` ConT ''Char)
I haven't yet narrowed down where the mkName'd string is
(inappropriately?) resolved in the GHC source.
Eric, special-casing for ArrowT probably avoids this problem for you.
The only thing to glean from this email is that you ideally wouldn't
need to worry about the special-casing for your current application —
I think there's a TH bug at play, though I haven't found an open GHC
ticket for it and it may very well still be a known issue.
On Sun, Oct 7, 2012 at 10:15 AM, Eric M. Pashman
Nicolas, thanks for the welcome, and thanks for pointing out the additional 'Type' constructors!
I'd looked over the available constructors, but apparently not very well. The 'ListT', 'TupleT', 'ArrowT', etc., constructors are precisely what I need to make this work in a straightforward fashion.
So I don't actually have a problem making the right 'Name' value, just a problem reading the TH source. Well, that's that. ...
Many thanks,
Eric
My pleasure. However,

Nicolas,
Intended usage seems to be something like
AppT ListT $ ConT . mkName $ "Int"
That works. So it seems that there is indeed no way to construct the syntactically special list type from its (valid) name, but it can easily be done as above.
In my opinion, it should be possible to do what we've been trying -- ConT (mkName "[]") `AppT` ConT "Char" -- or whatever. The problem seems simply to be that
ConT . mkName $ "[]" \= ListT
I don't know the first thing about the GHC source, but I would imagine that's easily fixable if the behavior we both expected is more broadly desired.
Regards,
Eric
On Oct 7, 2012, at 11:24 , Nicolas Frisby
The issue you had with applications of the [] type seems to be more insidious than my last email made it out to be. This expression
( $(return $ ConE (mkName "[]")) :: $(return $ ConT (mkName "[]") `AppT` ConT ''Char) )
fails with "[] is applied to too many arguments". I'm thinking that the "[]" in the type is being resolved somehow to the the [] data constructor, not the [] type constructor.
This seems specific to []; the following works for tuples, even though the data and type constructor also share a string name.
$(return $ ConE (mkName "(,)") `AppE` LitE (CharL 'c') `AppE` LitE (CharL 'a')) :: $(return $ ConT (mkName "(,)") `AppT` ConT ''Char `AppT` ConT ''Char)
I haven't yet narrowed down where the mkName'd string is (inappropriately?) resolved in the GHC source.
Eric, special-casing for ArrowT probably avoids this problem for you. The only thing to glean from this email is that you ideally wouldn't need to worry about the special-casing for your current application — I think there's a TH bug at play, though I haven't found an open GHC ticket for it and it may very well still be a known issue.
On Sun, Oct 7, 2012 at 10:15 AM, Eric M. Pashman
wrote: Nicolas, thanks for the welcome, and thanks for pointing out the additional 'Type' constructors!
I'd looked over the available constructors, but apparently not very well. The 'ListT', 'TupleT', 'ArrowT', etc., constructors are precisely what I need to make this work in a straightforward fashion.
So I don't actually have a problem making the right 'Name' value, just a problem reading the TH source. Well, that's that. ...
Many thanks,
Eric
My pleasure.
However,

Whoops, sorry for the bad code in my last message. I mean of course that the problem is that
ConT (mkName "[]") /= ListT
Regards,
Eric
On Oct 7, 2012, at 12:08 , Eric M. Pashman
Nicolas,
Intended usage seems to be something like
AppT ListT $ ConT . mkName $ "Int"
That works. So it seems that there is indeed no way to construct the syntactically special list type from its (valid) name, but it can easily be done as above.
In my opinion, it should be possible to do what we've been trying -- ConT (mkName "[]") `AppT` ConT "Char" -- or whatever. The problem seems simply to be that
ConT . mkName $ "[]" \= ListT
I don't know the first thing about the GHC source, but I would imagine that's easily fixable if the behavior we both expected is more broadly desired.
Regards,
Eric
On Oct 7, 2012, at 11:24 , Nicolas Frisby
wrote: The issue you had with applications of the [] type seems to be more insidious than my last email made it out to be. This expression
( $(return $ ConE (mkName "[]")) :: $(return $ ConT (mkName "[]") `AppT` ConT ''Char) )
fails with "[] is applied to too many arguments". I'm thinking that the "[]" in the type is being resolved somehow to the the [] data constructor, not the [] type constructor.
This seems specific to []; the following works for tuples, even though the data and type constructor also share a string name.
$(return $ ConE (mkName "(,)") `AppE` LitE (CharL 'c') `AppE` LitE (CharL 'a')) :: $(return $ ConT (mkName "(,)") `AppT` ConT ''Char `AppT` ConT ''Char)
I haven't yet narrowed down where the mkName'd string is (inappropriately?) resolved in the GHC source.
Eric, special-casing for ArrowT probably avoids this problem for you. The only thing to glean from this email is that you ideally wouldn't need to worry about the special-casing for your current application — I think there's a TH bug at play, though I haven't found an open GHC ticket for it and it may very well still be a known issue.
On Sun, Oct 7, 2012 at 10:15 AM, Eric M. Pashman
wrote: Nicolas, thanks for the welcome, and thanks for pointing out the additional 'Type' constructors!
I'd looked over the available constructors, but apparently not very well. The 'ListT', 'TupleT', 'ArrowT', etc., constructors are precisely what I need to make this work in a straightforward fashion.
So I don't actually have a problem making the right 'Name' value, just a problem reading the TH source. Well, that's that. ...
Many thanks,
Eric
My pleasure.
However,

Eric, Nicolas
Sorry to be slow on this thread. Here's a summary. Would one of you feel able to take this summary, edit in a few examples, and add it to the (user-land) Haskell Wiki at haskell.org? There are quite a few explanatory pages about GHC there, and this explanation will otherwise get buried in an un-findable email trail? (I don't have internet right now, so I can't tell you exactly where to hook it in, but would be happy to suggest once back online.) Thanks!
Simon
TypeRep
~~~~~
A TypeRep is defined like this (in Data.Typeable.Internals):
data TypeRep = TypeRep Fingerprint TyCon [TypeRep]
That is, a TypeRep is always the application of a TyCon to zero or more TypeReps. A TypeRep can't represent a polymorphic type or a type variable. (Well, not right now anyway.)
The Fingerprint uniquely identifies the TypeRep, allowing fast comparison.
TypeRep is an abstract type, but you can decompose it with
splitTyConApp :: TypeRep -> (TyCon, [TypeRep])
defined in Data.Typeable.
A TyCon is short for "type constructor". You can get its defining package, defining module, and occurrence name with
tyConPackage, -- :: TyCon -> String
tyConModule, -- :: TyCon -> String
tyConName, -- :: TyCon -> String
all in Data.Typeable.
Template Haskell Names
~~~~~~~~~~~~~~~
Template Haskell Names come in various kinds. Look at the Name data type declaration in Language.Haskell.TH.Syntax:
data Name = Name OccName NameFlavour
data NameFlavour
= NameS -- ^ An unqualified name; dynamically bound
| NameQ ModName -- ^ A qualified name; dynamically bound
| NameU Int# -- ^ A unique local name
| NameL Int# -- ^ Local name bound outside of the TH AST
| NameG NameSpace PkgName ModName
data NameSpace = VarName | DataName | TcClsName
Again the Name type is abstract, but TH provides constructor functions.
mkName :: String -> Name
(mkName "foo") and (mkName "Foo.foo") return a TH Name with a NameS or NameQ flavour respectively. They are bound to whatever "foo" or "Foo.foo" happens to be in scope at the *occurrence* site. This is like dynamic binding, to be *** avoided if at all possible ***, because it's subject to the stuff that's in scope at the point that this TH blob is finally spliced in.
Much better is
newName :: String -> Q Name
which makes up a fresh name, generating a NameU.
Finally, we have
mkNameG_v, mkNameG_tc, mkNameG_d :: String -> String -> String -> Name
These take three arguments (package, module, occurrence-name) and build a Name that means the thing *defined* in that package and module, with that occurrence name. There are three variants, for ordinary variables, type constructors, and data constructors. There's also a variant that takes a NameSpace argument:
mkNameG :: NameSpace -> String -> String -> String -> Name
Converting
~~~~~~~
If you want to get from a TyCon (from Data.Typeable) to a Name (from TH), you can just extract the package, module, and occurrence name, and use mkNameG_tc to construct the TH Name.
| -----Original Message-----
| From: glasgow-haskell-users-bounces@haskell.org [mailto:glasgow-haskell-users-
| bounces@haskell.org] On Behalf Of Eric M. Pashman
| Sent: 07 October 2012 18:09
| To: Nicolas Frisby
| Cc: glasgow-haskell-users@haskell.org
| Subject: Re: Constructing TH types
|
| Nicolas,
|
| Intended usage seems to be something like
|
| AppT ListT $ ConT . mkName $ "Int"
|
| That works. So it seems that there is indeed no way to construct the syntactically
| special list type from its (valid) name, but it can easily be done as above.
|
| In my opinion, it should be possible to do what we've been trying -- ConT
| (mkName "[]") `AppT` ConT "Char" -- or whatever. The problem seems simply to
| be that
|
| ConT . mkName $ "[]" \= ListT
|
| I don't know the first thing about the GHC source, but I would imagine that's
| easily fixable if the behavior we both expected is more broadly desired.
|
| Regards,
|
| Eric
|
| On Oct 7, 2012, at 11:24 , Nicolas Frisby
participants (3)
-
Eric M. Pashman
-
Nicolas Frisby
-
Simon Peyton-Jones