aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Readers
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2017-02-10 23:59:47 +0100
committerJohn MacFarlane <jgm@berkeley.edu>2017-02-11 00:14:44 +0100
commit76c55466d3087224eccdc47c804ab2904be50df5 (patch)
tree8e605c9a6ab89569d8b51898f31487ac0c005a22 /src/Text/Pandoc/Readers
parent8ad7e2c21fd00d8225c5f243bf3383c956b6c83b (diff)
downloadpandoc-76c55466d3087224eccdc47c804ab2904be50df5.tar.gz
Use new warnings throughout the code base.
Diffstat (limited to 'src/Text/Pandoc/Readers')
-rw-r--r--src/Text/Pandoc/Readers/Docx.hs9
-rw-r--r--src/Text/Pandoc/Readers/EPUB.hs4
-rw-r--r--src/Text/Pandoc/Readers/HTML.hs10
-rw-r--r--src/Text/Pandoc/Readers/LaTeX.hs19
-rw-r--r--src/Text/Pandoc/Readers/Markdown.hs25
-rw-r--r--src/Text/Pandoc/Readers/MediaWiki.hs6
-rw-r--r--src/Text/Pandoc/Readers/RST.hs61
-rw-r--r--src/Text/Pandoc/Readers/TWiki.hs6
-rw-r--r--src/Text/Pandoc/Readers/Textile.hs6
9 files changed, 69 insertions, 77 deletions
diff --git a/src/Text/Pandoc/Readers/Docx.hs b/src/Text/Pandoc/Readers/Docx.hs
index 2b92cceee..8936a0403 100644
--- a/src/Text/Pandoc/Readers/Docx.hs
+++ b/src/Text/Pandoc/Readers/Docx.hs
@@ -100,6 +100,7 @@ import Text.Pandoc.Error
import Control.Monad.Except (throwError)
import Text.Pandoc.Class (PandocMonad)
import qualified Text.Pandoc.Class as P
+import Text.Pandoc.Logging
readDocx :: PandocMonad m
=> ReaderOptions
@@ -108,12 +109,13 @@ readDocx :: PandocMonad m
readDocx opts bytes
| Right archive <- toArchiveOrFail bytes
, Right (docx, parserWarnings) <- archiveToDocxWithWarnings archive = do
- mapM_ P.warning parserWarnings
+ mapM_ (P.report . DocxParserWarning) parserWarnings
(meta, blks) <- docxToOutput opts docx
return $ Pandoc meta blks
readDocx _ _ =
throwError $ PandocSomeError "couldn't parse docx file"
+-- TODO remove this for 2.0:
readDocxWithWarnings :: PandocMonad m
=> ReaderOptions
-> B.ByteString
@@ -333,8 +335,9 @@ blocksToInlinesWarn cmtId blks = do
notParaOrPlain (Para _) = False
notParaOrPlain (Plain _) = False
notParaOrPlain _ = True
- when (not $ null $ filter notParaOrPlain blkList)
- ((lift . lift) $ P.warning $ "Docx comment " ++ cmtId ++ " will not retain formatting")
+ when (not $ null $ filter notParaOrPlain blkList) $
+ lift $ P.report $ DocxParserWarning $
+ "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/EPUB.hs b/src/Text/Pandoc/Readers/EPUB.hs
index 49a035c37..2eaa842b6 100644
--- a/src/Text/Pandoc/Readers/EPUB.hs
+++ b/src/Text/Pandoc/Readers/EPUB.hs
@@ -13,7 +13,6 @@ import Text.Pandoc.Definition hiding (Attr)
import Text.Pandoc.Readers.HTML (readHtml)
import Text.Pandoc.Walk (walk, query)
import Text.Pandoc.Options ( ReaderOptions(..))
-import Text.Pandoc.Logging (Verbosity(..))
import Text.Pandoc.Extensions (enableExtension, Extension(Ext_raw_html))
import Text.Pandoc.Shared (escapeURI, collapseFilePath, addMetaField)
import Network.URI (unEscapeString)
@@ -35,7 +34,7 @@ import qualified Data.Map as M (Map, lookup, fromList, elems)
import Data.Monoid ((<>))
import Control.DeepSeq (deepseq, NFData)
import Text.Pandoc.Error
-import Text.Pandoc.Class (PandocMonad, report)
+import Text.Pandoc.Class (PandocMonad)
import qualified Text.Pandoc.Class as P
type Items = M.Map String (FilePath, MimeType)
@@ -71,7 +70,6 @@ archiveToEPUB os archive = do
os' = os {readerExtensions = enableExtension Ext_raw_html (readerExtensions os)}
parseSpineElem :: PandocMonad m => FilePath -> (FilePath, MimeType) -> m Pandoc
parseSpineElem (normalise -> r) (normalise -> path, mime) = do
- report DEBUG ("parseSpineElem called with path " ++ show path)
doc <- mimeToReader mime r path
let docSpan = B.doc $ B.para $ B.spanWith (takeFileName path, [], []) mempty
return $ docSpan <> doc
diff --git a/src/Text/Pandoc/Readers/HTML.hs b/src/Text/Pandoc/Readers/HTML.hs
index c452d2acf..6b571fca5 100644
--- a/src/Text/Pandoc/Readers/HTML.hs
+++ b/src/Text/Pandoc/Readers/HTML.hs
@@ -48,7 +48,7 @@ import Text.Pandoc.Shared ( extractSpaces, renderTags', addMetaField
import Text.Pandoc.Options (ReaderOptions(readerExtensions), extensionEnabled,
Extension (Ext_epub_html_exts,
Ext_raw_html, Ext_native_divs, Ext_native_spans))
-import Text.Pandoc.Logging (Verbosity(..))
+import Text.Pandoc.Logging
import Text.Pandoc.Parsing hiding ((<|>))
import Text.Pandoc.Walk
import qualified Data.Map as M
@@ -59,7 +59,6 @@ import Control.Monad ( guard, mzero, void, unless )
import Control.Arrow ((***))
import Control.Applicative ( (<|>) )
import Data.Monoid (First (..))
-import Text.Printf (printf)
import Text.TeXMath (readMathML, writeTeX)
import Data.Default (Default (..), def)
import Control.Monad.Reader (ask, asks, local, ReaderT, runReaderT, lift)
@@ -69,7 +68,7 @@ import Data.Monoid ((<>))
import Text.Parsec.Error
import qualified Data.Set as Set
import Text.Pandoc.Error
-import Text.Pandoc.Class (PandocMonad, report, warningWithPos)
+import Text.Pandoc.Class (PandocMonad, report)
import Control.Monad.Except (throwError)
-- | Convert HTML-formatted string to 'Pandoc' document.
@@ -177,8 +176,7 @@ block = do
, pPlain
, pRawHtmlBlock
]
- report DEBUG $ printf "line %d: %s"
- (sourceLine pos) (take 60 $ show $ B.toList res)
+ report $ ParsingTrace (take 60 $ show $ B.toList res) pos
return res
namespaces :: PandocMonad m => [(String, TagParser m Inlines)]
@@ -378,7 +376,7 @@ ignore raw = do
-- raw can be null for tags like <!DOCTYPE>; see paRawTag
-- in this case we don't want a warning:
unless (null raw) $
- warningWithPos pos $ "Skipped " ++ raw
+ report $ SkippedContent raw pos
return mempty
pHtmlBlock :: PandocMonad m => String -> TagParser m String
diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs
index cc69786cf..0cce8bcb1 100644
--- a/src/Text/Pandoc/Readers/LaTeX.hs
+++ b/src/Text/Pandoc/Readers/LaTeX.hs
@@ -38,6 +38,7 @@ import Text.Pandoc.Definition
import Text.Pandoc.Walk
import Text.Pandoc.Shared
import Text.Pandoc.Options
+import Text.Pandoc.Logging
import Text.Pandoc.Parsing hiding ((<|>), many, optional, space,
mathDisplay, mathInline)
import Data.Char ( chr, ord, isLetter, isAlphaNum )
@@ -51,7 +52,7 @@ import qualified Data.Map as M
import Text.Pandoc.Highlighting (fromListingsLanguage, languagesByExtension)
import Text.Pandoc.ImageSize (numUnit, showFl)
import Control.Monad.Except (throwError)
-import Text.Pandoc.Class (PandocMonad, PandocPure, lookupEnv, warningWithPos,
+import Text.Pandoc.Class (PandocMonad, PandocPure, lookupEnv, report,
readFileFromDirs)
-- | Parse LaTeX from string and return 'Pandoc' document.
@@ -235,7 +236,7 @@ inline = (mempty <$ comment)
<|> (str . (:[]) <$> tildeEscape)
<|> (do res <- oneOf "#&~^'`\"[]"
pos <- getPosition
- warningWithPos pos ("Parsing unescaped '" ++ [res] ++ "'")
+ report $ ParsingUnescaped [res] pos
return $ str [res])
inlines :: PandocMonad m => LP m Inlines
@@ -312,7 +313,7 @@ optargs = snd <$> withRaw (skipopts *> skipMany (try $ optional sp *> braced))
ignore :: (Monoid a, PandocMonad m) => String -> ParserT s u m a
ignore raw = do
pos <- getPosition
- warningWithPos pos $ "Skipped " ++ raw
+ report $ SkippedContent raw pos
return mempty
ignoreBlocks :: PandocMonad m => String -> (String, LP m Blocks)
@@ -943,14 +944,14 @@ rawEnv name = do
let beginCommand = "\\begin{" ++ name ++ "}" ++ rawOptions
unless parseRaw $ do
pos1 <- getPosition
- warningWithPos pos1 $ "Skipped " ++ beginCommand
+ report $ SkippedContent beginCommand pos1
(bs, raw) <- withRaw $ env name blocks
raw' <- applyMacros' raw
if parseRaw
then return $ rawBlock "latex" $ beginCommand ++ raw'
else do
pos2 <- getPosition
- warningWithPos pos2 $ "Skipped \\end{" ++ name ++ "}"
+ report $ SkippedContent ("\\end{" ++ name ++ "}") pos2
return bs
----
@@ -982,10 +983,16 @@ include = do
inputListing :: PandocMonad m => LP m Blocks
inputListing = do
+ pos <- getPosition
options <- option [] keyvals
f <- filter (/='"') <$> braced
dirs <- (splitBy (==':') . fromMaybe ".") <$> lookupEnv "TEXINPUTS"
- codeLines <- lines <$> readFileFromDirs dirs f
+ mbCode <- readFileFromDirs dirs f
+ codeLines <- case mbCode of
+ Just s -> return $ lines s
+ Nothing -> do
+ report $ CouldNotLoadIncludeFile f pos
+ return []
let (ident,classes,kvs) = parseListingsOptions options
let language = case lookup "language" options >>= fromListingsLanguage of
Just l -> [l]
diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs
index e35b70240..9ed0c5880 100644
--- a/src/Text/Pandoc/Readers/Markdown.hs
+++ b/src/Text/Pandoc/Readers/Markdown.hs
@@ -51,7 +51,7 @@ import qualified Text.Pandoc.UTF8 as UTF8
import qualified Data.Vector as V
import Text.Pandoc.Builder (Inlines, Blocks, trimInlines)
import Text.Pandoc.Options
-import Text.Pandoc.Logging (Verbosity(..))
+import Text.Pandoc.Logging
import Text.Pandoc.Shared
import Text.Pandoc.Pretty (charWidth)
import Text.Pandoc.XML (fromEntities)
@@ -62,12 +62,10 @@ import Text.Pandoc.Readers.HTML ( htmlTag, htmlInBalanced, isInlineTag, isBlockT
import Control.Monad
import System.FilePath (takeExtension, addExtension)
import Text.HTML.TagSoup
-import Text.Printf (printf)
import Data.Monoid ((<>))
import Control.Monad.Trans (lift)
import Control.Monad.Except (throwError, catchError)
import Text.Pandoc.Class (PandocMonad, report)
-import qualified Text.Pandoc.Class as P
type MarkdownParser m = ParserT [Char] ParserState m
@@ -270,7 +268,8 @@ yamlMetaBlock = try $ do
) nullMeta hashmap
Right Yaml.Null -> return nullMeta
Right _ -> do
- P.warningWithPos pos "YAML header is not an object"
+ report $ CouldNotParseYamlMetadata "not an object"
+ pos
return nullMeta
Left err' -> do
case err' of
@@ -281,15 +280,13 @@ yamlMetaBlock = try $ do
yamlLine = yline
, yamlColumn = ycol
}}) ->
- P.warningWithPos (setSourceLine
+ report $ CouldNotParseYamlMetadata
+ problem (setSourceLine
(setSourceColumn pos
(sourceColumn pos + ycol))
(sourceLine pos + 1 + yline))
- $ "Could not parse YAML header: " ++
- problem
- _ -> P.warningWithPos pos
- $ "Could not parse YAML header: " ++
- show err'
+ _ -> report $ CouldNotParseYamlMetadata
+ (show err') pos
return nullMeta
updateState $ \st -> st{ stateMeta' = stateMeta' st <> (return meta') }
return mempty
@@ -406,7 +403,7 @@ referenceKey = try $ do
let oldkeys = stateKeys st
let key = toKey raw
case M.lookup key oldkeys of
- Just _ -> P.warningWithPos pos $ "Duplicate link reference `" ++ raw ++ "'"
+ Just _ -> report $ DuplicateLinkReference raw pos
Nothing -> return ()
updateState $ \s -> s { stateKeys = M.insert key (target, attr') oldkeys }
return $ return mempty
@@ -472,7 +469,7 @@ noteBlock = try $ do
let newnote = (ref, parsed)
oldnotes <- stateNotes' <$> getState
case lookup ref oldnotes of
- Just _ -> P.warningWithPos pos $ "Duplicate note reference `" ++ ref ++ "'"
+ Just _ -> report $ DuplicateNoteReference ref pos
Nothing -> return ()
updateState $ \s -> s { stateNotes' = newnote : oldnotes }
return mempty
@@ -512,8 +509,8 @@ block = do
, para
, plain
] <?> "block"
- report DEBUG $ printf "line %d: %s" (sourceLine pos)
- (take 60 $ show $ B.toList $ runF res defaultParserState)
+ report $ ParsingTrace
+ (take 60 $ show $ B.toList $ runF res defaultParserState) pos
return res
--
diff --git a/src/Text/Pandoc/Readers/MediaWiki.hs b/src/Text/Pandoc/Readers/MediaWiki.hs
index e70509bd1..14f9da9b6 100644
--- a/src/Text/Pandoc/Readers/MediaWiki.hs
+++ b/src/Text/Pandoc/Readers/MediaWiki.hs
@@ -41,7 +41,7 @@ import qualified Text.Pandoc.Builder as B
import Text.Pandoc.Builder (Inlines, Blocks, trimInlines)
import Data.Monoid ((<>))
import Text.Pandoc.Options
-import Text.Pandoc.Logging (Verbosity(..))
+import Text.Pandoc.Logging
import Text.Pandoc.Readers.HTML ( htmlTag, isBlockTag, isCommentTag )
import Text.Pandoc.XML ( fromEntities )
import Text.Pandoc.Parsing hiding ( nested )
@@ -56,7 +56,6 @@ import qualified Data.Map as M
import qualified Data.Set as Set
import Data.Char (isDigit, isSpace)
import Data.Maybe (fromMaybe)
-import Text.Printf (printf)
import Control.Monad.Except (throwError)
import Text.Pandoc.Class (PandocMonad, report)
@@ -207,8 +206,7 @@ block = do
<|> blockTag
<|> (B.rawBlock "mediawiki" <$> template)
<|> para
- report DEBUG $ printf "line %d: %s" (sourceLine pos)
- (take 60 $ show $ B.toList res)
+ report $ ParsingTrace (take 60 $ show $ B.toList res) pos
return res
para :: PandocMonad m => MWParser m Blocks
diff --git a/src/Text/Pandoc/Readers/RST.hs b/src/Text/Pandoc/Readers/RST.hs
index 3fbb533a8..c5ddbbad8 100644
--- a/src/Text/Pandoc/Readers/RST.hs
+++ b/src/Text/Pandoc/Readers/RST.hs
@@ -36,6 +36,7 @@ import Text.Pandoc.Builder (setMeta, fromList)
import Text.Pandoc.Shared
import Text.Pandoc.Parsing
import Text.Pandoc.Options
+import Text.Pandoc.Logging
import Text.Pandoc.Error
import Control.Monad ( when, liftM, guard, mzero )
import Data.List ( findIndex, intercalate, isInfixOf,
@@ -49,8 +50,7 @@ import Data.Sequence (viewr, ViewR(..))
import Data.Char (toLower, isHexDigit, isSpace, toUpper)
import Data.Monoid ((<>))
import Control.Monad.Except (throwError)
-import Text.Pandoc.Class (PandocMonad, warning, readFileFromDirs,
- warningWithPos)
+import Text.Pandoc.Class (PandocMonad, report, readFileFromDirs)
-- | Parse reStructuredText string and return Pandoc document.
readRST :: PandocMonad m
@@ -421,8 +421,12 @@ include = try $ do
when (f `elem` containers) $
throwError $ PandocParseError $ "Include file loop at " ++ show oldPos
updateState $ \s -> s{ stateContainers = f : stateContainers s }
- contents <- readFileFromDirs ["."] f
- let contentLines = lines contents
+ mbContents <- readFileFromDirs ["."] f
+ contentLines <- case mbContents of
+ Just s -> return $ lines s
+ Nothing -> do
+ report $ CouldNotLoadIncludeFile f oldPos
+ return []
let numLines = length contentLines
let startLine' = case startLine of
Nothing -> 1
@@ -688,7 +692,7 @@ directive' = do
return $ B.divWith attrs children
other -> do
pos <- getPosition
- warningWithPos pos $ "ignoring unknown directive: " ++ other
+ report $ SkippedContent (".. " ++ other) pos
return mempty
-- TODO:
@@ -696,6 +700,7 @@ directive' = do
-- change Text.Pandoc.Definition.Format to fix
addNewRole :: PandocMonad m => String -> [(String, String)] -> RSTParser m Blocks
addNewRole roleString fields = do
+ pos <- getPosition
(role, parentRole) <- parseFromString inheritedRole roleString
customRoles <- stateRstCustomRoles <$> getState
let getBaseRole (r, f, a) roles =
@@ -716,22 +721,18 @@ addNewRole roleString fields = do
-- warn about syntax we ignore
flip mapM_ fields $ \(key, _) -> case key of
- "language" -> when (baseRole /= "code") $ warning $
- "ignoring :language: field because the parent of role :" ++
- role ++ ": is :" ++ baseRole ++ ": not :code:"
- "format" -> when (baseRole /= "raw") $ warning $
- "ignoring :format: field because the parent of role :" ++
- role ++ ": is :" ++ baseRole ++ ": not :raw:"
- _ -> warning $ "ignoring unknown field :" ++ key ++
- ": in definition of role :" ++ role ++ ": in"
+ "language" -> when (baseRole /= "code") $ report $
+ SkippedContent ":language: [because parent of role is not :code:]"
+ pos
+ "format" -> when (baseRole /= "raw") $ report $
+ SkippedContent ":format: [because parent of role is not :raw:]" pos
+ _ -> report $ SkippedContent (":" ++ key ++ ":") pos
when (parentRole == "raw" && countKeys "format" > 1) $
- warning $
- "ignoring :format: fields after the first in the definition of role :"
- ++ role ++": in"
+ report $ SkippedContent ":format: [after first in definition of role]"
+ pos
when (parentRole == "code" && countKeys "language" > 1) $
- warning $
- "ignoring :language: fields after the first in the definition of role :"
- ++ role ++": in"
+ report $ SkippedContent
+ ":language: [after first in definition of role]" pos
updateState $ \s -> s {
stateRstCustomRoles =
@@ -1011,9 +1012,9 @@ simpleTable headless = do
case B.toList tbl of
[Table c a _w h l] -> return $ B.singleton $
Table c a (replicate (length a) 0) h l
- _ -> do
- warning "tableWith returned something unexpected"
- return tbl -- TODO error?
+ _ ->
+ throwError $ PandocShouldNeverHappenError
+ "tableWith returned something unexpected"
where
sep = return () -- optional (simpleTableSep '-')
@@ -1132,7 +1133,7 @@ renderRole contents fmt role attr = case role of
renderRole contents newFmt newRole newAttr
Nothing -> do
pos <- getPosition
- warningWithPos pos $ "ignoring unknown role :" ++ custom ++ ": in"
+ report $ SkippedContent (":" ++ custom ++ ":") pos
return $ B.str contents -- Undefined role
where
titleRef ref = return $ B.str ref -- FIXME: Not a sensible behaviour
@@ -1217,9 +1218,7 @@ explicitLink = try $ do
case M.lookup key keyTable of
Nothing -> do
pos <- getPosition
- warningWithPos pos $
- "Could not find reference for " ++
- show key
+ report $ ReferenceNotFound (show key) pos
return ("","",nullAttr)
Just ((s,t),a) -> return (s,t,a)
_ -> return (src, "", nullAttr)
@@ -1242,9 +1241,7 @@ referenceLink = try $ do
((src,tit), attr) <- case M.lookup key keyTable of
Nothing -> do
pos <- getPosition
- warningWithPos pos $
- "Could not find reference for " ++
- show key
+ report $ ReferenceNotFound (show key) pos
return (("",""),nullAttr)
Just val -> return val
-- if anonymous link, remove key so it won't be used again
@@ -1273,8 +1270,7 @@ subst = try $ do
case M.lookup key substTable of
Nothing -> do
pos <- getPosition
- warningWithPos pos $
- "Could not find reference for " ++ show key
+ report $ ReferenceNotFound (show key) pos
return mempty
Just target -> return target
@@ -1288,8 +1284,7 @@ note = try $ do
case lookup ref notes of
Nothing -> do
pos <- getPosition
- warningWithPos pos $
- "Could not find note for " ++ show ref
+ report $ ReferenceNotFound (show ref) pos
return mempty
Just raw -> do
-- We temporarily empty the note list while parsing the note,
diff --git a/src/Text/Pandoc/Readers/TWiki.hs b/src/Text/Pandoc/Readers/TWiki.hs
index af9b38895..3b89f2ee9 100644
--- a/src/Text/Pandoc/Readers/TWiki.hs
+++ b/src/Text/Pandoc/Readers/TWiki.hs
@@ -35,11 +35,10 @@ module Text.Pandoc.Readers.TWiki ( readTWiki
import Text.Pandoc.Definition
import qualified Text.Pandoc.Builder as B
import Text.Pandoc.Options
-import Text.Pandoc.Logging (Verbosity(..))
+import Text.Pandoc.Logging
import Text.Pandoc.Parsing hiding (enclosed, macro, nested)
import Text.Pandoc.Readers.HTML (htmlTag, isCommentTag)
import Control.Monad
-import Text.Printf (printf)
import Text.Pandoc.XML (fromEntities)
import Data.Maybe (fromMaybe)
import Text.HTML.TagSoup
@@ -133,8 +132,7 @@ block = do
<|> blockElements
<|> para
skipMany blankline
- report DEBUG $ printf "line %d: %s" (sourceLine pos)
- (take 60 $ show $ B.toList res)
+ report $ ParsingTrace (take 60 $ show $ B.toList res) pos
return res
blockElements :: PandocMonad m => TWParser m B.Blocks
diff --git a/src/Text/Pandoc/Readers/Textile.hs b/src/Text/Pandoc/Readers/Textile.hs
index f404079ec..6594b9ab8 100644
--- a/src/Text/Pandoc/Readers/Textile.hs
+++ b/src/Text/Pandoc/Readers/Textile.hs
@@ -56,8 +56,8 @@ import Text.Pandoc.Definition
import Text.Pandoc.Builder (Inlines, Blocks, trimInlines)
import qualified Text.Pandoc.Builder as B
import Text.Pandoc.Options
-import Text.Pandoc.Logging (Verbosity(..))
import Text.Pandoc.Parsing
+import Text.Pandoc.Logging
import Text.Pandoc.Readers.HTML ( htmlTag, isBlockTag, isInlineTag )
import Text.Pandoc.Shared (trim)
import Text.Pandoc.Readers.LaTeX ( rawLaTeXInline, rawLaTeXBlock )
@@ -67,7 +67,6 @@ import Data.List ( intercalate, transpose, intersperse )
import Data.Char ( digitToInt, isUpper )
import Control.Monad ( guard, liftM )
import Data.Monoid ((<>))
-import Text.Printf
import Text.Pandoc.Class (PandocMonad, report)
import Control.Monad.Except (throwError)
@@ -141,8 +140,7 @@ block :: PandocMonad m => ParserT [Char] ParserState m Blocks
block = do
res <- choice blockParsers <?> "block"
pos <- getPosition
- report DEBUG $ printf "line %d: %s" (sourceLine pos)
- (take 60 $ show $ B.toList res)
+ report $ ParsingTrace (take 60 $ show $ B.toList res) pos
return res
commentBlock :: PandocMonad m => ParserT [Char] ParserState m Blocks