From b35fae651145482f1218d32dbea5fffff60e0b0b Mon Sep 17 00:00:00 2001 From: John MacFarlane <jgm@berkeley.edu> Date: Fri, 26 Jul 2019 12:00:44 -0700 Subject: [PATCH] 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. --- MANUAL.txt | 25 +++++----- pandoc.cabal | 3 +- src/Text/Pandoc/App/CommandLineOptions.hs | 9 ++-- src/Text/Pandoc/App/OutputSettings.hs | 14 +++++- src/Text/Pandoc/Class.hs | 13 +++++ src/Text/Pandoc/Options.hs | 3 +- src/Text/Pandoc/Templates.hs | 29 ++++------- src/Text/Pandoc/Writers/AsciiDoc.hs | 9 ++-- src/Text/Pandoc/Writers/CommonMark.hs | 9 ++-- src/Text/Pandoc/Writers/ConTeXt.hs | 9 ++-- src/Text/Pandoc/Writers/Custom.hs | 11 ++--- src/Text/Pandoc/Writers/Docbook.hs | 24 ++++----- src/Text/Pandoc/Writers/DokuWiki.hs | 9 ++-- src/Text/Pandoc/Writers/HTML.hs | 2 +- src/Text/Pandoc/Writers/Haddock.hs | 9 ++-- src/Text/Pandoc/Writers/ICML.hs | 9 ++-- src/Text/Pandoc/Writers/JATS.hs | 26 +++++----- src/Text/Pandoc/Writers/Jira.hs | 9 ++-- src/Text/Pandoc/Writers/LaTeX.hs | 59 ++++++----------------- src/Text/Pandoc/Writers/Man.hs | 7 +-- src/Text/Pandoc/Writers/Markdown.hs | 9 ++-- src/Text/Pandoc/Writers/MediaWiki.hs | 9 ++-- src/Text/Pandoc/Writers/Ms.hs | 7 +-- src/Text/Pandoc/Writers/Muse.hs | 9 ++-- src/Text/Pandoc/Writers/OPML.hs | 9 ++-- src/Text/Pandoc/Writers/OpenDocument.hs | 9 ++-- src/Text/Pandoc/Writers/Org.hs | 9 ++-- src/Text/Pandoc/Writers/RST.hs | 9 ++-- src/Text/Pandoc/Writers/RTF.hs | 9 ++-- src/Text/Pandoc/Writers/TEI.hs | 9 ++-- src/Text/Pandoc/Writers/Texinfo.hs | 9 ++-- src/Text/Pandoc/Writers/Textile.hs | 9 ++-- src/Text/Pandoc/Writers/ZimWiki.hs | 9 ++-- stack.yaml | 1 + test/Tests/Helpers.hs | 2 +- test/Tests/Readers/Docx.hs | 2 +- test/Tests/Readers/FB2.hs | 2 +- test/Tests/Readers/Odt.hs | 2 +- test/Tests/Writers/Native.hs | 2 +- test/Tests/Writers/RST.hs | 19 ++++++-- test/writer.muse | 2 +- 41 files changed, 221 insertions(+), 214 deletions(-) diff --git a/MANUAL.txt b/MANUAL.txt index 1422224d5..4ac7b3f29 100644 --- a/MANUAL.txt +++ b/MANUAL.txt @@ -152,18 +152,17 @@ the PDF engine requires [`fontspec`]. `xelatex` uses `xelatex` will use [`mathspec`] instead of [`unicode-math`]. The [`upquote`] and [`microtype`] packages are used if available, and [`csquotes`] will be used for [typography] -if `\usepackage{csquotes}` is present in the template or -included via `/H/--include-in-header`. The [`natbib`], -[`biblatex`], [`bibtex`], and [`biber`] packages can optionally -be used for [citation rendering]. The following packages -will be used to improve output quality if present, but -pandoc does not require them to be present: -[`upquote`] (for straight quotes in verbatim environments), -[`microtype`] (for better spacing adjustments), -[`parskip`] (for better inter-paragraph spaces), -[`xurl`] (for better line breaks in URLs), -[`bookmark`] (for better PDF bookmarks), -and [`footnotehyper`] or [`footnote`] (to allow footnotes in tables). +if the `csquotes` variable or metadata field is set to a +true value. The [`natbib`], [`biblatex`], [`bibtex`], and +[`biber`] packages can optionally be used for [citation +rendering]. The following packages will be used to improve +output quality if present, but pandoc does not require them to +be present: [`upquote`] (for straight quotes in verbatim +environments), [`microtype`] (for better spacing adjustments), +[`parskip`] (for better inter-paragraph spaces), [`xurl`] (for +better line breaks in URLs), [`bookmark`] (for better PDF +bookmarks), and [`footnotehyper`] or [`footnote`] (to allow +footnotes in tables). [TeX Live]: http://www.tug.org/texlive/ [`amsfonts`]: https://ctan.org/pkg/amsfonts @@ -927,7 +926,7 @@ Options affecting specific writers {.options} all headings are shifted such that the top-level heading becomes the specified type. The default behavior is to determine the best division type via heuristics: unless other conditions apply, `section` is chosen. When the - LaTeX document class is set to `report`, `book`, or `memoir` (unless the + `documentclass` variable is set to `report`, `book`, or `memoir` (unless the `article` option is specified), `chapter` is implied as the setting for this option. If `beamer` is the output format, specifying either `chapter` or `part` will cause top-level headings to become `\part{..}`, while diff --git a/pandoc.cabal b/pandoc.cabal index 6356e1be4..0441cfa76 100644 --- a/pandoc.cabal +++ b/pandoc.cabal @@ -408,7 +408,7 @@ library JuicyPixels >= 3.1.6.1 && < 3.4, Glob >= 0.7 && < 0.11, cmark-gfm >= 0.2 && < 0.3, - doctemplates >= 0.2.2.1 && < 0.4, + doctemplates >= 0.3 && < 0.4, network-uri >= 2.6 && < 2.7, network >= 2.6, http-client >= 0.4.30 && < 0.7, @@ -677,6 +677,7 @@ test-suite test-pandoc build-depends: base >= 4.8 && < 5, pandoc, pandoc-types >= 1.17.5 && < 1.18, + mtl >= 2.2 && < 2.3, bytestring >= 0.9 && < 0.11, base64-bytestring >= 0.1 && < 1.1, text >= 1.1.1.0 && < 1.3, diff --git a/src/Text/Pandoc/App/CommandLineOptions.hs b/src/Text/Pandoc/App/CommandLineOptions.hs index 14f665aa9..0757e77ff 100644 --- a/src/Text/Pandoc/App/CommandLineOptions.hs +++ b/src/Text/Pandoc/App/CommandLineOptions.hs @@ -794,10 +794,11 @@ options = setUserDataDir Nothing getDefaultTemplate arg case templ of - Right "" -> -- e.g. for docx, odt, json: - E.throwIO $ PandocCouldNotFindDataFileError - ("templates/default." ++ arg) - Right t -> write t + Right t + | T.null t -> -- e.g. for docx, odt, json: + E.throwIO $ PandocCouldNotFindDataFileError + ("templates/default." ++ arg) + | otherwise -> write . T.unpack $ t Left e -> E.throwIO e exitSuccess) "FORMAT") diff --git a/src/Text/Pandoc/App/OutputSettings.hs b/src/Text/Pandoc/App/OutputSettings.hs index 31bd64c4c..ae78ba15e 100644 --- a/src/Text/Pandoc/App/OutputSettings.hs +++ b/src/Text/Pandoc/App/OutputSettings.hs @@ -163,7 +163,7 @@ optToOutputSettings opts = do return $ ("dzslides-core", dzcore) : vars else return vars) - templ <- case optTemplate opts of + templStr <- case optTemplate opts of _ | not standalone -> return Nothing Nothing -> Just <$> getDefaultTemplate format Just tp -> do @@ -171,7 +171,7 @@ optToOutputSettings opts = do let tp' = case takeExtension tp of "" -> tp <.> format _ -> tp - Just . UTF8.toString <$> + Just . UTF8.toText <$> ((do surl <- stSourceURL <$> getCommonState -- we don't want to look for templates remotely -- unless the full URL is specified: @@ -188,6 +188,16 @@ optToOutputSettings opts = do readDataFile ("templates" </> tp') _ -> throwError e)) + let templatePath = fromMaybe "" $ optTemplate opts + + templ <- case templStr of + Nothing -> return Nothing + Just ts -> do + res <- compileTemplate templatePath ts + case res of + Left e -> throwError $ PandocTemplateError e + Right t -> return $ Just t + case lookup "lang" (optMetadata opts) of Just l -> case parseBCP47 l of Left _ -> return () diff --git a/src/Text/Pandoc/Class.hs b/src/Text/Pandoc/Class.hs index 8d9caa6e8..cd71448fe 100644 --- a/src/Text/Pandoc/Class.hs +++ b/src/Text/Pandoc/Class.hs @@ -90,6 +90,7 @@ import Text.Parsec (ParsecT, getPosition, sourceLine, sourceName) import qualified Data.Time as IO (getCurrentTime) import Text.Pandoc.MIME (MimeType, getMimeType, extensionFromMimeType) import Text.Pandoc.Definition +import Text.DocTemplates (TemplateMonad(..)) import Data.Digest.Pure.SHA (sha1, showDigest) import Data.Maybe (fromMaybe) import Data.Time.Clock.POSIX ( utcTimeToPOSIXSeconds @@ -313,6 +314,18 @@ readFileFromDirs (d:ds) f = catchError ((Just . UTF8.toStringLazy) <$> readFileLazy (d </> f)) (\_ -> readFileFromDirs ds f) +instance TemplateMonad PandocIO where + getPartial fp = + lift $ UTF8.toText <$> + catchError (readFileStrict fp) + (\_ -> readDataFile ("templates" </> fp)) + +instance TemplateMonad PandocPure where + getPartial fp = + lift $ UTF8.toText <$> + catchError (readFileStrict fp) + (\_ -> readDataFile ("templates" </> fp)) + -- -- | 'CommonState' represents state that is used by all diff --git a/src/Text/Pandoc/Options.hs b/src/Text/Pandoc/Options.hs index 45650e395..0cc3f5ebe 100644 --- a/src/Text/Pandoc/Options.hs +++ b/src/Text/Pandoc/Options.hs @@ -41,6 +41,7 @@ import GHC.Generics (Generic) import Skylighting (SyntaxMap, defaultSyntaxMap) import Text.Pandoc.Extensions import Text.Pandoc.Highlighting (Style, pygments) +import Text.DocTemplates (Template) #ifdef DERIVE_JSON_VIA_TH import Data.Aeson.TH (deriveJSON, defaultOptions) @@ -151,7 +152,7 @@ data ReferenceLocation = EndOfBlock -- ^ End of block -- | Options for writers data WriterOptions = WriterOptions - { writerTemplate :: Maybe String -- ^ Template to use + { writerTemplate :: Maybe Template -- ^ Template to use , writerVariables :: [(String, String)] -- ^ Variables to set in template , writerTabStop :: Int -- ^ Tabstop for conversion btw spaces and tabs , writerTableOfContents :: Bool -- ^ Include table of contents 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 diff --git a/src/Text/Pandoc/Writers/AsciiDoc.hs b/src/Text/Pandoc/Writers/AsciiDoc.hs index 460cce3ae..d0bbc5784 100644 --- a/src/Text/Pandoc/Writers/AsciiDoc.hs +++ b/src/Text/Pandoc/Writers/AsciiDoc.hs @@ -35,7 +35,7 @@ import Text.Pandoc.Options import Text.Pandoc.Parsing hiding (blankline, space) import Text.Pandoc.Pretty import Text.Pandoc.Shared -import Text.Pandoc.Templates (renderTemplate') +import Text.Pandoc.Templates (renderTemplate) import Text.Pandoc.Writers.Shared data WriterState = WriterState { defListMarker :: String @@ -94,9 +94,10 @@ pandocToAsciiDoc opts (Pandoc meta blocks) = do isJust (writerTemplate opts)) $ defField "math" (hasMath st) $ defField "titleblock" titleblock metadata - case writerTemplate opts of - Nothing -> return main - Just tpl -> renderTemplate' tpl context + return $ + case writerTemplate opts of + Nothing -> main + Just tpl -> renderTemplate tpl context elementToAsciiDoc :: PandocMonad m => Int -> WriterOptions -> Element -> ADW m Doc diff --git a/src/Text/Pandoc/Writers/CommonMark.hs b/src/Text/Pandoc/Writers/CommonMark.hs index 6a763913a..c62a03097 100644 --- a/src/Text/Pandoc/Writers/CommonMark.hs +++ b/src/Text/Pandoc/Writers/CommonMark.hs @@ -29,7 +29,7 @@ import Text.Pandoc.Definition import Text.Pandoc.Options import Text.Pandoc.Shared (capitalize, isHeaderBlock, isTightList, linesToPara, onlySimpleTableCells, substitute, taskListItemToAscii) -import Text.Pandoc.Templates (renderTemplate') +import Text.Pandoc.Templates (renderTemplate) import Text.Pandoc.Walk (walk, walkM) import Text.Pandoc.Writers.HTML (writeHtml5String, tagWithAttributes) import Text.Pandoc.Writers.Shared @@ -59,9 +59,10 @@ writeCommonMark opts (Pandoc meta blocks) = do defField "toc" toc $ defField "table-of-contents" toc $ defField "body" main metadata - case writerTemplate opts of - Nothing -> return main - Just tpl -> renderTemplate' tpl context + return $ + case writerTemplate opts of + Nothing -> main + Just tpl -> renderTemplate tpl context softBreakToSpace :: Inline -> Inline softBreakToSpace SoftBreak = Space diff --git a/src/Text/Pandoc/Writers/ConTeXt.hs b/src/Text/Pandoc/Writers/ConTeXt.hs index 7b84eb1f5..94afc6dc2 100644 --- a/src/Text/Pandoc/Writers/ConTeXt.hs +++ b/src/Text/Pandoc/Writers/ConTeXt.hs @@ -28,7 +28,7 @@ import Text.Pandoc.Logging import Text.Pandoc.Options import Text.Pandoc.Pretty import Text.Pandoc.Shared -import Text.Pandoc.Templates (renderTemplate') +import Text.Pandoc.Templates (renderTemplate) import Text.Pandoc.Walk (query) import Text.Pandoc.Writers.Shared import Text.Printf (printf) @@ -99,9 +99,10 @@ pandocToConTeXt options (Pandoc meta blocks) = do _ -> id) metadata let context' = defField "context-dir" (toContextDir $ getField "dir" context) context - case writerTemplate options of - Nothing -> return main - Just tpl -> renderTemplate' tpl context' + return $ + case writerTemplate options of + Nothing -> main + Just tpl -> renderTemplate tpl context' toContextDir :: Maybe String -> String toContextDir (Just "rtl") = "r2l" diff --git a/src/Text/Pandoc/Writers/Custom.hs b/src/Text/Pandoc/Writers/Custom.hs index 5e2f3a583..7d85a262d 100644 --- a/src/Text/Pandoc/Writers/Custom.hs +++ b/src/Text/Pandoc/Writers/Custom.hs @@ -25,7 +25,6 @@ import Data.Typeable import Foreign.Lua (Lua, Pushable) import Text.Pandoc.Class (PandocIO) import Text.Pandoc.Definition -import Text.Pandoc.Error import Text.Pandoc.Lua (Global (..), LuaException (LuaException), runLua, setGlobals) import Text.Pandoc.Lua.Util (addField, dofileWithTraceback) @@ -109,12 +108,10 @@ writeCustom luaFile opts doc@(Pandoc meta _) = do let (body, context) = case res of Left (LuaException msg) -> throw (PandocLuaException msg) Right x -> x - case writerTemplate opts of - Nothing -> return $ pack body - Just tpl -> - case applyTemplate (pack tpl) $ setField "body" body context of - Left e -> throw (PandocTemplateError e) - Right r -> return r + return $ + case writerTemplate opts of + Nothing -> pack body + Just tpl -> renderTemplate tpl $ setField "body" body context docToCustom :: WriterOptions -> Pandoc -> Lua String docToCustom opts (Pandoc (Meta metamap) blocks) = do diff --git a/src/Text/Pandoc/Writers/Docbook.hs b/src/Text/Pandoc/Writers/Docbook.hs index 74b7cd32f..f3f78792b 100644 --- a/src/Text/Pandoc/Writers/Docbook.hs +++ b/src/Text/Pandoc/Writers/Docbook.hs @@ -17,7 +17,7 @@ import Prelude import Control.Monad.Reader import Data.Char (toLower) import Data.Generics (everywhere, mkT) -import Data.List (isPrefixOf, isSuffixOf, stripPrefix) +import Data.List (isPrefixOf, stripPrefix) import Data.Monoid (Any (..)) import Data.Text (Text) import qualified Text.Pandoc.Builder as B @@ -29,7 +29,7 @@ import Text.Pandoc.Logging import Text.Pandoc.Options import Text.Pandoc.Pretty import Text.Pandoc.Shared -import Text.Pandoc.Templates (renderTemplate') +import Text.Pandoc.Templates (renderTemplate) import Text.Pandoc.Walk import Text.Pandoc.Writers.Math import Text.Pandoc.Writers.Shared @@ -83,13 +83,8 @@ writeDocbook opts (Pandoc meta blocks) = do else Nothing let render' :: Doc -> Text render' = render colwidth - let opts' = if maybe False (("/book>" `isSuffixOf`) . trimr) - (writerTemplate opts) && - TopLevelDefault == writerTopLevelDivision opts - then opts{ writerTopLevelDivision = TopLevelChapter } - else opts -- The numbering here follows LaTeX's internal numbering - let startLvl = case writerTopLevelDivision opts' of + let startLvl = case writerTopLevelDivision opts of TopLevelPart -> -1 TopLevelChapter -> 0 TopLevelSection -> 1 @@ -98,20 +93,21 @@ writeDocbook opts (Pandoc meta blocks) = do let meta' = B.setMeta "author" auths' meta metadata <- metaToJSON opts (fmap (render' . vcat) . - mapM (elementToDocbook opts' startLvl) . + mapM (elementToDocbook opts startLvl) . hierarchicalize) - (fmap render' . inlinesToDocbook opts') + (fmap render' . inlinesToDocbook opts) meta' - main <- (render' . vcat) <$> mapM (elementToDocbook opts' startLvl) elements + main <- (render' . vcat) <$> mapM (elementToDocbook opts startLvl) elements let context = defField "body" main $ defField "mathml" (case writerHTMLMathMethod opts of MathML -> True _ -> False) metadata - (if writerPreferAscii opts then toEntities else id) <$> + return $ + (if writerPreferAscii opts then toEntities else id) $ case writerTemplate opts of - Nothing -> return main - Just tpl -> renderTemplate' tpl context + Nothing -> main + Just tpl -> renderTemplate tpl context -- | Convert an Element to Docbook. elementToDocbook :: PandocMonad m => WriterOptions -> Int -> Element -> DB m Doc diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs index 4cd6c9c7c..fd2f9a098 100644 --- a/src/Text/Pandoc/Writers/DokuWiki.hs +++ b/src/Text/Pandoc/Writers/DokuWiki.hs @@ -36,7 +36,7 @@ import Text.Pandoc.Logging import Text.Pandoc.Options (WrapOption (..), WriterOptions (writerTableOfContents, writerTemplate, writerWrapText)) import Text.Pandoc.Shared (camelCaseToHyphenated, escapeURI, isURI, linesToPara, removeFormatting, substitute, trimr) -import Text.Pandoc.Templates (renderTemplate') +import Text.Pandoc.Templates (renderTemplate) import Text.Pandoc.Writers.Shared (defField, metaToJSON) data WriterState = WriterState { @@ -78,9 +78,10 @@ pandocToDokuWiki opts (Pandoc meta blocks) = do let main = pack body let context = defField "body" main $ defField "toc" (writerTableOfContents opts) metadata - case writerTemplate opts of - Nothing -> return main - Just tpl -> renderTemplate' tpl context + return $ + case writerTemplate opts of + Nothing -> main + Just tpl -> renderTemplate tpl context -- | Escape special characters for DokuWiki. escapeString :: String -> String diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs index 5484ebba9..de1a98173 100644 --- a/src/Text/Pandoc/Writers/HTML.hs +++ b/src/Text/Pandoc/Writers/HTML.hs @@ -226,7 +226,7 @@ writeHtmlString' st opts d = do lookup "sourcefile" (writerVariables opts) report $ NoTitleElement fallback return $ resetField "pagetitle" fallback context - renderTemplate' tpl + return $ renderTemplate tpl (defField "body" (renderHtml' body) context') writeHtml' :: PandocMonad m => WriterState -> WriterOptions -> Pandoc -> m Html diff --git a/src/Text/Pandoc/Writers/Haddock.hs b/src/Text/Pandoc/Writers/Haddock.hs index 4b647da99..5e759110c 100644 --- a/src/Text/Pandoc/Writers/Haddock.hs +++ b/src/Text/Pandoc/Writers/Haddock.hs @@ -25,7 +25,7 @@ import Text.Pandoc.Logging import Text.Pandoc.Options import Text.Pandoc.Pretty import Text.Pandoc.Shared -import Text.Pandoc.Templates (renderTemplate') +import Text.Pandoc.Templates (renderTemplate) import Text.Pandoc.Writers.Shared type Notes = [[Block]] @@ -58,9 +58,10 @@ pandocToHaddock opts (Pandoc meta blocks) = do (fmap render' . inlineListToHaddock opts) meta let context = defField "body" main metadata - case writerTemplate opts of - Nothing -> return main - Just tpl -> renderTemplate' tpl context + return $ + case writerTemplate opts of + Nothing -> main + Just tpl -> renderTemplate tpl context -- | Return haddock representation of notes. notesToHaddock :: PandocMonad m diff --git a/src/Text/Pandoc/Writers/ICML.hs b/src/Text/Pandoc/Writers/ICML.hs index a919fb199..89f4146ca 100644 --- a/src/Text/Pandoc/Writers/ICML.hs +++ b/src/Text/Pandoc/Writers/ICML.hs @@ -33,7 +33,7 @@ import Text.Pandoc.Logging import Text.Pandoc.Options import Text.Pandoc.Pretty import Text.Pandoc.Shared (isURI, linesToPara, splitBy) -import Text.Pandoc.Templates (renderTemplate') +import Text.Pandoc.Templates (renderTemplate) import Text.Pandoc.Writers.Math (texMathToInlines) import Text.Pandoc.Writers.Shared import Text.Pandoc.XML @@ -149,10 +149,11 @@ writeICML opts (Pandoc meta blocks) = do $ defField "charStyles" (render' $ charStylesToDoc st) $ defField "parStyles" (render' $ parStylesToDoc st) $ defField "hyperlinks" (render' $ hyperlinksToDoc $ links st) metadata - (if writerPreferAscii opts then toEntities else id) <$> + return $ + (if writerPreferAscii opts then toEntities else id) $ case writerTemplate opts of - Nothing -> return main - Just tpl -> renderTemplate' tpl context + Nothing -> main + Just tpl -> renderTemplate tpl context -- | Auxiliary functions for parStylesToDoc and charStylesToDoc. contains :: String -> (String, (String, String)) -> [(String, String)] diff --git a/src/Text/Pandoc/Writers/JATS.hs b/src/Text/Pandoc/Writers/JATS.hs index 61a68d543..23e57663b 100644 --- a/src/Text/Pandoc/Writers/JATS.hs +++ b/src/Text/Pandoc/Writers/JATS.hs @@ -19,7 +19,7 @@ import Control.Monad.Reader import Control.Monad.State import Data.Char (toLower) import Data.Generics (everywhere, mkT) -import Data.List (isSuffixOf, partition, isPrefixOf) +import Data.List (partition, isPrefixOf) import qualified Data.Map as M import Data.Maybe (fromMaybe) import Data.Time (toGregorian, Day, parseTimeM, defaultTimeLocale, formatTime) @@ -33,7 +33,7 @@ import Text.Pandoc.Walk (walk) import Text.Pandoc.Options import Text.Pandoc.Pretty import Text.Pandoc.Shared -import Text.Pandoc.Templates (renderTemplate') +import Text.Pandoc.Templates (renderTemplate) import Text.Pandoc.Writers.Math import Text.Pandoc.Writers.Shared import Text.Pandoc.XML @@ -67,27 +67,22 @@ docToJATS opts (Pandoc meta blocks) = do else Nothing let render' :: Doc -> Text render' = render colwidth - let opts' = if maybe False (("/book>" `isSuffixOf`) . trimr) - (writerTemplate opts) && - TopLevelDefault == writerTopLevelDivision opts - then opts{ writerTopLevelDivision = TopLevelChapter } - else opts -- The numbering here follows LaTeX's internal numbering - let startLvl = case writerTopLevelDivision opts' of + let startLvl = case writerTopLevelDivision opts of TopLevelPart -> -1 TopLevelChapter -> 0 TopLevelSection -> 1 TopLevelDefault -> 1 metadata <- metaToJSON opts (fmap (render' . vcat) . - mapM (elementToJATS opts' startLvl) . + mapM (elementToJATS opts startLvl) . hierarchicalize) - (fmap render' . inlinesToJATS opts') + (fmap render' . inlinesToJATS opts) meta main <- (render' . vcat) <$> - mapM (elementToJATS opts' startLvl) elements + mapM (elementToJATS opts startLvl) elements notes <- reverse . map snd <$> gets jatsNotes - backs <- mapM (elementToJATS opts' startLvl) backElements + backs <- mapM (elementToJATS opts startLvl) backElements let fns = if null notes then mempty else inTagsIndented "fn-group" $ vcat notes @@ -110,10 +105,11 @@ docToJATS opts (Pandoc meta blocks) = do $ defField "mathml" (case writerHTMLMathMethod opts of MathML -> True _ -> False) metadata - (if writerPreferAscii opts then toEntities else id) <$> + return $ + (if writerPreferAscii opts then toEntities else id) $ case writerTemplate opts of - Nothing -> return main - Just tpl -> renderTemplate' tpl context + Nothing -> main + Just tpl -> renderTemplate tpl context -- | Convert an Element to JATS. elementToJATS :: PandocMonad m => WriterOptions -> Int -> Element -> JATS m Doc diff --git a/src/Text/Pandoc/Writers/Jira.hs b/src/Text/Pandoc/Writers/Jira.hs index 08e5c8e40..fe66d874d 100644 --- a/src/Text/Pandoc/Writers/Jira.hs +++ b/src/Text/Pandoc/Writers/Jira.hs @@ -25,7 +25,7 @@ import Text.Pandoc.Definition import Text.Pandoc.Logging (LogMessage (BlockNotRendered, InlineNotRendered)) import Text.Pandoc.Options (WriterOptions (writerTemplate)) import Text.Pandoc.Shared (blocksToInlines, linesToPara) -import Text.Pandoc.Templates (renderTemplate') +import Text.Pandoc.Templates (renderTemplate) import Text.Pandoc.Writers.Math (texMathToInlines) import Text.Pandoc.Writers.Shared (metaToJSON, defField) import qualified Data.Text as T @@ -59,9 +59,10 @@ pandocToJira opts (Pandoc meta blocks) = do notes <- gets $ T.intercalate "\n" . reverse . stNotes let main = body <> if T.null notes then "" else "\n\n" <> notes let context = defField "body" main metadata - case writerTemplate opts of - Nothing -> return main - Just tpl -> renderTemplate' tpl context + return $ + case writerTemplate opts of + Nothing -> main + Just tpl -> renderTemplate tpl context -- | Escape one character as needed for Jira. escapeCharForJira :: Char -> Text diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs index cdbdc8420..2f832b45b 100644 --- a/src/Text/Pandoc/Writers/LaTeX.hs +++ b/src/Text/Pandoc/Writers/LaTeX.hs @@ -21,10 +21,10 @@ import Prelude import Control.Applicative ((<|>)) import Control.Monad.State.Strict import Data.Monoid (Any(..)) -import Data.Aeson (FromJSON, object, (.=)) +import Data.Aeson (object, (.=)) import Data.Char (isAlphaNum, isAscii, isDigit, isLetter, isSpace, isPunctuation, ord, toLower) -import Data.List (foldl', intercalate, intersperse, isInfixOf, nubBy, +import Data.List (foldl', intercalate, intersperse, nubBy, stripPrefix, (\\), uncons) import Data.Maybe (catMaybes, fromMaybe, isJust, mapMaybe, isNothing) import qualified Data.Map as M @@ -45,7 +45,6 @@ import Text.Pandoc.Slides import Text.Pandoc.Templates import Text.Pandoc.Walk import Text.Pandoc.Writers.Shared -import qualified Text.Parsec as P import Text.Printf (printf) import qualified Data.Text.Normalize as Normalize @@ -131,7 +130,6 @@ pandocToLaTeX options (Pandoc meta blocks) = do let isInternalLink (Link _ _ ('#':xs,_)) = [xs] isInternalLink _ = [] modify $ \s -> s{ stInternalLinks = query isInternalLink blocks' } - let template = fromMaybe "" $ writerTemplate options let colwidth = if writerWrapText options == WrapAuto then Just $ writerColumns options else Nothing @@ -149,26 +147,17 @@ pandocToLaTeX options (Pandoc meta blocks) = do case lookup "documentclass" (writerVariables options) `mplus` fmap stringify (lookupMeta "documentclass" meta) of Just x -> x - Nothing -> - case P.parse pDocumentClass "template" template of - Right r -> r - Left _ - | beamer -> "beamer" - | otherwise -> case writerTopLevelDivision options of - TopLevelPart -> "book" - TopLevelChapter -> "book" - _ -> "article" + Nothing | beamer -> "beamer" + | otherwise -> case writerTopLevelDivision options of + TopLevelPart -> "book" + TopLevelChapter -> "book" + _ -> "article" when (documentClass `elem` chaptersClasses) $ modify $ \s -> s{ stHasChapters = True } - -- check for \usepackage...{csquotes}; if present, we'll use - -- \enquote{...} for smart quotes: - let headerIncludesField :: FromJSON a => Maybe a - headerIncludesField = getField "header-includes" metadata - let headerIncludes = fromMaybe [] $ mplus - (fmap return headerIncludesField) - headerIncludesField - when (any (isInfixOf "{csquotes}") (template : headerIncludes)) $ - modify $ \s -> s{stCsquotes = True} + case T.toLower <$> getField "csquotes" metadata of + Nothing -> return () + Just "false" -> return () + Just _ -> modify $ \s -> s{stCsquotes = True} let (blocks'', lastHeader) = if writerCiteMethod options == Citeproc then (blocks', []) else case reverse blocks' of @@ -288,9 +277,10 @@ pandocToLaTeX options (Pandoc meta blocks) = do $ defField "latex-dir-rtl" (getField "dir" context == Just ("rtl" :: String)) context - case writerTemplate options of - Nothing -> return main - Just tpl -> renderTemplate' tpl context' + return $ + case writerTemplate options of + Nothing -> main + Just tpl -> renderTemplate tpl context' -- | Convert Elements to LaTeX elementToLaTeX :: PandocMonad m => WriterOptions -> Element -> LW m Doc @@ -1658,22 +1648,3 @@ commonFromBcp47 (Lang l _ _ _) = fromIso l fromIso "vi" = "vietnamese" fromIso _ = "" -pDocumentOptions :: P.Parsec String () [String] -pDocumentOptions = do - P.char '[' - opts <- P.sepBy - (P.many $ P.spaces *> P.noneOf (" ,]" :: String) <* P.spaces) - (P.char ',') - P.char ']' - return opts - -pDocumentClass :: P.Parsec String () String -pDocumentClass = - do P.skipMany (P.satisfy (/='\\')) - P.string "\\documentclass" - classOptions <- pDocumentOptions <|> return [] - if ("article" :: String) `elem` classOptions - then return "article" - else do P.skipMany (P.satisfy (/='{')) - P.char '{' - P.manyTill P.letter (P.char '}') diff --git a/src/Text/Pandoc/Writers/Man.hs b/src/Text/Pandoc/Writers/Man.hs index 506461fac..cba44ee3a 100644 --- a/src/Text/Pandoc/Writers/Man.hs +++ b/src/Text/Pandoc/Writers/Man.hs @@ -76,9 +76,10 @@ pandocToMan opts (Pandoc meta blocks) = do $ defField "has-tables" hasTables $ defField "hyphenate" True $ defField "pandoc-version" pandocVersion metadata - case writerTemplate opts of - Nothing -> return main - Just tpl -> renderTemplate' tpl context + return $ + case writerTemplate opts of + Nothing -> main + Just tpl -> renderTemplate tpl context escString :: WriterOptions -> String -> String escString _ = escapeString AsciiOnly -- for better portability diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs index ade350565..00957e1ec 100644 --- a/src/Text/Pandoc/Writers/Markdown.hs +++ b/src/Text/Pandoc/Writers/Markdown.hs @@ -43,7 +43,7 @@ import Text.Pandoc.Options import Text.Pandoc.Parsing hiding (blankline, blanklines, char, space) import Text.Pandoc.Pretty import Text.Pandoc.Shared -import Text.Pandoc.Templates (renderTemplate') +import Text.Pandoc.Templates (renderTemplate) import Text.Pandoc.Walk import Text.Pandoc.Writers.HTML (writeHtml5String) import Text.Pandoc.Writers.Math (texMathToInlines) @@ -223,9 +223,10 @@ pandocToMarkdown opts (Pandoc meta blocks) = do then id else defField "titleblock" (render' titleblock)) $ addVariablesToJSON opts metadata - case writerTemplate opts of - Nothing -> return main - Just tpl -> renderTemplate' tpl context + return $ + case writerTemplate opts of + Nothing -> main + Just tpl -> renderTemplate tpl context -- | Return markdown representation of reference key table. refsToMarkdown :: PandocMonad m => WriterOptions -> Refs -> MD m Doc diff --git a/src/Text/Pandoc/Writers/MediaWiki.hs b/src/Text/Pandoc/Writers/MediaWiki.hs index a461daee4..5fed75037 100644 --- a/src/Text/Pandoc/Writers/MediaWiki.hs +++ b/src/Text/Pandoc/Writers/MediaWiki.hs @@ -26,7 +26,7 @@ import Text.Pandoc.Logging import Text.Pandoc.Options import Text.Pandoc.Pretty (render) import Text.Pandoc.Shared -import Text.Pandoc.Templates (renderTemplate') +import Text.Pandoc.Templates (renderTemplate) import Text.Pandoc.Writers.Shared import Text.Pandoc.XML (escapeStringForXML) @@ -66,9 +66,10 @@ pandocToMediaWiki (Pandoc meta blocks) = do let main = body ++ notes let context = defField "body" main $ defField "toc" (writerTableOfContents opts) metadata - case writerTemplate opts of - Nothing -> return $ pack main - Just tpl -> renderTemplate' tpl context + return $ + case writerTemplate opts of + Nothing -> pack main + Just tpl -> renderTemplate tpl context -- | Escape special characters for MediaWiki. escapeString :: String -> String diff --git a/src/Text/Pandoc/Writers/Ms.hs b/src/Text/Pandoc/Writers/Ms.hs index 180b7f24a..204fac7c6 100644 --- a/src/Text/Pandoc/Writers/Ms.hs +++ b/src/Text/Pandoc/Writers/Ms.hs @@ -83,9 +83,10 @@ pandocToMs opts (Pandoc meta blocks) = do $ defField "title-meta" titleMeta $ defField "author-meta" (intercalate "; " authorsMeta) $ defField "highlighting-macros" highlightingMacros metadata - case writerTemplate opts of - Nothing -> return main - Just tpl -> renderTemplate' tpl context + return $ + case writerTemplate opts of + Nothing -> main + Just tpl -> renderTemplate tpl context escapeStr :: WriterOptions -> String -> String escapeStr opts = diff --git a/src/Text/Pandoc/Writers/Muse.hs b/src/Text/Pandoc/Writers/Muse.hs index ec03d6292..1fd68fa8f 100644 --- a/src/Text/Pandoc/Writers/Muse.hs +++ b/src/Text/Pandoc/Writers/Muse.hs @@ -40,7 +40,7 @@ import Text.Pandoc.ImageSize import Text.Pandoc.Options import Text.Pandoc.Pretty import Text.Pandoc.Shared -import Text.Pandoc.Templates (renderTemplate') +import Text.Pandoc.Templates (renderTemplate) import Text.Pandoc.Writers.Math import Text.Pandoc.Writers.Shared @@ -114,9 +114,10 @@ pandocToMuse (Pandoc meta blocks) = do notes <- currentNotesToMuse let main = render colwidth $ body $+$ notes let context = defField "body" main metadata - case writerTemplate opts of - Nothing -> return main - Just tpl -> renderTemplate' tpl context + return $ + case writerTemplate opts of + Nothing -> main + Just tpl -> renderTemplate tpl context -- | Helper function for flatBlockListToMuse -- | Render all blocks and insert blank lines between the first two diff --git a/src/Text/Pandoc/Writers/OPML.hs b/src/Text/Pandoc/Writers/OPML.hs index a2090af07..14d29edd6 100644 --- a/src/Text/Pandoc/Writers/OPML.hs +++ b/src/Text/Pandoc/Writers/OPML.hs @@ -24,7 +24,7 @@ import Text.Pandoc.Error import Text.Pandoc.Options import Text.Pandoc.Pretty import Text.Pandoc.Shared -import Text.Pandoc.Templates (renderTemplate') +import Text.Pandoc.Templates (renderTemplate) import Text.Pandoc.Writers.HTML (writeHtml5String) import Text.Pandoc.Writers.Markdown (writeMarkdown) import Text.Pandoc.Writers.Shared @@ -44,10 +44,11 @@ writeOPML opts (Pandoc meta blocks) = do meta' main <- (render colwidth . vcat) <$> mapM (elementToOPML opts) elements let context = defField "body" main metadata - (if writerPreferAscii opts then toEntities else id) <$> + return $ + (if writerPreferAscii opts then toEntities else id) $ case writerTemplate opts of - Nothing -> return main - Just tpl -> renderTemplate' tpl context + Nothing -> main + Just tpl -> renderTemplate tpl context writeHtmlInlines :: PandocMonad m => [Inline] -> m Text diff --git a/src/Text/Pandoc/Writers/OpenDocument.hs b/src/Text/Pandoc/Writers/OpenDocument.hs index 828aec30f..4bc51fd20 100644 --- a/src/Text/Pandoc/Writers/OpenDocument.hs +++ b/src/Text/Pandoc/Writers/OpenDocument.hs @@ -32,7 +32,7 @@ import Text.Pandoc.Logging import Text.Pandoc.Options import Text.Pandoc.Pretty import Text.Pandoc.Shared (linesToPara) -import Text.Pandoc.Templates (renderTemplate') +import Text.Pandoc.Templates (renderTemplate) import qualified Text.Pandoc.Translations as Term (Term(Figure, Table)) import Text.Pandoc.Writers.Math import Text.Pandoc.Writers.Shared @@ -240,9 +240,10 @@ writeOpenDocument opts (Pandoc meta blocks) = do let context = defField "body" body $ defField "toc" (writerTableOfContents opts) $defField "automatic-styles" (render' automaticStyles) metadata - case writerTemplate opts of - Nothing -> return body - Just tpl -> renderTemplate' tpl context + return $ + case writerTemplate opts of + Nothing -> body + Just tpl -> renderTemplate tpl context withParagraphStyle :: PandocMonad m => WriterOptions -> String -> [Block] -> OD m Doc diff --git a/src/Text/Pandoc/Writers/Org.hs b/src/Text/Pandoc/Writers/Org.hs index 322174cff..43b4c2add 100644 --- a/src/Text/Pandoc/Writers/Org.hs +++ b/src/Text/Pandoc/Writers/Org.hs @@ -27,7 +27,7 @@ import Text.Pandoc.Logging import Text.Pandoc.Options import Text.Pandoc.Pretty import Text.Pandoc.Shared -import Text.Pandoc.Templates (renderTemplate') +import Text.Pandoc.Templates (renderTemplate) import Text.Pandoc.Writers.Shared data WriterState = @@ -66,9 +66,10 @@ pandocToOrg (Pandoc meta blocks) = do let context = defField "body" main . defField "math" hasMath $ metadata - case writerTemplate opts of - Nothing -> return main - Just tpl -> renderTemplate' tpl context + return $ + case writerTemplate opts of + Nothing -> main + Just tpl -> renderTemplate tpl context -- | Return Org representation of notes. notesToOrg :: PandocMonad m => [[Block]] -> Org m Doc diff --git a/src/Text/Pandoc/Writers/RST.hs b/src/Text/Pandoc/Writers/RST.hs index 871cc3e5a..ebfc599f4 100644 --- a/src/Text/Pandoc/Writers/RST.hs +++ b/src/Text/Pandoc/Writers/RST.hs @@ -28,7 +28,7 @@ import Text.Pandoc.Logging import Text.Pandoc.Options import Text.Pandoc.Pretty import Text.Pandoc.Shared -import Text.Pandoc.Templates (renderTemplate') +import Text.Pandoc.Templates (renderTemplate) import Text.Pandoc.Writers.Shared import Text.Pandoc.Walk @@ -88,9 +88,10 @@ pandocToRST (Pandoc meta blocks) = do $ defField "titleblock" (render Nothing title :: String) $ defField "math" hasMath $ defField "rawtex" rawTeX metadata - case writerTemplate opts of - Nothing -> return main - Just tpl -> renderTemplate' tpl context + return $ + case writerTemplate opts of + Nothing -> main + Just tpl -> renderTemplate tpl context where normalizeHeadings lev (Header l a i:bs) = Header lev a i:normalizeHeadings (lev+1) cont ++ normalizeHeadings lev bs' diff --git a/src/Text/Pandoc/Writers/RTF.hs b/src/Text/Pandoc/Writers/RTF.hs index 3d7657bb0..61ee7804b 100644 --- a/src/Text/Pandoc/Writers/RTF.hs +++ b/src/Text/Pandoc/Writers/RTF.hs @@ -30,7 +30,7 @@ import Text.Pandoc.ImageSize import Text.Pandoc.Logging import Text.Pandoc.Options import Text.Pandoc.Shared -import Text.Pandoc.Templates (renderTemplate') +import Text.Pandoc.Templates (renderTemplate) import Text.Pandoc.Walk import Text.Pandoc.Writers.Math import Text.Pandoc.Writers.Shared @@ -112,9 +112,10 @@ writeRTF options doc = do -- of the toc rather than a boolean: . defField "toc" toc else id) metadata - case writerTemplate options of - Just tpl -> renderTemplate' tpl context - Nothing -> return $ T.pack $ + return $ + case writerTemplate options of + Just tpl -> renderTemplate tpl context + Nothing -> T.pack $ case reverse body of ('\n':_) -> body _ -> body ++ "\n" diff --git a/src/Text/Pandoc/Writers/TEI.hs b/src/Text/Pandoc/Writers/TEI.hs index cd5ad5594..e4793e9e7 100644 --- a/src/Text/Pandoc/Writers/TEI.hs +++ b/src/Text/Pandoc/Writers/TEI.hs @@ -25,7 +25,7 @@ import Text.Pandoc.Logging import Text.Pandoc.Options import Text.Pandoc.Pretty import Text.Pandoc.Shared -import Text.Pandoc.Templates (renderTemplate') +import Text.Pandoc.Templates (renderTemplate) import Text.Pandoc.Writers.Shared import Text.Pandoc.XML @@ -54,9 +54,10 @@ writeTEI opts (Pandoc meta blocks) = do defField "mathml" (case writerHTMLMathMethod opts of MathML -> True _ -> False) metadata - case writerTemplate opts of - Nothing -> return main - Just tpl -> renderTemplate' tpl context + return $ + case writerTemplate opts of + Nothing -> main + Just tpl -> renderTemplate tpl context -- | Convert an Element to TEI. elementToTEI :: PandocMonad m => WriterOptions -> Int -> Element -> m Doc diff --git a/src/Text/Pandoc/Writers/Texinfo.hs b/src/Text/Pandoc/Writers/Texinfo.hs index 384863706..6ad932698 100644 --- a/src/Text/Pandoc/Writers/Texinfo.hs +++ b/src/Text/Pandoc/Writers/Texinfo.hs @@ -31,7 +31,7 @@ import Text.Pandoc.Logging import Text.Pandoc.Options import Text.Pandoc.Pretty import Text.Pandoc.Shared -import Text.Pandoc.Templates (renderTemplate') +import Text.Pandoc.Templates (renderTemplate) import Text.Pandoc.Writers.Shared import Text.Printf (printf) @@ -82,9 +82,10 @@ pandocToTexinfo options (Pandoc meta blocks) = do $ defField "titlepage" titlePage $ defField "strikeout" (stStrikeout st) metadata - case writerTemplate options of - Nothing -> return body - Just tpl -> renderTemplate' tpl context + return $ + case writerTemplate options of + Nothing -> body + Just tpl -> renderTemplate tpl context -- | Escape things as needed for Texinfo. stringToTexinfo :: String -> String diff --git a/src/Text/Pandoc/Writers/Textile.hs b/src/Text/Pandoc/Writers/Textile.hs index 0ccc71b14..3df0a2ec0 100644 --- a/src/Text/Pandoc/Writers/Textile.hs +++ b/src/Text/Pandoc/Writers/Textile.hs @@ -25,7 +25,7 @@ import Text.Pandoc.Logging import Text.Pandoc.Options import Text.Pandoc.Pretty (render) import Text.Pandoc.Shared -import Text.Pandoc.Templates (renderTemplate') +import Text.Pandoc.Templates (renderTemplate) import Text.Pandoc.Writers.Shared import Text.Pandoc.XML (escapeStringForXML) @@ -57,9 +57,10 @@ pandocToTextile opts (Pandoc meta blocks) = do notes <- gets $ unlines . reverse . stNotes let main = pack $ body ++ if null notes then "" else "\n\n" ++ notes let context = defField "body" main metadata - case writerTemplate opts of - Nothing -> return main - Just tpl -> renderTemplate' tpl context + return $ + case writerTemplate opts of + Nothing -> main + Just tpl -> renderTemplate tpl context withUseTags :: PandocMonad m => TW m a -> TW m a withUseTags action = do diff --git a/src/Text/Pandoc/Writers/ZimWiki.hs b/src/Text/Pandoc/Writers/ZimWiki.hs index 08060035f..04bdbc51b 100644 --- a/src/Text/Pandoc/Writers/ZimWiki.hs +++ b/src/Text/Pandoc/Writers/ZimWiki.hs @@ -29,7 +29,7 @@ import Text.Pandoc.Logging import Text.Pandoc.Options (WrapOption (..), WriterOptions (writerTableOfContents, writerTemplate, writerWrapText)) import Text.Pandoc.Shared (escapeURI, isURI, linesToPara, removeFormatting, substitute, trimr) -import Text.Pandoc.Templates (renderTemplate') +import Text.Pandoc.Templates (renderTemplate) import Text.Pandoc.Writers.Shared (defField, metaToJSON) data WriterState = WriterState { @@ -59,9 +59,10 @@ pandocToZimWiki opts (Pandoc meta blocks) = do let main = body let context = defField "body" main $ defField "toc" (writerTableOfContents opts) metadata - case writerTemplate opts of - Just tpl -> renderTemplate' tpl context - Nothing -> return main + return $ + case writerTemplate opts of + Just tpl -> renderTemplate tpl context + Nothing -> main -- | Escape special characters for ZimWiki. escapeString :: String -> String diff --git a/stack.yaml b/stack.yaml index 76d5b043b..19ab07679 100644 --- a/stack.yaml +++ b/stack.yaml @@ -19,6 +19,7 @@ extra-deps: - tasty-lua-0.2.0 - skylighting-core-0.8.2 - skylighting-0.8.2 +- doctemplates-0.3 ghc-options: "$locals": -Wall -fno-warn-unused-do-bind -Wincomplete-record-updates -Wnoncanonical-monad-instances -Wnoncanonical-monadfail-instances -Wincomplete-uni-patterns -Widentities -Wcpp-undef -fhide-source-paths -Wno-missing-home-modules resolver: lts-13.17 diff --git a/test/Tests/Helpers.hs b/test/Tests/Helpers.hs index c5dab8f23..5ad867065 100644 --- a/test/Tests/Helpers.hs +++ b/test/Tests/Helpers.hs @@ -136,7 +136,7 @@ instance ToString Pandoc where where s = case d of (Pandoc (Meta m) _) | M.null m -> Nothing - | otherwise -> Just "" -- need this to get meta output + | otherwise -> Just mempty -- need this to get meta output instance ToString Blocks where toString = unpack . purely (writeNative def) . toPandoc diff --git a/test/Tests/Readers/Docx.hs b/test/Tests/Readers/Docx.hs index e5bbabadf..9d0913e55 100644 --- a/test/Tests/Readers/Docx.hs +++ b/test/Tests/Readers/Docx.hs @@ -46,7 +46,7 @@ instance ToString NoNormPandoc where where s = case d of NoNormPandoc (Pandoc (Meta m) _) | M.null m -> Nothing - | otherwise -> Just "" -- need this to get meta output + | otherwise -> Just mempty -- need this to get meta output instance ToPandoc NoNormPandoc where toPandoc = unNoNorm diff --git a/test/Tests/Readers/FB2.hs b/test/Tests/Readers/FB2.hs index e64e8a2ce..dd228aeae 100644 --- a/test/Tests/Readers/FB2.hs +++ b/test/Tests/Readers/FB2.hs @@ -24,7 +24,7 @@ import Data.Text.Lazy (fromStrict) import System.FilePath (replaceExtension) fb2ToNative :: Text -> Text -fb2ToNative = purely (writeNative def{ writerTemplate = Just "" }) . purely (readFB2 def) +fb2ToNative = purely (writeNative def{ writerTemplate = Just mempty }) . purely (readFB2 def) fb2Test :: TestName -> FilePath -> TestTree fb2Test name path = goldenVsString name native (fromTextLazy . fromStrict . fb2ToNative . toText <$> BS.readFile path) diff --git a/test/Tests/Readers/Odt.hs b/test/Tests/Readers/Odt.hs index d66a4e98b..9dc93c92e 100644 --- a/test/Tests/Readers/Odt.hs +++ b/test/Tests/Readers/Odt.hs @@ -61,7 +61,7 @@ instance ToString NoNormPandoc where where s = case d of NoNormPandoc (Pandoc (Meta m) _) | M.null m -> Nothing - | otherwise -> Just "" -- need this for Meta output + | otherwise -> Just mempty -- need this for Meta output instance ToPandoc NoNormPandoc where toPandoc = unNoNorm diff --git a/test/Tests/Writers/Native.hs b/test/Tests/Writers/Native.hs index 708b5069c..905e83b1e 100644 --- a/test/Tests/Writers/Native.hs +++ b/test/Tests/Writers/Native.hs @@ -11,7 +11,7 @@ import Text.Pandoc.Arbitrary () p_write_rt :: Pandoc -> Bool p_write_rt d = - read (unpack $ purely (writeNative def{ writerTemplate = Just "" }) d) == d + read (unpack $ purely (writeNative def{ writerTemplate = Just mempty }) d) == d p_write_blocks_rt :: [Block] -> Bool p_write_blocks_rt bs = diff --git a/test/Tests/Writers/RST.hs b/test/Tests/Writers/RST.hs index 0d5b7c38a..07eef1f60 100644 --- a/test/Tests/Writers/RST.hs +++ b/test/Tests/Writers/RST.hs @@ -3,6 +3,7 @@ module Tests.Writers.RST (tests) where import Prelude +import Control.Monad.Identity import Test.Tasty import Test.Tasty.HUnit import Tests.Helpers @@ -10,6 +11,8 @@ import Text.Pandoc import Text.Pandoc.Arbitrary () import Text.Pandoc.Builder import Text.Pandoc.Writers.RST +import Text.Pandoc.Templates (compileTemplate) +import qualified Data.Text as T infix 4 =: (=:) :: (ToString a, ToPandoc a) @@ -18,8 +21,15 @@ infix 4 =: testTemplate :: (ToString a, ToString c, ToPandoc a) => String -> String -> (a, c) -> TestTree -testTemplate t = - test (purely (writeRST def{ writerTemplate = Just t }) . toPandoc) +testTemplate t = case runIdentity (compileTemplate [] (T.pack t)) of + Left e -> error $ "Could not compile RST template: " ++ e + Right templ -> test (purely (writeRST def{ writerTemplate = Just templ }) . toPandoc) + +bodyTemplate :: Template +bodyTemplate = case runIdentity (compileTemplate [] "$body$\n") of + Left e -> error $ + "Could not compile RST bodyTemplate" ++ e + Right templ -> templ tests :: [TestTree] tests = [ testGroup "rubrics" @@ -104,7 +114,8 @@ tests = [ testGroup "rubrics" [ "foo" , "==="] -- note: heading normalization is only done in standalone mode - , test (purely (writeRST def{ writerTemplate = Just "$body$\n" }) . toPandoc) + , test (purely (writeRST def{ writerTemplate = Just bodyTemplate }) + . toPandoc) "heading levels" $ header 1 (text "Header 1") <> header 3 (text "Header 2") <> @@ -134,7 +145,7 @@ tests = [ testGroup "rubrics" , "" , "Header 2" , "--------"] - , test (purely (writeRST def{ writerTemplate = Just "$body$\n" }) . toPandoc) + , test (purely (writeRST def{ writerTemplate = Just bodyTemplate }) . toPandoc) "minimal heading levels" $ header 2 (text "Header 1") <> header 3 (text "Header 2") <> diff --git a/test/writer.muse b/test/writer.muse index 35d43a751..415882677 100644 --- a/test/writer.muse +++ b/test/writer.muse @@ -1,4 +1,4 @@ -#author John MacFarlane +#author John MacFarlane, Anonymous #title Pandoc Test Suite #date July 17, 2006