Parsing: many1Till
: Check for the end condition before parsing
By not checking for the end condition before the first parse, the parser was applied too often, consuming too much of the input. This fixes the behaviour of `testStringWith (many1Till (oneOf "ab") (string "aa")) "aaa"` which before incorrectly returned `Right "a"`. With this change, it instead correctly fails with `Left (PandocParsecError ...)` because it is not able to parse at least one occurence of `oneOf "ab"` that is not `"aa"`. Note that this only affects `many1Till p end` where `p` matches on a prefix of `end`.
This commit is contained in:
parent
afb551429b
commit
5a71632d11
4 changed files with 8 additions and 7 deletions
|
@ -274,11 +274,12 @@ indentWith num = do
|
|||
, try (char '\t' >> indentWith (num - tabStop)) ]
|
||||
|
||||
-- | Like @manyTill@, but reads at least one item.
|
||||
many1Till :: Stream s m t
|
||||
many1Till :: (Show end, Stream s m t)
|
||||
=> ParserT s st m a
|
||||
-> ParserT s st m end
|
||||
-> ParserT s st m [a]
|
||||
many1Till p end = do
|
||||
notFollowedBy' end
|
||||
first <- p
|
||||
rest <- manyTill p end
|
||||
return (first:rest)
|
||||
|
@ -343,7 +344,7 @@ blanklines :: Stream s m Char => ParserT s st m [Char]
|
|||
blanklines = many1 blankline
|
||||
|
||||
-- | Parses material enclosed between start and end parsers.
|
||||
enclosed :: Stream s m Char => ParserT s st m t -- ^ start parser
|
||||
enclosed :: (Show end, Stream s m Char) => ParserT s st m t -- ^ start parser
|
||||
-> ParserT s st m end -- ^ end parser
|
||||
-> ParserT s st m a -- ^ content parser (to be used repeatedly)
|
||||
-> ParserT s st m [a]
|
||||
|
|
|
@ -687,13 +687,13 @@ mathEnd c = try $ do
|
|||
return res
|
||||
|
||||
|
||||
enclosedInlines :: PandocMonad m => OrgParser m a
|
||||
enclosedInlines :: (PandocMonad m, Show b) => OrgParser m a
|
||||
-> OrgParser m b
|
||||
-> OrgParser m (F Inlines)
|
||||
enclosedInlines start end = try $
|
||||
trimInlinesF . mconcat <$> enclosed start end inline
|
||||
|
||||
enclosedRaw :: PandocMonad m => OrgParser m a
|
||||
enclosedRaw :: (PandocMonad m, Show b) => OrgParser m a
|
||||
-> OrgParser m b
|
||||
-> OrgParser m String
|
||||
enclosedRaw start end = try $
|
||||
|
|
|
@ -349,13 +349,13 @@ linebreak = newline >> notFollowedBy newline >> (lastNewline <|> innerNewline)
|
|||
where lastNewline = eof >> return mempty
|
||||
innerNewline = return B.space
|
||||
|
||||
between :: (Monoid c, PandocMonad m)
|
||||
between :: (Monoid c, PandocMonad m, Show b)
|
||||
=> TWParser m a -> TWParser m b -> (TWParser m b -> TWParser m c)
|
||||
-> TWParser m c
|
||||
between start end p =
|
||||
mconcat <$> try (start >> notFollowedBy whitespace >> many1Till (p end) end)
|
||||
|
||||
enclosed :: (Monoid b, PandocMonad m)
|
||||
enclosed :: (Monoid b, PandocMonad m, Show a)
|
||||
=> TWParser m a -> (TWParser m a -> TWParser m b) -> TWParser m b
|
||||
enclosed sep p = between sep (try $ sep <* endMarker) p
|
||||
where
|
||||
|
|
|
@ -692,7 +692,7 @@ langAttr = do
|
|||
return $ \(id',classes,keyvals) -> (id',classes,("lang",lang):keyvals)
|
||||
|
||||
-- | Parses material surrounded by a parser.
|
||||
surrounded :: PandocMonad m
|
||||
surrounded :: (PandocMonad m, Show t)
|
||||
=> ParserT [Char] st m t -- ^ surrounding parser
|
||||
-> ParserT [Char] st m a -- ^ content parser (to be used repeatedly)
|
||||
-> ParserT [Char] st m [a]
|
||||
|
|
Loading…
Reference in a new issue