peggy-0.2.1: The Parser Generator for Haskell

Portabilityportable
Stabilityexperimental
Maintainertanaka.hideyuki@gmail.com

Text.Peggy.Quote

Contents

Description

The quasi-quoters of peggy syntax.

Synopsis

Quasi Quoters

peggy :: QuasiQuoterSource

quasi-quoter for peggy syntax When it is used at top-level of source code, definitions of parsers are generated.

 {-# LANGUAGE TemplateHaskell, QuasiQuotes, FlexibleContexts #-}
 import Text.Peggy
 
 [peggy|
 foo :: [Int]
   = num*
 num ::: Int
   = [0-9]+ { read $1 }
 |]
 
 main :: IO ()
 main = print . parseString foo "<stdin>" =<< getContents

When it is used as expression, the result value is Syntax.

 main = print [peggy|
 num :: Int
   = [0-9]+ { read $1 }
 |]

The result is:

 $ runhaskell Test.hs
 [Definition "num" "Int\n  " (Choice [Semantic (Sequence [Some (TerminalSet [CharRange '0' '9'])]) [Snippet "read ",Argument 1,Snippet " "]])]

peggyFile :: FilePath -> Q ExpSource

Parse peggy syntax from File Parse a peggy syntax file and return a Syntax as a result value.

 $ cat test.peggy
 num :: Int
   = [0-9]+ { return $1 }
 main = print $(peggyFile "test.peggy")

The result is:

 [Definition "num" "Int\n  " (Choice [Semantic (Sequence [Some (TerminalSet [CharRange '0' '9'])]) [Snippet "read ",Argument 1,Snippet " "]])]

Parser and Quasi-quoter generating function

genParserSource

Arguments

:: [(String, String)]

a list of pair of name of quasi-quoter and its start nonterminal

-> Syntax

syntax

-> Q [Dec]

definitions of parsers and quasi-quoters

Generates parsers and quasi-quoters. First argument is a list of names of quasi-quoter you want to define. For example:

 genParser [("fooqq", "foo")] [peggy|
 foo :: [Int]
   = num*
 num ::: Int
   = [0-9]+ { read $1 }
 |]

this code defines parsers named foo, num and quasi-quoter named fooqq.

It can use it as follow:

 main :: IO ()
 main = print [fooqq| 1 2 3 4 5 |]