SlideShare a Scribd company logo
Template Haskell Tutorial

                                      short, illustrated examples
         from Illustrated Haskell <http://illustratedhaskell.org>
Motivating example
    fst(x,_)      = x
    fst3(x,_,_)   = x
    fst4(x,_,_,_) = x
    …

    print $ fst3 ("hello world", 1, 2)
    print $ fst4 ("hello world", 1, 2, 3)

So repetitive!


    Illustrated Haskell <http://illustratedhaskell.org>
Template Haskell to the rescue!
Usage:

    {-# LANGUAGE TemplateHaskell #-}
    print $ $(fstN 3) ("hello world", 1, 2)
    print $ $(fstN 4) ("hello world", 1, 2, 3)




    Illustrated Haskell <http://illustratedhaskell.org>
How to write it?
-- FstN.hs
{-# LANGUAGE TemplateHaskell #-}
module FstN where
import Language.Haskell.TH

fstN :: Q Exp
fstN n = do
    x <- newName "x”
    return $ LamE [TupP $
        VarP x : replicate (n-1) WildP] (VarE x)


Illustrated Haskell <http://illustratedhaskell.org>
OK, how about explaining it?
 Every time you want to write something in TH, you start with:
runQ [| ... |]

    GHC will tell you how to write it. For example, if we wanted to
      write a splice that will produce (x,_,_) -> x

$ ghci – fth
> :m +Language.Haskell.TH
> runQ [| (x,_,_) -> x |]
LamE [TupP [VarP x_1,WildP,WildP]] (VarE x_1)
> :t it
it :: Exp

    That’s it, no need to remember anything! Just ask GHC!

    Illustrated Haskell <http://illustratedhaskell.org>
Writing fst3 in TH
 So we already have an Exp, how about those x_1?
LamE [TupP [VarP x_1,WildP,WildP]] (VarE x_1)

> :t (VarP, VarE)
(VarP, VarE) :: (Name -> Pat, Name -> Exp)

 So, VarP and VarE takes a Name. Let’s see how we can satisfy
    them:
> :t newName
newName :: String -> Q Name

    A ha! So we can just plug it into the expression GHC gave us:
fst3 = do
    x <- newName "x"
    LamE [TupP [VarP x,WildP,WildP]] (VarE x)

    Illustrated Haskell <http://illustratedhaskell.org>
Evolving fst3 into fstN
    The following corresponds to the expression (x,_,_) -> x
fst3 = do
    x <- newName "x"
    LamE [TupP [VarP x,WildP,WildP]] (VarE x)

    Not surprisingly, to make fst4, we just need to make 3 WildP:
fst4 = do
    x <- newName "x"
    LamE [TupP [VarP x,WildP,WildP,WildP]] (VarE x)

    And we can easily generalize it into fstN
fstN n = do
    x <- newName "x"
    LamE [TupP (VarP x : replicate (n-1) WildP)] (VarE x)


    Illustrated Haskell <http://illustratedhaskell.org>
Using fstN
    For technical reasons, splices must be defined in a
      separate module.
    So we need to create a new module to use the splice
      we defined:

-- TestFstN.hs
main = print $ $(fstN 3) ("hello world", 1, 3)




    Illustrated Haskell <http://illustratedhaskell.org>
Quasi Quotes
Quasi Quotes
    The [| … |] notation that you just used is the quasi quotes for Haskell
       expression.
    The contents within quasi quotes will be parsed at compile time.
    Example: in Data.Array.Repa.Stencil, you could define a stencil like this
[stencil2|           0 1 0
                     1 0 1
                     0 1 0 |]

    It is converted to:
makeStencil2 (Z:.3:.3)
   (ix -> case ix of
             Z :. -1 :. 0                       ->   Just 1
             Z :. 0 :. -1                       ->   Just 1
             Z :. 0 :. 1                        ->   Just 1
             Z :. 1 :. 0                        ->   Just 1
             _                                  ->   Nothing)


    Illustrated Haskell <http://illustratedhaskell.org>
Quasi Quotes
    When you do [| x -> x |], the string inside the
      brackets is parsed by the Haskell compiler and
      gives you back the AST (Abstract Syntax Tree)




    Illustrated Haskell <http://illustratedhaskell.org>
Let’s do a simple example
    We will build a structure to represent HTML documents
    For simplicity, we omit attributes, self closing tags, etc.
-- HTML.hs
{-# LANGUAGE TemplateHaskell, QuasiQuotes #-}
module HTML where
data Node = Tag String [Node] -- tag name, children
           | Text String
           deriving Show

    Our target is to use quasi quotes to build a document tree:
-- HTMLTest.hs
import HTML
doc :: Node
doc = [html|<html>Hello, <strong>TH</strong> world!</html>]
   -- Node "html" [Text "Hello, ”,
                   Tag "strong" [Text "TH"],
                   Text " world!"]

    Illustrated Haskell <http://illustratedhaskell.org>
First, a simple HTML parser
    We’ll sidetrack a bit and make a dead simple HTML parser
      using Parsec
    Our focus here isn’t Parsec so we can just skim over this
      function that does the right thing
-- HTML.hs
textNode :: Parser Node
textNode = fmap Text $ many1 $ satisfy (/='<')

tagNode :: Parser Node
tagNode = do
    tagName <- char '<' *> many1 letter <* char '>'
    children <- many $ try tagNode <|> textNode
    string "</" >> string tagName >> char '>'
    return $ Tag tagName children
    Illustrated Haskell <http://illustratedhaskell.org>
A simple test for our parser
$ ghci HTML.hs
> parseTest tagNode "<html>Hello, <strong>TH</strong> world!</html>"
Tag "html" [Text "Hello, ",Tag "strong" [Text "TH"],Text " world!”]


    It works!




    Illustrated Haskell <http://illustratedhaskell.org>
Now we can write our QuasiQuoter
-- HTML.hs                                                The QuasiQuoter takes 4
Html :: QuasiQuoter                                          parameters. Each will be
                                                             called when the quasi quote
Html = QuasiQuoter                                           is being invoked to create:
    htmlExpr                                                    An expression
    undefined                                                          foo = [html| ... |]
                                                                A pattern (for pattern
    undefined                                                       matching)
    undefined                                                          bar [html| ... |] = 3
                                                                A type
                                                                A top-level declaration
htmlExpr :: String -> Q Exp
htmlExpr = undefined                                      We will do expression and
                                                             pattern in this example
                                                          For more information consult
                                                             GHC’s documentation



 Illustrated Haskell <http://illustratedhaskell.org>
    htmlExpr is supposed to parse the contents within
       [html| … |] and give back an Exp
htmlExpr :: String -> Q Exp
htmlExpr str = do
   filename <- loc_filename `fmap` location
    case parse tagNode filename str of
        Left err -> undefined
        Right tag -> [| tag |]

    As easy as that, loc_filename and location will give
      us the filename of the user.

    Illustrated Haskell <http://illustratedhaskell.org>
Let’s compile it!
$ ghc HTML.hs
Error: No instance for (Lift Node) arising from
arising of `tag’…

    What is that? Well maybe we can satisfy it by
      implementing the Lift instance for Node, as
      instructed:
instance Lift Node where
    lift (Text t) = [| Text t |]
         lift (Tag name children) = [| Tag name children |]



    Illustrated Haskell <http://illustratedhaskell.org>
Let’s try it out
-- HTMLTest.hs
{-# LANGUAGE TemplateHaskell , QuasiQuotes #-}
import HTML
main = print [html|<html>Hello, <strong>TH</strong>
world!</html>|]

$ ghci HTMLTest.hs
> main
Tag "html" [Text "Hello, ",Tag "strong" [Text "TH"],Text
" world!"]

    It works!


    Illustrated Haskell <http://illustratedhaskell.org>
Quasi quoting for patterns
    Now let’s try to do some operations on our HTML
       structure
    In this example we will convert an HTML tree into
       Markdown
    Markdown is a simple wiki syntax

 Example Markdown:
Let’s **rock** and _roll_!
 Corresponding HTML:
<html>Let's <strong>rock</strong> and <em>roll</em></html>

    Usually people convert Markdown to HTML. We will do it
      the other way here.


    Illustrated Haskell <http://illustratedhaskell.org>
Let’s make a simple converter
-- HTMLTest.hs
markdown (Tag "strong" children)                     =    "**" ++ concatMap markdown children ++ "**"
markdown (Tag "em" children)                         =    "_" ++ concatMap markdown children ++ "_"
markdown (Tag _ children)                            =    concatMap markdown children
markdown (Text t)                                    =    t

    That’s some normal Haskell. For fun, we’re going to turn it into:
-- HTMLTest.hs
markdown [html|<strong>|]                 =   "**" ++ concatMap markdown children ++ "**"
markdown [html|<em>|]                     =   "_" ++ concatMap markdown children ++ "_"
markdown [html|<_>|]                      =   concatMap markdown children
markdown [html|#text|]                    =   text

    Are we gaining anything? Honestly not much. But we’ll do it for the sake of
       an TH example.




    Illustrated Haskell <http://illustratedhaskell.org>
Add a pattern parser to our QuasiQuoter
 -- HTML.hs
 html :: QuasiQuoter
 html = QuasiQuoter htmlExpr htmlPat
   undefined undefined

 htmlPat                :: String ->                  Q Pat
 htmlPat                "<_>"      =                  [p| Tag _ children |]
 htmlPat                "#text"    =                  [p| Text text |]
 htmlPat                ('<':rest) =                  undefined -- ...

Illustrated Haskell <http://illustratedhaskell.org>
Asking GHC again…
    Now how do we write the “rest” case? Let’s ask GHC
> runQ [p| Tag "strong" chlidren |]
ConP HTML.Tag [ LitP (StringL "strong")
              , VarP chlidren]

    So there we have almost had it.
    We just need to use Name at appropriate places and
       follow the types:
htmlPat ('<':rest) = return $
    ConP (mkName "HTML.Tag”)
        [ LitP (StringL (init rest))
        , VarP (mkName "children")]

    Illustrated Haskell <http://illustratedhaskell.org>
Some explanations
htmlPat ('<':rest) = return $
    ConP (mkName "HTML.Tag”)
        [ LitP (StringL (init rest))
        , VarP (mkName "children")]

 Here we see mkName intead of newName
 mkName "foo" will translate into an identifier "foo"
    literally
 mkName "foo" will become something like "foo_1".
 You’ll use this when you want to avoid name
    collisions

    Illustrated Haskell <http://illustratedhaskell.org>
Let’s test it out!
-- HTMLTest.hs
{-# LANGUAGE TemplateHaskell , QuasiQuotes #-}
import HTML

doc = [html|<html>Hello, <strong>TH</strong> world!</html>|]

markdown           [html|<_>|]      = concatMap markdown children
markdown           [html|#text|]    = text
markdown           [html|<strong>|] =
    "**"           ++ concatMap markdown children ++ "**”

main = print . markdown $ doc

    $ runhaskell HTMLTest.hs
    "Hello, **TH** world!"


    Illustrated Haskell <http://illustratedhaskell.org>
Summary
    Use runQ to have GHC write the splice for you
    Then just fix it up by following the type




    Illustrated Haskell <http://illustratedhaskell.org>

More Related Content

What's hot (20)

PDF
ปัญหาการเมือง เศรษฐกิจ สังคมแจก
Taraya Srivilas
 
PDF
โวหารการเขียน ม.6
WijittraSreepraram
 
PDF
การผลิตสื่อวิดีโอ (Video Production)
Dr.Kridsanapong Lertbumroongchai
 
PDF
ใบความรู้ที่่ 3.2 บทสคริปต์-storybord
Samorn Tara
 
PDF
Introdução à Programação Python e Tk
Carlos Campani
 
PDF
งานนำเสนอแรงจูงใจ กลุ่ม 2
ไกรลาศ จิบจันทร์
 
PDF
Aula 1 - 31 Jan 23.pdf
edilson42986
 
PDF
Gifographic
smittichai chaiyawong
 
PPT
พืช
Chamaiporn
 
PDF
15 เขียนคำขวัญ 1
กึม จันทิภา
 
PDF
Aula 1. Introdução: Interface Homem-Máquina
Silvia Dotta
 
DOCX
Đề tài: Quản trị vốn lưu động tại Công ty TNHH TM Khánh Mai, HAY
Dịch vụ viết bài trọn gói ZALO: 0936 885 877
 
PDF
Dreamweaver แนะโปรแกรมและวิธีใช้
Webidea Petchtharat
 
PDF
การศึกษาปฐมวัยของฟินแลนด์
Pattie Pattie
 
PDF
Concept VS Theme
siriporn pongvinyoo
 
DOC
Portfolio (แฟ้มผลงาน) ที่ดี
Tanchanok Pps
 
PDF
เห็นแก่ลูก
ssuser456899
 
PDF
Đề tài: Hiệu quả sử dụng vốn tại Công ty may xuất khẩu, HAY
Dịch Vụ Viết Bài Trọn Gói ZALO 0917193864
 
PDF
ใบความรู้ที่ 1 หลักการสร้างหนังสั้น
chaiwat vichianchai
 
PDF
ภาษากาย (Body language)
Taraya Srivilas
 
ปัญหาการเมือง เศรษฐกิจ สังคมแจก
Taraya Srivilas
 
โวหารการเขียน ม.6
WijittraSreepraram
 
การผลิตสื่อวิดีโอ (Video Production)
Dr.Kridsanapong Lertbumroongchai
 
ใบความรู้ที่่ 3.2 บทสคริปต์-storybord
Samorn Tara
 
Introdução à Programação Python e Tk
Carlos Campani
 
งานนำเสนอแรงจูงใจ กลุ่ม 2
ไกรลาศ จิบจันทร์
 
Aula 1 - 31 Jan 23.pdf
edilson42986
 
พืช
Chamaiporn
 
15 เขียนคำขวัญ 1
กึม จันทิภา
 
Aula 1. Introdução: Interface Homem-Máquina
Silvia Dotta
 
Đề tài: Quản trị vốn lưu động tại Công ty TNHH TM Khánh Mai, HAY
Dịch vụ viết bài trọn gói ZALO: 0936 885 877
 
Dreamweaver แนะโปรแกรมและวิธีใช้
Webidea Petchtharat
 
การศึกษาปฐมวัยของฟินแลนด์
Pattie Pattie
 
Concept VS Theme
siriporn pongvinyoo
 
Portfolio (แฟ้มผลงาน) ที่ดี
Tanchanok Pps
 
เห็นแก่ลูก
ssuser456899
 
Đề tài: Hiệu quả sử dụng vốn tại Công ty may xuất khẩu, HAY
Dịch Vụ Viết Bài Trọn Gói ZALO 0917193864
 
ใบความรู้ที่ 1 หลักการสร้างหนังสั้น
chaiwat vichianchai
 
ภาษากาย (Body language)
Taraya Srivilas
 

Similar to Template Haskell Tutorial (20)

PDF
Template Haskell
Sergey Stretovich
 
PDF
Real World Haskell: Lecture 1
Bryan O'Sullivan
 
PPTX
Haste (Same Language, Multiple Platforms) and Tagless Final Style (Same Synta...
takeoutweight
 
PDF
DEFUN 2008 - Real World Haskell
Bryan O'Sullivan
 
PPT
chapter2.ppt
ssuser54d1db
 
PDF
An introduction on language processing
Ralf Laemmel
 
PDF
Haskell
Roberto Casadei
 
PDF
Dutch hug
guest51f8ea
 
ODP
Parsec
Phil Freeman
 
PPTX
Functional programming seminar (haskell)
Bikram Thapa
 
PDF
Real World Haskell: Lecture 7
Bryan O'Sullivan
 
PDF
Text Manipulation with/without Parsec
ujihisa
 
PPTX
Solving Haskell Assignment: Engaging Challenges and Solutions for University ...
Programming Homework Help
 
PDF
Conf 2018 Track 2 - Try Elm
TechExeter
 
PPTX
Introduction to Haskell: 2011-04-13
Jay Coskey
 
PPTX
Haskell code tools
begriffs
 
PDF
Building a website in Haskell coming from Node.js
Nicolas Hery
 
PPT
Chapter2 Haskell
Chuy Lugo
 
PPT
haskell5.ppt is a marketing document lol
dopointt
 
KEY
Metaprogramming in Haskell
Hiromi Ishii
 
Template Haskell
Sergey Stretovich
 
Real World Haskell: Lecture 1
Bryan O'Sullivan
 
Haste (Same Language, Multiple Platforms) and Tagless Final Style (Same Synta...
takeoutweight
 
DEFUN 2008 - Real World Haskell
Bryan O'Sullivan
 
chapter2.ppt
ssuser54d1db
 
An introduction on language processing
Ralf Laemmel
 
Dutch hug
guest51f8ea
 
Parsec
Phil Freeman
 
Functional programming seminar (haskell)
Bikram Thapa
 
Real World Haskell: Lecture 7
Bryan O'Sullivan
 
Text Manipulation with/without Parsec
ujihisa
 
Solving Haskell Assignment: Engaging Challenges and Solutions for University ...
Programming Homework Help
 
Conf 2018 Track 2 - Try Elm
TechExeter
 
Introduction to Haskell: 2011-04-13
Jay Coskey
 
Haskell code tools
begriffs
 
Building a website in Haskell coming from Node.js
Nicolas Hery
 
Chapter2 Haskell
Chuy Lugo
 
haskell5.ppt is a marketing document lol
dopointt
 
Metaprogramming in Haskell
Hiromi Ishii
 
Ad

Recently uploaded (20)

PPTX
From Sci-Fi to Reality: Exploring AI Evolution
Svetlana Meissner
 
PDF
Newgen Beyond Frankenstein_Build vs Buy_Digital_version.pdf
darshakparmar
 
PDF
How Startups Are Growing Faster with App Developers in Australia.pdf
India App Developer
 
PDF
"AI Transformation: Directions and Challenges", Pavlo Shaternik
Fwdays
 
PDF
IoT-Powered Industrial Transformation – Smart Manufacturing to Connected Heal...
Rejig Digital
 
PDF
Building Real-Time Digital Twins with IBM Maximo & ArcGIS Indoors
Safe Software
 
PPTX
Designing Production-Ready AI Agents
Kunal Rai
 
PPTX
AI Penetration Testing Essentials: A Cybersecurity Guide for 2025
defencerabbit Team
 
PPTX
Q2 FY26 Tableau User Group Leader Quarterly Call
lward7
 
PPTX
AUTOMATION AND ROBOTICS IN PHARMA INDUSTRY.pptx
sameeraaabegumm
 
PPTX
OpenID AuthZEN - Analyst Briefing July 2025
David Brossard
 
DOCX
Python coding for beginners !! Start now!#
Rajni Bhardwaj Grover
 
PDF
Smart Trailers 2025 Update with History and Overview
Paul Menig
 
PPTX
Webinar: Introduction to LF Energy EVerest
DanBrown980551
 
PDF
Using FME to Develop Self-Service CAD Applications for a Major UK Police Force
Safe Software
 
PPTX
WooCommerce Workshop: Bring Your Laptop
Laura Hartwig
 
PDF
POV_ Why Enterprises Need to Find Value in ZERO.pdf
darshakparmar
 
PDF
[Newgen] NewgenONE Marvin Brochure 1.pdf
darshakparmar
 
PPTX
"Autonomy of LLM Agents: Current State and Future Prospects", Oles` Petriv
Fwdays
 
PPTX
Future Tech Innovations 2025 – A TechLists Insight
TechLists
 
From Sci-Fi to Reality: Exploring AI Evolution
Svetlana Meissner
 
Newgen Beyond Frankenstein_Build vs Buy_Digital_version.pdf
darshakparmar
 
How Startups Are Growing Faster with App Developers in Australia.pdf
India App Developer
 
"AI Transformation: Directions and Challenges", Pavlo Shaternik
Fwdays
 
IoT-Powered Industrial Transformation – Smart Manufacturing to Connected Heal...
Rejig Digital
 
Building Real-Time Digital Twins with IBM Maximo & ArcGIS Indoors
Safe Software
 
Designing Production-Ready AI Agents
Kunal Rai
 
AI Penetration Testing Essentials: A Cybersecurity Guide for 2025
defencerabbit Team
 
Q2 FY26 Tableau User Group Leader Quarterly Call
lward7
 
AUTOMATION AND ROBOTICS IN PHARMA INDUSTRY.pptx
sameeraaabegumm
 
OpenID AuthZEN - Analyst Briefing July 2025
David Brossard
 
Python coding for beginners !! Start now!#
Rajni Bhardwaj Grover
 
Smart Trailers 2025 Update with History and Overview
Paul Menig
 
Webinar: Introduction to LF Energy EVerest
DanBrown980551
 
Using FME to Develop Self-Service CAD Applications for a Major UK Police Force
Safe Software
 
WooCommerce Workshop: Bring Your Laptop
Laura Hartwig
 
POV_ Why Enterprises Need to Find Value in ZERO.pdf
darshakparmar
 
[Newgen] NewgenONE Marvin Brochure 1.pdf
darshakparmar
 
"Autonomy of LLM Agents: Current State and Future Prospects", Oles` Petriv
Fwdays
 
Future Tech Innovations 2025 – A TechLists Insight
TechLists
 
Ad

Template Haskell Tutorial

  • 1. Template Haskell Tutorial short, illustrated examples from Illustrated Haskell <http://illustratedhaskell.org>
  • 2. Motivating example  fst(x,_) = x  fst3(x,_,_) = x  fst4(x,_,_,_) = x  …  print $ fst3 ("hello world", 1, 2)  print $ fst4 ("hello world", 1, 2, 3) So repetitive! Illustrated Haskell <http://illustratedhaskell.org>
  • 3. Template Haskell to the rescue! Usage:  {-# LANGUAGE TemplateHaskell #-}  print $ $(fstN 3) ("hello world", 1, 2)  print $ $(fstN 4) ("hello world", 1, 2, 3) Illustrated Haskell <http://illustratedhaskell.org>
  • 4. How to write it? -- FstN.hs {-# LANGUAGE TemplateHaskell #-} module FstN where import Language.Haskell.TH fstN :: Q Exp fstN n = do x <- newName "x” return $ LamE [TupP $ VarP x : replicate (n-1) WildP] (VarE x) Illustrated Haskell <http://illustratedhaskell.org>
  • 5. OK, how about explaining it?  Every time you want to write something in TH, you start with: runQ [| ... |]  GHC will tell you how to write it. For example, if we wanted to write a splice that will produce (x,_,_) -> x $ ghci – fth > :m +Language.Haskell.TH > runQ [| (x,_,_) -> x |] LamE [TupP [VarP x_1,WildP,WildP]] (VarE x_1) > :t it it :: Exp  That’s it, no need to remember anything! Just ask GHC! Illustrated Haskell <http://illustratedhaskell.org>
  • 6. Writing fst3 in TH  So we already have an Exp, how about those x_1? LamE [TupP [VarP x_1,WildP,WildP]] (VarE x_1) > :t (VarP, VarE) (VarP, VarE) :: (Name -> Pat, Name -> Exp)  So, VarP and VarE takes a Name. Let’s see how we can satisfy them: > :t newName newName :: String -> Q Name  A ha! So we can just plug it into the expression GHC gave us: fst3 = do x <- newName "x" LamE [TupP [VarP x,WildP,WildP]] (VarE x) Illustrated Haskell <http://illustratedhaskell.org>
  • 7. Evolving fst3 into fstN  The following corresponds to the expression (x,_,_) -> x fst3 = do x <- newName "x" LamE [TupP [VarP x,WildP,WildP]] (VarE x)  Not surprisingly, to make fst4, we just need to make 3 WildP: fst4 = do x <- newName "x" LamE [TupP [VarP x,WildP,WildP,WildP]] (VarE x)  And we can easily generalize it into fstN fstN n = do x <- newName "x" LamE [TupP (VarP x : replicate (n-1) WildP)] (VarE x) Illustrated Haskell <http://illustratedhaskell.org>
  • 8. Using fstN  For technical reasons, splices must be defined in a separate module.  So we need to create a new module to use the splice we defined: -- TestFstN.hs main = print $ $(fstN 3) ("hello world", 1, 3) Illustrated Haskell <http://illustratedhaskell.org>
  • 10. Quasi Quotes  The [| … |] notation that you just used is the quasi quotes for Haskell expression.  The contents within quasi quotes will be parsed at compile time.  Example: in Data.Array.Repa.Stencil, you could define a stencil like this [stencil2| 0 1 0 1 0 1 0 1 0 |]  It is converted to: makeStencil2 (Z:.3:.3) (ix -> case ix of Z :. -1 :. 0 -> Just 1 Z :. 0 :. -1 -> Just 1 Z :. 0 :. 1 -> Just 1 Z :. 1 :. 0 -> Just 1 _ -> Nothing) Illustrated Haskell <http://illustratedhaskell.org>
  • 11. Quasi Quotes  When you do [| x -> x |], the string inside the brackets is parsed by the Haskell compiler and gives you back the AST (Abstract Syntax Tree) Illustrated Haskell <http://illustratedhaskell.org>
  • 12. Let’s do a simple example  We will build a structure to represent HTML documents  For simplicity, we omit attributes, self closing tags, etc. -- HTML.hs {-# LANGUAGE TemplateHaskell, QuasiQuotes #-} module HTML where data Node = Tag String [Node] -- tag name, children | Text String deriving Show  Our target is to use quasi quotes to build a document tree: -- HTMLTest.hs import HTML doc :: Node doc = [html|<html>Hello, <strong>TH</strong> world!</html>] -- Node "html" [Text "Hello, ”, Tag "strong" [Text "TH"], Text " world!"] Illustrated Haskell <http://illustratedhaskell.org>
  • 13. First, a simple HTML parser  We’ll sidetrack a bit and make a dead simple HTML parser using Parsec  Our focus here isn’t Parsec so we can just skim over this function that does the right thing -- HTML.hs textNode :: Parser Node textNode = fmap Text $ many1 $ satisfy (/='<') tagNode :: Parser Node tagNode = do tagName <- char '<' *> many1 letter <* char '>' children <- many $ try tagNode <|> textNode string "</" >> string tagName >> char '>' return $ Tag tagName children Illustrated Haskell <http://illustratedhaskell.org>
  • 14. A simple test for our parser $ ghci HTML.hs > parseTest tagNode "<html>Hello, <strong>TH</strong> world!</html>" Tag "html" [Text "Hello, ",Tag "strong" [Text "TH"],Text " world!”]  It works! Illustrated Haskell <http://illustratedhaskell.org>
  • 15. Now we can write our QuasiQuoter -- HTML.hs  The QuasiQuoter takes 4 Html :: QuasiQuoter parameters. Each will be called when the quasi quote Html = QuasiQuoter is being invoked to create: htmlExpr  An expression undefined  foo = [html| ... |]  A pattern (for pattern undefined matching) undefined  bar [html| ... |] = 3  A type  A top-level declaration htmlExpr :: String -> Q Exp htmlExpr = undefined  We will do expression and pattern in this example  For more information consult GHC’s documentation Illustrated Haskell <http://illustratedhaskell.org>
  • 16. htmlExpr is supposed to parse the contents within [html| … |] and give back an Exp htmlExpr :: String -> Q Exp htmlExpr str = do filename <- loc_filename `fmap` location case parse tagNode filename str of Left err -> undefined Right tag -> [| tag |]  As easy as that, loc_filename and location will give us the filename of the user. Illustrated Haskell <http://illustratedhaskell.org>
  • 17. Let’s compile it! $ ghc HTML.hs Error: No instance for (Lift Node) arising from arising of `tag’…  What is that? Well maybe we can satisfy it by implementing the Lift instance for Node, as instructed: instance Lift Node where lift (Text t) = [| Text t |] lift (Tag name children) = [| Tag name children |] Illustrated Haskell <http://illustratedhaskell.org>
  • 18. Let’s try it out -- HTMLTest.hs {-# LANGUAGE TemplateHaskell , QuasiQuotes #-} import HTML main = print [html|<html>Hello, <strong>TH</strong> world!</html>|] $ ghci HTMLTest.hs > main Tag "html" [Text "Hello, ",Tag "strong" [Text "TH"],Text " world!"]  It works!  Illustrated Haskell <http://illustratedhaskell.org>
  • 19. Quasi quoting for patterns  Now let’s try to do some operations on our HTML structure  In this example we will convert an HTML tree into Markdown  Markdown is a simple wiki syntax  Example Markdown: Let’s **rock** and _roll_!  Corresponding HTML: <html>Let's <strong>rock</strong> and <em>roll</em></html>  Usually people convert Markdown to HTML. We will do it the other way here. Illustrated Haskell <http://illustratedhaskell.org>
  • 20. Let’s make a simple converter -- HTMLTest.hs markdown (Tag "strong" children) = "**" ++ concatMap markdown children ++ "**" markdown (Tag "em" children) = "_" ++ concatMap markdown children ++ "_" markdown (Tag _ children) = concatMap markdown children markdown (Text t) = t  That’s some normal Haskell. For fun, we’re going to turn it into: -- HTMLTest.hs markdown [html|<strong>|] = "**" ++ concatMap markdown children ++ "**" markdown [html|<em>|] = "_" ++ concatMap markdown children ++ "_" markdown [html|<_>|] = concatMap markdown children markdown [html|#text|] = text  Are we gaining anything? Honestly not much. But we’ll do it for the sake of an TH example. Illustrated Haskell <http://illustratedhaskell.org>
  • 21. Add a pattern parser to our QuasiQuoter -- HTML.hs html :: QuasiQuoter html = QuasiQuoter htmlExpr htmlPat undefined undefined htmlPat :: String -> Q Pat htmlPat "<_>" = [p| Tag _ children |] htmlPat "#text" = [p| Text text |] htmlPat ('<':rest) = undefined -- ... Illustrated Haskell <http://illustratedhaskell.org>
  • 22. Asking GHC again…  Now how do we write the “rest” case? Let’s ask GHC > runQ [p| Tag "strong" chlidren |] ConP HTML.Tag [ LitP (StringL "strong") , VarP chlidren]  So there we have almost had it.  We just need to use Name at appropriate places and follow the types: htmlPat ('<':rest) = return $ ConP (mkName "HTML.Tag”) [ LitP (StringL (init rest)) , VarP (mkName "children")] Illustrated Haskell <http://illustratedhaskell.org>
  • 23. Some explanations htmlPat ('<':rest) = return $ ConP (mkName "HTML.Tag”) [ LitP (StringL (init rest)) , VarP (mkName "children")]  Here we see mkName intead of newName  mkName "foo" will translate into an identifier "foo" literally  mkName "foo" will become something like "foo_1".  You’ll use this when you want to avoid name collisions Illustrated Haskell <http://illustratedhaskell.org>
  • 24. Let’s test it out! -- HTMLTest.hs {-# LANGUAGE TemplateHaskell , QuasiQuotes #-} import HTML doc = [html|<html>Hello, <strong>TH</strong> world!</html>|] markdown [html|<_>|] = concatMap markdown children markdown [html|#text|] = text markdown [html|<strong>|] = "**" ++ concatMap markdown children ++ "**” main = print . markdown $ doc  $ runhaskell HTMLTest.hs  "Hello, **TH** world!" Illustrated Haskell <http://illustratedhaskell.org>
  • 25. Summary  Use runQ to have GHC write the splice for you  Then just fix it up by following the type Illustrated Haskell <http://illustratedhaskell.org>