
{-# OPTIONS_GHC -fglasgow-exts -fno-monomorphism-restriction #-} -- Many people ask if GHC will evaluate toplevel constants at compile -- time, you know, since Haskell is pure it'd be great if those -- computations could be done once and not use up cycles during -- runtime. Not an entirely bad idea, I think. -- -- So I set about allowing just that: for arbitrary expressions to be -- evaluated, and the expanded expression spliced into client code. -- -- If you had some data in a file just out of convenience, you could say: -- > yourData = $(compileTimeIO $ parseFile $ readFile "data.txt") -- -- Or if you had an expensive computation that you want done at compile: -- > result = $(compileTimeEval $ expensiveComputation) -- -- I would appreciate comments. I wrote this completely blind with just -- the TH and Generics haddocks, so if I'm doing something tremendously -- stupid that can be improved, let me know. :) Especially if you can -- think of a less awkward way to go from Generics' data to TH -- expressions than using 'showConstr'... -- -- I wrote this with 6.6.1, in case there's any incompatibilities. Copy/ -- paste this post into CompileTime.hs, load into ghci, :set -fth, and -- futz around with the splices. -- -- -- Nicholas Messenger (nmessenger at gmail.com, omnId on #haskell) module CompileTime(compileTimeEval, compileTimeIO) where import Data.Generics import Language.Haskell.TH import Control.Monad import Data.Tree import Data.Ratio -- Expands a datum into an expression tree to be spliced into -- client code. compileTimeEval :: Data a => a -> ExpQ compileTimeEval = return . toExp -- Runs the IO action and splices in the evaluated result datum. compileTimeIO :: Data a => IO a -> ExpQ compileTimeIO = liftM toExp . runIO -- Does the work. :) toTree gets us a tree of constructors, so -- we mostly just have to fold the tree with AppE, except for -- TH's bizarre TupE. toExp :: Data d => d -> Exp toExp = applyAll . toTree where applyAll (Node k args) | isTuple k = TupE (map applyAll args) | otherwise = foldl AppE k (map applyAll args) isTuple (ConE n) = all (==',') (nameBase n) isTuple _ = False -- Synonym to shorten the definition of exp below type Ex a = a -> Exp -- Turns some datum into a tree of TH expressions representing -- that datum. The Exp at each node represents the constructor, -- the subtrees are its arguments. toTree :: Data d => d -> Tree Exp toTree x = Node (exp x) (gmapQ toTree x) where -- The various ways to turn a (Data d => d) into an -- Exp representing its constructor. any = ConE . mkName . deparen . showConstr . toConstr char = LitE . CharL int = sigged $ LitE . IntegerL . toInteger rat = sigged $ LitE . RationalL . toRational sigged f x = SigE (f x) (ConT . mkName . show $ typeOf x) -- The above functions combined together for different types. -- This is what gives the constructor Exp at each Node. There -- are definitely more types to cover that 'any' gets wrong... exp = any `extQ` (int::Ex Int) `extQ` (int::Ex Integer) `extQ` char `extQ` (rat::Ex Float) `extQ` (rat::Ex Double) `extQ` (rat::Ex Rational) -- Generics' showConstr puts parens around infix -- constructors. TH's ConE doesn't like 'em. deparen s = (if last s == ')' then init else id) . (if head s == '(' then tail else id) $ s

On Fri, 2 Nov 2007 05:11:53 -0500
"Nicholas Messenger"
-- Many people ask if GHC will evaluate toplevel constants at compile -- time, you know, since Haskell is pure it'd be great if those -- computations could be done once and not use up cycles during -- runtime. Not an entirely bad idea, I think.
I implemented the same idea. First a note about nomenclature: since there is a Template Haskell class for the concept of "translating actual values into TH representations of those values" called Lift, I call that "lifting"; I also call evaluating and storing top-level constants at compile time "baking them into the executable".
From glancing at your code, my approach has two main differences (apart from the fact that I didn't implement support for all of the types that you did):
1. A generic lifter using Data.Generics does not work for certain types, like IntSet. So I implemented the Template Haskell class Lift for each of my own data types that I wanted to use in lifting, and where it would work, called my generic lifter function, otherwise lifted it more manually (as shown below). 2. I used synthesise instead of gmapQ, and did not use an intermediate Tree data structure. Here is the module which does most of the work. (You will not be able to compile this as-is, obviously, because I have not published the rest of my code yet.) {-# OPTIONS_GHC -fglasgow-exts -fallow-overlapping-instances -fallow-undecidable-instances -XTemplateHaskell #-} module Language.Coq.Syntax.AbstractionBaking where import Data.Generics.Basics (ConstrRep(..), constrRep, Data, toConstr, Typeable) import Data.Generics.Schemes (synthesize) import Data.List (foldl') import Data.IntSet (IntSet) import qualified Data.IntSet as IntSet (fromList, toList) import Data.Set (Set) import qualified Data.Set as Set (fromList, toList) import Language.Haskell.TH.Lib (appE, charL, conE, ExpQ, infixE, integerL, litE) import Language.Haskell.TH.Syntax (Lift(..), mkName) import System.FilePath ((>)) import Data.DList (DList) import Data.ListLike (fromList, ListLike, toList) import Language.Coq.Parser (CoqParserState(..)) import Language.Coq.Syntax.Abstract (CoqState(..), Sentence, Term) import Language.Coq.Syntax.Concrete (NotationRec(..)) import Language.Coq.Syntax.ParseSpec lifter :: Data d => d -> ExpQ lifter = head . synthesize [] (++) combiner where combiner x args = [case rep of IntConstr i -> litE $ integerL i AlgConstr _ -> algebraic (show constr) args StringConstr (h:_) -> litE $ charL h _ -> fail $ "Unimplemented constrRep: " ++ show rep] where constr = toConstr x rep = constrRep constr algebraic "(:)" = cons algebraic name = foldl' appE $ conE $ mkName name cons [] = [e| (:) |] cons [left] = infixE (Just left) (cons []) Nothing cons [left, right] = infixE (Just left) (cons []) $ Just right instance Lift NotationRec where lift (NotationRec w x y z) = appE (appE (appE (appE [| NotationRec |] $ lift w) $ lift x) $ lift y) $ lift z instance Lift ParseSpecTok where lift = lifter instance Lift Associativity where lift = lifter instance Lift Sentence where lift = lifter instance Lift Term where lift = lifter instance Lift CoqState where lift (CoqState x y) = appE (appE [| CoqState |] $ lift x) $ lift y instance Lift CoqParserState where lift (CoqParserState x y z) = appE (appE (appE [| CoqParserState |] $ lift x) $ lift y) $ lift z instance (Lift a, ListLike full a) => Lift full where lift = appE [| fromList |] . lift . toList instance Lift IntSet where lift = appE [| IntSet.fromList |] . lift . IntSet.toList instance Lift a => Lift (Set a) where lift = appE [| Set.fromList |] . lift . Set.toList -- Robin

On 11/2/07, Robin Green
<snip> ...since there is a Template Haskell class for the concept of "translating actual values into TH representations of those values" called Lift... <snip>
There's a WHAT?! *checks docs* You're telling me all that horrendous pain in implementing toExp and it already exists?!? GRRAAAAAGGHHRAWWRRRAAAAAAGGGH! *sob* ... Ah, well, I learned me some Data.Generics anyway. :3 -- Nicholas Messenger (nmessenger at gmail.com, omnId on #haskell)

Hi Nicholas,
compileTimeEval :: Data a => a -> ExpQ compileTimeEval = return . toExp
You're telling me all that horrendous pain in implementing toExp and it already exists?!?
Yes unfortunately, compileTimeEval already exists in TH, it's called lift compileTimeEval :: Lift a => a -> ExpQ compileTimeEval = lift But don't be so hard on yourself. Your approach has one advantage. GHC supports automatic derivation of Data whereas Lift instances have to be created manually. Note, however, that Lift instances can also be generated using Igloo's th-lift package[1]. Cheers, Fons [1] http://hackage.haskell.org/cgi-bin/hackage-scripts/package/th-lift-0.2
participants (3)
-
Alfonso Acosta
-
Nicholas Messenger
-
Robin Green