A RetroSearch Logo

Home - News ( United States | United Kingdom | Italy | Germany ) - Football scores

Search Query:

Showing content from https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/exts/template_haskell.html below:

Website Navigation


6.13. Template Haskell — Glasgow Haskell Compiler 9.12.2 User's Guide

6.13. Template Haskell¶

Template Haskell allows you to do compile-time meta-programming in Haskell. The background to the main technical innovations is discussed in “Template Meta-programming for Haskell” (Proc Haskell Workshop 2002).

The Template Haskell page on the GHC Wiki has a wealth of information. You may also consult the Haddock reference documentation Language.Haskell.TH. Many changes to the original design are described in Notes on Template Haskell version 2. Not all of these changes are in GHC, however.

The first example from that paper is set out below (A Template Haskell Worked Example) as a worked example to help get you started.

The documentation here describes the realisation of Template Haskell in GHC. It is not detailed enough to understand Template Haskell; see the Wiki page.

6.13.1. Syntax¶
TemplateHaskell¶
Implies:

TemplateHaskellQuotes

Since:

6.0. Typed splices introduced in GHC 7.8.1.

Enable Template Haskell’s splice and quotation syntax.

TemplateHaskellQuotes¶
Since:

8.0.1

Enable Template Haskell’s quotation syntax.

Template Haskell has the following new syntactic constructions. You need to use the extension TemplateHaskell to switch these syntactic extensions on. Alternatively, the TemplateHaskellQuotes extension can be used to enable the quotation subset of Template Haskell (i.e. without top-level splices). The TemplateHaskellQuotes extension is considered safe under Safe Haskell while TemplateHaskell is not.

(Compared to the original paper, there are many differences of detail. The syntax for a declaration splice uses “$” not “splice”. The type of the enclosed expression must be Quote m => m [Dec], not [Q Dec]. Typed expression splices and quotations are supported.)

-fenable-th-splice-warnings¶

Template Haskell splices won’t be checked for warnings, because the code causing the warning might originate from a third-party library and possibly was not written by the user. If you want to have warnings for splices anyway, pass -fenable-th-splice-warnings.

6.13.2. Using Template Haskell¶

Template Haskell works in any mode (--make, --interactive, or file-at-a-time). There used to be a restriction to the former two, but that restriction has been lifted.

6.13.3. Viewing Template Haskell generated code¶

