问题
In a haskell project using template haskell, I am trying to generate an expression that has a type annotation as a phantom type.
A simple example would be a situation with DataKinds
and KindSignatures
like:
{-# LANGUAGE DataKinds, KindSignatures #-}
data Foo = A | B
data GenMe (w :: Foo) = GenMe Int
[| $(generate some code) :: GenMe $(genType someCompileTimeData) |]
How can I write a function, like genType
such that
genType :: Foo -> Q Type
lifting just lifts the variable holding the compile time Foo
value? I don't know which constructor to use from the Type Data Constructors
to make data kinds.
Any thoughts? Thanks!
回答1:
Another way to slice this problem is to define a promote :: Exp -> Maybe Type
function and then use lift on Foo
.
-- | Takes the AST for an expression and tries to produce the corresponding
-- promoted type AST.
promote :: Exp -> Q Type
promote (VarE n) = fail ("Cannot promote variable " ++ show n)
promote (ConE n) = pure (PromotedT n)
promote (LitE l) = LitT <$> promoteLit l
promote (TupE es) = foldl AppT (PromotedTupleT (length es)) <$> (traverse promote es)
promote (ListE es) = foldr (\x xs -> AppT (AppT PromotedConsT x) xs) PromotedNilT <$> (traverse promote es)
promote (ParensE e) = ParensT <$> promote e
promote (AppE e1 e2) = AppT <$> promote e1 <*> promote e2
promote (InfixE (Just e1) e2 (Just e3)) = AppT <$> (AppT <$> promote e2 <*> promote e1) <*> promote e3
promote _ = fail "Either impossible to promote or unimplemented"
-- | Promote an expression literal to a type one
promoteLit :: Lit -> Q TyLit
promoteLit (StringL s) = pure (StrTyLit s)
promoteLit (IntegerL i) = pure (NumTyLit i)
promoteLit _ = fail "Expression literal cannot be promoted"
Then, I think something along the lines of the following should work
ghci> :set -XDeriveLift -XDataKinds -XKindSignatures -XTemplateHaskell -XQuasiQuotes
ghci> data Foo = A | B deriving (Lift)
ghci> foo1 = A
ghci> data GenMe (w :: Foo) = GenMe Int
ghci> runQ [| GenMe 1 :: GenMe $(promote =<< lift foo1) |]
SigE (AppE (ConE Ghci5.GenMe) (LitE (IntegerL 1))) (AppT (ConT Ghci5.GenMe) (PromotedT Ghci3.A))
来源:https://stackoverflow.com/questions/46718002/generating-a-type-annotation-using-datakinds-within-a-th-quasiquote