Constructing TH types
Eric M. Pashman
eric.pashman at gmail.com
Sat Oct 6 21:24:04 CEST 2012
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.
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. 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?)
Alternative approaches and general tips and hints are welcome as well. I'm fairly new to Haskell in general.
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
More information about the Glasgow-haskell-users
mailing list