aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--src/Text/Pandoc/Readers/LaTeX.hs2
-rw-r--r--src/Text/Pandoc/Readers/Markdown.hs10
-rw-r--r--src/Text/Pandoc/Readers/RST.hs4
-rw-r--r--src/Text/ParserCombinators/Pandoc.hs10
4 files changed, 8 insertions, 18 deletions
diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs
index 5e5324f79..33c4a75ee 100644
--- a/src/Text/Pandoc/Readers/LaTeX.hs
+++ b/src/Text/Pandoc/Readers/LaTeX.hs
@@ -322,7 +322,7 @@ itemBlock = try (do
--
specialEnvironment = do -- these are always parsed as raw
- followedBy' (choice (map (\name -> begin name) ["tabular", "figure",
+ lookAhead (choice (map (\name -> begin name) ["tabular", "figure",
"tabbing", "eqnarry", "picture", "table", "verse", "theorem"]))
rawLaTeXEnvironment
diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs
index afd0056ab..a94a0a06e 100644
--- a/src/Text/Pandoc/Readers/Markdown.hs
+++ b/src/Text/Pandoc/Readers/Markdown.hs
@@ -394,7 +394,7 @@ rawListItem start = try (do
-- or (in compact lists) endline.
-- note: nested lists are parsed as continuations
listContinuation start = try (do
- followedBy' indentSpaces
+ lookAhead indentSpaces
result <- many1 (listContinuationLine start)
blanks <- many blankline
return ((concat result) ++ blanks))
@@ -443,10 +443,10 @@ para = try (do
newline
st <- getState
if stateStrict st
- then choice [followedBy' blockQuote, followedBy' header,
- (do{blanklines; return ()})]
- else choice [followedBy' emacsBoxQuote,
- (do{blanklines; return ()})]
+ then choice [lookAhead blockQuote, lookAhead header,
+ (do{blanklines; return Null})]
+ else choice [(do{lookAhead emacsBoxQuote; return Null}),
+ (do{blanklines; return Null})]
let result' = normalizeSpaces result
return (Para result'))
diff --git a/src/Text/Pandoc/Readers/RST.hs b/src/Text/Pandoc/Readers/RST.hs
index 29518fbe1..70d55476e 100644
--- a/src/Text/Pandoc/Readers/RST.hs
+++ b/src/Text/Pandoc/Readers/RST.hs
@@ -198,7 +198,7 @@ codeBlockStart = try (do
-- paragraph that ends in a :: starting a code block
paraBeforeCodeBlock = try (do
result <- many1 (do {notFollowedBy' codeBlockStart; inline})
- followedBy' (string "::")
+ lookAhead (string "::")
return (Para (if (last result == Space)
then normalizeSpaces result
else (normalizeSpaces result) ++ [Str ":"])))
@@ -446,7 +446,7 @@ listItem start = try (do
rest <- many (listContinuation markerLength)
blanks <- choice [ try (do
b <- many blankline
- followedBy' start
+ lookAhead start
return b),
many1 blankline ] -- whole list must end with blank
-- parsing with ListItemState forces markers at beginning of lines to
diff --git a/src/Text/ParserCombinators/Pandoc.hs b/src/Text/ParserCombinators/Pandoc.hs
index 93494241a..ced0cb7ca 100644
--- a/src/Text/ParserCombinators/Pandoc.hs
+++ b/src/Text/ParserCombinators/Pandoc.hs
@@ -30,7 +30,6 @@ Special parser combinators for Pandoc readers.
module Text.ParserCombinators.Pandoc (
anyLine,
many1Till,
- followedBy',
notFollowedBy',
oneOfStrings,
spaceChar,
@@ -119,15 +118,6 @@ notFollowedBy' :: Show b => GenParser a st b -> GenParser a st ()
notFollowedBy' parser = try (do { c <- try parser; unexpected (show c) }
<|> return ())
--- | The inverse of @notFollowedBy'@. Fails if parser will fail, otherwise
--- returns @()@ (but does not consume any input).
-followedBy' :: (Show b) => GenParser a st b -> GenParser a st ()
-followedBy' parser = do
- isNotFollowed <- option False (do{ notFollowedBy' parser; return True})
- if isNotFollowed
- then fail "not followed by parser"
- else return ()
-
-- | Parses one of a list of strings (tried in order).
oneOfStrings :: [String] -> GenParser Char st String
oneOfStrings listOfStrings = choice $ map (try . string) listOfStrings