Getting a type value out of a Typed Expression (template haskell)

Hi folks, I’m exploring Typed Expressions in Template Haskell. I’m hoping to use them in place of regular, untyped expressions, in a program which separately tracks the (supposed) type of said expression. My hope is I can infer the type from the typed-expression and remove the record fields which I’m using to try and track it independently. (I’m not cluttering this question with too many specifics of the program but I can expand on it and link to its source if desired)

It’s relatively straightforward to extract the untyped Expression from a Typed one; but I’m having a lot of trouble getting the type out. I’m not even sure it’s possible.

What I’d ideally like is a :: Name of the type but I could work with something more primitive. The TExp data type itself has the signature (cf)

TExp (a :: TYPE (r :: RuntimeRep))

Where TYPE, I hadn’t come across before, appears to be some (potentially internal) GHC type (the hyperlinks in that Hackage Haddock documentation I linked are broken, but elsewhere I’ve seen them link over to ghc-prim)

There does not appear to be any constructor or convenience function provided in template-haskell library to get the type out as a value. Can anyone give me a hint as to how I might achieve that? Thanks!

2 Likes

If I understand the problem correctly, there doesn’t seem to be an easy way to get the type of a TExp as a quoted TH.Type at the moment. This could be done using a class:

class LiftType (a :: k) where
  liftType :: TH.Type  -- a should be equal to $(pure (liftType @a))

instance {-# OVERLAPPABLE #-} (LiftType a, LiftType b) => LiftType (a b) where
  liftType = AppT (liftType @a) (liftType @b)

instance LiftType Int where liftType = ConT ''Int
instance LiftType [] where liftType = ConT ''[]
-- etc.

typeOf :: forall a. LiftType a => texp a -> TH.Type
typeOf = liftType @a
1 Like