How to properly communicate compile-time information to Template Haskell functions? - haskell

I need to communicate some information from compile scripts into 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. 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?

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.
A simple module allows TH to read compile-time environment. 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;
DEBUG="yes" runhaskell Main.hs prints Just "yes".

It looks like what you are trying to do here, The -D option in ghc seems to define a compile time variable.
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

Related

How can I get the string of Haskell code (along with the value)

I'd like to get both the string and value of arbitrary Haskell code. For example:
f (1+1) -> (2,"1+1")
The reason I want to do this is because I'm writing a programming language and I'd like to provide an option to interpret the code (for fast running, i.e. scripting) or compile it to Haskell code (for efficient runtime). So for each builtin I only want to provide the implementation once. That is I don't want to say
plusop = ((+),"(+)")
I have some ideas involving reading the raw haskell source or a separate script that generates a compiler, but these seem much less elegant that what would be done if this question is possible.
It looks like QuasiQuotation could make this possible, but I can't figure out how to get the Haskell value of the expression if I use it (I can only get the String).
Is it possible? How can it be done?
I don't know exactly what you want to do, but here's an example of using Template Haskell to do something similar to your example:
-- TH.hs
{-# LANGUAGE TemplateHaskell #-}
module TH where
import Language.Haskell.TH.Syntax
import Language.Haskell.TH.Ppr
showAndRun :: Q Exp -> Q Exp
showAndRun m = do
x <- m
let s = pprint x
[| ($m, s) |]
-- Main.hs
{-# LANGUAGE TemplateHaskell #-}
import TH
main :: IO ()
main = print $(showAndRun [| 1 + 1 |])
$ runhaskell Main.hs
(2,"1 GHC.Num.+ 1")
I don't know how to pretty print the expression without the qualified GHC.Num prefix. You could try copying the implementation of Language.Haskell.TH.Ppr and change it in the necessary places. Or the easiest is perhaps just a post-processing step where you strip each word that starts with a capital letter and ends in a ..

How do you include a multiline number in a Haskell source file?

I would like to paste in a large number constant into my Haskell code, and for readability I would like to have it formatted over several lines instead of one line.
Is this possible?
This is a possible approach. I'm not completely sure about it, though. There might be an easier way.
largeConstant :: Integer
largeConstant = read $
"12345" ++
"12345" ++
"12345"
Alternatively, we could use multiline string literals, even though they are not very commonly used in Haskell.
largeConstant :: Integer
largeConstant = read
"12345\
\12345\
\12345"
Enabling CPP is also an option, but seems a bit overkill.
largeConstant = 12345\
12345\
12345
You could make a quasiquoter. Might even want to upload it to hackage:
module X where
import Language.Haskell.TH
import Language.Haskell.TH.Quote
import Data.Char
iQQ :: QuasiQuoter
iQQ = QuasiQuoter {
quoteExp = return . LitE . IntegerL . read . filter isDigit,
quotePat = \_ -> fail "illegal integer QuasiQuote \
\(allowed as expression only, used as a pattern)",
quoteType = \_ -> fail "illegal integer QuasiQuote \
\(allowed as expression only, used as a type)",
quoteDec = \_ -> fail "illegal integer QuasiQuote \
\(allowed as expression only, used as a declaration)"
}
And the use:
{-# LANGUAGE QuasiQuotes #-}
import X
value = [iQQ|123
456|]
Resulting in:
Ok, two modules loaded.
*Main> value
123456
Or a larger number:
value = [iQQ|
44444444444444444444444444444444444444444444444444444444444444444444444444444444
45555555555555555555555555555555555555555555555555555555555555555555555555555555
66666666666666666666666666666666666666666666666666666666666666666666666666666666
|]
And in GHCi:
Ok, two modules loaded.
*Main> value
444444444444444444444444444444444444444444444444444444444444444444444444444444444555555555555555555555555555555555555555555555555555555555555555555555555555555566666666666666666666666666666666666666666666666666666666666666666666666666666666

Running Q Exp in a GhcMonad [duplicate]

Is it possible to generate and run TemplateHaskell generated code at runtime?
Using C, at runtime, I can:
create the source code of a function,
call out to gcc to compile it to a .so (linux) (or use llvm, etc.),
load the .so and
call the function.
Is a similar thing possible with Template Haskell?
Yes, it's possible. The GHC API will compile Template Haskell. A proof-of-concept is available at https://github.com/JohnLato/meta-th, which, although not very sophisticated, shows one general technique that even provides a modicum of type safety. Template Haskell expressions are build using the Meta type, which can then be compiled and loaded into a usable function.
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-}
{-# OPTIONS_GHC -Wall #-}
module Data.Meta.Meta (
-- * Meta type
Meta (..)
-- * Functions
, metaCompile
) where
import Language.Haskell.TH
import Data.Typeable as Typ
import Control.Exception (bracket)
import System.Plugins -- from plugins
import System.IO
import System.Directory
newtype Meta a = Meta { unMeta :: ExpQ }
-- | Super-dodgy for the moment, the Meta type should register the
-- imports it needs.
metaCompile :: forall a. Typeable a => Meta a -> IO (Either String a)
metaCompile (Meta expr) = do
expr' <- runQ expr
-- pretty-print the TH expression as source code to be compiled at
-- run-time
let interpStr = pprint expr'
typeTypeRep = Typ.typeOf (undefined :: a)
let opener = do
(tfile, h) <- openTempFile "." "fooTmpFile.hs"
hPutStr h (unlines
[ "module TempMod where"
, "import Prelude"
, "import Language.Haskell.TH"
, "import GHC.Num"
, "import GHC.Base"
, ""
, "myFunc :: " ++ show typeTypeRep
, "myFunc = " ++ interpStr] )
hFlush h
hClose h
return tfile
bracket opener removeFile $ \tfile -> do
res <- make tfile ["-O2", "-ddump-simpl"]
let ofile = case res of
MakeSuccess _ fp -> fp
MakeFailure errs -> error $ show errs
print $ "loading from: " ++ show ofile
r2 <- load (ofile) [] [] "myFunc"
print "loaded"
case r2 of
LoadFailure er -> return (Left (show er))
LoadSuccess _ (fn :: a) -> return $ Right fn
This function takes an ExpQ, and first runs it in IO to create a plain Exp. The Exp is then pretty-printed into source code, which is compiled and loaded at run-time. In practice, I've found that one of the more difficult obstacles is specifying the correct imports in the generated TH code.
From what I understand you want to create and run a code at runtime which I think you can do using GHC API but I am not very sure of the scope of what you can achieve. If you want something like hot code swapping you can look at the package hotswap.

Can a quasiquoter 'use' variables defined in the same file it is called?

So, I'm starting to experiment with quasiquotation and template haskell.
I want to modify an existing (large) quasiquotation code, while using the actual value of a variable defined where it is 'called'. To illustrate with a simple example:
main.hs
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TemplateHaskell #-}
import Language.Haskell.TH
import Exp02
x = "cde"
main = do
putStrLn [str|$x|]
Exp02.hs
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TemplateHaskell #-}
module Exp02 where
import Language.Haskell.TH
import Language.Haskell.TH.Syntax
import Language.Haskell.TH.Quote
xpto :: String -> ExpQ
xpto [] = stringE []
xpto ('$':rest) = varE (mkName rest)
xpto str = stringE str
str = QuasiQuoter
{ quoteExp = xpto
, quotePat = fail $ "patterns"
, quoteType= fail $ "types"
, quoteDec = fail $ "declarations"
}
While this compiles and prints out "cde", this is not what I want. My understanding is that the resulting code in main after splicing is: putStrLn x. What I want is to generate putStrLn cde (I know this is not valid haskell code, but it's just to represent my point).
Thus, to put it in another way, I do not want to 'create a reference to the variable x in the main file', I want to actually use its value inside the xpto quasiquoter code.
I am guessing this may not be possible, since it would imply a circular reference between main.hs and Exp02.hs, and thus face the TH stage restriction. Is this correct, or is there a way to use x value inside the xpto code?
Thanks!
No, what you are trying to do isn't currently possible. From the template haskell docs:
You can only run a function at compile time if it is imported from another module that is not part of a mutually-recursive group of modules that includes the module currently being compiled. Furthermore, all of the modules of the mutually-recursive group must be reachable by non-SOURCE imports from the module where the splice is to be run.
For example, when compiling module A, you can only run Template Haskell functions imported from B if B does not import A (directly or indirectly). The reason should be clear: to run B we must compile and run A, but we are currently type-checking A.
You are attempting to run the function (or more strictly value) x at compile time in the same module as x was defined, which is clearly stated to not be allowed.

Dynamic module name

I want to do something like this in Haskell, but the compiler is not letting me.
Is there any way to accomplish this task?
-- both modules export function named "hello"
-- and I want to run it in every module
import qualified MyMod as M1
import qualified MyAnotherMod as M2
runmodules = map (\m -> m.hello) [M1, M2]
Modules in Haskell are not even remotely first-class entities in the ways this would require, I'm afraid.
However, as bzn commented, Template Haskell can be used for problems like this. The result can be a bit clumsy, but if you really need some quick metaprogramming hacks it's not a bad choice. I'm not really an expert with TH, but what you want is pretty simple, with one catch: Neither "ambiguous identifiers" nor "module names" can be captured or quoted in any way, as far as I know, so you'll have to put them in strings given as arguments to the TH function.
Here's a quick and dirty, minimal example:
{-# LANGUAGE TemplateHaskell #-}
module MapModuleTH where
import Language.Haskell.TH
mapQual :: [String] -> String -> ExpQ
mapQual ms n = listE $ map (\m -> varE . mkName $ m ++ "." ++ n) ms
mapMQual :: [String] -> String -> ExpQ
mapMQual ms n = appE (varE 'sequence) $ listE $ map (\m -> varE . mkName $ m ++ "." ++ n) ms
You phrased things as "running the function" which sounds more like doing a bunch of IO actions, not just collecting a list of stuff, so I added a variant that also sequences the result.
Note that, despite the use of strings here, this is still statically typed--if the qualified names don't exist, or the types don't match up, you'll get the expected compile-time error just as if you'd written everything out by hand.
Here's a quick example of using it. Given the following:
{-# LANGUAGE TemplateHaskell #-}
module MapModule where
import MapModuleTH
import qualified Test1 as T1
import qualified Test2 as T2
tests = do xs <- $(mapMQual ["T1", "T2"] "test")
putStrLn $ "Count: " ++ show (length xs)
Assuming the other modules are there and define test, then in GHCi we can see:
> tests
Test 1
Test 2
Count: 2
I don't think you can quote a qualified name prefix like that in template haskell, and the hello identifier isn't in scope, so you might have to fall back to programming with strings.
module ModuleParamsTH where
import Language.Haskell.TH
getAll :: String -> [String] -> ExpQ
getAll valueName moduleNames =
listE $ map (varE . mkName . (++ suffix)) moduleNames
where suffix = "." ++ valueName
which can then be used like so,
{-# LANGUAGE TemplateHaskell #-}
import ModuleParamsTH
import qualified ModuleParamsM1 as M1
import qualified ModuleParamsM2 as M2
runmodules = $(getAll "hello" ["M1", "M2"])
However, I would not do all this. You could just write [M1.hello, M2.hello] or use a type class to abstract over implementations.
Modules aren't values in Haskell. Therefore that isn't possible. What do you want to achieve?

Resources