diff options
author | fiddlosopher <fiddlosopher@788f1e2b-df1e-0410-8736-df70ead52e1b> | 2009-12-31 01:15:33 +0000 |
---|---|---|
committer | fiddlosopher <fiddlosopher@788f1e2b-df1e-0410-8736-df70ead52e1b> | 2009-12-31 01:15:33 +0000 |
commit | 5ba6c0911cb44c3a095bc3cedc51e4afa79c6b30 (patch) | |
tree | 7b6d47fe8c560e9cf4121da03754a254c49a7079 | |
parent | 16f0604beca57b17c6e1fa330930a903a4fd81c7 (diff) | |
download | pandoc-5ba6c0911cb44c3a095bc3cedc51e4afa79c6b30.tar.gz |
Added $for$ to template system.
git-svn-id: https://pandoc.googlecode.com/svn/trunk@1720 788f1e2b-df1e-0410-8736-df70ead52e1b
-rw-r--r-- | README | 20 | ||||
-rw-r--r-- | man/man1/pandoc.1.md | 20 | ||||
-rw-r--r-- | src/Text/Pandoc/Templates.hs | 55 |
3 files changed, 77 insertions, 18 deletions
@@ -472,6 +472,8 @@ the string `$title$` in will be replaced by the document title. +To write a literal `$` in a template, use `$$`. + Some variables are set automatically by pandoc. These vary somewhat depending on the output format, but include: @@ -485,12 +487,10 @@ depending on the output format, but include: : body of document `title` : title of document, as specified in title block -`authors` -: authors of document, as specified in title block +`author` +: author of document, as specified in title block `date` : date of document, as specified in title block -`css` -: links to CSS files, as specified using `-c/--css` Variables may be set at the command line using the `-V/--variable` option. This allows users to include custom variables in their @@ -509,7 +509,17 @@ value; otherwise it will include `Y`. `X` and `Y` are placeholders for any valid template text, and may include interpolated variables or other conditionals. The `$else$` section may be omitted. -To write a literal `$` in a template, use `$$`. +When variables can have multiple values (for example, `author` in +a multi-author document), you can use the `$for$` keyword: + + $for(author)$ + <meta name="author" content="$author$" /> + $endfor$ + +You can optionally specify a separator to be used between +consecutive items: + + $for(author)$$author$$sep$, $endfor$ Pandoc's markdown vs. standard markdown ======================================= diff --git a/man/man1/pandoc.1.md b/man/man1/pandoc.1.md index eb8aa3fdc..dad9eb9d3 100644 --- a/man/man1/pandoc.1.md +++ b/man/man1/pandoc.1.md @@ -253,6 +253,8 @@ the string `$title$` in will be replaced by the document title. +To write a literal `$` in a template, use `$$`. + Some variables are set automatically by pandoc. These vary somewhat depending on the output format, but include: @@ -266,12 +268,10 @@ depending on the output format, but include: : body of document `title` : title of document, as specified in title block -`authors` -: authors of document, as specified in title block +`author` +: author of document, as specified in title block `date` : date of document, as specified in title block -`css` -: links to CSS files, as specified using `-c/--css` Variables may be set at the command line using the `-V/--variable` option. This allows users to include custom variables in their @@ -290,7 +290,17 @@ value; otherwise it will include `Y`. `X` and `Y` are placeholders for any valid template text, and may include interpolated variables or other conditionals. The `$else$` section may be omitted. -To write a literal `$` in a template, use `$$`. +When variables can have multiple values (for example, `author` in +a multi-author document), you can use the `$for$` keyword: + + $for(author)$ + <meta name="author" content="$author$" /> + $endfor$ + +You can optionally specify a separator to be used between +consecutive items: + + $for(author)$$author$$sep$, $endfor$ # SEE ALSO diff --git a/src/Text/Pandoc/Templates.hs b/src/Text/Pandoc/Templates.hs index abd761099..548bf7db5 100644 --- a/src/Text/Pandoc/Templates.hs +++ b/src/Text/Pandoc/Templates.hs @@ -29,9 +29,9 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA 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." +> 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 @@ -48,6 +48,20 @@ is used. Conditional keywords should not be indented, or unexpected spacing problems may occur. + +If a variable name is associated with multiple values in the association +list passed to 'renderTemplate', you may use the @$for$@ keyword to +iterate over them: + +> renderTemplate [("name","Sam"),("name","Joe")] $ +> "$for(name)$\nHi, $name$.\n$endfor$" +> "Hi, Sam.\nHi, Joe." + +You may optionally specify separators using @$sep$@: + +> renderTemplate [("name","Sam"),("name","Joe"),("name","Lynn")] $ +> "Hi, $for(name)$$name$$sep$, $endfor$" +> "Hi, Sam, Joe, Lynn." -} module Text.Pandoc.Templates ( renderTemplate @@ -55,11 +69,11 @@ module Text.Pandoc.Templates ( renderTemplate , getDefaultTemplate) where import Text.ParserCombinators.Parsec -import Control.Monad (liftM, when) +import Control.Monad (liftM, when, forM) import qualified Control.Exception as E (try, IOException) import System.FilePath import Text.Pandoc.Shared (readDataFile) -import Data.List (intercalate) +import Data.List (intercalate, intersperse) import Text.PrettyPrint (text, Doc) import Text.XHtml (primHtml, Html) import Data.ByteString.Lazy.UTF8 (ByteString, fromString) @@ -111,11 +125,11 @@ renderTemplate vals templ = Right r -> toTarget $ concat r reservedWords :: [String] -reservedWords = ["else","endif"] +reservedWords = ["else","endif","for","endfor","sep"] parseTemplate :: GenParser Char TemplateState [String] parseTemplate = - many $ (plaintext <|> escapedDollar <|> conditional <|> variable) + many $ (plaintext <|> escapedDollar <|> conditional <|> for <|> variable) >>= adjustPosition plaintext :: GenParser Char TemplateState String @@ -124,9 +138,11 @@ plaintext = many1 $ noneOf "$" escapedDollar :: GenParser Char TemplateState String escapedDollar = try $ string "$$" >> return "$" +skipEndline :: GenParser Char st () +skipEndline = try $ skipMany (oneOf " \t") >> newline >> return () + conditional :: GenParser Char TemplateState String conditional = try $ do - let skipEndline = try $ skipMany (oneOf " \t") >> newline TemplateState pos vars <- getState string "$if(" id' <- ident @@ -149,6 +165,29 @@ conditional = try $ do when multiline $ optional skipEndline return contents +for :: GenParser Char TemplateState String +for = try $ do + TemplateState pos vars <- getState + string "$for(" + id' <- ident + string ")$" + -- if newline after the "if", then a newline after "endif" will be swallowed + multiline <- option False $ try $ skipEndline >> return True + let matches = filter (\(k,_) -> k == id') vars + let indent = replicate pos ' ' + contents <- forM matches $ \m -> do + updateState $ \(TemplateState p v) -> TemplateState p (m:v) + raw <- liftM concat $ lookAhead parseTemplate + return $ intercalate ('\n':indent) $ lines $ raw ++ "\n" + parseTemplate + sep <- option "" $ do try (string "$sep$") + when multiline $ optional skipEndline + liftM concat parseTemplate + string "$endfor$" + when multiline $ optional skipEndline + setState $ TemplateState pos vars + return $ concat $ intersperse sep contents + ident :: GenParser Char TemplateState String ident = do first <- letter |