aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Templates.hs
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2019-07-26 12:00:44 -0700
committerJohn MacFarlane <jgm@berkeley.edu>2019-07-28 19:25:45 -0700
commitb35fae651145482f1218d32dbea5fffff60e0b0b (patch)
tree02175f056c40aee4329b8f944ada9c9cd6ac1284 /src/Text/Pandoc/Templates.hs
parent99e24cf18337b0b460005bf77e367783c34b75e7 (diff)
downloadpandoc-b35fae651145482f1218d32dbea5fffff60e0b0b.tar.gz
Use doctemplates 0.3, change type of writerTemplate.
* Require recent doctemplates. It is more flexible and supports partials. * Changed type of writerTemplate to Maybe Template instead of Maybe String. * Remove code from the LaTeX, Docbook, and JATS writers that looked in the template for strings to determine whether it is a book or an article, or whether csquotes is used. This was always kludgy and unreliable. To use csquotes for LaTeX, set `csquotes` in your variables or metadata. It is no longer sufficient to put `\usepackage{csquotes}` in your template or header includes. To specify a book style, use the `documentclass` variable or `--top-level-division`. * Change template code to use new API for doctemplates.
Diffstat (limited to 'src/Text/Pandoc/Templates.hs')
-rw-r--r--src/Text/Pandoc/Templates.hs29
1 files changed, 9 insertions, 20 deletions
diff --git a/src/Text/Pandoc/Templates.hs b/src/Text/Pandoc/Templates.hs
index d0880a43f..36eacfdd8 100644
--- a/src/Text/Pandoc/Templates.hs
+++ b/src/Text/Pandoc/Templates.hs
@@ -12,26 +12,23 @@ A simple templating system with variable substitution and conditionals.
-}
-module Text.Pandoc.Templates ( module Text.DocTemplates
- , renderTemplate'
+module Text.Pandoc.Templates ( Template
+ , compileTemplate
+ , renderTemplate
, getDefaultTemplate
) where
import Prelude
-import Control.Monad.Except (throwError)
-import Data.Aeson (ToJSON (..))
-import qualified Data.Text as T
import System.FilePath ((<.>), (</>))
-import Text.DocTemplates (Template, applyTemplate,
- compileTemplate, renderTemplate)
+import Text.DocTemplates (Template, compileTemplate, renderTemplate)
import Text.Pandoc.Class (PandocMonad, readDataFile)
-import Text.Pandoc.Error
import qualified Text.Pandoc.UTF8 as UTF8
+import Data.Text (Text)
-- | Get default template for the specified writer.
getDefaultTemplate :: PandocMonad m
=> String -- ^ Name of writer
- -> m String
+ -> m Text
getDefaultTemplate writer = do
let format = takeWhile (`notElem` ("+-" :: String)) writer -- strip off extensions
case format of
@@ -52,14 +49,6 @@ getDefaultTemplate writer = do
"markdown_mmd" -> getDefaultTemplate "markdown"
"markdown_phpextra" -> getDefaultTemplate "markdown"
"gfm" -> getDefaultTemplate "commonmark"
- _ -> let fname = "templates" </> "default" <.> format
- in UTF8.toString <$> readDataFile fname
-
--- | Like 'applyTemplate', but runs in PandocMonad and
--- raises an error if compilation fails.
-renderTemplate' :: (PandocMonad m, ToJSON a)
- => String -> a -> m T.Text
-renderTemplate' template context =
- case applyTemplate (T.pack template) context of
- Left e -> throwError (PandocTemplateError e)
- Right r -> return r
+ _ -> do
+ let fname = "templates" </> "default" <.> format
+ UTF8.toText <$> readDataFile fname