aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--src/Text/Pandoc/Templates.hs18
-rw-r--r--src/pandoc.hs4
2 files changed, 11 insertions, 11 deletions
diff --git a/src/Text/Pandoc/Templates.hs b/src/Text/Pandoc/Templates.hs
index 59fbe8e73..9f677608d 100644
--- a/src/Text/Pandoc/Templates.hs
+++ b/src/Text/Pandoc/Templates.hs
@@ -66,7 +66,7 @@ You may optionally specify separators using @$sep$@:
module Text.Pandoc.Templates ( renderTemplate
, TemplateTarget
- , getTemplate ) where
+ , getDefaultTemplate ) where
import Text.ParserCombinators.Parsec
import Control.Monad (liftM, when, forM)
@@ -86,14 +86,14 @@ import System.IO.UTF8 ( readFile )
#endif
import Paths_pandoc (getDataFileName)
--- | Get a template for the specified writer.
-getTemplate :: (Maybe FilePath) -- ^ User data directory to search first
- -> String -- ^ Name of writer
- -> IO (Either E.IOException String)
-getTemplate _ "native" = return $ Right ""
-getTemplate user "s5" = getTemplate user "html"
-getTemplate user "odt" = getTemplate user "opendocument"
-getTemplate user writer = do
+-- | Get default template for the specified writer.
+getDefaultTemplate :: (Maybe FilePath) -- ^ User data directory to search first
+ -> String -- ^ Name of writer
+ -> IO (Either E.IOException String)
+getDefaultTemplate _ "native" = return $ Right ""
+getDefaultTemplate user "s5" = getDefaultTemplate user "html"
+getDefaultTemplate user "odt" = getDefaultTemplate user "opendocument"
+getDefaultTemplate user writer = do
let format = takeWhile (/='+') writer -- strip off "+lhs" if present
let fname = "templates" </> format <.> "template"
E.try $ case user of
diff --git a/src/pandoc.hs b/src/pandoc.hs
index 2c5e06253..4504daec9 100644
--- a/src/pandoc.hs
+++ b/src/pandoc.hs
@@ -441,7 +441,7 @@ options =
, Option "D" ["print-default-template"]
(ReqArg
(\arg _ -> do
- templ <- getTemplate Nothing arg
+ templ <- getDefaultTemplate Nothing arg
case templ of
Right t -> hPutStr stdout t
Left e -> error $ show e
@@ -650,7 +650,7 @@ main = do
Just r -> return r
Nothing -> error ("Unknown writer: " ++ writerName')
- templ <- getTemplate (Just datadir) writerName'
+ templ <- getDefaultTemplate (Just datadir) writerName'
let defaultTemplate = case templ of
Right t -> t
Left e -> error (show e)