aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--src/Text/Pandoc/App/CommandLineOptions.hs8
-rw-r--r--src/Text/Pandoc/App/OutputSettings.hs44
-rw-r--r--src/Text/Pandoc/Writers/HTML.hs8
3 files changed, 30 insertions, 30 deletions
diff --git a/src/Text/Pandoc/App/CommandLineOptions.hs b/src/Text/Pandoc/App/CommandLineOptions.hs
index 9f1905741..c6f88af24 100644
--- a/src/Text/Pandoc/App/CommandLineOptions.hs
+++ b/src/Text/Pandoc/App/CommandLineOptions.hs
@@ -278,7 +278,7 @@ options =
, Option "H" ["include-in-header"]
(ReqArg
(\arg opt -> return opt{ optIncludeInHeader =
- arg : optIncludeInHeader opt,
+ optIncludeInHeader opt ++ [arg],
optStandalone = True })
"FILE")
"" -- "File to include at end of header (implies -s)"
@@ -286,7 +286,7 @@ options =
, Option "B" ["include-before-body"]
(ReqArg
(\arg opt -> return opt{ optIncludeBeforeBody =
- arg : optIncludeBeforeBody opt,
+ optIncludeBeforeBody opt ++ [arg],
optStandalone = True })
"FILE")
"" -- "File to include before document body"
@@ -294,7 +294,7 @@ options =
, Option "A" ["include-after-body"]
(ReqArg
(\arg opt -> return opt{ optIncludeAfterBody =
- arg : optIncludeAfterBody opt,
+ optIncludeAfterBody opt ++ [arg],
optStandalone = True })
"FILE")
"" -- "File to include after document body"
@@ -583,7 +583,7 @@ options =
, Option "c" ["css"]
(ReqArg
- (\arg opt -> return opt{ optCss = arg : optCss opt })
+ (\arg opt -> return opt{ optCss = optCss opt ++ [arg] })
-- add new link to end, so it is included in proper order
"URL")
"" -- "Link to CSS style sheet"
diff --git a/src/Text/Pandoc/App/OutputSettings.hs b/src/Text/Pandoc/App/OutputSettings.hs
index 1d2f66dd6..b29860c03 100644
--- a/src/Text/Pandoc/App/OutputSettings.hs
+++ b/src/Text/Pandoc/App/OutputSettings.hs
@@ -19,6 +19,9 @@ module Text.Pandoc.App.OutputSettings
, optToOutputSettings
) where
import Prelude
+import qualified Data.Map as M
+import qualified Data.Text as T
+import Text.DocTemplates (toVal, Context(..))
import qualified Control.Exception as E
import Control.Monad
import Control.Monad.Except (catchError, throwError)
@@ -111,41 +114,34 @@ optToOutputSettings opts = do
hlStyle <- maybe (return Nothing) (fmap Just . lookupHighlightStyle)
(optHighlightStyle opts)
- -- note: this reverses the list constructed in option parsing,
- -- which in turn was reversed from the command-line order,
- -- so we end up with the correct order in the variable list:
- let withList _ [] vars = return vars
- withList f (x:xs) vars = f x vars >>= withList f xs
-
let setVariableM k v = return . setVariable k v
- let addContentsAsVariable varname fp vars = do
- s <- UTF8.toString . fst <$> fetchItem fp
- setVariableM varname s vars
+ let setListVariableM k vs =
+ return . Context .
+ (M.insert (T.pack k) (toVal $ map T.pack vs)) . unContext
+
+ let getStringContents fp = UTF8.toString . fst <$> fetchItem fp
+
+ let setFilesVariableM k fps ctx = do
+ xs <- mapM getStringContents fps
+ setListVariableM k xs ctx
curdir <- liftIO getCurrentDirectory
variables <-
- withList (setVariableM "sourcefile")
- -- we reverse this list because, unlike
- -- the other option lists here, it is
- -- not reversed when parsed from CLI arguments.
- -- See withList, above.
- (reverse $ optInputFiles opts)
- (optVariables opts)
+ return (optVariables opts)
+ >>=
+ setListVariableM "sourcefile" (optInputFiles opts)
>>=
- setVariableM "outputfile" (fromMaybe "-" (optOutputFile opts))
+ setVariableM "outputfile" outputFile
>>=
- withList (addContentsAsVariable "include-before")
- (optIncludeBeforeBody opts)
+ setFilesVariableM "include-before" (optIncludeBeforeBody opts)
>>=
- withList (addContentsAsVariable "include-after")
- (optIncludeAfterBody opts)
+ setFilesVariableM "include-after" (optIncludeAfterBody opts)
>>=
- withList (addContentsAsVariable "header-includes")
- (optIncludeInHeader opts)
+ setFilesVariableM "header-includes" (optIncludeInHeader opts)
>>=
- withList (setVariableM "css") (optCss opts)
+ setListVariableM "css" (optCss opts)
>>=
maybe return (setVariableM "title-prefix")
(optTitlePrefix opts)
diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs
index 783aaa8fd..3971b7740 100644
--- a/src/Text/Pandoc/Writers/HTML.hs
+++ b/src/Text/Pandoc/Writers/HTML.hs
@@ -223,8 +223,12 @@ writeHtmlString' st opts d = do
case getField "pagetitle" context of
Just (s :: Text) | not (T.null s) -> return context
_ -> do
- let fallback = maybe "Untitled" (takeBaseName . T.unpack) $
- lookupContext "sourcefile" (writerVariables opts)
+ let fallback =
+ case lookupContext "sourcefile"
+ (writerVariables opts) of
+ Nothing -> "Untitled"
+ Just [] -> "Untitled"
+ Just (x:_) -> takeBaseName $ T.unpack x
report $ NoTitleElement fallback
return $ resetField "pagetitle" (T.pack fallback) context
return $ render Nothing $ renderTemplate tpl