summaryrefslogtreecommitdiffstats
path: root/tv/5pkgs/haskell/th-env/src/THEnv.hs
diff options
context:
space:
mode:
authorlassulus <lassulus@lassul.us>2020-10-18 19:25:11 +0200
committerlassulus <lassulus@lassul.us>2020-10-18 19:25:11 +0200
commit5b29d7a435092aafcea15f588effbb6f45a6a56e (patch)
tree07340bc138d7bdea55bbb33e50fc2fa1b5387a57 /tv/5pkgs/haskell/th-env/src/THEnv.hs
parent9626d3cda953929e903b5a06595e98972cb08ffc (diff)
parentb034f63f7a2e4361b32c33c0e1a980eecf1a5aa6 (diff)
Merge remote-tracking branch 'ni/master'
Diffstat (limited to 'tv/5pkgs/haskell/th-env/src/THEnv.hs')
-rw-r--r--tv/5pkgs/haskell/th-env/src/THEnv.hs49
1 files changed, 49 insertions, 0 deletions
diff --git a/tv/5pkgs/haskell/th-env/src/THEnv.hs b/tv/5pkgs/haskell/th-env/src/THEnv.hs
new file mode 100644
index 00000000..b04f2ce0
--- /dev/null
+++ b/tv/5pkgs/haskell/th-env/src/THEnv.hs
@@ -0,0 +1,49 @@
+{-# 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