我需要将编译脚本中的一些信息传递给Template Haskell。目前,编译脚本将信息保存在系统环境中,因此我只是使用System.Environment.getEnvironment
中包含的runIO
来阅读它。有没有更好的方法,例如将一些参数传递给ghc
(类似于C预处理器的-D...
),或者也许是为TH专门为此目的设计的?
答案 0 :(得分:13)
由于有这么多人对这个问题感兴趣,我会添加我目前的方法,也许有人会发现它很有用。可能最好的方法是,如果TH允许在GHC的命令行上读取-D
参数,但似乎没有像现在这样的实现。
一个简单的模块允许TH读取编译时环境。辅助函数也允许读取文件;例如,从环境中读取配置文件的路径,然后读取文件。
{-# LANGUAGE TemplateHaskell #-}
module THEnv
(
-- * Compile-time configuration
lookupCompileEnv
, lookupCompileEnvExp
, getCompileEnv
, getCompileEnvExp
, fileAsString
) where
import Control.Monad
import qualified Data.Text as T
import qualified Data.Text.IO as T
import Language.Haskell.TH
import Language.Haskell.TH.Syntax (Lift(..))
import System.Environment (getEnvironment)
-- Functions that work with compile-time configuration
-- | Looks up a compile-time environment variable.
lookupCompileEnv :: String -> Q (Maybe String)
lookupCompileEnv key = lookup key `liftM` runIO getEnvironment
-- | Looks up a compile-time environment variable. The result is a TH
-- expression of type @Maybe String@.
lookupCompileEnvExp :: String -> Q Exp
lookupCompileEnvExp = (`sigE` [t| Maybe String |]) . lift <=< lookupCompileEnv
-- We need to explicly type the result so that things like `print Nothing`
-- work.
-- | Looks up an compile-time environment variable and fail, if it's not
-- present.
getCompileEnv :: String -> Q String
getCompileEnv key =
lookupCompileEnv key >>=
maybe (fail $ "Environment variable " ++ key ++ " not defined") return
-- | Looks up an compile-time environment variable and fail, if it's not
-- present. The result is a TH expression of type @String@.
getCompileEnvExp :: String -> Q Exp
getCompileEnvExp = lift <=< getCompileEnv
-- | Loads the content of a file as a string constant expression.
-- The given path is relative to the source directory.
fileAsString :: FilePath -> Q Exp
fileAsString = do
-- addDependentFile path -- works only with template-haskell >= 2.7
stringE . T.unpack . T.strip <=< runIO . T.readFile
可以像这样使用:
{-# LANGUAGE TemplateHaskell #-}
import THEnv
main = print $( lookupCompileEnvExp "DEBUG" )
然后:
runhaskell Main.hs
打印Nothing
; DEBUG="yes" runhaskell Main.hs
打印Just "yes"
。答案 1 :(得分:3)