Skip to content

Instantly share code, notes, and snippets.

@facundominguez
Last active August 19, 2017 02:13
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 facundominguez/82f6768e1f4d5fbfecf008115226a484 to your computer and use it in GitHub Desktop.
Save facundominguez/82f6768e1f4d5fbfecf008115226a484 to your computer and use it in GitHub Desktop.
Make available at runtime the result of computing in all splices of a module.
-- This example shows how to make available at runtime the result of
-- processing all the splices in a module. Needs ghc-8.2.1.
--
-- Related to https://ghc.haskell.org/trac/ghc/ticket/14090#comment:13
{-# LANGUAGE TemplateHaskell #-}
import Language.Haskell.TH
import Language.Haskell.TH.Syntax
f :: IO ()
f = $(do
-- The first splice creates a foreign import.
-- After all the splices run, a C function will be provided with
-- the final result.
n <- newName "c_loadBytecode"
putQ (n, 1 :: Int)
ds <- sequence [ ForeignD . ImportF CCall Safe "loadBytecode" n
<$> [t| IO () |]
]
addTopDecls ds
varE n
)
g :: IO ()
g = $(do
-- The module finalizer generates the C function.
addModFinalizer $ do
Just (_, i) <- getQ :: Q (Maybe (Name, Int))
addForeignFile LangC $ unlines
[ "#include <stdio.h>"
, "void loadBytecode() {"
, "printf(\"Found %d splices.\\n\", " ++ show i ++ "); }"
]
Just (n, i) <- getQ
putQ (n, i + 1 :: Int)
varE n
)
main :: IO ()
main = f >> g
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment