Bor*_*ris 9 haskell template-haskell
我正在编写一个代码生成器,其输出依赖于存储在其类实例中的数据类型字段描述.但是,我找不到如何使用TH生成的参数运行函数.
{-# LANGUAGE TemplateHaskell, ScopedTypeVariables #-}
module Generator where
import Language.Haskell.TH
import Language.Haskell.TH.Syntax
data Description = Description String [Description] deriving Show
class HasDescription a where
getDescription :: a -> Description
instance HasDescription Int where
getDescription _ = Description "Int" []
instance (HasDescription a, HasDescription b) => HasDescription (a, b) where
getDescription (_ :: (a, b)) = Description "Tuple2" [getDescription (undefined :: a), getDescription (undefined :: b)]
-- | creates instance of HasDescription for the passed datatype changing descriptions of its fields
mkHasDescription :: Name -> Q [Dec]
mkHasDescription dName = do
reify dName >>= runIO . print
TyConI (DataD cxt name tyVarBndr [NormalC cName types] derives) <- reify dName
-- Attempt to get description of data to modify it.
let mkSubDesc t = let Description desc ds = getDescription (undefined :: $(return t)) in [| Description $(lift $ desc ++ "Modified") $(lift ds) |]
let body = [| Description $(lift $ nameBase dName) $(listE $ map (mkSubDesc . snd) types) |]
getDescription' <- funD 'getDescription [clause [wildP] (normalB body) []]
return [ InstanceD [] (AppT (ConT ''HasDescription) (ConT dName)) [getDescription'] ]
Run Code Online (Sandbox Code Playgroud)
当另一个模块尝试使用Generator时
{-# LANGUAGE TemplateHaskell, ScopedTypeVariables #-}
import Generator
data MyData = MyData Int Int
mkHasDescription ''MyData
{- the code I want to generate
instance HasDescription MyData where
getDescription _ = Description "MyData" [Description "IntModified" [], Description "IntModified" []]
-}
Run Code Online (Sandbox Code Playgroud)
出现错误
Generator.hs:23:85:
GHC stage restriction: `t'
is used in a top-level splice or annotation,
and must be imported, not defined locally
In the first argument of `return', namely `t'
In the expression: return t
In an expression type signature: $(return t)
Run Code Online (Sandbox Code Playgroud)
编辑:
当问我认为问题出现只是因为我没有抓住TH中的关键部分,并且可以通过将一些功能移动到其他模块来解决.
如果不可能像问题中的例子那样生成预先计算的数据,我想更多地了解TH的理论限制.
你可以通过移动let
牛津支架内的绑定来修复它:
let mkSubDesc t = [| let Description desc ds = getDescription (undefined :: $(return t))
in Description (desc ++ "Modified") ds |]
Run Code Online (Sandbox Code Playgroud)
当然,这意味着这将是生成的代码的一部分,但至少在这种情况下,这应该不重要.
这确实是阶段限制的问题。正如哈马尔指出的那样,问题在于对 的调用getDescription
。
let mkSubDesc t = ... getDescription (undefined :: $(return t)) ...
Run Code Online (Sandbox Code Playgroud)
该函数getDescription
被重载,编译器根据其参数的类型选择实现。
class HasDescription a where
getDescription :: a -> Description
Run Code Online (Sandbox Code Playgroud)
类型类根据类型进行重载。转换为类型的唯一方法t
是编译它。但编译它会将类型放入已编译的程序中。对 的调用在编译时getDescription
运行,因此它无法访问该类型。
如果您确实想getDescription
在 Template Haskell 中进行评估,则必须编写自己的实现来getDescription
读取编译时可用的 Template Haskell 数据结构。
getDescription2 :: Type -> Q Description
getDescription2 t = cases con [ ([t| Int |], "Int")
, (return (TupleT 2), "Tuple")
]
where
(con, ts) = fromApp t
fromApp (AppT t1 t2) = let (c, ts) = fromApp t1 in (c, ts ++ [t2])
fromApp t = (t, [])
cases x ((make_y, name):ys) = do y <- make_y
if x == y
then do ds <- mapM getDescription2 ts
return $ Description name ds
else cases x ys
cases x [] = error "getDescription: Unrecognized type"
Run Code Online (Sandbox Code Playgroud)
归档时间: |
|
查看次数: |
1304 次 |
最近记录: |