9

クラスインスタンスに格納されているデータ型フィールドの説明に出力が依存するコードジェネレーターを作成しています。ただし、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'] ]

別のモジュールが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" []]
-}

エラーが表示されます

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の理論上の制限について詳しく知りたいと思います。

4

2 に答える 2

7

letバインディングをオックスフォード ブラケット内に移動することで修正できます。

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

もちろん、これは生成されたコードの一部になることを意味しますが、少なくともこの場合は問題になりません。

于 2012-04-02T16:49:24.823 に答える
4

これは確かにステージ制限の問題です。ハンマーが指摘したように、問題はへの呼び出しにありますgetDescription

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

関数getDescriptionはオーバーロードされ、コンパイラーは引数のタイプに基づいて実装を選択します。

class HasDescription a where
  getDescription :: a -> Description

型クラスは型に基づいてオーバーロードされます。型に変換する唯一の方法tは、それをコンパイルすることです。しかし、それをコンパイルすると、その型はコンパイルされたプログラムに入れられます。の呼び出しはコンパイル時getDescriptionに実行されるため、そのタイプにアクセスすることはできません。

テンプレートHaskellで本当に評価したい場合は、コンパイル時に利用可能なテンプレートHaskellデータ構造を読み取るgetDescription独自の実装を作成する必要があります。getDescription

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"
于 2012-04-02T20:49:16.597 に答える