Constructing TH types

Eric M. Pashman eric.pashman at gmail.com
Sun Oct 7 17:15:28 CEST 2012


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 <nicolas.frisby at gmail.com> wrote:

> On Sat, Oct 6, 2012 at 2:24 PM, Eric M. Pashman <eric.pashman at gmail.com> 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 at haskell.org
>> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users




More information about the Glasgow-haskell-users mailing list