これはかなり壊れやすい方法の1つですが、ある種の作業です。テンプレートhaskellが使用するExpで?xを参照することはできませんが、次のような別のモジュールで定義を参照することができます。
reserved_prefix_x = ?x
以下は、ghcの1回の実行で上記のような変数を生成するコードであり、ghcの2回目の実行では、変数は実際には暗黙のパラメーターを参照します。
{-# LANGUAGE TemplateHaskell, NoMonomorphismRestriction #-}
module GenMod (h) where
import Data.Generics
import Data.IORef
import Data.List
import Language.Haskell.Meta.Parse as P
import Language.Haskell.TH
import Language.Haskell.TH.Quote
import Language.Haskell.TH.Syntax
import qualified Data.Set as S
import qualified Language.Haskell.Exts.QQ as Q
import System.IO.Unsafe
h = Q.hs { quoteExp = \s -> do
r <- either fail (upVars . return) (P.parseExp s)
writeMod'
return r
}
pfx = "q_"
{-# NOINLINE vars #-}
vars :: IORef (S.Set String)
vars = unsafePerformIO (newIORef S.empty)
writeMod' = runIO $ writeFile "GEN.hs" . ppMod =<< readIORef vars
writeMod = -- might be needed to avoid multiple calls to writeFile?
-- in this example this is called for every use of `h'
QuasiQuoter { quoteDec = \ _ -> do
writeMod'
[d| _ = () |] }
ppMod xs = "{-# LANGUAGE NoMonomorphismRestriction, ImplicitParams #-}\n\
\module GEN where\n" ++
unlines (map (\x -> pfx ++ x ++ " = ?" ++ x) (S.toList xs))
upVars x = do
x' <- x
runIO $ modifyIORef vars (S.union (getMatchingVars x'))
runIO $ print =<< readIORef vars
return x'
getMatchingVars =
everything
S.union
(mkQ S.empty
(\ (OccName x) -> maybe S.empty S.singleton (stripPrefix pfx x)))
準クォーターGenMod.hsを使用するMain.hsファイル:
{-# LANGUAGE NoMonomorphismRestriction, ImplicitParams, QuasiQuotes, TemplateHaskell, CPP #-}
import GenMod
#ifndef stage1
import GEN
#endif
f_ = [h| q_hithere |]
次のように、ghcを2回呼び出す必要があります。
ghci -Dstage1 Main.hs
GHCi, version 7.6.1: http://www.haskell.org/ghc/ :? for help
[1 of 2] Compiling GenMod ( GenMod.hs, interpreted )
[2 of 2] Compiling Main ( Ex.hs, interpreted )
fromList ["hithere"]
Ex.hs:8:6: Not in scope: `q_hithere'
Failed, modules loaded: GenMod.
ghcは失敗しますが、それでも以下を含むGEN.hsを生成します。
{-# LANGUAGE NoMonomorphismRestriction, ImplicitParams #-}
module GEN where
q_hithere = ?hithere
Mainをロードするときにどちらが表示されますか(-Dフラグは省略)
*Main> :t f_
f_ :: (?hithere::t) => t
この種のトラブルはおそらくそれだけの価値はありません。たぶん、THから他のプログラムを呼び出す他の状況は、他の言語へのインライン呼び出しなど、より動機付けになりますhttp://hpaste.org/50837(gfortranの例)
haskell-src-metaのデフォルトのパーサーを使用したので、準引用符は「?x」ではなく「reserved_prefix_x」の変数を使用するようになります。「?x」をそれほど難しくなく受け入れることができるはずです。