Merge Data.Parser.ParserD test cases to Data.Parser (#2458)

Co-authored-by: Harendra Kumar <harendra@composewell.com>
This commit is contained in:
Ranjeet Ranjan 2023-08-02 15:54:24 +05:30 committed by GitHub
parent 3fb676b98b
commit 9bf458f682
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
5 changed files with 256 additions and 111 deletions

View File

@ -4,7 +4,7 @@ core/src/Streamly/Internal/Unicode/Stream.hs
src/Streamly/Internal/Data/SmallArray/Type.hs
test/Streamly/Test/Data/Array.hs
test/Streamly/Test/Data/Parser.hs
test/Streamly/Test/Data/Parser/ParserD.hs
test/Streamly/Test/Data/ParserK.hs
test/Streamly/Test/Data/SmallArray.hs
test/Streamly/Test/Data/Unfold.hs
test/Streamly/Test/FileSystem/Event.hs
@ -21,7 +21,7 @@ benchmark/lib/Streamly/Benchmark/Prelude.hs
benchmark/NanoBenchmarks.hs
benchmark/Streamly/Benchmark/Data/Array.hs
benchmark/Streamly/Benchmark/Data/Parser.hs
benchmark/Streamly/Benchmark/Data/Parser/ParserD.hs
benchmark/Streamly/Benchmark/Data/ParserK.hs
benchmark/Streamly/Benchmark/Data/Stream/StreamDK.hs
benchmark/Streamly/Benchmark/Data/Stream/StreamK.hs
benchmark/Streamly/Benchmark/Data/Unfold.hs

View File

@ -107,7 +107,8 @@ extra-source-files:
test/Streamly/Test/Data/MutArray.hs
test/Streamly/Test/Data/Ring/Unboxed.hs
test/Streamly/Test/Data/Array/Stream.hs
test/Streamly/Test/Data/Parser/ParserD.hs
test/Streamly/Test/Data/Parser.hs
test/Streamly/Test/Data/ParserK.hs
test/Streamly/Test/Data/Stream/Concurrent.hs
test/Streamly/Test/FileSystem/Event.hs
test/Streamly/Test/FileSystem/Event/Common.hs

View File

@ -1,5 +1,6 @@
module Main (main) where
import Control.Applicative ((<|>))
import Control.Exception (displayException)
import Data.Foldable (for_)
import Data.Word (Word8, Word32, Word64)
@ -8,7 +9,7 @@ import Test.Hspec (Spec, hspec, describe)
import Test.Hspec.QuickCheck
import Test.QuickCheck
(arbitrary, forAll, elements, Property, property, listOf,
vectorOf, Gen)
vectorOf, Gen, (.&&.))
import Test.QuickCheck.Monadic (monadicIO, assert, run)
import Prelude hiding (sequence)
@ -16,10 +17,13 @@ import Prelude hiding (sequence)
import qualified Control.Monad.Fail as Fail
import qualified Data.List as List
import qualified Prelude
import qualified Streamly.Data.Stream as S
import qualified Streamly.Internal.Data.Array as A
import qualified Streamly.Internal.Data.Fold as FL
import qualified Streamly.Internal.Data.Parser as P
import qualified Streamly.Internal.Data.Stream as S
import qualified Streamly.Internal.Data.Producer.Source as Source
import qualified Streamly.Internal.Data.Producer as Producer
import qualified Streamly.Internal.Data.Unfold as Unfold
import qualified Test.Hspec as H
#if MIN_VERSION_QuickCheck(2,14,0)
@ -213,6 +217,13 @@ takeBetween =
Left _ ->
property ((m >= 0 && n >= 0 && m > n) || inputLen < m)
take :: Property
take =
forAll (chooseInt (min_value, max_value)) $ \n ->
forAll (listOf (chooseInt (min_value, max_value))) $ \ls ->
case runIdentity $ S.parse (P.fromFold $ FL.take n FL.toList) (S.fromList ls) of
Right parsed_list -> checkListEqual parsed_list (Prelude.take n ls)
Left _ -> property False
takeEQPass :: Property
takeEQPass =
@ -263,7 +274,6 @@ takeGE =
else property False
Left _ -> property (n > list_length)
nLessThanEqual0 ::
( Int
-> FL.Fold Identity Int [Int]
@ -286,21 +296,23 @@ takeProperties =
prop "takeGE n FL.toList xs = xs" $
nLessThanEqual0 P.takeGE (\_ -> id)
-- lookAheadPass :: Property
-- lookAheadPass =
-- forAll (chooseInt (min_value + 1, max_value)) $ \n ->
-- let
-- takeWithoutConsume = P.lookAhead $ P.take n FL.toList
-- parseTwice = do
-- parsed_list_1 <- takeWithoutConsume
-- parsed_list_2 <- takeWithoutConsume
-- return (parsed_list_1, parsed_list_2)
-- in
-- forAll (chooseInt (n, max_value)) $ \list_length ->
-- forAll (vectorOf list_length (chooseInt (min_value, max_value))) $ \ls ->
-- case S.parse parseTwice (S.fromList ls) of
-- Right (ls_1, ls_2) -> checkListEqual ls_1 ls_2 .&&. checkListEqual ls_1 (Prelude.take n ls)
-- Left _ -> property $ False
-- XXX lookAhead can't deal with EOF which in this case means when
-- n==list_length, this test will fail. So excluding that case for now.
lookAheadPass :: Property
lookAheadPass =
forAll (chooseInt (min_value, max_value)) $ \n ->
let
takeWithoutConsume = P.lookAhead $ P.fromFold $ FL.take n FL.toList
parseTwice = do
parsed_list_1 <- takeWithoutConsume
parsed_list_2 <- takeWithoutConsume
return (parsed_list_1, parsed_list_2)
in
forAll (chooseInt (n+1, max_value)) $ \list_length ->
forAll (vectorOf list_length (chooseInt (min_value, max_value))) $ \ls ->
case runIdentity $ S.parse parseTwice (S.fromList ls) of
Right (ls_1, ls_2) -> checkListEqual ls_1 ls_2 .&&. checkListEqual ls_1 (Prelude.take n ls)
Left _ -> property $ False
-- lookAheadFail :: Property
-- lookAheadFail =
@ -318,22 +330,22 @@ takeProperties =
-- Right _ -> False
-- Left _ -> True
-- lookAhead :: Property
-- lookAhead =
-- forAll (chooseInt (min_value, max_value)) $ \n ->
-- let
-- takeWithoutConsume = P.lookAhead $ P.take n FL.toList
-- parseTwice = do
-- parsed_list_1 <- takeWithoutConsume
-- parsed_list_2 <- takeWithoutConsume
-- return (parsed_list_1, parsed_list_2)
-- in
-- forAll (listOf (chooseInt (min_value, max_value))) $ \ls ->
-- case S.parse parseTwice (S.fromList ls) of
-- Right (ls_1, ls_2) -> checkListEqual ls_1 ls_2 .&&. checkListEqual ls_1 (Prelude.take n ls)
-- Left _ -> property ((list_length < n) || (list_length == n && n == 0))
-- where
-- list_length = Prelude.length ls
lookAhead :: Property
lookAhead =
forAll (chooseInt (min_value, max_value)) $ \n ->
let
takeWithoutConsume = P.lookAhead $ P.fromFold $ FL.take n FL.toList
parseTwice = do
parsed_list_1 <- takeWithoutConsume
parsed_list_2 <- takeWithoutConsume
return (parsed_list_1, parsed_list_2)
in
forAll (listOf (chooseInt (min_value, max_value))) $ \ls ->
case runIdentity $ S.parse parseTwice (S.fromList ls) of
Right (ls_1, ls_2) -> checkListEqual ls_1 ls_2 .&&. checkListEqual ls_1 (Prelude.take n ls)
Left _ -> property ((list_length < n) || (list_length == n && n == 0))
where
list_length = Prelude.length ls
takeEndBy_ :: Property
takeEndBy_ =
@ -347,6 +359,16 @@ takeEndBy_ =
prsr = P.many (P.satisfy (const True)) FL.toList
tkwhl ls = Prelude.takeWhile (not . predicate) ls
takeEndByOrMax_ :: Property
takeEndByOrMax_ =
forAll (chooseInt (min_value, max_value)) $ \n ->
forAll (listOf (chooseInt (0, 1))) $ \ls ->
case runIdentity $ S.parse (P.fromFold $ FL.takeEndBy_ predicate (FL.take n FL.toList)) (S.fromList ls) of
Right parsed_list -> checkListEqual parsed_list (Prelude.take n (Prelude.takeWhile (not . predicate) ls))
Left _ -> property False
where
predicate = (== 1)
takeStartBy :: Property
takeStartBy =
forAll (listOf (chooseInt (min_value, max_value))) $ \ls ->
@ -464,6 +486,25 @@ groupBy =
| null lst = []
| otherwise = head $ List.groupBy cmp lst
groupByRolling :: Property
groupByRolling =
forAll (listOf (chooseInt (0, 1)))
$ \ls ->
case runIdentity $ S.parse parser (S.fromList ls) of
Right parsed -> checkListEqual parsed (groupByLF Nothing ls)
Left _ -> property False
where
cmp = (==)
parser = P.groupBy cmp FL.toList
groupByLF _ [] = []
groupByLF Nothing (x:xs) = x : groupByLF (Just x) xs
groupByLF (Just y) (x:xs) =
if cmp y x
then x : groupByLF (Just x) xs
else []
wordBy :: Property
wordBy =
forAll (listOf (elements [' ', 's']))
@ -530,42 +571,41 @@ parseManyWordQuotedBy =
, ["The qui[ck] brown", "fox"])
]
splitWith :: Property
splitWith =
forAll (listOf (chooseInt (0, 1))) $ \ls ->
case runIdentity $ S.parse (P.splitWith (,) (P.satisfy (== 0)) (P.satisfy (== 1))) (S.fromList ls) of
Right (result_first, result_second) -> case ls of
0 : 1 : _ -> (result_first == 0) && (result_second == 1)
_ -> False
Left _ -> case ls of
0 : 1 : _ -> False
_ -> True
-- splitWithPass :: Property
-- splitWithPass =
-- forAll (listOf (chooseInt (0, 1))) $ \ls ->
-- case S.parse (P.splitWith (,) (P.satisfy (== 0)) (P.satisfy (== 1))) (S.fromList ls) of
-- Right (result_first, result_second) -> case ls of
-- 0 : 1 : _ -> (result_first == 0) && (result_second == 1)
-- _ -> False
-- Left _ -> case ls of
-- 0 : 1 : _ -> False
-- _ -> True
splitWithFailLeft :: Property
splitWithFailLeft =
property (case runIdentity $ S.parse (P.splitWith (,) (P.die "die") (P.fromPure (1 :: Int))) (S.fromList [1 :: Int]) of
Right _ -> False
Left _ -> True)
-- splitWithFailLeft :: Property
-- splitWithFailLeft =
-- property (case S.parse (P.splitWith (,) (P.die "die") (P.fromPure (1 :: Int))) (S.fromList [1 :: Int]) of
-- Right _ -> False
-- Left _ -> True)
splitWithFailRight :: Property
splitWithFailRight =
property (case runIdentity $ S.parse (P.splitWith (,) (P.fromPure (1 :: Int)) (P.die "die")) (S.fromList [1 :: Int]) of
Right _ -> False
Left _ -> True)
-- splitWithFailRight :: Property
-- splitWithFailRight =
-- property (case S.parse (P.splitWith (,) (P.fromPure (1 :: Int)) (P.die "die")) (S.fromList [1 :: Int]) of
-- Right _ -> False
-- Left _ -> True)
-- splitWithFailBoth :: Property
-- splitWithFailBoth =
-- property (case S.parse (P.splitWith (,) (P.die "die") (P.die "die")) (S.fromList [1 :: Int]) of
-- Right _ -> False
-- Left _ -> True)
splitWithFailBoth :: Property
splitWithFailBoth =
property (case runIdentity $ S.parse (P.splitWith (,) (P.die "die") (P.die "die")) (S.fromList [1 :: Int]) of
Right _ -> False
Left _ -> True)
-- teeWithPass :: Property
-- teeWithPass =
-- forAll (chooseInt (0, 10000)) $ \n ->
-- forAll (chooseInt (min_value, max_value)) $ \n ->
-- forAll (listOf (chooseInt (0, 1))) $ \ls ->
-- let
-- prsr = P.take n FL.toList
-- prsr = P.fromFold $ FL.take n FL.toList
-- in
-- case S.parse (P.teeWith (,) prsr prsr) (S.fromList ls) of
-- Right (ls_1, ls_2) -> checkListEqual (Prelude.take n ls) ls_1 .&&. checkListEqual ls_1 ls_2
@ -610,50 +650,86 @@ deintercalate =
-- shortestPass =
-- forAll (listOf (chooseInt(min_value, max_value))) $ \ls ->
-- let
-- prsr_1 = P.takeWhile (<= (mid_value `Prelude.div` 2)) FL.toList
-- half_mid_value = mid_value `Prelude.div` 2
-- prsr_1 = P.takeWhile (<= half_mid_value) FL.toList
-- prsr_2 = P.takeWhile (<= mid_value) FL.toList
-- prsr_shortest = P.shortest prsr_1 prsr_2
-- in
-- case S.parse prsr_shortest (S.fromList ls) of
-- Right short_list -> checkListEqual short_list (Prelude.takeWhile (<= 2500) ls)
-- Right short_list -> checkListEqual short_list (Prelude.takeWhile (<= half_mid_value) ls)
-- Left _ -> property False
-- shortestFailLeft :: Property
-- shortestFailLeft =
-- shortestPassLeft :: Property
-- shortestPassLeft =
-- property (case S.parse (P.shortest (P.die "die") (P.fromPure (1 :: Int))) (S.fromList [1 :: Int]) of
-- Right r -> r == 1
-- Left _ -> False)
-- shortestFailRight :: Property
-- shortestFailRight =
--
-- shortestPassRight :: Property
-- shortestPassRight =
-- property (case S.parse (P.shortest (P.fromPure (1 :: Int)) (P.die "die")) (S.fromList [1 :: Int]) of
-- Right r -> r == 1
-- Left _ -> False)
-- shortestFailBoth :: Property
-- shortestFailBoth =
-- property (case S.parse (P.shortest (P.die "die") (P.die "die")) (S.fromList [1 :: Int]) of
-- property
-- (case S.parse
-- (P.shortest (P.die "die") (P.die "die"))
-- (S.fromList [1 :: Int]) of
-- Right _ -> False
-- Left _ -> True)
--
-- longestPass :: Property
-- longestPass =
-- forAll (listOf (chooseInt(min_value, max_value))) $ \ls ->
-- let
-- half_mid_value = mid_value `Prelude.div` 2
-- prsr_1 = P.takeWhile (<= half_mid_value) FL.toList
-- prsr_2 = P.takeWhile (<= mid_value) FL.toList
-- prsr_longest = P.longest prsr_1 prsr_2
-- in
-- case S.parse prsr_longest (S.fromList ls) of
-- Right long_list -> long_list == Prelude.takeWhile (<= mid_value) ls
-- Left _ -> False
--
-- longestPassLeft :: Property
-- longestPassLeft =
-- property (case S.parse (P.shortest (P.die "die") (P.fromPure (1 :: Int))) (S.fromList [1 :: Int]) of
-- Right r -> r == 1
-- Left _ -> False)
--
-- longestPassRight :: Property
-- longestPassRight =
-- property (case S.parse (P.shortest (P.fromPure (1 :: Int)) (P.die "die")) (S.fromList [1 :: Int]) of
-- Right r -> r == 1
-- Left _ -> False)
--
-- longestFailBoth :: Property
-- longestFailBoth =
-- property
-- (case S.parse (P.shortest (P.die "die") (P.die "die")) (S.fromList [1 :: Int]) of
-- Right _ -> False
-- Left _ -> True)
many :: Property
many =
forAll (listOf (chooseInt (0, 1))) $ \ls ->
let fldstp conL currL = return $ FL.Partial $ conL ++ currL
let fldstp conL currL = return $ FL.Partial (conL ++ currL)
concatFold = FL.Fold fldstp (return (FL.Partial [])) return
prsr =
flip P.many concatFold $ P.fromFold $ FL.takeEndBy_ (== 1) FL.toList
in
case runIdentity $ S.parse prsr (S.fromList ls) of
Right res_list -> checkListEqual res_list
$ Prelude.filter (== 0) ls
flip P.many concatFold
$ P.fromFold $ FL.takeEndBy_ (== 1) FL.toList
in case runIdentity $ S.parse prsr (S.fromList ls) of
Right res_list ->
checkListEqual res_list (Prelude.filter (== 0) ls)
Left _ -> property False
-- many_empty :: Property
-- many_empty =
-- property (case S.parse (P.many FL.toList (P.die "die")) (S.fromList [1 :: Int]) of
-- Right res_list -> checkListEqual res_list ([] :: [Int])
-- Left _ -> property False)
many_empty :: Property
many_empty =
property (case runIdentity $ S.parse (flip P.many FL.toList (P.die "die")) (S.fromList [1 :: Int]) of
Right res_list -> checkListEqual res_list ([] :: [Int])
Left _ -> property False)
some :: Property
some =
@ -663,17 +739,17 @@ some =
fldstp conL currL = return $ FL.Partial $ conL ++ currL
concatFold = FL.Fold fldstp (return (FL.Partial [])) return
prsr =
flip P.some concatFold $ P.fromFold $ FL.takeEndBy_ (== 1) FL.toList
in
case runIdentity $ S.parse prsr (S.fromList ls) of
flip P.some concatFold
$ P.fromFold $ FL.takeEndBy_ (== 1) FL.toList
in case runIdentity $ S.parse prsr (S.fromList ls) of
Right res_list -> res_list == Prelude.filter (== 0) ls
Left _ -> False
-- someFail :: Property
-- someFail =
-- property (case S.parse (P.some FL.toList (P.die "die")) (S.fromList [1 :: Int]) of
-- Right _ -> False
-- Left _ -> True)
someFail :: Property
someFail =
property (case runIdentity $ S.parse (P.some (P.die "die") FL.toList) (S.fromList [1 :: Int]) of
Right _ -> False
Left _ -> True)
-------------------------------------------------------------------------------
-- Instances
@ -687,12 +763,10 @@ applicative =
(,)
<$> P.fromFold (FL.take (length list1) FL.toList)
<*> P.fromFold (FL.take (length list2) FL.toList)
in monadicIO $ do
s <- S.parse parser (S.fromList $ list1 ++ list2)
return $
case s of
Right (olist1, olist2) -> olist1 == list1 && olist2 == list2
Left _ -> False
in
case runIdentity $ S.parse parser (S.fromList $ list1 ++ list2) of
Right (olist1, olist2) -> olist1 == list1 && olist2 == list2
Left _ -> False
sequence :: Property
sequence =
@ -708,6 +782,28 @@ sequence =
Right ls -> ls == ins
Left _ -> False
altEOF1 :: Property
altEOF1 =
monadicIO $ do
s1 <- S.parse
(P.satisfy (> 0) <|> return 66)
(S.fromList ([]::[Int]))
return $
case s1 of
Right x -> x == 66
Left _ -> False
altEOF2 :: Property
altEOF2 =
monadicIO $ do
s1 <- S.parse
((P.takeEQ 2 FL.toList) <|> (P.takeEQ 1 FL.toList))
(S.fromList ([51]::[Int]))
return $
case s1 of
Right x -> x == [51]
Left _ -> False
monad :: Property
monad =
forAll (listOf (chooseAny :: Gen Int)) $ \ list1 ->
@ -740,6 +836,49 @@ parseMany =
$ S.parseMany p (S.fromList $ concat ins)
listEquals (==) outs ins
-- basic sanity test for parsing from arrays
parseUnfold :: Property
parseUnfold = do
let len = 200
-- ls = input list (stream)
-- clen = chunk size
-- tlen = parser take size
forAll
((,,)
<$> vectorOf len (chooseAny :: Gen Int)
<*> chooseInt (1, len)
<*> chooseInt (1, len)) $ \(ls, clen, tlen) ->
monadicIO $ do
arrays <- S.toList $ S.chunksOf clen (S.fromList ls)
let src = Source.source (Just (Producer.OuterLoop arrays))
let parser = P.fromFold (FL.take tlen FL.toList)
let readSrc =
Source.producer
$ Producer.concat Producer.fromList A.producer
let streamParser =
Producer.simplify (Source.parseManyD parser readSrc)
xs <- run
$ S.toList
$ S.unfoldMany Unfold.fromList
$ S.catRights
$ S.unfold streamParser src
listEquals (==) xs ls
parserSequence :: Property
parserSequence =
forAll (vectorOf 11 (listOf (chooseAny :: Gen Int))) $ \ins ->
monadicIO $ do
let parsers = S.fromList
$ fmap (\xs -> P.fromFold $ FL.take (length xs) FL.sum) ins
let sequencedParser = P.sequence parsers FL.sum
outs <-
S.parse sequencedParser $ S.concatMap S.fromList (S.fromList ins)
return $
case outs of
Right x -> x == sum (map sum ins)
Left _ -> False
-------------------------------------------------------------------------------
-- Test for a particular case hit during fs events testing
-------------------------------------------------------------------------------
@ -1145,11 +1284,15 @@ main =
describe "Instances" $ do
prop "applicative" applicative
prop "Alternative: end of input 1" altEOF1
prop "Alternative: end of input 2" altEOF2
prop "monad" monad
prop "sequence" sequence
describe "Stream parsing" $ do
prop "parseMany" parseMany
prop "parseMany2Events" parseMany2Events
prop "parseUnfold" parseUnfold
prop "parserSequence" parserSequence
describe "test for accumulator" $ do
prop "P.fromFold FL.sum = FL.sum" fromFold
@ -1174,16 +1317,15 @@ main =
takeBetweenPass
prop ("P.takeBetween = Prelude.take when len >= m and len <= n and fail"
++ "otherwise fail") Main.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
prop "P.takeGE n ls = ls when len >= n" takeGEPass
prop "P.takeGE n ls = ls when len >= n and fail otherwise" Main.takeGE
-- prop "lookAhead . take n >> lookAhead . take n = lookAhead . take n" lookAheadPass
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.takeEndBy_ test" Main.takeEndBy_
prop "lookAhead . take n >> lookAhead . take n = lookAhead . take n, else fail" lookAhead
prop ("P.takeStartBy pred = head : Prelude.takeWhile (not . pred)"
++ " tail") takeStartBy
prop "P.takeWhile = Prelude.takeWhile" Main.takeWhile
@ -1192,13 +1334,14 @@ main =
prop "takeWhileP prd P.take = takeWhileMaxLen prd" takeWhileP
prop ("P.takeP = Prelude.take") takeP
prop "P.groupBy = Prelude.head . Prelude.groupBy" groupBy
prop "groupByRolling" groupByRolling
prop "many (P.wordBy ' ') = words'" wordBy
parseManyWordQuotedBy
-- prop "choice" choice
-- prop "" splitWithPass
-- prop "" splitWithFailLeft
-- prop "" splitWithFailRight
-- prop "" splitWithFailBoth
prop "parse 0, then 1, else fail" splitWith
prop "fail due to die as left parser" splitWithFailLeft
prop "fail due to die as right parser" splitWithFailRight
prop "fail due to die as both parsers" splitWithFailBoth
-- prop "" teeWithPass
-- prop "" teeWithFailLeft
-- prop "" teeWithFailRight
@ -1210,13 +1353,14 @@ main =
-- prop "" shortestFailBoth
prop ("P.many concatFold $ P.takeEndBy_ (== 1) FL.toList ="
++ "Prelude.filter (== 0)") many
-- prop "[] due to parser being die" many_empty
prop "[] due to parser being die" many_empty
prop ("P.some concatFold $ P.takeEndBy_ (== 1) FL.toList ="
++ "Prelude.filter (== 0)") some
-- prop "fail due to parser being die" someFail
prop "fail due to parser being die" someFail
prop "P.many == S.parseMany" manyEqParseMany
prop "takeEndBy_" takeEndBy_
prop "takeEndByOrMax_" takeEndByOrMax_
prop "takeEndBy1" takeEndBy1
prop "takeEndBy2" takeEndBy2
prop "takeEndByEsc" takeEndByEsc

View File

@ -757,7 +757,7 @@ parseMany2Events =
-------------------------------------------------------------------------------
moduleName :: String
moduleName = "Data.Parser.ParserD"
moduleName = "Data.ParserK"
main :: IO ()
main =

View File

@ -293,10 +293,10 @@ test-suite Data.Parser
if flag(limit-build-mem)
ghc-options: +RTS -M4000M -RTS
test-suite Data.Parser.ParserD
test-suite Data.ParserK
import: test-options
type: exitcode-stdio-1.0
main-is: Streamly/Test/Data/Parser/ParserD.hs
main-is: Streamly/Test/Data/ParserK.hs
if flag(limit-build-mem)
ghc-options: +RTS -M1500M -RTS