Skip to content

Instantly share code, notes, and snippets.

@luite
Created August 22, 2013 20:04
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save luite/6312097 to your computer and use it in GitHub Desktop.
Save luite/6312097 to your computer and use it in GitHub Desktop.
How to use RunQuasiQuoterHook
{-# LANGUAGE QuasiQuotes #-}
module B where
import Text.Hamlet
import Text.Blaze
f :: Markup
f = [shamlet| <h1>Hello
<p>world
|]
import GHC
import Outputable
import GHC.Paths ( libdir )
--GHC.Paths is available via cabal install ghc-paths
import DynFlags
import Hooks
import TcSplice
import HscMain
import MonadUtils
import TcRnTypes
targetFile = "B.hs"
main =
defaultErrorHandler defaultFatalMessager defaultFlushOut $ do
runGhc (Just libdir) $ do
dflags0 <- getSessionDynFlags
let dflags1 = setopts gopt_set [Opt_ForceRecomp]
$ setopts xopt_set [Opt_Cpp, Opt_ImplicitPrelude, Opt_MagicHash]
$ dflags0 { hooks = insertHook RunQuasiQuoteHook runQQ (hooks dflags0) }
setopts f opts dfs = foldl f dfs opts
setSessionDynFlags dflags1
target <- guessTarget targetFile Nothing
setTargets [target]
load LoadAllTargets
runQQ :: HsQuasiQuote Name -> RnM (HsQuasiQuote Name)
runQQ q@(HsQuasiQuote name span quoted) = do
liftIO (putStrLn $ "running quasiquoter on\n" ++ show quoted)
return q
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment