Parsing: Removed charsInBalanced', added param to charsInBalanced.

The extra parameter is a character parser.  This is needed for
proper handling of escapes, etc.
This commit is contained in:
John MacFarlane 2011-12-05 20:54:46 -08:00
parent c39cdc15ba
commit fa255f68ba

View file

@ -42,7 +42,6 @@ module Text.Pandoc.Parsing ( (>>~),
parseFromString, parseFromString,
lineClump, lineClump,
charsInBalanced, charsInBalanced,
charsInBalanced',
romanNumeral, romanNumeral,
emailAddress, emailAddress,
uri, uri,
@ -174,29 +173,23 @@ lineClump = blanklines
-- | Parse a string of characters between an open character -- | Parse a string of characters between an open character
-- and a close character, including text between balanced -- and a close character, including text between balanced
-- pairs of open and close, which must be different. For example, -- pairs of open and close, which must be different. For example,
-- @charsInBalanced '(' ')'@ will parse "(hello (there))" -- @charsInBalanced '(' ')' anyChar@ will parse "(hello (there))"
-- and return "hello (there)". Stop if a blank line is -- and return "hello (there)".
-- encountered. charsInBalanced :: Char -> Char -> GenParser Char st Char
charsInBalanced :: Char -> Char -> GenParser Char st String -> GenParser Char st String
charsInBalanced open close = try $ do charsInBalanced open close parser = try $ do
char open char open
raw <- many $ (many1 (satisfy $ \c -> let isDelim c = c == open || c == close
c /= open && c /= close && c /= '\n')) raw <- many $ many1 (notFollowedBy (satisfy isDelim) >> parser)
<|> (do res <- charsInBalanced open close <|> (do res <- charsInBalanced open close parser
return $ [open] ++ res ++ [close]) return $ [open] ++ res ++ [close])
<|> try (string "\n" >>~ notFollowedBy' blanklines)
char close char close
return $ concat raw return $ concat raw
-- | Like @charsInBalanced@, but allow blank lines in the content. -- old charsInBalanced would be:
charsInBalanced' :: Char -> Char -> GenParser Char st String -- charsInBalanced open close (noneOf "\n" <|> char '\n' >> notFollowedBy blankline)
charsInBalanced' open close = try $ do -- old charsInBalanced' would be:
char open -- charsInBalanced open close anyChar
raw <- many $ (many1 (satisfy $ \c -> c /= open && c /= close))
<|> (do res <- charsInBalanced' open close
return $ [open] ++ res ++ [close])
char close
return $ concat raw
-- Auxiliary functions for romanNumeral: -- Auxiliary functions for romanNumeral: