简体   繁体   English

如何正确地将编译时信息传达给Template Haskell函数?

[英]How to properly communicate compile-time information to Template Haskell functions?

I need to communicate some information from compile scripts into Template Haskell. 我需要将一些信息从编译脚本传达到Template Haskell中。 Currently the compile scripts keep the information in the system environment, so I just read it using System.Environment.getEnvironment wrapped in runIO . 当前,编译脚本将信息保存在系统环境中,因此我只是使用包装在runIO System.Environment.getEnvironmentrunIO Is there a better way, such as passing some arguments to ghc (similar to -D... for the C pre-processor), or perhaps something specifically designed for this purpose in TH? 是否有更好的方法,例如将一些参数传递给ghc (类似于C预处理器的-D... ),或者为此专门在TH中设计了某种方法?

Since so many people are interested in the question, I'll add my current approach, perhaps somebody will find it useful. 由于有这么多人对此问题感兴趣,所以我将添加当前的方法,也许有人会觉得它有用。 Probably the best way would be if TH allowed to read -D parameters on GHC's command line, but it seems nothing like this is currently implemented. 最好的方法可能是TH允许在GHC的命令行上读取-D参数,但是似乎目前没有实现。

A simple module allows TH to read compile-time environment. 一个简单的模块允许TH读取编译时环境。 A helper function also allows to read files; 辅助功能还允许读取文件。 for example read the path of a configuration file from the environment and then read the file. 例如,从环境中读取配置文件的路径,然后读取该文件。

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

It can be used like this: 可以这样使用:

{-# LANGUAGE TemplateHaskell #-}
import THEnv
main = print $( lookupCompileEnvExp "DEBUG" )

Then: 然后:

  • runhaskell Main.hs prints Nothing ; runhaskell Main.hs打印Nothing
  • DEBUG="yes" runhaskell Main.hs prints Just "yes" . DEBUG="yes" runhaskell Main.hs打印Just "yes"

It looks like what you are trying to do here , The -D option in ghc seems to define a compile time variable. 看起来您在这里想要做什么,ghc中的-D选项似乎定义了一个编译时间变量。

Here, on the same subject is a question that seems to also answer the other part of your question. 这里,关于同一主题的问题似乎也回答了您问题的另一部分。 From what I can tell, to do conditional compilation, you do something like: 据我所知,要进行条件编译,您需要执行以下操作:

    #ifdef MACRO_NAME
    //Do stuff here
    #endif

声明:本站的技术帖子网页,遵循CC BY-SA 4.0协议,如果您需要转载,请注明本站网址或者原文地址。任何问题请咨询:yoyou2525@163.com.

 
粤ICP备18138465号  © 2020-2024 STACKOOM.COM