Added templates module.
git-svn-id: https://pandoc.googlecode.com/svn/trunk@1673 788f1e2b-df1e-0410-8736-df70ead52e1b
This commit is contained in:
parent
d86c01795f
commit
a42bae619a
2 changed files with 112 additions and 0 deletions
|
@ -193,6 +193,7 @@ Library
|
|||
Text.Pandoc.Writers.S5
|
||||
Other-Modules: Text.Pandoc.XML,
|
||||
Text.Pandoc.TH,
|
||||
Text.Pandoc.Templates
|
||||
Paths_pandoc
|
||||
Extensions: CPP, TemplateHaskell, FlexibleInstances
|
||||
Ghc-Options: -O2 -Wall
|
||||
|
|
111
src/Text/Pandoc/Templates.hs
Normal file
111
src/Text/Pandoc/Templates.hs
Normal file
|
@ -0,0 +1,111 @@
|
|||
{-
|
||||
Copyright (C) 2009 John MacFarlane <jgm@berkeley.edu>
|
||||
|
||||
This program is free software; you can redistribute it and/or modify
|
||||
it under the terms of the GNU General Public License as published by
|
||||
the Free Software Foundation; either version 2 of the License, or
|
||||
(at your option) any later version.
|
||||
|
||||
This program is distributed in the hope that it will be useful,
|
||||
but WITHOUT ANY WARRANTY; without even the implied warranty of
|
||||
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
|
||||
GNU General Public License for more details.
|
||||
|
||||
You should have received a copy of the GNU General Public License
|
||||
along with this program; if not, write to the Free Software
|
||||
Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
|
||||
-}
|
||||
|
||||
{- |
|
||||
Module : Text.Pandoc.Templates
|
||||
Copyright : Copyright (C) 2009 John MacFarlane
|
||||
License : GNU GPL, version 2 or above
|
||||
|
||||
Maintainer : John MacFarlane <jgm@berkeley.edu>
|
||||
Stability : alpha
|
||||
Portability : portable
|
||||
|
||||
A simple templating system with variable substitution and conditionals.
|
||||
Example:
|
||||
|
||||
> > renderTemplate [("name","Sam"),("salary","50,000")] $
|
||||
> "Hi, $name$. $if(salary)$You make $$$salary$.$else$No salary data.$endif$"
|
||||
> > "Hi, John. You make $50,000."
|
||||
|
||||
A slot for an interpolated variable is a variable name surrounded
|
||||
by dollar signs. To include a literal @$@ in your template, use
|
||||
@$$@. Variable names must begin with a letter and can contain letters,
|
||||
numbers, @_@, and @-@.
|
||||
|
||||
A conditional begins with @$if(variable_name)$@ and ends with @$endif$@.
|
||||
It may optionally contain an @$else$@ section. The if section is
|
||||
used if @variable_name@ has a non-null value, otherwise the else section
|
||||
is used.
|
||||
-}
|
||||
|
||||
module Text.Pandoc.Templates (renderTemplate) where
|
||||
|
||||
import Text.ParserCombinators.Parsec
|
||||
import Control.Monad (liftM)
|
||||
|
||||
-- | Renders a template
|
||||
renderTemplate :: [(String,String)] -- ^ Assoc. list of values for variables
|
||||
-> String -- ^ Template
|
||||
-> String
|
||||
renderTemplate vals templ =
|
||||
case runParser (do x <- parseTemplate; eof; return x) vals "template" templ of
|
||||
Left e -> show e
|
||||
Right r -> concat r
|
||||
|
||||
reservedWords :: [String]
|
||||
reservedWords = ["else","endif"]
|
||||
|
||||
parseTemplate :: GenParser Char [(String,String)] [String]
|
||||
parseTemplate =
|
||||
many $ plaintext <|> escapedDollar <|> conditional <|> variable
|
||||
|
||||
plaintext :: GenParser Char [(String,String)] String
|
||||
plaintext = many1 $ satisfy (/='$')
|
||||
|
||||
escapedDollar :: GenParser Char [(String,String)] String
|
||||
escapedDollar = try $ string "$$" >> return "$"
|
||||
|
||||
conditional :: GenParser Char [(String,String)] String
|
||||
conditional = try $ do
|
||||
string "$if("
|
||||
id' <- ident
|
||||
string ")$"
|
||||
skipMany (oneOf " \t")
|
||||
optional newline
|
||||
ifContents <- liftM concat parseTemplate
|
||||
elseContents <- option "" $ do try (string "$else$")
|
||||
skipMany (oneOf " \t")
|
||||
optional newline
|
||||
liftM concat parseTemplate
|
||||
string "$endif$"
|
||||
skipMany (oneOf " \t")
|
||||
optional newline
|
||||
st <- getState
|
||||
return $ case lookup id' st of
|
||||
Just "" -> elseContents
|
||||
Just _ -> ifContents
|
||||
Nothing -> elseContents
|
||||
|
||||
ident :: GenParser Char [(String,String)] String
|
||||
ident = do
|
||||
first <- letter
|
||||
rest <- many (alphaNum <|> oneOf "_-")
|
||||
let id' = first : rest
|
||||
if id' `elem` reservedWords
|
||||
then pzero
|
||||
else return id'
|
||||
|
||||
variable :: GenParser Char [(String,String)] String
|
||||
variable = try $ do
|
||||
char '$'
|
||||
id' <- ident
|
||||
char '$'
|
||||
st <- getState
|
||||
return $ case lookup id' st of
|
||||
Just val -> val
|
||||
Nothing -> ""
|
Loading…
Reference in a new issue