summaryrefslogtreecommitdiff
path: root/src/Text/Pandoc
diff options
context:
space:
mode:
authorfiddlosopher <fiddlosopher@788f1e2b-df1e-0410-8736-df70ead52e1b>2009-12-31 01:14:35 +0000
committerfiddlosopher <fiddlosopher@788f1e2b-df1e-0410-8736-df70ead52e1b>2009-12-31 01:14:35 +0000
commitd5907b3034994c98d9ea534574b36942717bb241 (patch)
tree3166e39abba1925f2e48e336d609f13b4dec2b3e /src/Text/Pandoc
parent22dcf7afdd7ea4508d9b739a3b48138022d361e6 (diff)
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
Diffstat (limited to 'src/Text/Pandoc')
-rw-r--r--src/Text/Pandoc/Templates.hs30
-rw-r--r--src/Text/Pandoc/Writers/HTML.hs7
2 files changed, 30 insertions, 7 deletions
diff --git a/src/Text/Pandoc/Templates.hs b/src/Text/Pandoc/Templates.hs
index b40cf7fdb..abd761099 100644
--- a/src/Text/Pandoc/Templates.hs
+++ b/src/Text/Pandoc/Templates.hs
@@ -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"]
diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs
index a544ad781..cae2bb021 100644
--- a/src/Text/Pandoc/Writers/HTML.hs
+++ b/src/Text/Pandoc/Writers/HTML.hs
@@ -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