aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Readers
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Readers')
-rw-r--r--src/Text/Pandoc/Readers/Docx.hs4
-rw-r--r--src/Text/Pandoc/Readers/Markdown.hs10
-rw-r--r--src/Text/Pandoc/Readers/RST.hs14
-rw-r--r--src/Text/Pandoc/Readers/TWiki.hs2
4 files changed, 15 insertions, 15 deletions
diff --git a/src/Text/Pandoc/Readers/Docx.hs b/src/Text/Pandoc/Readers/Docx.hs
index 16542fd1f..490fdf878 100644
--- a/src/Text/Pandoc/Readers/Docx.hs
+++ b/src/Text/Pandoc/Readers/Docx.hs
@@ -108,7 +108,7 @@ readDocx :: PandocMonad m
readDocx opts bytes
| Right archive <- toArchiveOrFail bytes
, Right (docx, parserWarnings) <- archiveToDocxWithWarnings archive = do
- mapM_ P.addWarning parserWarnings
+ mapM_ P.warning parserWarnings
(meta, blks) <- docxToOutput opts docx
return $ Pandoc meta blks
readDocx _ _ =
@@ -334,7 +334,7 @@ blocksToInlinesWarn cmtId blks = do
notParaOrPlain (Plain _) = False
notParaOrPlain _ = True
when (not $ null $ filter notParaOrPlain blkList)
- ((lift . lift) $ P.addWarning $ "Docx comment " ++ cmtId ++ " will not retain formatting")
+ ((lift . lift) $ P.warning $ "Docx comment " ++ cmtId ++ " will not retain formatting")
return $ fromList $ blocksToInlines blkList
parPartToInlines :: PandocMonad m => ParPart -> DocxContext m Inlines
diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs
index b59e5a5f1..012edfe3b 100644
--- a/src/Text/Pandoc/Readers/Markdown.hs
+++ b/src/Text/Pandoc/Readers/Markdown.hs
@@ -280,7 +280,7 @@ yamlMetaBlock = try $ do
) nullMeta hashmap
Right Yaml.Null -> return nullMeta
Right _ -> do
- P.addWarningWithPos (Just pos) "YAML header is not an object"
+ P.warningWithPos (Just pos) "YAML header is not an object"
return nullMeta
Left err' -> do
case err' of
@@ -291,13 +291,13 @@ yamlMetaBlock = try $ do
yamlLine = yline
, yamlColumn = ycol
}}) ->
- P.addWarningWithPos (Just $ setSourceLine
+ P.warningWithPos (Just $ setSourceLine
(setSourceColumn pos
(sourceColumn pos + ycol))
(sourceLine pos + 1 + yline))
$ "Could not parse YAML header: " ++
problem
- _ -> P.addWarningWithPos (Just pos)
+ _ -> P.warningWithPos (Just pos)
$ "Could not parse YAML header: " ++
show err'
return nullMeta
@@ -420,7 +420,7 @@ referenceKey = try $ do
let oldkeys = stateKeys st
let key = toKey raw
case M.lookup key oldkeys of
- Just _ -> P.addWarningWithPos (Just pos) $ "Duplicate link reference `" ++ raw ++ "'"
+ Just _ -> P.warningWithPos (Just pos) $ "Duplicate link reference `" ++ raw ++ "'"
Nothing -> return ()
updateState $ \s -> s { stateKeys = M.insert key (target, attr') oldkeys }
return $ return mempty
@@ -486,7 +486,7 @@ noteBlock = try $ do
let newnote = (ref, parsed)
oldnotes <- stateNotes' <$> getState
case lookup ref oldnotes of
- Just _ -> P.addWarningWithPos (Just pos) $ "Duplicate note reference `" ++ ref ++ "'"
+ Just _ -> P.warningWithPos (Just pos) $ "Duplicate note reference `" ++ ref ++ "'"
Nothing -> return ()
updateState $ \s -> s { stateNotes' = newnote : oldnotes }
return mempty
diff --git a/src/Text/Pandoc/Readers/RST.hs b/src/Text/Pandoc/Readers/RST.hs
index df6a8114b..5e8aa20f5 100644
--- a/src/Text/Pandoc/Readers/RST.hs
+++ b/src/Text/Pandoc/Readers/RST.hs
@@ -626,7 +626,7 @@ directive' = do
return $ B.divWith attrs children
other -> do
pos <- getPosition
- P.addWarningWithPos (Just pos) $ "ignoring unknown directive: " ++ other
+ P.warningWithPos (Just pos) $ "ignoring unknown directive: " ++ other
return mempty
-- TODO:
@@ -654,20 +654,20 @@ addNewRole roleString fields = do
-- warn about syntax we ignore
flip mapM_ fields $ \(key, _) -> case key of
- "language" -> when (baseRole /= "code") $ lift $ P.addWarning $
+ "language" -> when (baseRole /= "code") $ lift $ P.warning $
"ignoring :language: field because the parent of role :" ++
role ++ ": is :" ++ baseRole ++ ": not :code:"
- "format" -> when (baseRole /= "raw") $ lift $ P.addWarning $
+ "format" -> when (baseRole /= "raw") $ lift $ P.warning $
"ignoring :format: field because the parent of role :" ++
role ++ ": is :" ++ baseRole ++ ": not :raw:"
- _ -> lift $ P.addWarning $ "ignoring unknown field :" ++ key ++
+ _ -> lift $ P.warning $ "ignoring unknown field :" ++ key ++
": in definition of role :" ++ role ++ ": in"
when (parentRole == "raw" && countKeys "format" > 1) $
- lift $ P.addWarning $
+ lift $ P.warning $
"ignoring :format: fields after the first in the definition of role :"
++ role ++": in"
when (parentRole == "code" && countKeys "language" > 1) $
- lift $ P.addWarning $
+ lift $ P.warning $
"ignoring :language: fields after the first in the definition of role :"
++ role ++": in"
@@ -1065,7 +1065,7 @@ renderRole contents fmt role attr = case role of
renderRole contents newFmt newRole newAttr
Nothing -> do
pos <- getPosition
- P.addWarningWithPos (Just pos) $ "ignoring unknown role :" ++ custom ++ ": in"
+ P.warningWithPos (Just pos) $ "ignoring unknown role :" ++ custom ++ ": in"
return $ B.str contents -- Undefined role
where
titleRef ref = return $ B.str ref -- FIXME: Not a sensible behaviour
diff --git a/src/Text/Pandoc/Readers/TWiki.hs b/src/Text/Pandoc/Readers/TWiki.hs
index cc4f8f39c..b4546883b 100644
--- a/src/Text/Pandoc/Readers/TWiki.hs
+++ b/src/Text/Pandoc/Readers/TWiki.hs
@@ -58,7 +58,7 @@ readTWiki :: PandocMonad m
-> m Pandoc
readTWiki opts s = case readTWikiWithWarnings' opts s of
Right (doc, warns) -> do
- mapM_ P.addWarning warns
+ mapM_ P.warning warns
return doc
Left e -> throwError e