I am writing a simple HashString class, which is just a string and its hash:
data HashString = HashString Int -- ^ hash
T.Text -- ^ string!
Now I'm trying to generate these at compile time with something like:
$(hString "hello, world") :: HashString
I want the hash, and the text packing to happen at compile time. How do I do this?
Here's what I've tried so far, but I'm not sure if its right, nor am I sure it does everything at compile time:
hString :: String -> Q Exp
hString s = [| HashString (hash $ T.pack s) (T.pack s) |]
The way you've written your code, no evaluation will happen at compile-time. When you quote a Haskell expression with [| ... |], the quoted code/AST is inserted where you apply it without any evaluation, so writing:
$(hString "hello, world")
is exactly the same as writing:
let s = "hello, world" in HashString (hash $ T.pack s) (T.pack s)
But think about it like this: you use [| ... |] to quote an expression to be inserted later, and you generate code at compile-time with $(...). So, if you include some code $(foo) in a quoted expression bla = [| bar $(foo) |], doing $(bla) will generate the code bar $(foo), which in turn will evaluate foo at compile time. Also, to take a value that you generate at compile time and generate an expression from it, you use the lift function. So, what you want to do is this:
import Data.String (fromString)
import Language.Haskell.TH.Syntax
hString s = [| HashString $(lift . hash . T.pack $ s) (fromString s) |]
This evaluates the hash function at compile time, since the inner splice is resolved after the outer splice was resolved. By the way, using fromString from Data.String is the generic way of constructing some OverloadedString data type from a String.
Also, you should consider making a quasi-quoter for your HashString interface. Using quasi-quoters is more natural than manually calling splice functions (And you've already used them; the nameless [| ... |] quoter quotes Haskell expressions).
You would create a quasiquoter like this:
import Language.Haskell.TH.Quote
hstr =
QuasiQuoter
{ quoteExp = hString -- Convenient: You already have this function
, quotePat = undefined
, quoteType = undefined
, quoteDec = undefined
}
This would let you write HashStrings with this syntax:
{-# LANGUAGE QuasiQuotes #-}
myHashString = [hstr|hello, world|]
Related
I use quasi quoters to create my smart-constructed data types at compile time. This looks something like:
import qualified Data.Text as T
import Language.Haskell.TH.Quote (QuasiQuoter(..))
import Language.Haskell.TH (Q, Exp, Pat(..), Lit(..))
import Language.Haskell.TH.Syntax (Lift(..))
import qualified Language.Haskell.TH.Syntax as TH
import Instances.TH.Lift () -- th-lift-instances package
newtype NonEmptyText = NonEmptyText Text
textIsWhitespace :: Text -> Bool
textIsWhitespace = T.all (== ' ')
mkNonEmptyText :: Text -> Maybe NonEmptyText
mkNonEmptyText t = if textIsWhitespace t then Nothing else (Just (NonEmptyText t))
compileNonEmptyText :: QuasiQuoter
compileNonEmptyText = QuasiQuoter
{ quoteExp = compileNonEmptyText'
, quotePat = error "NonEmptyText is not supported as a pattern"
, quoteDec = error "NonEmptyText is not supported at top-level"
, quoteType = error "NonEmptyText is not supported as a type"
}
where
compileNonEmptyText' :: String -> Q Exp
compileNonEmptyText' s = case mkNonEmptyText (pack s) of
Nothing -> fail $ "Invalid NonEmptyText: " ++ s
Just txt -> [| txt |]
(I can provide a standalone working example if necessary—I just pulled this example out of a larger codebase)
Essentially, by just deriving Lift for my newtypes, I can place the data type in an expression quasi quoter [| txt |] to implement quoteExp.
But I'm having trouble with quotePat. If I do e.g.:
Just txt -> [p| txt |]
Then I get a warning that the first txt is unused, and the second shadows the first. I'm pretty sure that that pattern is just creating a new name txt rather than splicing in the in-scope txt like the expression quasi quoter did, since when I do:
f :: NonEmptyText -> Bool
f [compileNonEmptyText|test|] = True
f _ = False
everything matches the first statement.
Alright I think I've got it. Starting from the base string s, I can wrap that in StringL and LitP to get a literal string, which because of Text's IsString instance will become a Text. From there I need to apply the NonEmptyText constructor using ConP:
compileNonEmptyTextPattern' :: String -> Q TH.Pat
compileNonEmptyTextPattern' s = case mkNonEmptyText (pack s) of
Nothing -> fail $ "Invalid NonEmptyText: " ++ s
Just (NonEmptyText txt) -> pure $ ConP 'NonEmptyText [(LitP (StringL (T.unpack txt)))]
It's unfortunate that this is so much more verbose than the expression version, though! I wonder if there could be a typeclass for Q Pat like Lift is for Q Exp?
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.
I just start learning Template Haskell, and stuck on simple problem with splicing.
In one module I've implemented function tupleN which replies N-th element of the tuple:
tupleN :: Lift a => a -> Int -> Q Exp
tupleN a n = do
(TupE as) <- lift a
return $ as !! n
In the Main module I have:
main :: IO ()
main = do
let tup = (1::Int,'a',"hello")
putStrLn $ show $(tupleN $tup 1)
This seems to be working, but it wouldn't. Compiler prints error:
GHC stage restriction: `tup'
is used in a top-level splice or annotation,
and must be imported, not defined locally
In the expression: tup
In the first argument of `tupleN', namely `$tup'
In the expression: tupleN ($tup) 1
If I put tuple description right into spliced expression, code become working:
main :: IO ()
main = do
putStrLn $ show $(tupleN (1::Int,'a',"hello") 1)
What I missing with the first variant?
You've tried to use tup as a splice, but tup is just an ordinary value. You don't want to prefix it with a $.
Moreover, as the compile error states, since Template Haskell runs during the compilation process, GHC really needs to know what it's doing before it has finished compiling the current module. That means your splice expression can't depend on tup, because that's still being compiled. Inside splices, you can only use literals, imported values, and the special 'name and ''TypeName forms (which you can think of as a sort of literal, I suppose). You can get at some of the information from this compilation by using e.g. reify, but even that can only give you data that's available at compile time – if you want a function you can pass user input, or data constructed from user input, to, that's just impossible.
In short, you can't do exactly what you want to do using Template Haskell. You could, however, define a splice that expands to a function to get the ith element of a tuple of size sz:
import Control.Monad (unless)
import Language.Haskell.TH
tupleN :: Int -> Int -> Q Exp
tupleN sz i = do
unless (i < sz) . reportError $ "tupleN: index " ++ show i
++ " out of bounds for " ++ show sz ++ "-tuple"
lamE
[tupP (replicate i wildP
++ [varP (mkName "x")]
++ replicate (sz - i - 1) wildP)]
(varE (mkName "x"))
I'm trying to become familiar with Template Haskell, and to my surprise the code below compiles under ghc (version 6.10.4).
main = do
let
y = [| "hello" + 1 |]
putStr ""
This suggest to me that there's no typechecking inside quasi-quotes. This is not what I'd have expected after reading the original paper on Template Haskell. Moreover the following program does not compile.
main = do
let
y = [| "hello" && True |]
putStr ""
What's going on here?
It looks like GHC does type check all quotations but assumes that all generated instance constraints can be satisfied.
In this code:
main = do
let
y = [| "hello" + 1 |]
putStr ""
The y bracket is typeable under the assumption that we have a Num String instance. Since GHC can't say for sure that you won't introduce such an instance before y is spliced in, it doesn't give a type error.
In this code:
main = do
let
y = [| "hello" && True |]
putStr ""
There is no way that y can ever be spliced in successfully, no matter what instance environment you set up.
This is just one example of how Template Haskell's typechecking mechanism is too lenient -- further examples are discussed in Simon PJ's blog post at http://hackage.haskell.org/trac/ghc/blog/Template%20Haskell%20Proposal, where he proposes a change to not type check any quotations at all.
Template Haskell has two main operations:
lifting: [| |]
splicing $( )
When you wrap something in the Oxford brackets, you delay its type checking (and evaluation), and instead build an AST fragment that will be type checked when it is spliced back in.
The AST that is built can be observed:
{-# LANGUAGE TemplateHaskell #-}
import Language.Haskell.TH
main = print =<< runQ [| "hello" + 1 |]
Running this program (or typing the bracket expression into GHCi), and we get a well-formed AST, but one that is not type correct if treated as a Haskell fragment:
InfixE (Just (LitE (StringL "hello"))) (VarE GHC.Num.+) (Just (LitE (IntegerL 1)))
Now when we try to actually splice it, type checking happens:
*Main> :t [| "hello" + 1 |]
[| "hello" + 1 |] :: Q Exp
*Main> $( [| "hello" + 1 |] )
<interactive>:1:4:
No instance for (Num [Char])
arising from the literal `1'
As we expect. So, yes, TH expressions are type checked, but at a late point, when spliced back into a program.
Actually I have some formula like "x + y", which is a String.
I managed to replace the x/y variable with specific values like "1.2", which is still String type.
Now I have expression like "1 + 2".
So the problem is how to evaluate a expression of a string type and get the result.
ps: I wanna sth like read, that can directly convert the whole string expression instead of handling the operator (+/-,etc) case by case. Is that possible?
Your question leaves a lot of room for interpretation. I'm taking a guess you aren't accustom to building a whole pipeline of lexing, parsing, maybe type checking, and evaluating. The long answer would involve you defining what language you wish to evaluate (Just integers with '+', perhaps all rationals with '+', '-' '*', '/', or even a larger language?) and perform each of the above steps for that language.
The short answer is: to evaluate Haskell expressions, which includes the basic math operators you're probably talking about, just use the "hint" package:
$ cabal install hint
...
$ ghci
> import Language.Haskell.Interpreter
> runInterpreter $ setImports ["Prelude"] >> eval "3 + 5"
Right "8"
Yay!
Might be worth reading the Parsec section of Real World Haskell. You could parse it into an expression tree and then substitute the values in. As you use Parsec you'd build up an expression tree using types (very roughly, I'm sure I've made some mistakes which I'll edit in fixes for as and when people point them out!) like that below.
data Op = Plus | Minus
data Term = Variable String
| Value Int
data Expression = Expr Expression Op Expression
| Term
Then 1 + 2 would be (Expr (Variable "x") Plus (Variable "y")) and you could apply the appropriate substitutions.
To get the result, I guess you could right a simple function evaluate :: Map String Int -> Expression -> Either ErrorMessage Int which would apply the bindings in the map and then calculate the result if possible.
Well I've been banging my head against hint but I give up for now. I know hint can do this but I'm not sure how. [edit] See TomMD's answer for how to set imports up for hint. [/edit]
import Language.Haskell.Interpreter (eval, runInterpreter, Interpreter, InterpreterError)
main = do let resIO = eval "3" :: Interpreter String
res <- runInterpreter resIO
print res
This uninterestingly produces Right "3" as the result. I tried the following variants, only to run into baffling errors:
... eval "3 + 3" ....
-- yields --
Left (WontCompile [GhcError (errMsg = "Not in scope: `+'"])
The + operator isn't in scope??? wtf...
import Language.Haskell.Interpreter (interpret, as, runInterpreter, Interpreter)
main = do let resIO = interpret "3" (as :: Int) :: Interpreter Int
res <- runInterpreter resIO
print res
-- yields --
Left (WontCompile [GhcError (errMsg = "Not in scope: type constructor or class 'Int'")])
The Int class isn't in scope??? ugh...
I invite those more knowledgeable than me to expound on the finer details of hint.
The accepted answer shows a minimal example of using the hint, but it lacks couple of things:
How to evaluate using bindings like let x = 1 in x + 1.
How to handle exceptions, specifically divide by zero.
Here is a more complete example:
import qualified Control.DeepSeq as DS
import Control.Exception (ArithException (..))
import qualified Control.Exception as Ex
import qualified Control.Monad as M
import qualified Data.Either as E
import qualified Language.Haskell.Interpreter as I
evalExpr :: String -> [(String, Integer)] -> IO (Maybe Integer)
evalExpr expr a = Ex.handle handler $ do
i <- I.runInterpreter $ do
I.setImports ["Prelude"]
-- let var = value works too
let stmts = map (\(var, val) -> var ++ " <- return " ++ show val) a
M.forM_ stmts $ \s -> do
I.runStmt s
I.interpret expr (I.as :: Integer)
-- without force, exception is not caught
(Ex.evaluate . DS.force) (E.either (const Nothing) Just i)
where
handler :: ArithException -> IO (Maybe Integer)
handler DivideByZero = return Nothing
handler ex = error $ show ex