The flag -ddump-splices shows the expansion of all top-level declaration splices, both typed and untyped, as they happen. As with all dump flags, the default is for this output to be sent to stdout. For a non-trivial program, you may be interested in combining this with the -ddump-to-file flag (see Dumping out compiler intermediate structures. For each file using Template Haskell, this will show the output in a .dump-splices file.

The flag -dth-dec-file dumps the expansions of all top-level TH declaration splices, both typed and untyped, in the file M.th.hs for each module M being compiled. Note that other types of splices (expressions, types, and patterns) are not shown. Application developers can check this into their repository so that they can grep for identifiers that were defined in Template Haskell. This is similar to using -ddump-to-file with -ddump-splices but it always generates a file instead of being coupled to -ddump-to-file. The format is also different: it does not show code from the original file, instead it only shows generated code and has a comment for the splice location of the original file.

Below is a sample output of -ddump-splices

TH_pragma.hs:(6,4)-(8,26): Splicing declarations
  [d| foo :: Int -> Int
      foo x = x + 1 |]
======>
  foo :: Int -> Int
  foo x = (x + 1)

Below is the output of the same sample using -dth-dec-file

-- TH_pragma.hs:(6,4)-(8,26): Splicing declarations
foo :: Int -> Int
foo x = (x + 1)
6.13.4. A Template Haskell Worked Example¶

To help you get over the confidence barrier, try out this skeletal worked example. First cut and paste the two modules below into Main.hs and Printf.hs:

{- Main.hs -}
module Main where

-- Import our template "pr"
import Printf ( pr )

-- The splice operator $ takes the Haskell source code
-- generated at compile time by "pr" and splices it into
-- the argument of "putStrLn".
main = putStrLn ( $(pr "Hello") )


{- Printf.hs -}
module Printf where

-- Skeletal printf from the paper.
-- It needs to be in a separate module to the one where
-- you intend to use it.

-- Import some Template Haskell syntax
import Language.Haskell.TH

-- Describe a format string
data Format = D | S | L String

-- Parse a format string.  This is left largely to you
-- as we are here interested in building our first ever
-- Template Haskell program and not in building printf.
parse :: String -> [Format]
parse s   = [ L s ]

-- Generate Haskell source code from a parsed representation
-- of the format string.  This code will be spliced into
-- the module which calls "pr", at compile time.
gen :: Quote m => [Format] -> m Exp
gen [D]   = [| \n -> show n |]
gen [S]   = [| \s -> s |]
gen [L s] = stringE s

-- Here we generate the Haskell code for the splice
-- from an input format string.
pr :: Quote m => String -> m Exp
pr s = gen (parse s)

Now run the compiler,

$ ghc --make -XTemplateHaskell main.hs -o main

Run main and here is your output:

6.13.5. Template Haskell quotes and Rebindable Syntax¶

Rebindable syntax does not play well with untyped TH quotes: applying the rebindable syntax rules would go against the lax nature of untyped quotes that are accepted even in the presence of unbound identifiers (see #18102). Applying the rebindable syntax rules to them would force the code that defines the said quotes to have all the necessary functions (e.g ifThenElse or fromInteger) in scope, instead of delaying the resolution of those symbols to the code that splices the quoted Haskell syntax, as is usually done with untyped TH. For this reason, even if a module has untyped TH quotes with RebindableSyntax enabled, GHC turns off rebindable syntax while processing the quotes. The code that splices the quotes is however free to turn on RebindableSyntax to have the usual rules applied to the resulting code.

Typed TH quotes on the other hand are perfectly compatible with the eager application of rebindable syntax rules, and GHC will therefore process any such quotes according to the rebindable syntax rules whenever the RebindableSyntax extension is turned on in the modules where such quotes appear.

6.13.6. Using Template Haskell with Profiling¶

Template Haskell relies on GHC’s built-in bytecode compiler and interpreter to run the splice expressions. The bytecode interpreter runs the compiled expression on top of the same runtime on which GHC itself is running; this means that the compiled code referred to by the interpreted expression must be compatible with this runtime, and in particular this means that object code that is compiled for profiling cannot be loaded and used by a splice expression, because profiled object code is only compatible with the profiling version of the runtime.

This causes difficulties if you have a multi-module program containing Template Haskell code and you need to compile it for profiling, because GHC cannot load the profiled object code and use it when executing the splices.

Fortunately GHC provides two workarounds.

The first option is to compile the program twice:

  1. Compile the program or library first the normal way, without -prof.

  2. Then compile it again with -prof, and additionally use -osuf p_o to name the object files differently (you can choose any suffix that isn’t the normal object suffix here). GHC will automatically load the object files built in the first step when executing splice expressions. If you omit the -osuf ⟨suffix⟩ flag when building with -prof and Template Haskell is used, GHC will emit an error message.

The second option is to add the flag -fexternal-interpreter (see Running the interpreter in a separate process), which runs the interpreter in a separate process, wherein it can load and run the profiled code directly. There’s no need to compile the code twice, just add -fexternal-interpreter and it should just work. (this option is experimental in GHC 8.0.x, but it may become the default in future releases).

6.13.7. Template Haskell Quasi-quotation¶
QuasiQuotes¶
Since:

6.10.1

Enable Template Haskell Quasi-quotation syntax.

Quasi-quotation allows patterns and expressions to be written using programmer-defined concrete syntax; the motivation behind the extension and several examples are documented in “Why It’s Nice to be Quoted: Quasiquoting for Haskell” (Proc Haskell Workshop 2007). The example below shows how to write a quasiquoter for a simple expression language.

Here are the salient features

Warning

QuasiQuotes introduces an unfortunate ambiguity with list comprehension syntax. Consider the following,

let x = [v| v <- [0..10]]

Without QuasiQuotes this is parsed as a list comprehension. With QuasiQuotes this is parsed as a quasi-quote; however, this parse will fail due to the lack of a closing |]. See #11679.

The example below shows quasi-quotation in action. The quoter expr is bound to a value of type QuasiQuoter defined in module Expr. The example makes use of an antiquoted variable n, indicated by the syntax 'int:n (this syntax for anti-quotation was defined by the parser’s author, not by GHC). This binds n to the integer value argument of the constructor IntExpr when pattern matching. Please see the referenced paper for further details regarding anti-quotation as well as the description of a technique that uses SYB to leverage a single parser of type String -> a to generate both an expression parser that returns a value of type Q Exp and a pattern parser that returns a value of type Q Pat.

Quasiquoters must obey the same stage restrictions as Template Haskell, e.g., in the example, expr cannot be defined in Main.hs where it is used, but must be imported.

{- ------------- file Main.hs --------------- -}
module Main where

import Expr

main :: IO ()
main = do { print $ eval [expr|1 + 2|]
          ; case IntExpr 1 of
              { [expr|'int:n|] -> print n
              ;  _              -> return ()
              }
          }


{- ------------- file Expr.hs --------------- -}
module Expr where

import qualified Language.Haskell.TH as TH
import Language.Haskell.TH.Quote

data Expr  =  IntExpr Integer
           |  AntiIntExpr String
           |  BinopExpr BinOp Expr Expr
           |  AntiExpr String
    deriving(Show, Typeable, Data)

data BinOp  =  AddOp
            |  SubOp
            |  MulOp
            |  DivOp
    deriving(Show, Typeable, Data)

eval :: Expr -> Integer
eval (IntExpr n)        = n
eval (BinopExpr op x y) = (opToFun op) (eval x) (eval y)
  where
    opToFun AddOp = (+)
    opToFun SubOp = (-)
    opToFun MulOp = (*)
    opToFun DivOp = div

expr = QuasiQuoter { quoteExp = parseExprExp, quotePat =  parseExprPat }

-- Parse an Expr, returning its representation as
-- either a Q Exp or a Q Pat. See the referenced paper
-- for how to use SYB to do this by writing a single
-- parser of type String -> Expr instead of two
-- separate parsers.

parseExprExp :: String -> Q Exp
parseExprExp ...

parseExprPat :: String -> Q Pat
parseExprPat ...

Now run the compiler:

$ ghc --make -XQuasiQuotes Main.hs -o main

Run “main” and here is your output:


RetroSearch is an open source project built by @garambo | Open a GitHub Issue

Search and Browse the WWW like it's 1997 | Search results from DuckDuckGo

HTML: 3.2 | Encoding: UTF-8 | Version: 0.7.4