diff options
| -rw-r--r-- | src/Text/Pandoc/Templates.hs | 78 | ||||
| -rw-r--r-- | templates/html.template | 56 | 
2 files changed, 77 insertions, 57 deletions
| diff --git a/src/Text/Pandoc/Templates.hs b/src/Text/Pandoc/Templates.hs index b8c70c569..69cd5c554 100644 --- a/src/Text/Pandoc/Templates.hs +++ b/src/Text/Pandoc/Templates.hs @@ -46,10 +46,11 @@ is used.  module Text.Pandoc.Templates (renderTemplate, getDefaultTemplate) where  import Text.ParserCombinators.Parsec -import Control.Monad (liftM) +import Control.Monad (liftM, when)  import qualified Control.Exception as E (try, IOException)  import System.FilePath  import Text.Pandoc.Shared (readDataFile) +import Data.List (intercalate)  -- | Get the default template, either from the application's user data  -- directory (~/.pandoc on unix) or from the cabal data directory. @@ -60,51 +61,67 @@ getDefaultTemplate "odt" = getDefaultTemplate "opendocument"  getDefaultTemplate format = do    let format' = takeWhile (/='+') format  -- strip off "+lhs" if present    E.try $ readDataFile $ "templates" </> format' <.> "template" -  + +data TemplateState = TemplateState Int [(String,String)] + +adjustPosition :: String -> GenParser Char TemplateState String +adjustPosition str = do +  let lastline = takeWhile (/= '\n') $ reverse str +  updateState $ \(TemplateState pos x) -> +    if str == lastline +       then TemplateState (pos + length lastline) x +       else TemplateState (length lastline) x +  return str +  -- | 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 +  case runParser (do x <- parseTemplate; eof; return x) (TemplateState 0 vals) "template" templ of         Left e        -> error $ show e         Right r       -> concat r  reservedWords :: [String]  reservedWords = ["else","endif"] -parseTemplate :: GenParser Char [(String,String)] [String] +parseTemplate :: GenParser Char TemplateState [String]  parseTemplate = -  many $ plaintext <|> escapedDollar <|> conditional <|> variable +  many $ (plaintext <|> escapedDollar <|> conditional <|> variable) +           >>= adjustPosition -plaintext :: GenParser Char [(String,String)] String -plaintext = many1 $ satisfy (/='$') +plaintext :: GenParser Char TemplateState String +plaintext = many1 $ noneOf "$" -escapedDollar :: GenParser Char [(String,String)] String +escapedDollar :: GenParser Char TemplateState String  escapedDollar = try $ string "$$" >> return "$" -conditional :: GenParser Char [(String,String)] String +conditional :: GenParser Char TemplateState String  conditional = try $ do +  TemplateState pos vars <- getState    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 +  -- if newline after the "if", then a newline after "endif" will be swallowed +  multiline <- option False $ try $ +                   newline >> count pos (char ' ') >> return True +  let conditionSatisfied = case lookup id' vars of +                                Nothing -> False +                                Just "" -> False +                                Just _  -> True +  contents <- if conditionSatisfied +                 then liftM concat parseTemplate +                 else do +                   parseTemplate  -- skip if part, then reset position +                   setState $ TemplateState pos vars +                   option "" $ do try (string "$else$") +                                  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 +  when multiline $ optional $ newline +  return contents + +ident :: GenParser Char TemplateState String  ident = do    first <- letter    rest <- many (alphaNum <|> oneOf "_-") @@ -113,12 +130,13 @@ ident = do       then pzero       else return id' -variable :: GenParser Char [(String,String)] String +variable :: GenParser Char TemplateState String  variable = try $ do    char '$'    id' <- ident    char '$' -  st <- getState -  return $ case lookup id' st of -           Just val  -> val -           Nothing   -> "" +  TemplateState pos vars <- getState +  let indent = replicate pos ' ' +  return $ case lookup id' vars of +             Just val  -> intercalate ('\n' : indent) $ lines val +             Nothing   -> "" diff --git a/templates/html.template b/templates/html.template index 3a756ee6e..45eb225ef 100644 --- a/templates/html.template +++ b/templates/html.template @@ -1,47 +1,49 @@  <!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd">  <html xmlns="http://www.w3.org/1999/xhtml">  <head> -  <title>$if(title-prefix)$$title-prefix$ - $endif$$if(pagetitle)$$pagetitle$$endif$</title> +  <title> +    $if(title-prefix)$$title-prefix$ - $endif$$if(pagetitle)$$pagetitle$$endif$ +  </title>    <meta http-equiv="Content-Type" content="text/html; charset=utf-8" />    <meta name="generator" content="pandoc" />    <meta name="author" content="$authors$" />    <meta name="date" content="$date$" />    $if(highlighting)$    <style type="text/css"> -  table.sourceCode, tr.sourceCode, td.lineNumbers, td.sourceCode, table.sourceCode pre { margin: 0; padding: 0; border: 0; vertical-align: baseline; border: none; } -  td.lineNumbers { border-right: 1px solid #AAAAAA; text-align: right; color: #AAAAAA; padding-right: 5px; padding-left: 5px; } -  td.sourceCode { padding-left: 5px; } -  pre.sourceCode { } -  pre.sourceCode span.Normal { } -  pre.sourceCode span.Keyword { color: #007020; font-weight: bold; }  -  pre.sourceCode span.DataType { color: #902000; } -  pre.sourceCode span.DecVal { color: #40a070; } -  pre.sourceCode span.BaseN { color: #40a070; } -  pre.sourceCode span.Float { color: #40a070; } -  pre.sourceCode span.Char { color: #4070a0; } -  pre.sourceCode span.String { color: #4070a0; } -  pre.sourceCode span.Comment { color: #60a0b0; font-style: italic; } -  pre.sourceCode span.Others { color: #007020; } -  pre.sourceCode span.Alert { color: red; font-weight: bold; } -  pre.sourceCode span.Function { color: #06287e; } -  pre.sourceCode span.RegionMarker { } -  pre.sourceCode span.Error { color: red; font-weight: bold; } +    table.sourceCode, tr.sourceCode, td.lineNumbers, td.sourceCode, table.sourceCode pre { margin: 0; padding: 0; border: 0; vertical-align: baseline; border: none; } +    td.lineNumbers { border-right: 1px solid #AAAAAA; text-align: right; color: #AAAAAA; padding-right: 5px; padding-left: 5px; } +    td.sourceCode { padding-left: 5px; } +    pre.sourceCode { } +    pre.sourceCode span.Normal { } +    pre.sourceCode span.Keyword { color: #007020; font-weight: bold; }  +    pre.sourceCode span.DataType { color: #902000; } +    pre.sourceCode span.DecVal { color: #40a070; } +    pre.sourceCode span.BaseN { color: #40a070; } +    pre.sourceCode span.Float { color: #40a070; } +    pre.sourceCode span.Char { color: #4070a0; } +    pre.sourceCode span.String { color: #4070a0; } +    pre.sourceCode span.Comment { color: #60a0b0; font-style: italic; } +    pre.sourceCode span.Others { color: #007020; } +    pre.sourceCode span.Alert { color: red; font-weight: bold; } +    pre.sourceCode span.Function { color: #06287e; } +    pre.sourceCode span.RegionMarker { } +    pre.sourceCode span.Error { color: red; font-weight: bold; }    </style>    $endif$    $if(header-includes)$ -  $header-includes$ +    $header-includes$    $endif$    $if(latexmathml-script)$ -  $latexmathml-script$ +    $latexmathml-script$    $endif$  </head>  <body> -$if(title)$ +  $if(title)$    <h1 class="title">$title$</h1> -$endif$ -$if(toc)$ -$toc$ -$endif$ -$body$ +  $endif$ +  $if(toc)$ +  $toc$ +  $endif$ +  $body$  </body>  </html> | 
