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/HTML.hs4
-rw-r--r--src/Text/Pandoc/Readers/LaTeX.hs4
-rw-r--r--src/Text/Pandoc/Readers/LaTeX/Parsing.hs10
-rw-r--r--src/Text/Pandoc/Readers/Man.hs4
-rw-r--r--src/Text/Pandoc/Readers/Markdown.hs4
-rw-r--r--src/Text/Pandoc/Readers/Muse.hs4
-rw-r--r--src/Text/Pandoc/Readers/RST.hs2
-rw-r--r--src/Text/Pandoc/Readers/Roff.hs6
-rw-r--r--src/Text/Pandoc/Readers/Textile.hs2
9 files changed, 20 insertions, 20 deletions
diff --git a/src/Text/Pandoc/Readers/HTML.hs b/src/Text/Pandoc/Readers/HTML.hs
index 392530609..bb4e3a913 100644
--- a/src/Text/Pandoc/Readers/HTML.hs
+++ b/src/Text/Pandoc/Readers/HTML.hs
@@ -445,7 +445,7 @@ headerLevel tagtype =
-- return (level - 1))
-- <|>
return level
- Nothing -> fail "Could not retrieve header level"
+ Nothing -> Prelude.fail "Could not retrieve header level"
eTitlePage :: PandocMonad m => TagParser m ()
eTitlePage = try $ do
@@ -1238,7 +1238,7 @@ htmlTag f = try $ do
if stripComments
then return (next, "")
else return (next, "<!--" <> s <> "-->")
- | otherwise -> fail "bogus comment mode, HTML5 parse error"
+ | otherwise -> Prelude.fail "bogus comment mode, HTML5 parse error"
TagOpen tagname attr -> do
guard $ isPI tagname || all (isName . fst) attr
handleTag tagname
diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs
index a73dfb9a5..7313dd90c 100644
--- a/src/Text/Pandoc/Readers/LaTeX.hs
+++ b/src/Text/Pandoc/Readers/LaTeX.hs
@@ -1239,7 +1239,7 @@ romanNumeralArg = spaces *> (parser <|> inBraces)
Tok _ Word s <- satisfyTok isWordTok
let (digits, rest) = T.span isDigit s
unless (T.null rest) $
- fail "Non-digits in argument to \\Rn or \\RN"
+ Prelude.fail "Non-digits in argument to \\Rn or \\RN"
safeRead $ T.unpack digits
newToggle :: (Monoid a, PandocMonad m) => [Tok] -> LP m a
@@ -2268,7 +2268,7 @@ parseAligns = try $ do
case safeRead ds of
Just n ->
getInput >>= setInput . (mconcat (replicate n spec) ++)
- Nothing -> fail $ "Could not parse " ++ ds ++ " as number"
+ Nothing -> Prelude.fail $ "Could not parse " ++ ds ++ " as number"
bgroup
spaces
maybeBar
diff --git a/src/Text/Pandoc/Readers/LaTeX/Parsing.hs b/src/Text/Pandoc/Readers/LaTeX/Parsing.hs
index a0d604ea8..018ee2578 100644
--- a/src/Text/Pandoc/Readers/LaTeX/Parsing.hs
+++ b/src/Text/Pandoc/Readers/LaTeX/Parsing.hs
@@ -244,7 +244,7 @@ applyMacros s = (guardDisabled Ext_latex_macros >> return s) <|>
, sMacros = extractMacros pstate }
res <- runParserT retokenize lstate "math" (tokenize "math" (T.pack s))
case res of
- Left e -> fail (show e)
+ Left e -> Prelude.fail (show e)
Right s' -> return s'
tokenize :: SourceName -> Text -> [Tok]
@@ -452,7 +452,7 @@ doMacros' n inp = do
lstate <- getState
res <- lift $ runParserT getargs' lstate "args" ts
case res of
- Left _ -> fail $ "Could not parse arguments for " ++
+ Left _ -> Prelude.fail $ "Could not parse arguments for " ++
T.unpack name
Right (args, rest) -> do
-- first boolean param is true if we're tokenizing
@@ -576,11 +576,11 @@ primEscape = do
Just (c, _)
| c >= '\64' && c <= '\127' -> return (chr (ord c - 64))
| otherwise -> return (chr (ord c + 64))
- Nothing -> fail "Empty content of Esc1"
+ Nothing -> Prelude.fail "Empty content of Esc1"
Esc2 -> case safeRead ('0':'x':T.unpack (T.drop 2 t)) of
Just x -> return (chr x)
- Nothing -> fail $ "Could not read: " ++ T.unpack t
- _ -> fail "Expected an Esc1 or Esc2 token" -- should not happen
+ Nothing -> Prelude.fail $ "Could not read: " ++ T.unpack t
+ _ -> Prelude.fail "Expected an Esc1 or Esc2 token" -- should not happen
bgroup :: PandocMonad m => LP m Tok
bgroup = try $ do
diff --git a/src/Text/Pandoc/Readers/Man.hs b/src/Text/Pandoc/Readers/Man.hs
index c21fd00c3..ddf469222 100644
--- a/src/Text/Pandoc/Readers/Man.hs
+++ b/src/Text/Pandoc/Readers/Man.hs
@@ -131,7 +131,7 @@ parseTable = do
Left _ -> do
res' <- lift $ readWithMTokens blockstcell st ts'
case res' of
- Left _ -> fail "Could not parse table cell"
+ Left _ -> Prelude.fail "Could not parse table cell"
Right x -> do
modifyState $ \s -> s{ tableCellsPlain = False }
return x
@@ -492,4 +492,4 @@ skipUnknownMacro = do
ControlLine mkind _ pos -> do
report $ SkippedContent ('.':mkind) pos
return mempty
- _ -> fail "the impossible happened"
+ _ -> Prelude.fail "the impossible happened"
diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs
index 316dfc9d0..e00604ea0 100644
--- a/src/Text/Pandoc/Readers/Markdown.hs
+++ b/src/Text/Pandoc/Readers/Markdown.hs
@@ -261,7 +261,7 @@ yamlBsToMeta bstr = do
nodeToKey :: Monad m => YAML.Node YE.Pos -> m Text
nodeToKey (YAML.Scalar _ (YAML.SStr t)) = return t
nodeToKey (YAML.Scalar _ (YAML.SUnknown _ t)) = return t
-nodeToKey _ = fail "Non-string key in YAML mapping"
+nodeToKey _ = Prelude.fail "Non-string key in YAML mapping"
toMetaValue :: PandocMonad m
=> Text -> MarkdownParser m (F MetaValue)
@@ -767,7 +767,7 @@ lhsCodeBlockInverseBird = lhsCodeBlockBirdWith '<'
lhsCodeBlockBirdWith :: PandocMonad m => Char -> MarkdownParser m String
lhsCodeBlockBirdWith c = try $ do
pos <- getPosition
- when (sourceColumn pos /= 1) $ fail "Not in first column"
+ when (sourceColumn pos /= 1) $ Prelude.fail "Not in first column"
lns <- many1 $ birdTrackLine c
-- if (as is normal) there is always a space after >, drop it
let lns' = if all (\ln -> null ln || take 1 ln == " ") lns
diff --git a/src/Text/Pandoc/Readers/Muse.hs b/src/Text/Pandoc/Readers/Muse.hs
index 94584a697..0b2ee9ff3 100644
--- a/src/Text/Pandoc/Readers/Muse.hs
+++ b/src/Text/Pandoc/Readers/Muse.hs
@@ -496,7 +496,7 @@ amuseNoteBlockUntil end = try $ do
ref <- noteMarker
pos <- getPosition
void spaceChar <|> lookAhead eol
- (content, e) <- allowPara $ listItemContentsUntil (sourceColumn pos) (fail "x") end
+ (content, e) <- allowPara $ listItemContentsUntil (sourceColumn pos) (Prelude.fail "x") end
addNote ref pos content
return (mempty, e)
@@ -558,7 +558,7 @@ museOrderedListMarker style =
LowerRoman -> lowerRoman
UpperAlpha -> upperAlpha
LowerAlpha -> lowerAlpha
- _ -> fail "Unhandled case"
+ _ -> Prelude.fail "Unhandled case"
orderedListItemsUntil :: PandocMonad m
=> Int
diff --git a/src/Text/Pandoc/Readers/RST.hs b/src/Text/Pandoc/Readers/RST.hs
index fd20351b4..ce7af9866 100644
--- a/src/Text/Pandoc/Readers/RST.hs
+++ b/src/Text/Pandoc/Readers/RST.hs
@@ -312,7 +312,7 @@ doubleHeader' = try $ do
txt <- trimInlines . mconcat <$> many1 (notFollowedBy blankline >> inline)
pos <- getPosition
let len = sourceColumn pos - 1
- when (len > lenTop) $ fail "title longer than border"
+ when (len > lenTop) $ Prelude.fail "title longer than border"
blankline -- spaces and newline
count lenTop (char c) -- the bottom line
blanklines
diff --git a/src/Text/Pandoc/Readers/Roff.hs b/src/Text/Pandoc/Readers/Roff.hs
index 5381b2a30..6519587c6 100644
--- a/src/Text/Pandoc/Readers/Roff.hs
+++ b/src/Text/Pandoc/Readers/Roff.hs
@@ -180,7 +180,7 @@ resolveGlyph delimChar glyph = do
'[' -> escUnknown ("\\[" ++ glyph ++ "]")
'(' -> escUnknown ("\\(" ++ glyph)
'\'' -> escUnknown ("\\C'" ++ glyph ++ "'")
- _ -> fail "resolveGlyph: unknown glyph delimiter"
+ _ -> Prelude.fail "resolveGlyph: unknown glyph delimiter"
readUnicodeChar :: String -> Maybe Char
readUnicodeChar ('u':cs@(_:_:_:_:_)) =
@@ -562,7 +562,7 @@ resolveMacro macroName args pos = do
lexStringDef :: PandocMonad m => [Arg] -> RoffLexer m RoffTokens
lexStringDef args = do -- string definition
case args of
- [] -> fail "No argument to .ds"
+ [] -> Prelude.fail "No argument to .ds"
(x:ys) -> do
let ts = singleTok $ TextLine (intercalate [RoffStr " " ] ys)
let stringName = linePartsToString x
@@ -578,7 +578,7 @@ lexMacroDef args = do -- macro definition
(x : y : _) -> return (linePartsToString x, linePartsToString y)
-- optional second arg
(x:_) -> return (linePartsToString x, ".")
- [] -> fail "No argument to .de"
+ [] -> Prelude.fail "No argument to .de"
let stop = try $ do
char '.' <|> char '\''
skipMany spacetab
diff --git a/src/Text/Pandoc/Readers/Textile.hs b/src/Text/Pandoc/Readers/Textile.hs
index 6cd7781cb..a638fdf40 100644
--- a/src/Text/Pandoc/Readers/Textile.hs
+++ b/src/Text/Pandoc/Readers/Textile.hs
@@ -484,7 +484,7 @@ note = try $ do
ref <- char '[' *> many1 digit <* char ']'
notes <- stateNotes <$> getState
case lookup ref notes of
- Nothing -> fail "note not found"
+ Nothing -> Prelude.fail "note not found"
Just raw -> B.note <$> parseFromString' parseBlocks raw
-- | Special chars