Change the signature of Parser.deintercalate, move fold at end (#1904)

This commit is contained in:
Ranjeet Ranjan 2022-10-07 13:51:50 +05:30 committed by GitHub
parent e061109f76
commit 61eb3f4dfa
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
4 changed files with 11 additions and 11 deletions

View File

@ -199,7 +199,7 @@ deintercalate _ = Stream.parse (partition even)
partition p =
PR.deintercalate
Fold.drain (PR.takeWhile (not . p) Fold.sum) (PR.takeWhile p Fold.sum)
(PR.takeWhile (not . p) Fold.sum) (PR.takeWhile p Fold.sum) Fold.drain
{-# INLINE manyWordByEven #-}
manyWordByEven :: MonadThrow m => Stream m Int -> m ()

View File

@ -1446,14 +1446,14 @@ manyThen _parser _recover _f = undefined
--
{-# INLINE deintercalate #-}
deintercalate :: Monad m =>
Fold m (Either x y) z
-> Parser m a x
Parser m a x
-> Parser m a y
-> Fold m (Either x y) z
-> Parser m a z
deintercalate sink contentL contentR =
deintercalate contentL contentR sink =
D.toParserK
$ D.deintercalate
sink (D.fromParserK contentL) (D.fromParserK contentR)
(D.fromParserK contentL) (D.fromParserK contentR) sink
-- | Parse items separated by a separator parsed by the supplied parser. At
-- least one item must be present for the parser to succeed.
@ -1474,7 +1474,7 @@ sepBy1 sink p sep = do
-- run, when it is done content parser is run again and so on. If none of the
-- parsers consumes an input then parser returns a failure.
--
-- >>> sepBy sink = Parser.deintercalate (Fold.lefts sink)
-- >>> sepBy sink p1 p2 = Parser.deintercalate p1 p2 (Fold.lefts sink)
-- >>> sepBy sink content sep = Parser.sepBy1 sink content sep <|> return mempty
--
{-# INLINE sepBy #-}

View File

@ -1835,14 +1835,14 @@ data DeintercalateState fs sp ss =
--
{-# INLINE deintercalate #-}
deintercalate :: Monad m =>
Fold m (Either x y) z
-> Parser m a x
Parser m a x
-> Parser m a y
-> Fold m (Either x y) z
-> Parser m a z
deintercalate
(Fold fstep finitial fextract)
(Parser stepL initialL extractL)
(Parser stepR initialR extractR) = Parser step initial extract
(Parser stepR initialR extractR)
(Fold fstep finitial fextract) = Parser step initial extract
where

View File

@ -605,7 +605,7 @@ deintercalate =
partition =
FL.tee (fmap concat $ FL.lefts FL.toList)
(fmap concat $ FL.rights FL.toList)
p = P.deintercalate partition p1 p2
p = P.deintercalate p1 p2 partition
-- shortestPass :: Property
-- shortestPass =