diff options
Diffstat (limited to 'src/Text')
-rw-r--r-- | src/Text/Pandoc/App/CommandLineOptions.hs | 20 | ||||
-rw-r--r-- | src/Text/Pandoc/App/OutputSettings.hs | 21 |
2 files changed, 20 insertions, 21 deletions
diff --git a/src/Text/Pandoc/App/CommandLineOptions.hs b/src/Text/Pandoc/App/CommandLineOptions.hs index 68aec8216..55ce17bd8 100644 --- a/src/Text/Pandoc/App/CommandLineOptions.hs +++ b/src/Text/Pandoc/App/CommandLineOptions.hs @@ -202,7 +202,8 @@ options = (\arg opt -> do let (key, val) = splitField arg return opt{ optVariables = - setVariable key val $ optVariables opt }) + setVariable (T.pack key) (T.pack val) $ + optVariables opt }) "KEY[:VALUE]") "" @@ -586,7 +587,8 @@ options = (\arg opt -> return opt { optVariables = - setVariable "title-prefix" arg $ optVariables opt, + setVariable "title-prefix" (T.pack arg) $ + optVariables opt, optStandalone = True }) "STRING") "" -- "String to prefix to HTML window title" @@ -609,7 +611,7 @@ options = (ReqArg (\arg opt -> return opt { optVariables = - setVariable "epub-cover-image" arg $ + setVariable "epub-cover-image" (T.pack arg) $ optVariables opt }) "FILE") "" -- "Path of epub cover image" @@ -1029,13 +1031,11 @@ deprecatedOption o msg = Left e -> E.throwIO e -- | Set text value in text context. -setVariable :: String -> String -> Context Text -> Context Text -setVariable key val (Context ctx) = Context $ M.alter go (T.pack key) ctx - where go Nothing = Just $ toVal (T.pack val) - go (Just (ListVal xs)) - = Just $ ListVal $ xs ++ - [toVal (T.pack val)] - go (Just x) = Just $ ListVal [x, toVal (T.pack val)] +setVariable :: Text -> Text -> Context Text -> Context Text +setVariable key val (Context ctx) = Context $ M.alter go key ctx + where go Nothing = Just $ toVal val + go (Just (ListVal xs)) = Just $ ListVal $ xs ++ [toVal val] + go (Just x) = Just $ ListVal [x, toVal val] addMeta :: String -> String -> Meta -> Meta addMeta k v meta = diff --git a/src/Text/Pandoc/App/OutputSettings.hs b/src/Text/Pandoc/App/OutputSettings.hs index 9a8e9969f..3363acbb9 100644 --- a/src/Text/Pandoc/App/OutputSettings.hs +++ b/src/Text/Pandoc/App/OutputSettings.hs @@ -28,7 +28,7 @@ import Control.Monad import Control.Monad.Except (throwError) import Control.Monad.Trans import Data.Char (toLower) -import Data.List (find, isPrefixOf) +import Data.List (find) import Data.Maybe (fromMaybe) import Skylighting (defaultSyntaxMap) import Skylighting.Parser (addSyntaxDefinition, parseSyntaxDefinition) @@ -36,7 +36,6 @@ import System.Directory (getCurrentDirectory) import System.Exit (exitSuccess) import System.FilePath import System.IO (stdout) -import Data.String import Text.Pandoc import Text.Pandoc.App.FormatHeuristics (formatFromFilePaths) import Text.Pandoc.App.Opt (Opt (..)) @@ -116,7 +115,7 @@ optToOutputSettings opts = do hlStyle <- maybe (return Nothing) (fmap Just . lookupHighlightStyle . T.unpack) (optHighlightStyle opts) - let setVariableM k v = return . setVariable k (fromString v) + let setVariableM k v = return . setVariable k v let setListVariableM _ [] ctx = return ctx setListVariableM k vs ctx = do @@ -143,7 +142,7 @@ optToOutputSettings opts = do setListVariableM "sourcefile" (maybe ["-"] (fmap T.pack) (optInputFiles opts)) >>= - setVariableM "outputfile" outputFile + setVariableM "outputfile" (T.pack outputFile) >>= setFilesVariableM "include-before" (optIncludeBeforeBody opts) >>= @@ -153,21 +152,21 @@ optToOutputSettings opts = do >>= setListVariableM "css" (map T.pack $ optCss opts) >>= - maybe return (setVariableM "title-prefix" . T.unpack) (optTitlePrefix opts) + maybe return (setVariableM "title-prefix") (optTitlePrefix opts) >>= maybe return (setVariableM "epub-cover-image") - (optEpubCoverImage opts) + (T.pack <$> optEpubCoverImage opts) >>= - setVariableM "curdir" curdir + setVariableM "curdir" (T.pack curdir) >>= (\vars -> if format == "dzslides" then do - dztempl <- UTF8.toString <$> readDataFile + dztempl <- UTF8.toText <$> readDataFile ("dzslides" </> "template.html") let dzline = "<!-- {{{{ dzslides core" - let dzcore = unlines - $ dropWhile (not . (dzline `isPrefixOf`)) - $ lines dztempl + let dzcore = T.unlines + $ dropWhile (not . (dzline `T.isPrefixOf`)) + $ T.lines dztempl setVariableM "dzslides-core" dzcore vars else return vars) |