diff options
| author | John MacFarlane <jgm@berkeley.edu> | 2019-10-09 11:46:20 -0700 | 
|---|---|---|
| committer | John MacFarlane <jgm@berkeley.edu> | 2019-10-09 11:46:20 -0700 | 
| commit | 5419988f225d1debcf9735f5de75a269db143bba (patch) | |
| tree | 3d66f1cbd5e50012250d803620030402fa39c093 /src/Text/Pandoc | |
| parent | 3351dcfc45cf2053ae6cb6fb811d88cb6ebbc969 (diff) | |
| download | pandoc-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')
| -rw-r--r-- | src/Text/Pandoc/App.hs | 54 | ||||
| -rw-r--r-- | src/Text/Pandoc/App/CommandLineOptions.hs | 32 | ||||
| -rw-r--r-- | src/Text/Pandoc/App/Opt.hs | 7 | ||||
| -rw-r--r-- | src/Text/Pandoc/App/OutputSettings.hs | 7 | 
4 files changed, 48 insertions, 52 deletions
| diff --git a/src/Text/Pandoc/App.hs b/src/Text/Pandoc/App.hs index 288fa7788..38a469669 100644 --- a/src/Text/Pandoc/App.hs +++ b/src/Text/Pandoc/App.hs @@ -50,7 +50,7 @@ import Text.Pandoc.App.Opt (Opt (..), LineEnding (..), defaultOpts)  import Text.Pandoc.App.CommandLineOptions (parseOptions, options)  import Text.Pandoc.App.OutputSettings (OutputSettings (..), optToOutputSettings)  import Text.Pandoc.BCP47 (Lang (..), parseBCP47) -import Text.Pandoc.Builder (setMeta, deleteMeta) +import Text.Pandoc.Builder (setMeta)  import Text.Pandoc.Filter (Filter (JSONFilter, LuaFilter), applyFilters)  import Text.Pandoc.PDF (makePDF)  import Text.Pandoc.Readers.Markdown (yamlToMeta) @@ -58,6 +58,7 @@ import Text.Pandoc.SelfContained (makeDataURI, makeSelfContained)  import Text.Pandoc.Shared (eastAsianLineBreakFilter, stripEmptyParagraphs,           headerShift, isURI, tabFilter, uriPathToPath, filterIpynbOutput,           defaultUserDataDirs) +import Text.Pandoc.Writers.Shared (lookupMetaString)  import qualified Text.Pandoc.UTF8 as UTF8  #ifndef _WINDOWS  import System.Posix.IO (stdOutput) @@ -79,7 +80,8 @@ convertWithOpts opts = do    let isPandocCiteproc (JSONFilter f) = takeBaseName f == "pandoc-citeproc"        isPandocCiteproc _              = False    -- --bibliography implies -F pandoc-citeproc for backwards compatibility: -  let needsCiteproc = isJust (lookup "bibliography" (optMetadata opts)) && +  let needsCiteproc = isJust (lookupMeta "bibliography" +                                (optMetadata opts)) &&                        optCiteMethod opts `notElem` [Natbib, Biblatex] &&                        all (not . isPandocCiteproc) filters    let filters' = if needsCiteproc then JSONFilter "pandoc-citeproc" : filters @@ -195,20 +197,21 @@ convertWithOpts opts = do                      Just f  -> UTF8.toString <$> readFileStrict f      metadata <- if format == "jats" && -                   isNothing (lookup "csl" (optMetadata opts)) && -                   isNothing (lookup "citation-style" (optMetadata opts)) +                   isNothing (lookupMeta "csl" (optMetadata opts)) && +                   isNothing (lookupMeta "citation-style" +                                               (optMetadata opts))                     then do                       jatsCSL <- readDataFile "jats.csl"                       let jatsEncoded = makeDataURI                                           ("application/xml", jatsCSL) -                     return $ ("csl", jatsEncoded) : optMetadata opts +                     return $ setMeta "csl" jatsEncoded $ optMetadata opts                     else return $ optMetadata opts -    case lookup "lang" (optMetadata opts) of -           Just l  -> case parseBCP47 l of -                           Left _   -> return () +    case lookupMetaString "lang" (optMetadata opts) of +           ""      -> setTranslations $ Lang "en" "" "US" [] +           l       -> case parseBCP47 l of +                           Left _   -> report $ InvalidLang l                             Right l' -> setTranslations l' -           Nothing -> setTranslations $ Lang "en" "" "US" []      let readerOpts = def{              readerStandalone = standalone @@ -279,8 +282,8 @@ convertWithOpts opts = do                (   (if isJust (optExtractMedia opts)                        then fillMediaBag                        else return) -              >=> return . addNonPresentMetadata metadataFromFile -              >=> return . addMetadata metadata +              >=> return . adjustMetadata (<> metadataFromFile) +              >=> return . adjustMetadata (metadata <>)                >=> applyTransforms transforms                >=> applyFilters readerOpts filters' [format]                >=> maybe return extractMedia (optExtractMedia opts) @@ -319,33 +322,8 @@ htmlFormat = (`elem` ["html","html4","html5","s5","slidy",  isTextFormat :: String -> Bool  isTextFormat s = s `notElem` ["odt","docx","epub2","epub3","epub","pptx"] -addNonPresentMetadata :: Text.Pandoc.Meta -> Pandoc -> Pandoc -addNonPresentMetadata newmeta (Pandoc meta bs) = Pandoc (meta <> newmeta) bs - -addMetadata :: [(String, String)] -> Pandoc -> Pandoc -addMetadata kvs pdc = foldr addMeta (removeMetaKeys kvs pdc) kvs - -addMeta :: (String, String) -> Pandoc -> Pandoc -addMeta (k, v) (Pandoc meta bs) = Pandoc meta' bs -  where 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 -        v' = readMetaValue v - -removeMetaKeys :: [(String,String)] -> Pandoc -> Pandoc -removeMetaKeys kvs pdc = foldr (deleteMeta . fst) pdc kvs - -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 +adjustMetadata :: (Meta -> Meta) -> Pandoc -> Pandoc +adjustMetadata f (Pandoc meta bs) = Pandoc (f meta) bs  -- Transformations of a Pandoc document post-parsing: 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 | 
