Made renderTemplate polymorphic; added TemplateTarget class.

Now renderTemplate can return an Html, a Doc, a ByteString, or
a String.

git-svn-id: https://pandoc.googlecode.com/svn/trunk@1712 788f1e2b-df1e-0410-8736-df70ead52e1b
This commit is contained in:
fiddlosopher 2009-12-31 01:14:35 +00:00
parent 22dcf7afdd
commit d5907b3034
2 changed files with 30 additions and 7 deletions

View file

@ -1,3 +1,4 @@
{-# LANGUAGE TypeSynonymInstances #-}
{-
Copyright (C) 2009 John MacFarlane <jgm@berkeley.edu>
@ -49,7 +50,9 @@ Conditional keywords should not be indented, or unexpected spacing
problems may occur.
-}
module Text.Pandoc.Templates (renderTemplate, getDefaultTemplate) where
module Text.Pandoc.Templates ( renderTemplate
, TemplateTarget
, getDefaultTemplate) where
import Text.ParserCombinators.Parsec
import Control.Monad (liftM, when)
@ -57,6 +60,9 @@ import qualified Control.Exception as E (try, IOException)
import System.FilePath
import Text.Pandoc.Shared (readDataFile)
import Data.List (intercalate)
import Text.PrettyPrint (text, Doc)
import Text.XHtml (primHtml, Html)
import Data.ByteString.Lazy.UTF8 (ByteString, fromString)
-- | Get the default template, either from the application's user data
-- directory (~/.pandoc on unix) or from the cabal data directory.
@ -79,14 +85,30 @@ adjustPosition str = do
else TemplateState (length lastline) x
return str
class TemplateTarget a where
toTarget :: String -> a
instance TemplateTarget String where
toTarget = id
instance TemplateTarget ByteString where
toTarget = fromString
instance TemplateTarget Html where
toTarget = primHtml
instance TemplateTarget Doc where
toTarget = text
-- | Renders a template
renderTemplate :: [(String,String)] -- ^ Assoc. list of values for variables
renderTemplate :: TemplateTarget a
=> [(String,String)] -- ^ Assoc. list of values for variables
-> String -- ^ Template
-> String
-> a
renderTemplate vals templ =
case runParser (do x <- parseTemplate; eof; return x) (TemplateState 0 vals) "template" templ of
Left e -> error $ show e
Right r -> concat r
Right r -> toTarget $ concat r
reservedWords :: [String]
reservedWords = ["else","endif"]

View file

@ -89,7 +89,7 @@ writeHtml opts d =
let (tit, auths, date, toc, body', newvars) = evalState (pandocToHtml opts d)
defaultWriterState
in if writerStandalone opts
then primHtml $ inTemplate opts tit auths date toc body' newvars
then inTemplate opts tit auths date toc body' newvars
else body'
-- result is (title, authors, date, toc, body, new variables)
@ -135,14 +135,15 @@ pandocToHtml opts (Pandoc (Meta title' authors' date') blocks) = do
[("math", renderHtmlFragment math) | stMath st]
return (tit, auths, date, toc, thebody, newvars)
inTemplate :: WriterOptions
inTemplate :: TemplateTarget a
=> WriterOptions
-> Html
-> [Html]
-> Html
-> Html
-> Html
-> [(String,String)]
-> String
-> a
inTemplate opts tit auths date toc body' newvars =
let renderedTit = showHtmlFragment tit
topTitle' = stripTags renderedTit