aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/App
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2019-10-09 11:46:20 -0700
committerJohn MacFarlane <jgm@berkeley.edu>2019-10-09 11:46:20 -0700
commit5419988f225d1debcf9735f5de75a269db143bba (patch)
tree3d66f1cbd5e50012250d803620030402fa39c093 /src/Text/Pandoc/App
parent3351dcfc45cf2053ae6cb6fb811d88cb6ebbc969 (diff)
downloadpandoc-5419988f225d1debcf9735f5de75a269db143bba.tar.gz
T.P.App.Opt: Changed optMetadata to Meta, to allow structured values.
[API change] The current behavior of the `--metadata` option stays the same.
Diffstat (limited to 'src/Text/Pandoc/App')
-rw-r--r--src/Text/Pandoc/App/CommandLineOptions.hs32
-rw-r--r--src/Text/Pandoc/App/Opt.hs7
-rw-r--r--src/Text/Pandoc/App/OutputSettings.hs7
3 files changed, 32 insertions, 14 deletions
diff --git a/src/Text/Pandoc/App/CommandLineOptions.hs b/src/Text/Pandoc/App/CommandLineOptions.hs
index 696ab091c..9674a5aa0 100644
--- a/src/Text/Pandoc/App/CommandLineOptions.hs
+++ b/src/Text/Pandoc/App/CommandLineOptions.hs
@@ -41,6 +41,7 @@ import System.Exit (exitSuccess)
import System.FilePath
import System.IO (stdout)
import Text.Pandoc
+import Text.Pandoc.Builder (setMeta)
import Text.Pandoc.App.Opt (Opt (..), LineEnding (..))
import Text.Pandoc.Filter (Filter (..))
import Text.Pandoc.Highlighting (highlightingStyles)
@@ -163,7 +164,8 @@ options =
(ReqArg
(\arg opt -> do
let (key, val) = splitField arg
- return opt{ optMetadata = (key, val) : optMetadata opt })
+ return opt{ optMetadata = addMeta key val $
+ optMetadata opt })
"KEY[:VALUE]")
""
@@ -626,7 +628,8 @@ options =
, Option "" ["bibliography"]
(ReqArg
(\arg opt -> return opt{ optMetadata =
- ("bibliography", arg) : optMetadata opt })
+ addMeta "bibliography" arg $
+ optMetadata opt })
"FILE")
""
@@ -634,7 +637,7 @@ options =
(ReqArg
(\arg opt ->
return opt{ optMetadata =
- ("csl", arg) : optMetadata opt })
+ addMeta "csl" arg $ optMetadata opt })
"FILE")
""
@@ -642,7 +645,8 @@ options =
(ReqArg
(\arg opt ->
return opt{ optMetadata =
- ("citation-abbreviations", arg): optMetadata opt })
+ addMeta "citation-abbreviations" arg $
+ optMetadata opt })
"FILE")
""
@@ -981,6 +985,26 @@ setVariable :: String -> String -> Context Text -> Context Text
setVariable key val (Context ctx) =
Context $ M.insert (T.pack key) (toVal (T.pack val)) ctx
+addMeta :: String -> String -> Meta -> Meta
+addMeta k v meta =
+ case lookupMeta k meta of
+ Nothing -> setMeta k v' meta
+ Just (MetaList xs) ->
+ setMeta k (MetaList (xs ++ [v'])) meta
+ Just x -> setMeta k (MetaList [x, v']) meta
+ where
+ v' = readMetaValue v
+
+readMetaValue :: String -> MetaValue
+readMetaValue s
+ | s == "true" = MetaBool True
+ | s == "True" = MetaBool True
+ | s == "TRUE" = MetaBool True
+ | s == "false" = MetaBool False
+ | s == "False" = MetaBool False
+ | s == "FALSE" = MetaBool False
+ | otherwise = MetaString s
+
-- On Windows with ghc 8.6+, we need to rewrite paths
-- beginning with \\ to \\?\UNC\. -- See #5127.
normalizePath :: FilePath -> FilePath
diff --git a/src/Text/Pandoc/App/Opt.hs b/src/Text/Pandoc/App/Opt.hs
index 5fbbbc525..3e90ec0d3 100644
--- a/src/Text/Pandoc/App/Opt.hs
+++ b/src/Text/Pandoc/App/Opt.hs
@@ -21,7 +21,7 @@ module Text.Pandoc.App.Opt (
) where
import Prelude
import Data.Char (isLower, toLower)
-import GHC.Generics
+import GHC.Generics hiding (Meta)
import Text.Pandoc.Filter (Filter (..))
import Text.Pandoc.Logging (Verbosity (WARNING))
import Text.Pandoc.Options (TopLevelDivision (TopLevelDefault),
@@ -35,6 +35,7 @@ import Text.DocTemplates (Context(..))
import Data.Text (Text)
import Data.Aeson (defaultOptions, Options(..))
import Data.Aeson.TH (deriveJSON)
+import Text.Pandoc.Definition (Meta)
-- | The type of line-endings to be used when writing plain-text.
data LineEnding = LF | CRLF | Native deriving (Show, Generic)
@@ -50,7 +51,7 @@ data Opt = Opt
, optShiftHeadingLevelBy :: Int -- ^ Shift heading level by
, optTemplate :: Maybe FilePath -- ^ Custom template
, optVariables :: Context Text -- ^ Template variables to set
- , optMetadata :: [(String, String)] -- ^ Metadata fields to set
+ , optMetadata :: Meta -- ^ Metadata fields to set
, optMetadataFile :: [FilePath] -- ^ Name of YAML metadata file
, optOutputFile :: Maybe FilePath -- ^ Name of output file
, optInputFiles :: [FilePath] -- ^ Names of input files
@@ -124,7 +125,7 @@ defaultOpts = Opt
, optShiftHeadingLevelBy = 0
, optTemplate = Nothing
, optVariables = mempty
- , optMetadata = []
+ , optMetadata = mempty
, optMetadataFile = []
, optOutputFile = Nothing
, optInputFiles = []
diff --git a/src/Text/Pandoc/App/OutputSettings.hs b/src/Text/Pandoc/App/OutputSettings.hs
index cd591ce18..6e430a76e 100644
--- a/src/Text/Pandoc/App/OutputSettings.hs
+++ b/src/Text/Pandoc/App/OutputSettings.hs
@@ -37,7 +37,6 @@ import Text.Pandoc.App.FormatHeuristics (formatFromFilePaths)
import Text.Pandoc.App.Opt (Opt (..))
import Text.Pandoc.App.CommandLineOptions (engines, lookupHighlightStyle,
setVariable)
-import Text.Pandoc.BCP47 (Lang (..), parseBCP47)
import qualified Text.Pandoc.UTF8 as UTF8
-- | Settings specifying how document output should be produced.
@@ -197,12 +196,6 @@ optToOutputSettings opts = do
Left e -> throwError $ PandocTemplateError e
Right t -> return $ Just t
- case lookup "lang" (optMetadata opts) of
- Just l -> case parseBCP47 l of
- Left _ -> return ()
- Right l' -> setTranslations l'
- Nothing -> setTranslations $ Lang "en" "" "US" []
-
let writerOpts = def {
writerTemplate = templ
, writerVariables = variables