diff options
| author | mb21 <mb21@users.noreply.github.com> | 2018-03-30 21:48:14 +0200 | 
|---|---|---|
| committer | mb21 <mb21@users.noreply.github.com> | 2018-09-15 16:48:04 +0200 | 
| commit | 6aa5fcac13ea702de19ee1a605631e3ac75d7e05 (patch) | |
| tree | aedc06346c0dd697077c3867862947506d2bccd5 /src/Text/Pandoc | |
| parent | 73fa70c3974fa37aeb9a9d1535c1e09fb549bbcf (diff) | |
| download | pandoc-6aa5fcac13ea702de19ee1a605631e3ac75d7e05.tar.gz | |
introduce --metadata-file option
closes #1960
API change: Text.Pandoc.Readers.Markdown exports now `yamlToMeta`
Diffstat (limited to 'src/Text/Pandoc')
| -rw-r--r-- | src/Text/Pandoc/App.hs | 17 | ||||
| -rw-r--r-- | src/Text/Pandoc/Readers/Markdown.hs | 16 | 
2 files changed, 31 insertions, 2 deletions
| diff --git a/src/Text/Pandoc/App.hs b/src/Text/Pandoc/App.hs index 44bb30223..cb1db4f89 100644 --- a/src/Text/Pandoc/App.hs +++ b/src/Text/Pandoc/App.hs @@ -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 diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs index 50780b379..502abae9a 100644 --- a/src/Text/Pandoc/Readers/Markdown.hs +++ b/src/Text/Pandoc/Readers/Markdown.hs @@ -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 | 
