aboutsummaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2019-09-28 11:56:51 -0700
committerJohn MacFarlane <jgm@berkeley.edu>2019-09-28 11:56:51 -0700
commitc86691fb84ec830086bc9b5e54b1ec8e41d160c8 (patch)
treebff78fc2259df9ddad1edde9d57b0f17a3877e68 /src
parent981b5de790d7625b717083cb1bcf6a88224f34dd (diff)
downloadpandoc-c86691fb84ec830086bc9b5e54b1ec8e41d160c8.tar.gz
Use Prelude.fail to avoid ambiguity with fail from GHC.Base.
Diffstat (limited to 'src')
-rw-r--r--src/Text/Pandoc/Extensions.hs2
-rw-r--r--src/Text/Pandoc/Parsing.hs12
-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
-rw-r--r--src/Text/Pandoc/Translations.hs6
-rw-r--r--src/Text/Pandoc/Writers/Docx.hs2
-rw-r--r--src/Text/Pandoc/Writers/HTML.hs2
-rw-r--r--src/Text/Pandoc/Writers/Muse.hs6
-rw-r--r--src/Text/Pandoc/Writers/OOXML.hs4
-rw-r--r--src/Text/Pandoc/Writers/Powerpoint/Output.hs2
17 files changed, 38 insertions, 38 deletions
diff --git a/src/Text/Pandoc/Extensions.hs b/src/Text/Pandoc/Extensions.hs
index 4d85eb2e6..1c787b7d3 100644
--- a/src/Text/Pandoc/Extensions.hs
+++ b/src/Text/Pandoc/Extensions.hs
@@ -397,7 +397,7 @@ parseFormatSpec = parse formatSpec ""
Just n -> return n
Nothing
| name == "lhs" -> return Ext_literate_haskell
- | otherwise -> fail $ "Unknown extension: " ++ name
+ | otherwise -> Prelude.fail $ "Unknown extension: " ++ name
return $ case polarity of
'-' -> disableExtension ext
_ -> enableExtension ext
diff --git a/src/Text/Pandoc/Parsing.hs b/src/Text/Pandoc/Parsing.hs
index 49414a9a5..cffe846a5 100644
--- a/src/Text/Pandoc/Parsing.hs
+++ b/src/Text/Pandoc/Parsing.hs
@@ -343,16 +343,16 @@ notFollowedBy' p = try $ join $ do a <- try p
-- (This version due to Andrew Pimlott on the Haskell mailing list.)
oneOfStrings' :: Stream s m Char => (Char -> Char -> Bool) -> [String] -> ParserT s st m String
-oneOfStrings' _ [] = fail "no strings"
+oneOfStrings' _ [] = Prelude.fail "no strings"
oneOfStrings' matches strs = try $ do
c <- anyChar
let strs' = [xs | (x:xs) <- strs, x `matches` c]
case strs' of
- [] -> fail "not found"
+ [] -> Prelude.fail "not found"
_ -> (c:) <$> oneOfStrings' matches strs'
<|> if "" `elem` strs'
then return [c]
- else fail "not found"
+ else Prelude.fail "not found"
-- | Parses one of a list of strings. If the list contains
-- two strings one of which is a prefix of the other, the longer
@@ -525,7 +525,7 @@ romanNumeral upperCase = do
hundreds + nineties + fifties + forties + tens + nines +
fives + fours + ones
if total == 0
- then fail "not a roman numeral"
+ then Prelude.fail "not a roman numeral"
else return total
-- Parsers for email addresses and URIs
@@ -698,7 +698,7 @@ characterReference = try $ do
_ -> ent ++ ";"
case lookupEntity ent' of
Just (c : _) -> return c
- _ -> fail "entity not found"
+ _ -> Prelude.fail "entity not found"
-- | Parses an uppercase roman numeral and returns (UpperRoman, number).
upperRoman :: Stream s m Char => ParserT s st m (ListNumberStyle, Int)
@@ -1312,7 +1312,7 @@ failIfInQuoteContext :: (HasQuoteContext st m, Stream s m t)
-> ParserT s st m ()
failIfInQuoteContext context = do
context' <- getQuoteContext
- when (context' == context) $ fail "already inside quotes"
+ when (context' == context) $ Prelude.fail "already inside quotes"
charOrRef :: Stream s m Char => String -> ParserT s st m Char
charOrRef cs =
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
diff --git a/src/Text/Pandoc/Translations.hs b/src/Text/Pandoc/Translations.hs
index 6d091bf92..50b172eda 100644
--- a/src/Text/Pandoc/Translations.hs
+++ b/src/Text/Pandoc/Translations.hs
@@ -71,7 +71,7 @@ newtype Translations = Translations (M.Map Term String)
instance FromJSON Term where
parseJSON (String t) = case safeRead (T.unpack t) of
Just t' -> pure t'
- Nothing -> fail $ "Invalid Term name " ++
+ Nothing -> Prelude.fail $ "Invalid Term name " ++
show t
parseJSON invalid = Aeson.typeMismatch "Term" invalid
@@ -79,7 +79,7 @@ instance YAML.FromYAML Term where
parseYAML (YAML.Scalar _ (YAML.SStr t)) =
case safeRead (T.unpack t) of
Just t' -> pure t'
- Nothing -> fail $ "Invalid Term name " ++
+ Nothing -> Prelude.fail $ "Invalid Term name " ++
show t
parseYAML invalid = YAML.typeMismatch "Term" invalid
@@ -89,7 +89,7 @@ instance FromJSON Translations where
return $ Translations (M.fromList xs)
where addItem (k,v) =
case safeRead (T.unpack k) of
- Nothing -> fail $ "Invalid Term name " ++ show k
+ Nothing -> Prelude.fail $ "Invalid Term name " ++ show k
Just t ->
case v of
(String s) -> return (t, T.unpack $ T.strip s)
diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs
index 4b709358f..1c5dda84c 100644
--- a/src/Text/Pandoc/Writers/Docx.hs
+++ b/src/Text/Pandoc/Writers/Docx.hs
@@ -580,7 +580,7 @@ writeDocx opts doc@(Pandoc meta _) = do
settingsEntry <- copyChildren refArchive distArchive settingsPath epochtime settingsList
let entryFromArchive arch path =
- maybe (fail $ path ++ " missing in reference docx")
+ maybe (Prelude.fail $ path ++ " missing in reference docx")
return
(findEntryByPath path arch `mplus` findEntryByPath path distArchive)
docPropsAppEntry <- entryFromArchive refArchive "docProps/app.xml"
diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs
index 52825fb09..c74d677e0 100644
--- a/src/Text/Pandoc/Writers/HTML.hs
+++ b/src/Text/Pandoc/Writers/HTML.hs
@@ -429,7 +429,7 @@ parseMailto s =
let (name', rest) = span (/='@') addr
let domain = drop 1 rest
return (name', domain)
- _ -> fail "not a mailto: URL"
+ _ -> Prelude.fail "not a mailto: URL"
-- | Obfuscate a "mailto:" link.
obfuscateLink :: PandocMonad m
diff --git a/src/Text/Pandoc/Writers/Muse.hs b/src/Text/Pandoc/Writers/Muse.hs
index 8c0410a56..90b23b6dd 100644
--- a/src/Text/Pandoc/Writers/Muse.hs
+++ b/src/Text/Pandoc/Writers/Muse.hs
@@ -607,7 +607,7 @@ inlineToMuse (Subscript lst) = do
modify $ \st -> st { stUseTags = False }
return $ "<sub>" <> contents <> "</sub>"
inlineToMuse SmallCaps {} =
- fail "SmallCaps should be expanded before normalization"
+ Prelude.fail "SmallCaps should be expanded before normalization"
inlineToMuse (Quoted SingleQuote lst) = do
contents <- inlineListToMuse lst
modify $ \st -> st { stUseTags = False }
@@ -617,7 +617,7 @@ inlineToMuse (Quoted DoubleQuote lst) = do
modify $ \st -> st { stUseTags = False }
return $ "“" <> contents <> "”"
inlineToMuse Cite {} =
- fail "Citations should be expanded before normalization"
+ Prelude.fail "Citations should be expanded before normalization"
inlineToMuse (Code _ str) = do
useTags <- gets stUseTags
modify $ \st -> st { stUseTags = False }
@@ -625,7 +625,7 @@ inlineToMuse (Code _ str) = do
then "<code>" <> text (substitute "</code>" "<</code><code>/code>" str) <> "</code>"
else "=" <> text str <> "="
inlineToMuse Math{} =
- fail "Math should be expanded before normalization"
+ Prelude.fail "Math should be expanded before normalization"
inlineToMuse (RawInline (Format f) str) = do
modify $ \st -> st { stUseTags = False }
return $ "<literal style=\"" <> text f <> "\">" <> text str <> "</literal>"
diff --git a/src/Text/Pandoc/Writers/OOXML.hs b/src/Text/Pandoc/Writers/OOXML.hs
index 3c62a4f79..cd90845af 100644
--- a/src/Text/Pandoc/Writers/OOXML.hs
+++ b/src/Text/Pandoc/Writers/OOXML.hs
@@ -54,9 +54,9 @@ parseXml :: (PandocMonad m) => Archive -> Archive -> String -> m Element
parseXml refArchive distArchive relpath =
case findEntryByPath relpath refArchive `mplus`
findEntryByPath relpath distArchive of
- Nothing -> fail $ relpath ++ " missing in reference file"
+ Nothing -> Prelude.fail $ relpath ++ " missing in reference file"
Just e -> case parseXMLDoc . UTF8.toStringLazy . fromEntry $ e of
- Nothing -> fail $ relpath ++ " corrupt in reference file"
+ Nothing -> Prelude.fail $ relpath ++ " corrupt in reference file"
Just d -> return d
-- Copied from Util
diff --git a/src/Text/Pandoc/Writers/Powerpoint/Output.hs b/src/Text/Pandoc/Writers/Powerpoint/Output.hs
index 79a5ed65f..4a8dc1528 100644
--- a/src/Text/Pandoc/Writers/Powerpoint/Output.hs
+++ b/src/Text/Pandoc/Writers/Powerpoint/Output.hs
@@ -173,7 +173,7 @@ copyFileToArchive arch fp = do
refArchive <- asks envRefArchive
distArchive <- asks envDistArchive
case findEntryByPath fp refArchive `mplus` findEntryByPath fp distArchive of
- Nothing -> fail $ fp ++ " missing in reference file"
+ Nothing -> Prelude.fail $ fp ++ " missing in reference file"
Just e -> return $ addEntryToArchive e arch
alwaysInheritedPatterns :: [Pattern]