Constructing TH types
Simon Peyton-Jones
simonpj at microsoft.com
Tue Oct 16 02:10:23 CEST 2012
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 at haskell.org [mailto:glasgow-haskell-users-
| bounces at haskell.org] On Behalf Of Eric M. Pashman
| Sent: 07 October 2012 18:09
| To: Nicolas Frisby
| Cc: glasgow-haskell-users at 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 <nicolas.frisby at gmail.com> 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
| <eric.pashman at gmail.com> 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,
|
|
| _______________________________________________
| Glasgow-haskell-users mailing list
| Glasgow-haskell-users at haskell.org
| http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
More information about the Glasgow-haskell-users
mailing list