aboutsummaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2020-10-07 13:02:36 -0700
committerJohn MacFarlane <jgm@berkeley.edu>2020-10-07 13:12:32 -0700
commit428f8b4d204bf90118f01b0a03b6763b626a6532 (patch)
tree91f552dc7c9a09d7d498a21a73cbab2ae64dcb68 /src
parent69b030c7dfa0e7dc454cc589747f8fc7f5987510 (diff)
downloadpandoc-428f8b4d204bf90118f01b0a03b6763b626a6532.tar.gz
Raise informative errors when YAML metadata parsing fails.
Closes #6730. Previously the command would succeed, returning empty metadata, with no errors or warnings. API changes: - Remove now unused CouldNotParseYamlMetadata constructor for LogMessage (T.P.Logging). - Add 'Maybe FilePath' parameter to yamlToMeta in T.P.Readers.Markdown.
Diffstat (limited to 'src')
-rw-r--r--src/Text/Pandoc/App.hs5
-rw-r--r--src/Text/Pandoc/Citeproc.hs6
-rw-r--r--src/Text/Pandoc/Logging.hs10
-rw-r--r--src/Text/Pandoc/Parsing.hs2
-rw-r--r--src/Text/Pandoc/Readers/Markdown.hs16
-rw-r--r--src/Text/Pandoc/Readers/Metadata.hs40
6 files changed, 37 insertions, 42 deletions
diff --git a/src/Text/Pandoc/App.hs b/src/Text/Pandoc/App.hs
index 58f605a19..5c3ebaed9 100644
--- a/src/Text/Pandoc/App.hs
+++ b/src/Text/Pandoc/App.hs
@@ -221,8 +221,9 @@ convertWithOpts opts = do
metadataFromFile <-
case optMetadataFiles opts of
[] -> return mempty
- paths -> mapM readFileLazy paths >>=
- fmap mconcat . mapM (yamlToMeta readerOpts)
+ paths -> mconcat <$>
+ mapM (\path -> do raw <- readFileLazy path
+ yamlToMeta readerOpts (Just path) raw) paths
let transforms = (case optShiftHeadingLevelBy opts of
0 -> id
diff --git a/src/Text/Pandoc/Citeproc.hs b/src/Text/Pandoc/Citeproc.hs
index 2a71f619a..202fc5506 100644
--- a/src/Text/Pandoc/Citeproc.hs
+++ b/src/Text/Pandoc/Citeproc.hs
@@ -191,7 +191,7 @@ getRefsFromBib locale idpred t = do
let fp = T.unpack t
raw <- readFileStrict fp
case formatFromExtension fp of
- Just f -> getRefs locale f idpred raw
+ Just f -> getRefs locale f idpred (Just fp) raw
Nothing -> throwError $ PandocAppError $
"Could not deterine bibliography format for " <> t
@@ -199,9 +199,10 @@ getRefs :: PandocMonad m
=> Locale
-> BibFormat
-> (Text -> Bool)
+ -> Maybe FilePath
-> ByteString
-> m [Reference Inlines]
-getRefs locale format idpred raw =
+getRefs locale format idpred mbfp raw =
case format of
Format_bibtex ->
either (throwError . PandocAppError . T.pack . show) return .
@@ -216,6 +217,7 @@ getRefs locale format idpred raw =
Format_yaml -> do
rs <- yamlToRefs idpred
def{ readerExtensions = pandocExtensions }
+ mbfp
(L.fromStrict raw)
return $ mapMaybe metaValueToReference rs
diff --git a/src/Text/Pandoc/Logging.hs b/src/Text/Pandoc/Logging.hs
index f6a2a6e1a..5c9330b7b 100644
--- a/src/Text/Pandoc/Logging.hs
+++ b/src/Text/Pandoc/Logging.hs
@@ -61,7 +61,6 @@ instance FromYAML Verbosity where
data LogMessage =
SkippedContent Text.Text SourcePos
| IgnoredElement Text.Text
- | CouldNotParseYamlMetadata Text.Text SourcePos
| DuplicateLinkReference Text.Text SourcePos
| DuplicateNoteReference Text.Text SourcePos
| NoteDefinedButNotUsed Text.Text SourcePos
@@ -113,11 +112,6 @@ instance ToJSON LogMessage where
"column" .= sourceColumn pos]
IgnoredElement s ->
["contents" .= s]
- CouldNotParseYamlMetadata s pos ->
- ["message" .= s,
- "source" .= sourceName pos,
- "line" .= toJSON (sourceLine pos),
- "column" .= toJSON (sourceColumn pos)]
DuplicateLinkReference s pos ->
["contents" .= s,
"source" .= sourceName pos,
@@ -251,9 +245,6 @@ showLogMessage msg =
"Skipped '" <> s <> "' at " <> showPos pos
IgnoredElement s ->
"Ignored element " <> s
- CouldNotParseYamlMetadata s pos ->
- "Could not parse YAML metadata at " <> showPos pos <>
- if Text.null s then "" else ": " <> s
DuplicateLinkReference s pos ->
"Duplicate link reference '" <> s <> "' at " <> showPos pos
DuplicateNoteReference s pos ->
@@ -348,7 +339,6 @@ messageVerbosity msg =
case msg of
SkippedContent{} -> INFO
IgnoredElement{} -> INFO
- CouldNotParseYamlMetadata{} -> WARNING
DuplicateLinkReference{} -> WARNING
DuplicateNoteReference{} -> WARNING
NoteDefinedButNotUsed{} -> WARNING
diff --git a/src/Text/Pandoc/Parsing.hs b/src/Text/Pandoc/Parsing.hs
index b17cace88..8395c96de 100644
--- a/src/Text/Pandoc/Parsing.hs
+++ b/src/Text/Pandoc/Parsing.hs
@@ -179,7 +179,9 @@ module Text.Pandoc.Parsing ( take1WhileP,
setSourceColumn,
setSourceLine,
incSourceColumn,
+ incSourceLine,
newPos,
+ initialPos,
Line,
Column
)
diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs
index 1a4c63de0..d8296ea61 100644
--- a/src/Text/Pandoc/Readers/Markdown.hs
+++ b/src/Text/Pandoc/Readers/Markdown.hs
@@ -67,11 +67,17 @@ readMarkdown opts s = do
-- String scalars in the YAML are parsed as Markdown.
yamlToMeta :: PandocMonad m
=> ReaderOptions
+ -> Maybe FilePath
-> BL.ByteString
-> m Meta
-yamlToMeta opts bstr = do
+yamlToMeta opts mbfp bstr = do
let parser = do
+ oldPos <- getPosition
+ case mbfp of
+ Nothing -> return ()
+ Just fp -> setPosition $ initialPos fp
meta <- yamlBsToMeta (fmap B.toMetaValue <$> parseBlocks) bstr
+ setPosition oldPos
return $ runF meta defaultParserState
parsed <- readWithM parser def{ stateOptions = opts } ""
case parsed of
@@ -84,11 +90,17 @@ yamlToMeta opts bstr = do
yamlToRefs :: PandocMonad m
=> (Text -> Bool)
-> ReaderOptions
+ -> Maybe FilePath
-> BL.ByteString
-> m [MetaValue]
-yamlToRefs idpred opts bstr = do
+yamlToRefs idpred opts mbfp bstr = do
let parser = do
+ oldPos <- getPosition
+ case mbfp of
+ Nothing -> return ()
+ Just fp -> setPosition $ initialPos fp
refs <- yamlBsToRefs (fmap B.toMetaValue <$> parseBlocks) idpred bstr
+ setPosition oldPos
return $ runF refs defaultParserState
parsed <- readWithM parser def{ stateOptions = opts } ""
case parsed of
diff --git a/src/Text/Pandoc/Readers/Metadata.hs b/src/Text/Pandoc/Readers/Metadata.hs
index 5154e3174..bdc4c29bf 100644
--- a/src/Text/Pandoc/Readers/Metadata.hs
+++ b/src/Text/Pandoc/Readers/Metadata.hs
@@ -37,21 +37,19 @@ yamlBsToMeta :: PandocMonad m
-> BL.ByteString
-> ParserT Text ParserState m (F Meta)
yamlBsToMeta pMetaValue bstr = do
- pos <- getPosition
case YAML.decodeNode' YAML.failsafeSchemaResolver False False bstr of
Right (YAML.Doc (YAML.Mapping _ _ o):_)
-> fmap Meta <$> yamlMap pMetaValue o
Right [] -> return . return $ mempty
Right [YAML.Doc (YAML.Scalar _ YAML.SNull)]
-> return . return $ mempty
- Right _ -> do logMessage $ CouldNotParseYamlMetadata "not an object"
- pos
- return . return $ mempty
- Left (_pos, err')
- -> do logMessage $ CouldNotParseYamlMetadata
- (T.pack err') pos
- return . return $ mempty
-
+ Right _ -> fail "expected YAML object"
+ Left (yamlpos, err')
+ -> do pos <- getPosition
+ setPosition $ incSourceLine
+ (setSourceColumn pos (YE.posColumn yamlpos))
+ (YE.posLine yamlpos - 1)
+ fail err'
fakePos :: YAML.Pos
fakePos = YAML.Pos (-1) (-1) 1 0
@@ -71,8 +69,7 @@ yamlBsToRefs :: PandocMonad m
-> (Text -> Bool) -- ^ Filter for id
-> BL.ByteString
-> ParserT Text ParserState m (F [MetaValue])
-yamlBsToRefs pMetaValue idpred bstr = do
- pos <- getPosition
+yamlBsToRefs pMetaValue idpred bstr =
case YAML.decodeNode' YAML.failsafeSchemaResolver False False bstr of
Right (YAML.Doc o@(YAML.Mapping _ _ _):_)
-> case lookupYAML "references" o of
@@ -90,26 +87,17 @@ yamlBsToRefs pMetaValue idpred bstr = do
Nothing -> False
sequence <$>
mapM (yamlToMetaValue pMetaValue) (filter g ns)
- Just _ -> do
- logMessage $ CouldNotParseYamlMetadata
- ("expecting sequence in 'references' field") pos
- return . return $ mempty
- Nothing -> do
- logMessage $ CouldNotParseYamlMetadata
- ("expecting 'references' field") pos
- return . return $ mempty
+ Just _ ->
+ fail "expecting sequence in 'references' field"
+ Nothing ->
+ fail "expecting 'references' field"
Right [] -> return . return $ mempty
Right [YAML.Doc (YAML.Scalar _ YAML.SNull)]
-> return . return $ mempty
- Right _ -> do logMessage $ CouldNotParseYamlMetadata "not an object"
- pos
- return . return $ mempty
+ Right _ -> fail "expecting YAML object"
Left (_pos, err')
- -> do logMessage $ CouldNotParseYamlMetadata
- (T.pack err') pos
- return . return $ mempty
-
+ -> fail err'
nodeToKey :: YAML.Node YE.Pos -> Maybe Text