Templates: change signature of getDefaultTemplate.
Now it runs in any instance of PandocMonad, and returns a String rather than an Either value.
This commit is contained in:
parent
2ce6b492e1
commit
992943d98e
2 changed files with 14 additions and 13 deletions
|
@ -218,7 +218,8 @@ convertWithOpts opts = do
|
|||
templ <- case optTemplate opts of
|
||||
_ | not standalone -> return Nothing
|
||||
Nothing -> do
|
||||
deftemp <- getDefaultTemplate datadir format
|
||||
deftemp <- runIO $
|
||||
getDefaultTemplate datadir format
|
||||
case deftemp of
|
||||
Left e -> E.throwIO e
|
||||
Right t -> return (Just t)
|
||||
|
@ -991,10 +992,10 @@ options =
|
|||
, Option "D" ["print-default-template"]
|
||||
(ReqArg
|
||||
(\arg _ -> do
|
||||
templ <- getDefaultTemplate Nothing arg
|
||||
templ <- runIO $ getDefaultTemplate Nothing arg
|
||||
case templ of
|
||||
Right t -> UTF8.hPutStr stdout t
|
||||
Left e -> E.throwIO $ PandocAppError (show e)
|
||||
Left e -> E.throwIO e
|
||||
exitSuccess)
|
||||
"FORMAT")
|
||||
"" -- "Print default template for FORMAT"
|
||||
|
|
|
@ -38,28 +38,28 @@ module Text.Pandoc.Templates ( module Text.DocTemplates
|
|||
, getDefaultTemplate
|
||||
) where
|
||||
|
||||
import qualified Control.Exception as E (IOException, try)
|
||||
import Control.Monad.Except (throwError)
|
||||
import Data.Aeson (ToJSON (..))
|
||||
import qualified Data.Text as T
|
||||
import System.FilePath ((<.>), (</>))
|
||||
import Text.DocTemplates (Template, TemplateTarget, applyTemplate,
|
||||
compileTemplate, renderTemplate, varListToJSON)
|
||||
import Text.Pandoc.Class (PandocMonad)
|
||||
import Text.Pandoc.Class (PandocMonad(readDataFile))
|
||||
import Text.Pandoc.Error
|
||||
import Text.Pandoc.Shared (readDataFileUTF8)
|
||||
import qualified Text.Pandoc.UTF8 as UTF8
|
||||
|
||||
-- | Get default template for the specified writer.
|
||||
getDefaultTemplate :: (Maybe FilePath) -- ^ User data directory to search first
|
||||
getDefaultTemplate :: PandocMonad m
|
||||
=> (Maybe FilePath) -- ^ User data directory to search 1st
|
||||
-> String -- ^ Name of writer
|
||||
-> IO (Either E.IOException String)
|
||||
-> m String
|
||||
getDefaultTemplate user writer = do
|
||||
let format = takeWhile (`notElem` ("+-" :: String)) writer -- strip off extensions
|
||||
case format of
|
||||
"native" -> return $ Right ""
|
||||
"json" -> return $ Right ""
|
||||
"docx" -> return $ Right ""
|
||||
"fb2" -> return $ Right ""
|
||||
"native" -> return ""
|
||||
"json" -> return ""
|
||||
"docx" -> return ""
|
||||
"fb2" -> return ""
|
||||
"odt" -> getDefaultTemplate user "opendocument"
|
||||
"html" -> getDefaultTemplate user "html5"
|
||||
"docbook" -> getDefaultTemplate user "docbook5"
|
||||
|
@ -70,7 +70,7 @@ getDefaultTemplate user writer = do
|
|||
"markdown_mmd" -> getDefaultTemplate user "markdown"
|
||||
"markdown_phpextra" -> getDefaultTemplate user "markdown"
|
||||
_ -> let fname = "templates" </> "default" <.> format
|
||||
in E.try $ readDataFileUTF8 user fname
|
||||
in UTF8.toString <$> readDataFile user fname
|
||||
|
||||
-- | Like 'applyTemplate', but runs in PandocMonad and
|
||||
-- raises an error if compilation fails.
|
||||
|
|
Loading…
Reference in a new issue