Implement slicesepby, add tests and benchmarks

This commit is contained in:
Anurag Hooda 2021-01-11 18:41:11 +05:30 committed by Harendra Kumar
parent 6e513737d5
commit 5ccf51dcae
6 changed files with 51 additions and 9 deletions

View File

@ -161,6 +161,12 @@ split_ value =
(PR.drainWhile (<= value))
)
{-# INLINE sliceSepBy #-}
sliceSepBy :: MonadCatch m
=> Int -> SerialT m Int -> m()
sliceSepBy value = IP.parse (PR.sliceSepBy (>= value) (PR.many FL.drain
(PR.satisfy (const True))))
{-# INLINE teeAllAny #-}
teeAllAny :: MonadCatch m
=> Int -> SerialT m Int -> m ((), ())
@ -281,6 +287,7 @@ o_1_space_serial value =
, benchIOSink value "splitApBefore" $ splitApBefore value
, benchIOSink value "splitApAfter" $ splitApAfter value
, benchIOSink value "splitWith" $ splitWith value
, benchIOSink value "sliceSepBy" $ sliceSepBy value
, benchIOSink value "many" many
, benchIOSink value "many (wordBy even)" $ manyWordByEven
, benchIOSink value "some" some

View File

@ -100,6 +100,10 @@ someAlt xs = do
x <- IP.parseD (AP.some (PR.satisfy (> 0))) xs
return $ Prelude.length x
{-#INLINE sliceSepBy #-}
sliceSepBy :: MonadCatch m => Int -> SerialT m Int -> m ()
sliceSepBy value = IP.parseD (PR.sliceSepBy (>= value) (PR.many FL.drain
(PR.satisfy (const True))))
{-# INLINE manyTill #-}
manyTill :: MonadCatch m => Int -> SerialT m Int -> m Int
manyTill value =
@ -214,6 +218,7 @@ o_1_space_serial value =
, benchIOSink value "many" many
, benchIOSink value "many (wordBy even)" $ manyWordByEven
, benchIOSink value "some" some
, benchIOSink value "sliceSepBy" $ sliceSepBy value
, benchIOSink value "manyTill" $ manyTill value
, benchIOSink value "tee (all,any)" $ teeAllAny value
, benchIOSink value "teeFst (all,any)" $ teeFstAllAny value

View File

@ -487,12 +487,13 @@ drainWhile p = takeWhile p FL.drain
-- sliceSepByBetween cond m n p = sliceBy cond (takeBetween m n p)
-- @
--
-- /Unimplemented/
-- /Internal/
--
{-# INLINABLE sliceSepBy #-}
sliceSepBy :: -- MonadCatch m =>
sliceSepBy ::
MonadCatch m =>
(a -> Bool) -> Parser m a b -> Parser m a b
sliceSepBy _cond = undefined -- K.toParserK . D.sliceSepBy cond
sliceSepBy cond = K.toParserK . D.sliceSepBy cond . K.fromParserK
-- | Like 'sliceSepBy' but does not drop the separator element, instead
-- separator is emitted as a separate element in the output.

View File

@ -487,9 +487,22 @@ takeWhile1 predicate (Fold fstep finitial fextract) =
--
-- /Internal/
--
sliceSepBy :: -- MonadCatch m =>
sliceSepBy :: MonadCatch m =>
(a -> Bool) -> Parser m a b -> Parser m a b
sliceSepBy _cond = undefined
sliceSepBy cond (Parser pstep pinitial pextract) =
Parser step initial pextract
where
initial = pinitial
step s a =
if cond a
then do
res <- pextract s
return $ Done 0 res
else pstep s a
-- | See 'Streamly.Internal.Data.Parser.sliceBeginWith'.
--

View File

@ -311,6 +311,17 @@ takeProperties =
-- where
-- list_length = Prelude.length ls
sliceSepBy :: Property
sliceSepBy =
forAll (listOf (chooseInt (min_value, max_value ))) $ \ls ->
case S.parse (P.sliceSepBy predicate prsr) (S.fromList ls) of
Right parsed_list -> checkListEqual parsed_list (Prelude.takeWhile
(not. predicate) ls)
Left _ -> property False
where
predicate = (>= 100)
prsr = P.many FL.toList (P.satisfy (const True))
takeWhile :: Property
takeWhile =
forAll (listOf (chooseInt (0, 1))) $ \ ls ->
@ -693,6 +704,7 @@ main =
-- prop "lookAhead . take n >> lookAhead . take n = lookAhead . take n" lookAheadPass
-- prop "Fail when stream length exceeded" lookAheadFail
-- prop "lookAhead . take n >> lookAhead . take n = lookAhead . take n, else fail" lookAhead
prop "P.sliceSepBy test" Main.sliceSepBy
prop "P.takeWhile = Prelude.takeWhile" Main.takeWhile
prop ("P.takeWhile1 = Prelude.takeWhile if taken something,"
++ " else check why failed") takeWhile1

View File

@ -292,6 +292,7 @@ lookAhead =
where
list_length = Prelude.length ls
takeWhile :: Property
takeWhile =
forAll (listOf (chooseInt (0, 1))) $ \ ls ->
@ -336,12 +337,15 @@ groupBy =
sliceSepBy :: Property
sliceSepBy =
forAll (listOf (chooseInt (0, 1))) $ \ls ->
case S.parseD (P.fromFold $ FL.sliceSepBy predicate FL.toList) (S.fromList ls) of
Right parsed_list -> checkListEqual parsed_list (Prelude.takeWhile (not . predicate) ls)
forAll (listOf (chooseInt (min_value, max_value ))) $ \ls ->
case S.parseD (P.sliceSepBy predicate prsr) (S.fromList ls) of
Right parsed_list -> checkListEqual parsed_list (Prelude.takeWhile
(not. predicate) ls)
Left _ -> property False
where
predicate = (== 1)
predicate = (>= 100)
prsr = P.many FL.toList (P.satisfy (const True))
sliceSepByMax :: Property
sliceSepByMax =