Introduce and expose chunkEq and chunkEqBy

This commit is contained in:
Adithya Kumar 2023-07-19 11:02:37 +05:30
parent 6a4d26b170
commit daabcb84b7
3 changed files with 45 additions and 0 deletions

View File

@ -158,6 +158,14 @@ takeFramedByEsc_ _ = Stream.parse parser
listEqBy :: Int -> Stream IO Int -> IO (Either ParseError [Int])
listEqBy len = Stream.parse (PR.listEqBy (==) [1 .. len])
{-# INLINE chunkEqBy #-}
chunkEqBy :: Int -> Stream IO Int -> IO (Either ParseError [Int])
chunkEqBy len = Stream.parse (PR.chunkEqBy (==) [1 .. len])
{-# INLINE chunkEq #-}
chunkEq :: Int -> Stream IO Int -> IO (Either ParseError [Int])
chunkEq len = Stream.parse (PR.chunkEq [1 .. len])
{-# INLINE streamEqBy #-}
streamEqBy :: Int -> Stream IO Int -> IO (Either ParseError ())
streamEqBy len = Stream.parse (PR.streamEqBy (==) (Stream.enumerateFromTo 1 len))
@ -831,6 +839,8 @@ o_n_heap_serial value =
, benchIOSink value "manyAlt" manyAlt
, benchIOSink value "someAlt" someAlt
, benchIOSink value "listEqBy" (listEqBy value)
, benchIOSink value "chunkEqBy" (chunkEqBy value)
, benchIOSink value "chunkEq" (chunkEq value)
]
-- accumulate results in a list in IO

View File

@ -60,6 +60,8 @@ module Streamly.Data.Parser
, streamEqBy
, listEqBy
, listEq
, chunkEqBy
, chunkEq
-- * Combinators
-- Mapping on output

View File

@ -78,6 +78,8 @@ module Streamly.Internal.Data.Parser.ParserD
-- ** Exact match
, listEq
, listEqBy
, chunkEq
, chunkEqBy
, streamEqBy
, subsequenceBy
@ -2203,6 +2205,37 @@ streamEqBy cmp stream = streamEqByInternal cmp stream *> fromPure ()
listEq :: (Monad m, Eq a) => [a] -> Parser a m [a]
listEq = listEqBy (==)
-- | Match the given sequence of elements using the given comparison function.
-- Returns the original sequence if successful.
--
-- Definition:
--
-- >>> chunkEqBy cmp xs = Parser.streamEqBy cmp (Stream.fromFoldable xs) *> Parser.fromPure xs
--
-- Examples:
--
-- >>> Stream.parse (Parser.chunkEqBy (==) "string") $ Stream.fromList "string"
-- Right "string"
--
-- >>> Stream.parse (Parser.chunkEqBy (==) "mismatch") $ Stream.fromList "match"
-- Left (ParseError "streamEqBy: mismtach occurred")
--
{-# INLINE chunkEqBy #-}
chunkEqBy
:: (Foldable f, Monad m) => (a -> a -> Bool) -> f a -> Parser a m (f a)
chunkEqBy cmp xs = streamEqByInternal cmp (D.fromFoldable xs) *> fromPure xs
-- | Match the input sequence with the supplied Foldable and return it if
-- successful.
--
-- >>> chunkEq = Parser.chunkEqBy (==)
--
{-# INLINE chunkEq #-}
chunkEq
:: (Eq a, Foldable f, Monad m)
=> f a -> Parser a m (f a)
chunkEq = chunkEqBy (==)
-- | Match if the input stream is a subsequence of the argument stream i.e. all
-- the elements of the input stream occur, in order, in the argument stream.
-- The elements do not have to occur consecutively. A sequence is considered a