From 817d2048da08f44ab4a9efae7c761aff99e3d959 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Wed, 11 Dec 2019 10:29:49 -0800 Subject: Improved template API and fixed a bug. Closes #5979. * Text.Pandoc.Templates [API change] + Add Monad wrappers `WithDefaultPartials` and `WithPartials`. Wrapping these around an instance of `PandocMonad` gives us different instances of `TemplateMonad`, with different search behavior in retrieving partials. To compile a template and limit partial search to pandoc's data files, use `runWithDefaultPartials (compileTemplate ...)`. To compile a template and allow partials to be found locally (either on the file system or via HTTP, in the event that the main template has an absolute URL), ue `runWithPartials (compileTemplate ...)`. + Export `getTemplate`, which seeks a template locally, or via HTTP if the template has an absolute URL, falling back to the data files if not found. + Export `compileDefaultTemplate` -- does `getDefaultTemplate` and compiles the result, raising an error on failure. * Text.Pandoc.Class [API change] + Remove `TemplateMonad` instances for `PandocIO` and `PandocPure`. These were too limiting and caused a bug whereby a local partial could be used even when the default template was requested. We now rely on instances provided in the Templates module. Text.Pandoc.App.OutputSettings + Simplify template retrieval code. --- src/Text/Pandoc/App/OutputSettings.hs | 36 +++++++---------------------------- 1 file changed, 7 insertions(+), 29 deletions(-) (limited to 'src/Text/Pandoc/App') diff --git a/src/Text/Pandoc/App/OutputSettings.hs b/src/Text/Pandoc/App/OutputSettings.hs index 944f1b63b..9a8e9969f 100644 --- a/src/Text/Pandoc/App/OutputSettings.hs +++ b/src/Text/Pandoc/App/OutputSettings.hs @@ -25,7 +25,7 @@ import qualified Data.Text as T import Text.DocTemplates (toVal, Context(..), Val(..)) import qualified Control.Exception as E import Control.Monad -import Control.Monad.Except (catchError, throwError) +import Control.Monad.Except (throwError) import Control.Monad.Trans import Data.Char (toLower) import Data.List (find, isPrefixOf) @@ -171,40 +171,18 @@ optToOutputSettings opts = do setVariableM "dzslides-core" dzcore vars else return vars) - templStr <- case optTemplate opts of + templ <- case optTemplate opts of _ | not standalone -> return Nothing - Nothing -> Just <$> getDefaultTemplate format + Nothing -> Just <$> compileDefaultTemplate format Just tp -> do -- strip off extensions let tp' = case takeExtension tp of "" -> tp <.> T.unpack format _ -> tp - Just . UTF8.toText <$> - ((do surl <- stSourceURL <$> getCommonState - -- we don't want to look for templates remotely - -- unless the full URL is specified: - modifyCommonState $ \st -> st{ - stSourceURL = Nothing } - (bs, _) <- fetchItem $ T.pack tp' - modifyCommonState $ \st -> st{ - stSourceURL = surl } - return bs) - `catchError` - (\e -> - case e of - PandocResourceNotFound _ -> - 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 $ T.pack e - Right t -> return $ Just t + res <- getTemplate tp' >>= runWithPartials . compileTemplate tp' + case res of + Left e -> throwError $ PandocTemplateError $ T.pack e + Right t -> return $ Just t let writerOpts = def { writerTemplate = templ -- cgit v1.2.3