Add tests and benchmarks for takeBetween

This commit is contained in:
Anurag Hooda 2020-12-18 02:06:51 +05:30 committed by Harendra Kumar
parent 4ee157f973
commit 656bfc6bc8
5 changed files with 97 additions and 4 deletions

View File

@ -60,6 +60,10 @@ benchIOSink value name f =
-- Parsers
-------------------------------------------------------------------------------
{-# INLINE takeBetween #-}
takeBetween :: MonadCatch m => Int -> SerialT m a -> m ()
takeBetween value = IP.parse (PR.takeBetween 0 value FL.drain)
{-# INLINE takeEQ #-}
takeEQ :: MonadCatch m => Int -> SerialT m a -> m ()
takeEQ value = IP.parse (PR.takeEQ value FL.drain)
@ -267,7 +271,8 @@ moduleName = "Data.Parser"
o_1_space_serial :: Int -> [Benchmark]
o_1_space_serial value =
[ benchIOSink value "takeEQ" $ takeEQ value
[ benchIOSink value "takeBetween" $ takeBetween value
, benchIOSink value "takeEQ" $ takeEQ value
, benchIOSink value "takeWhile" $ takeWhile value
, benchIOSink value "drainWhile" $ drainWhile value
, benchIOSink value "groupBy" $ groupBy

View File

@ -173,7 +173,7 @@ benchmark Prelude.Serial
, Serial.Nested
, Serial.Exceptions
, Serial.Split
ghc-options: +RTS -M750M -RTS
ghc-options: +RTS -M1000M -RTS
if impl(ghcjs)
buildable: False
else
@ -314,6 +314,7 @@ benchmark Data.Parser
import: bench-options
type: exitcode-stdio-1.0
hs-source-dirs: Streamly/Benchmark/Data
ghc-options: +RTS -M750M -RTS
main-is: Parser.hs
if impl(ghcjs)
buildable: False

View File

@ -337,8 +337,8 @@ either = K.toParserK . D.either
-- | @takeBetween m n@ takes a minimum of @m@ and a maximum of @n@ input
-- elements and folds them using the supplied fold.
--
-- Stops after @m@ elements.
-- Fails if the stream ends before @n@ elements could be taken.
-- Stops after @n@ elements.
-- Fails if the stream ends before @m@ elements could be taken.
--
-- Examples: -
--

View File

@ -155,6 +155,54 @@ satisfy =
predicate = (>= mid_value)
-- Sequence Parsers Tests
takeBetweenPass :: Property
takeBetweenPass =
forAll (chooseInt (min_value, max_value)) $ \m ->
forAll (chooseInt (m, max_value)) $ \n ->
forAll (chooseInt (m, max_value)) $ \list_length ->
forAll (vectorOf list_length (chooseInt (min_value, max_value))) $ \ls ->
case S.parse (P.takeBetween m n FL.toList) (S.fromList ls) of
Right parsed_list ->
let lpl = Prelude.length parsed_list
in checkListEqual parsed_list (Prelude.take lpl ls)
Left _ -> property False
takeBetween :: Property
takeBetween =
forAll (chooseInt (min_value, max_value)) $ \m ->
forAll (chooseInt (min_value, max_value)) $ \n ->
forAll (listOf(chooseInt (min_value, max_value))) $ \ls ->
let
list_length = Prelude.length ls
in
case S.parse (P.takeBetween m n FL.toList) (S.fromList ls) of
Right parsed_list ->
if m <= list_length && n >= list_length
then
let lpl = Prelude.length parsed_list
in checkListEqual parsed_list (Prelude.take
lpl ls)
else property False
Left _ -> property (m > n || list_length < m)
-- takeBetween :: Property
-- takeBetween =
-- forAll (chooseInt (min_value, max_value)) $ \m ->
-- forAll (chooseInt (min_value, max_value)) $ \n ->
-- forAll (listOf (chooseInt (min_value, max_value))) $ \ls ->
-- let
-- list_length = Prelude.length ls
-- in
-- case S.parseD (P.takeBetween m n FL.toList) (S.fromList ls) of
-- Right parsed_list ->
-- if m <= list_length && n >= list_length
-- then
-- let lpl = Prelude.length parsed_list
-- in checkListEqual parsed_list (Prelude.take
-- lpl ls)
-- else property False
-- Left _ -> property (m > n || list_length < m)
takeEQPass :: Property
takeEQPass =
@ -634,6 +682,11 @@ main =
prop "check first element exists and satisfies predicate" satisfy
describe "test for sequence parser" $ do
prop "P.takeBetween = Prelude.take when len >= m and len <= n"
takeBetweenPass
prop ("P.takeBetween = Prelude.take when len >= m and len <= n and fail"
++ "otherwise fail") Main.takeBetween
prop "P.takeEQ = Prelude.take when len >= n" takeEQPass
prop "P.takeEQ = Prelude.take when len >= n and fail otherwise" Main.takeEQ
prop "P.takeGE n ls = ls when len >= n" takeGEPass

View File

@ -147,6 +147,36 @@ satisfy =
predicate = (>= mid_value)
-- Sequence Parsers Tests
takeBetweenPass :: Property
takeBetweenPass =
forAll (chooseInt (min_value, max_value)) $ \m ->
forAll (chooseInt (m, max_value)) $ \n ->
forAll (chooseInt (m, max_value)) $ \list_length ->
forAll (vectorOf list_length (chooseInt (min_value, max_value))) $ \ls ->
case S.parseD (P.takeBetween m n FL.toList) (S.fromList ls) of
Right parsed_list ->
let lpl = Prelude.length parsed_list
in checkListEqual parsed_list (Prelude.take lpl ls)
Left _ -> property False
takeBetween :: Property
takeBetween =
forAll (chooseInt (min_value, max_value)) $ \m ->
forAll (chooseInt (min_value, max_value)) $ \n ->
forAll (listOf (chooseInt (min_value, max_value))) $ \ls ->
let
list_length = Prelude.length ls
in
case S.parseD (P.takeBetween m n FL.toList) (S.fromList ls) of
Right parsed_list ->
if m <= list_length && n >= list_length
then
let lpl = Prelude.length parsed_list
in checkListEqual parsed_list (Prelude.take
lpl ls)
else property False
Left _ -> property (m > n || list_length < m)
take :: Property
take =
@ -662,6 +692,10 @@ main =
prop "check first element exists and satisfies predicate" satisfy
describe "test for sequence parser" $ do
prop "P.takeBetween m n = Prelude.take when len >= m and len <= n"
takeBetweenPass
prop "P.takeBetween m n = Prelude.take when len >= m and len <= n and\
\fail otherwise" takeBetween
prop "P.take = Prelude.take" Main.take
prop "P.takeEQ = Prelude.take when len >= n" takeEQPass
prop "P.takeEQ = Prelude.take when len >= n and fail otherwise" Main.takeEQ