2012-04-02 36 views
9

我正在寫一個代碼生成器,其輸出取決於存儲在其類實例中的數據類型字段描述。但是,我找不到如何用TH生成的參數運行函數。如何規避GHC階段限制?

{-# 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'] ] 

當另一個模塊嘗試使用發電機

{-# 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" []] 
-} 

似乎有一個錯誤

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) 

編輯:

當問我想,這個問題似乎只是因爲我只是沒有掌握TH中至關重要的一些東西,可以通過將某些功能移到TH中來解決其他模塊。

如果無法生成預先計算的數據,例如問題,我想了解更多關於TH的理論限制。

+1

我發現......令人驚訝的是,那是行不通的。也許你還需要打開QuasiQuotes? – 2012-04-02 16:26:25

回答

4

這確實是舞臺限制的問題。正如哈馬爾指出的那樣,問題在於撥打getDescription

let mkSubDesc t = ... getDescription (undefined :: $(return t)) ... 

功能getDescription過載,並且所述編譯器選擇基於其參數的類型的實施。

class HasDescription a where 
    getDescription :: a -> Description 

類型類根據類型重載。將t轉換爲類型的唯一方法是編譯它。但編譯它會將放入編譯的程序中。對getDescription的調用在編譯時間處運行,因此它無法訪問該類型。

如果你真的想在模板Haskell中評估getDescription,你必須編寫你自己的實現getDescription,它讀取模板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" 
7

可以通過移動let牛津括號內結合修復:

let mkSubDesc t = [| let Description desc ds = getDescription (undefined :: $(return t)) 
        in Description (desC++ "Modified") ds |] 

當然,這意味着,這將是所產生的代碼的一部分,但至少對於這種情況下,當不可沒關係。

+1

感謝您的建議。我想早些時候在括號內部移動,但是代碼會被頻繁調用,所以它必須很快。標準基準測試表明,使用let的getDescription比已經修改過的描述要慢(實際上我在其他函數和數據類型上嘗試過 - HasDescription只是一種簡化)。 – Boris 2012-04-02 19:49:13