introduce --metadata-file option
closes #1960 API change: Text.Pandoc.Readers.Markdown exports now `yamlToMeta`
This commit is contained in:
parent
73fa70c397
commit
6aa5fcac13
3 changed files with 44 additions and 3 deletions
14
MANUAL.txt
14
MANUAL.txt
|
@ -578,6 +578,16 @@ Reader options
|
|||
printed in some output formats) and metadata values will be escaped
|
||||
when inserted into the template.
|
||||
|
||||
`--metadata-file=`*FILE*
|
||||
|
||||
: Read metadata from the supplied YAML (or JSON) file.
|
||||
This option can be used with every input format, but string
|
||||
scalars in the YAML file will always be parsed as Markdown.
|
||||
Generally, the input will be handled the same as in
|
||||
[YAML metadata blocks][Extension: `yaml_metadata_block`].
|
||||
Metadata values specified inside the document, or by using `-M`,
|
||||
overwrite values specified with this option.
|
||||
|
||||
`-p`, `--preserve-tabs`
|
||||
|
||||
: Preserve tabs instead of converting them to spaces (the default).
|
||||
|
@ -3061,7 +3071,9 @@ and pass it to pandoc as an argument, along with your Markdown files:
|
|||
pandoc chap1.md chap2.md chap3.md metadata.yaml -s -o book.html
|
||||
|
||||
Just be sure that the YAML file begins with `---` and ends with `---` or
|
||||
`...`.)
|
||||
`...`.) Alternatively, you can use the `--metadata-file` option. Using
|
||||
that approach however, you cannot reference content (like footnotes)
|
||||
from the main markdown input document.
|
||||
|
||||
Metadata will be taken from the fields of the YAML object and added to any
|
||||
existing document metadata. Metadata can contain lists and objects (nested
|
||||
|
|
|
@ -89,6 +89,7 @@ import Text.Pandoc.Builder (setMeta, deleteMeta)
|
|||
import Text.Pandoc.Filter (Filter (JSONFilter, LuaFilter), applyFilters)
|
||||
import Text.Pandoc.Highlighting (highlightingStyles)
|
||||
import Text.Pandoc.PDF (makePDF)
|
||||
import Text.Pandoc.Readers.Markdown (yamlToMeta)
|
||||
import Text.Pandoc.SelfContained (makeDataURI, makeSelfContained)
|
||||
import Text.Pandoc.Shared (eastAsianLineBreakFilter, stripEmptyParagraphs,
|
||||
headerShift, isURI, ordNub, safeRead, tabFilter, uriPathToPath)
|
||||
|
@ -399,6 +400,10 @@ convertWithOpts opts = do
|
|||
("application/xml", jatsCSL)
|
||||
return $ ("csl", jatsEncoded) : optMetadata opts
|
||||
else return $ optMetadata opts
|
||||
metadataFromFile <-
|
||||
case optMetadataFile opts of
|
||||
Nothing -> return mempty
|
||||
Just file -> readFileLazy file >>= yamlToMeta
|
||||
|
||||
case lookup "lang" (optMetadata opts) of
|
||||
Just l -> case parseBCP47 l of
|
||||
|
@ -491,6 +496,7 @@ convertWithOpts opts = do
|
|||
( (if isJust (optExtractMedia opts)
|
||||
then fillMediaBag
|
||||
else return)
|
||||
>=> return . addNonPresentMetadata metadataFromFile
|
||||
>=> return . addMetadata metadata
|
||||
>=> applyTransforms transforms
|
||||
>=> applyFilters readerOpts filters' [format]
|
||||
|
@ -556,6 +562,7 @@ data Opt = Opt
|
|||
, optTemplate :: Maybe FilePath -- ^ Custom template
|
||||
, optVariables :: [(String,String)] -- ^ Template variables to set
|
||||
, optMetadata :: [(String, String)] -- ^ Metadata fields to set
|
||||
, optMetadataFile :: Maybe FilePath -- ^ Name of YAML metadata file
|
||||
, optOutputFile :: Maybe FilePath -- ^ Name of output file
|
||||
, optInputFiles :: [FilePath] -- ^ Names of input files
|
||||
, optNumberSections :: Bool -- ^ Number sections in LaTeX
|
||||
|
@ -628,6 +635,7 @@ defaultOpts = Opt
|
|||
, optTemplate = Nothing
|
||||
, optVariables = []
|
||||
, optMetadata = []
|
||||
, optMetadataFile = Nothing
|
||||
, optOutputFile = Nothing
|
||||
, optInputFiles = []
|
||||
, optNumberSections = False
|
||||
|
@ -687,6 +695,9 @@ defaultOpts = Opt
|
|||
, optStripComments = False
|
||||
}
|
||||
|
||||
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
|
||||
|
||||
|
@ -963,6 +974,12 @@ options =
|
|||
"KEY[:VALUE]")
|
||||
""
|
||||
|
||||
, Option "" ["metadata-file"]
|
||||
(ReqArg
|
||||
(\arg opt -> return opt{ optMetadataFile = Just arg })
|
||||
"FILE")
|
||||
""
|
||||
|
||||
, Option "V" ["variable"]
|
||||
(ReqArg
|
||||
(\arg opt -> do
|
||||
|
|
|
@ -31,7 +31,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
|
|||
|
||||
Conversion of markdown-formatted plain text to 'Pandoc' document.
|
||||
-}
|
||||
module Text.Pandoc.Readers.Markdown ( readMarkdown ) where
|
||||
module Text.Pandoc.Readers.Markdown ( readMarkdown, yamlToMeta ) where
|
||||
|
||||
import Prelude
|
||||
import Control.Monad
|
||||
|
@ -246,11 +246,23 @@ yamlMetaBlock = try $ do
|
|||
updateState $ \st -> st{ stateMeta' = (stateMeta' st) <> newMetaF }
|
||||
return mempty
|
||||
|
||||
-- | Read a YAML string and convert it to pandoc metadata.
|
||||
-- String scalars in the YAML are parsed as Markdown.
|
||||
yamlToMeta :: PandocMonad m => BS.ByteString -> m Meta
|
||||
yamlToMeta bstr = do
|
||||
let parser = do
|
||||
meta <- yamlBsToMeta bstr
|
||||
return $ runF meta defaultParserState
|
||||
parsed <- readWithM parser def ""
|
||||
case parsed of
|
||||
Right result -> return result
|
||||
Left e -> throwError e
|
||||
|
||||
yamlBsToMeta :: PandocMonad m => BS.ByteString -> MarkdownParser m (F Meta)
|
||||
yamlBsToMeta bstr = do
|
||||
pos <- getPosition
|
||||
case YAML.decodeNode' YAML.failsafeSchemaResolver False False bstr of
|
||||
Right [YAML.Doc (YAML.Mapping _ o)] -> (fmap Meta) <$> yamlMap o
|
||||
Right ((YAML.Doc (YAML.Mapping _ o)):_) -> (fmap Meta) <$> yamlMap o
|
||||
Right [] -> return . return $ mempty
|
||||
Right [YAML.Doc (YAML.Scalar YAML.SNull)] -> return . return $ mempty
|
||||
Right _ -> do
|
||||
|
|
Loading…
Reference in a new issue