Modularize test cases (#1707)

* Modularize test cases

* Make it build with test-core flag

And several other changes.

Co-authored-by: Harendra Kumar <harendra@composewell.com>
This commit is contained in:
Ranjeet Ranjan 2022-08-20 00:45:57 +05:30 committed by GitHub
parent ca76876369
commit ec760805c9
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
18 changed files with 334 additions and 197 deletions

View File

@ -3,7 +3,6 @@ core/src/Streamly/Internal/Data/Pipe/Type.hs
src/Streamly/Internal/Data/SmallArray/Type.hs
src/Streamly/Internal/Unicode/Stream.hs
test/Streamly/Test/Data/Array.hs
test/Streamly/Test/Data/Array/Foreign.hs
test/Streamly/Test/Data/Parser.hs
test/Streamly/Test/Data/Parser/ParserD.hs
test/Streamly/Test/Data/SmallArray.hs

View File

@ -28,7 +28,6 @@ import System.IO (Handle, hClose)
import System.Random (randomRIO)
import qualified Prelude
import qualified Streamly.Data.Unfold as UF
import qualified Streamly.FileSystem.Handle as FH
import qualified Streamly.Internal.Data.Fold as FL
import qualified Streamly.Internal.Data.Unfold as UF

View File

@ -84,7 +84,6 @@ import Streamly.Internal.Data.Stream.Type
-- >>> import System.IO.Unsafe (unsafePerformIO)
-- >>> import Streamly.Internal.Data.Stream as Stream
-- >>> import qualified Streamly.Data.Array.Unboxed as Array
-- >>> import qualified Streamly.Data.Unfold as Unfold
-- >>> import qualified Streamly.Internal.Data.Fold as Fold
-- >>> import qualified Streamly.Internal.Data.Parser as Parser
-- >>> import qualified Streamly.Internal.Data.Unfold as Unfold

View File

@ -180,8 +180,10 @@ module Streamly.Internal.Data.Unfold
-- ** From Memory
, fromPtr
-- ** From Stream
, fromStreamK
, fromStreamD
, fromStream
-- * Combinators
-- ** Mapping on Input
@ -281,6 +283,7 @@ import qualified Data.Tuple as Tuple
import qualified Streamly.Internal.Data.Fold.Type as FL
import qualified Streamly.Internal.Data.Stream.StreamD.Type as D
import qualified Streamly.Internal.Data.Stream.StreamK.Type as K
import qualified Streamly.Internal.Data.Stream.Type as Stream
import Streamly.Internal.Data.Unfold.Enumeration
import Streamly.Internal.Data.Unfold.Type
@ -585,6 +588,10 @@ fromStreamK = Unfold step pure
Just (x, xs) -> Yield x xs
Nothing -> Stop) <$> K.uncons stream
{-# INLINE fromStream #-}
fromStream :: Applicative m => Unfold m (Stream.Stream m a) a
fromStream = lmap Stream.toStreamK fromStreamK
-------------------------------------------------------------------------------
-- Unfolds
-------------------------------------------------------------------------------

View File

@ -74,6 +74,8 @@ cradle:
component: "test:Data.Array"
- path: "./test/Streamly/Test/Data/Array/Unboxed.hs"
component: "test:Data.Array.Unboxed"
- path: "./test/Streamly/Test/Data/Array/Unboxed/Mut.hs"
component: "test:Data.Array.Unboxed.Mut"
- path: "./test/Streamly/Test/Data/Array/Stream/Foreign.hs"
component: "test:Data.Array.Stream.Foreign"
- path: "./test/Streamly/Test/Data/Fold.hs"

View File

@ -213,7 +213,7 @@ import Prelude hiding
, zipWith
)
import Streamly.Internal.Data.Stream.IsStream.Type (IsStream)
import Streamly.Internal.Data.Unfold
import Streamly.Internal.Data.Unfold hiding (fromStream)
import qualified Streamly.Internal.Data.Stream.IsStream.Type as IsStream
import qualified Streamly.Internal.Data.Unfold as Unfold

View File

@ -92,6 +92,7 @@ extra-source-files:
test/Streamly/Test/Data/Array/CommonImports.hs
test/Streamly/Test/Data/Array/Common.hs
test/Streamly/Test/Data/Array/Unboxed.hs
test/Streamly/Test/Data/Array/Unboxed/Mut.hs
test/Streamly/Test/Data/Ring/Unboxed.hs
test/Streamly/Test/Data/Array/Stream/Foreign.hs
test/Streamly/Test/Data/Parser/ParserD.hs

View File

@ -11,6 +11,8 @@ module Streamly.Test.Data.Array (main) where
#include "Streamly/Test/Data/Array/CommonImports.hs"
import qualified Streamly.Internal.Data.Array as A
import qualified Streamly.Internal.Data.Fold as Fold
type Array = A.Array
moduleName :: String
@ -30,7 +32,7 @@ testFromList =
forAll (vectorOf len (arbitrary :: Gen Int)) $ \list ->
monadicIO $ do
let arr = A.fromList list
xs <- run $ S.toList $ (S.unfold A.read) arr
xs <- run $ S.fold Fold.toList $ S.unfold A.read arr
assert (xs == list)
testLengthFromStream :: Property

View File

@ -4,7 +4,7 @@ import Data.Word (Word8)
import Streamly.Test.Common (listEquals, chooseInt)
import Test.Hspec (hspec, describe, shouldBe)
import Test.Hspec.QuickCheck
import Test.QuickCheck (forAll, Property, vectorOf, Gen)
import Test.QuickCheck (forAll, Property, vectorOf, Gen, Arbitrary (arbitrary))
import Test.QuickCheck.Monadic (monadicIO, run)
import qualified Streamly.Internal.Data.Array.Unboxed as Array
@ -71,6 +71,18 @@ splitOnSuffix sep inp out = do
moduleName :: String
moduleName = "Data.Array.Stream.Foreign"
-- Instead of hard coding 10000 here we can have maxStreamLength for operations
-- that use stream of arrays.
concatArrayW8 :: Property
concatArrayW8 =
forAll (vectorOf 10000 (arbitrary :: Gen Word8))
$ \w8List -> do
let w8ArrList = Array.fromList . (: []) <$> w8List
f2 <- Stream.toList $ ArrayStream.concat $ Stream.fromList w8ArrList
w8List `shouldBe` f2
main :: IO ()
main =
hspec $
@ -79,6 +91,7 @@ main =
describe moduleName $ do
describe "Stream parsing" $ do
prop "parseBreak" parseBreak
prop "concatArrayW8" concatArrayW8
describe "splifOnSuffix" $ do
Hspec.it "splitOnSuffix 0 [1, 2, 0, 4, 0, 5, 6]"
$ splitOnSuffix 0 [1, 2, 0, 4, 0, 5, 6]

View File

@ -18,11 +18,10 @@ import Streamly.Internal.Data.Unboxed (Unboxed)
import Test.QuickCheck (chooseInt, listOf)
import GHC.Ptr (plusPtr)
import qualified Streamly.Internal.Data.Fold as Fold
import qualified Streamly.Internal.Data.Array.Unboxed as A
import qualified Streamly.Internal.Data.Array.Unboxed.Type as A
import qualified Streamly.Internal.Data.Array.Unboxed.Mut.Type as MA
import qualified Streamly.Internal.Data.Array.Stream.Foreign as AS
import qualified Streamly.Internal.Data.Fold as Fold
type Array = A.Array
@ -43,13 +42,12 @@ testFromList =
forAll (vectorOf len (arbitrary :: Gen Int)) $ \list ->
monadicIO $ do
let arr = A.fromList list
xs <- run $ S.toList $ S.unfold A.read arr
xs <- run $ S.fold Fold.toList $ S.unfold A.read arr
assert (xs == list)
testLengthFromStream :: Property
testLengthFromStream = genericTestFrom (const A.fromStream)
unsafeWriteIndex :: [Int] -> Int -> Int -> IO Bool
unsafeWriteIndex xs i x = do
arr <- MA.fromList xs
@ -121,38 +119,12 @@ testStripNull = do
x <- MA.toList dt'
return $ x == ""
-- Instead of hard coding 10000 here we can have maxStreamLength for operations
-- that use stream of arrays.
concatArrayW8 :: Property
concatArrayW8 =
forAll (vectorOf 10000 (arbitrary :: Gen Word8))
$ \w8List -> do
let w8ArrList = A.fromList . (: []) <$> w8List
f2 <- S.toList $ AS.concat $ S.fromList w8ArrList
w8List `shouldBe` f2
unsafeSlice :: Int -> Int -> [Int] -> Bool
unsafeSlice i n list =
let lst = take n $ drop i list
arr = A.toList $ A.getSliceUnsafe i n $ A.fromList list
in arr == lst
{-
testAppend :: Property
testAppend =
forAll (listOf (chooseInt (-50, 100))) $ \ls0 ->
monadicIO $ action ls0
where
action ls = do
x <- S.fold
(MA.append (MA.newArray 0))
(S.fromList (ls::[Int]))
lst <- MA.toList x
assert (ls == lst)
-}
testBubbleWith :: Bool -> Property
testBubbleWith asc =
forAll (listOf (chooseInt (-50, 100))) $ \ls0 ->
@ -257,7 +229,6 @@ main =
prop "fromList" testFromList
prop "foldMany with writeNUnsafe concats to original"
(foldManyWith (\n -> Fold.take n (A.writeNUnsafe n)))
prop "AS.concat . (A.fromList . (:[]) <$>) === id" concatArrayW8
describe "unsafeSlice" $ do
it "partial" $ unsafeSlice 2 4 [1..10]
it "none" $ unsafeSlice 10 0 [1..10]

View File

@ -0,0 +1,42 @@
module Streamly.Test.Data.Array.Unboxed.Mut (main) where
import Test.QuickCheck (listOf)
import Streamly.Test.Common (chooseInt)
import Test.Hspec (hspec, describe)
import Test.Hspec.QuickCheck
import Test.QuickCheck (forAll, Property)
import Test.QuickCheck.Monadic (monadicIO, assert)
import qualified Streamly.Internal.Data.Array.Unboxed.Mut as MArray
import qualified Streamly.Internal.Data.Stream as Stream
import qualified Test.Hspec as Hspec
maxTestCount :: Int
maxTestCount = 100
moduleName :: String
moduleName = "Data.Array.Unboxed.Mut"
testAppend :: Property
testAppend =
forAll (listOf (chooseInt (-50, 100))) $ \ls0 ->
monadicIO $ action ls0
where
action ls = do
x <- Stream.fold
(MArray.append (MArray.newArray 0))
(Stream.fromList (ls::[Int]))
lst <- MArray.toList x
assert (ls == lst)
main :: IO ()
main =
hspec $
Hspec.parallel $
modifyMaxSuccess (const maxTestCount) $ do
describe moduleName $ do
describe "Stream Append" $ do
prop "testAppend" testAppend

View File

@ -23,11 +23,9 @@ import Test.QuickCheck.Monadic (monadicIO, assert, run)
import qualified Data.Map
import qualified Prelude
import qualified Streamly.Internal.Data.Fold as F
import qualified Streamly.Prelude as S
import qualified Streamly.Internal.Data.Array.Unboxed.Mut.Type as MA
import qualified Streamly.Internal.Data.Stream.IsStream as Stream
import qualified Streamly.Data.Fold as FL
import qualified Streamly.Internal.Data.Array.Unboxed.Mut as MArray
import qualified Streamly.Internal.Data.Fold as Fold
import qualified Streamly.Internal.Data.Stream as Stream
import Prelude hiding
(maximum, minimum, elem, notElem, null, product, sum, head, last, take)
@ -62,26 +60,31 @@ rollingHashFirstN =
forAll (choose (0, len)) $ \n ->
forAll (vectorOf len (arbitrary :: Gen Int)) $ \vec ->
monadicIO $ do
a <- run $ S.fold F.rollingHash $ S.take n $ S.fromList vec
b <- run $ S.fold (F.rollingHashFirstN n) $ S.fromList vec
a <- run
$ Stream.fold Fold.rollingHash
$ Stream.take n
$ Stream.fromList vec
b <- run
$ Stream.fold (Fold.rollingHashFirstN n)
$ Stream.fromList vec
assert $ a == b
head :: [Int] -> Expectation
head ls = S.fold FL.head (S.fromList ls) `shouldReturn` headl ls
head ls = Stream.fold Fold.head (Stream.fromList ls) `shouldReturn` headl ls
headl :: [a] -> Maybe a
headl [] = Nothing
headl (x:_) = Just x
length :: [Int] -> Expectation
length ls = S.fold FL.length (S.fromList ls) `shouldReturn` Prelude.length ls
length ls = Stream.fold Fold.length (Stream.fromList ls) `shouldReturn` Prelude.length ls
sum :: [Int] -> Expectation
sum ls = S.fold FL.sum (S.fromList ls) `shouldReturn` Prelude.sum ls
sum ls = Stream.fold Fold.sum (Stream.fromList ls) `shouldReturn` Prelude.sum ls
product :: [Int] -> Expectation
product ls =
S.fold FL.product (S.fromList ls) `shouldReturn` Prelude.product ls
Stream.fold Fold.product (Stream.fromList ls) `shouldReturn` Prelude.product ls
lesser :: (a -> a -> Ordering) -> a -> a -> a
lesser f x y = if f x y == LT then x else y
@ -97,29 +100,29 @@ foldMaybe f acc ls =
maximumBy :: (Ord a, Show a) => a -> (a -> a -> Ordering) -> [a] -> Expectation
maximumBy genmin f ls =
S.fold (FL.maximumBy f) (S.fromList ls)
Stream.fold (Fold.maximumBy f) (Stream.fromList ls)
`shouldReturn` foldMaybe (greater f) genmin ls
maximum :: (Show a, Ord a) => a -> [a] -> Expectation
maximum genmin ls =
S.fold FL.maximum (S.fromList ls)
Stream.fold Fold.maximum (Stream.fromList ls)
`shouldReturn` foldMaybe (greater compare) genmin ls
minimumBy :: (Ord a, Show a) => a -> (a -> a -> Ordering) -> [a] -> Expectation
minimumBy genmax f ls =
S.fold (FL.minimumBy f) (S.fromList ls)
Stream.fold (Fold.minimumBy f) (Stream.fromList ls)
`shouldReturn` foldMaybe (lesser f) genmax ls
minimum :: (Show a, Ord a) => a -> [a] -> Expectation
minimum genmax ls =
S.fold FL.minimum (S.fromList ls)
Stream.fold Fold.minimum (Stream.fromList ls)
`shouldReturn` foldMaybe (lesser compare) genmax ls
toList :: [Int] -> Expectation
toList ls = S.fold FL.toList (S.fromList ls) `shouldReturn` ls
toList ls = Stream.fold Fold.toList (Stream.fromList ls) `shouldReturn` ls
toListRev :: [Int] -> Expectation
toListRev ls = S.fold FL.toListRev (S.fromList ls) `shouldReturn` reverse ls
toListRev ls = Stream.fold Fold.toListRev (Stream.fromList ls) `shouldReturn` reverse ls
safeLast :: [a] -> Maybe a
safeLast [] = Nothing
@ -127,7 +130,7 @@ safeLast (x:[]) = Just x
safeLast (_:xs) = safeLast xs
last :: [String] -> Expectation
last ls = S.fold FL.last (S.fromList ls) `shouldReturn` safeLast ls
last ls = Stream.fold Fold.last (Stream.fromList ls) `shouldReturn` safeLast ls
mapMaybe :: [Int] -> Expectation
mapMaybe ls =
@ -135,8 +138,8 @@ mapMaybe ls =
if even x
then Just x
else Nothing
f = FL.mapMaybe maybeEven FL.toList
in S.fold f (S.fromList ls) `shouldReturn` filter even ls
f = Fold.mapMaybe maybeEven Fold.toList
in Stream.fold f (Stream.fromList ls) `shouldReturn` filter even ls
nth :: Int -> [a] -> Maybe a
nth idx (x : xs)
@ -147,18 +150,18 @@ nth _ [] = Nothing
index :: Int -> [String] -> Expectation
index idx ls =
let x = S.fold (FL.index idx) (S.fromList ls)
let x = Stream.fold (Fold.index idx) (Stream.fromList ls)
in x `shouldReturn` nth idx ls
find :: (Show a, Eq a) => (a -> Bool) -> [a] -> Expectation
find f ls = do
y <- S.fold (FL.findIndex f) (S.fromList ls)
y <- Stream.fold (Fold.findIndex f) (Stream.fromList ls)
case y of
Nothing ->
let fld = S.fold (FL.find f) (S.fromList ls)
let fld = Stream.fold (Fold.find f) (Stream.fromList ls)
in fld `shouldReturn` Nothing
Just idx ->
let fld = S.fold (FL.any f) (S.fromList $ Prelude.take idx ls)
let fld = Stream.fold (Fold.any f) (Stream.fromList $ Prelude.take idx ls)
in fld `shouldReturn` False
neg :: (a -> Bool) -> a -> Bool
@ -166,17 +169,17 @@ neg f x = not (f x)
findIndex :: (a -> Bool) -> [a] -> Expectation
findIndex f ls = do
y <- S.fold (FL.findIndex f) (S.fromList ls)
y <- Stream.fold (Fold.findIndex f) (Stream.fromList ls)
case y of
Nothing ->
let fld = S.fold (FL.all $ neg f) (S.fromList ls)
let fld = Stream.fold (Fold.all $ neg f) (Stream.fromList ls)
in fld `shouldReturn` True
Just idx ->
if idx == 0
then
S.fold (FL.all f) (S.fromList []) `shouldReturn` True
Stream.fold (Fold.all f) (Stream.fromList []) `shouldReturn` True
else
S.fold (FL.all f) (S.fromList $ Prelude.take idx ls)
Stream.fold (Fold.all f) (Stream.fromList $ Prelude.take idx ls)
`shouldReturn` False
predicate :: Int -> Bool
@ -184,19 +187,21 @@ predicate x = x * x < 100
elemIndex :: Int -> [Int] -> Expectation
elemIndex elm ls = do
y <- S.fold (FL.elemIndex elm) (S.fromList ls)
y <- Stream.fold (Fold.elemIndex elm) (Stream.fromList ls)
case y of
Nothing ->
let fld = S.fold (FL.any (== elm)) (S.fromList ls)
let fld = Stream.fold (Fold.any (== elm)) (Stream.fromList ls)
in fld `shouldReturn` False
Just idx ->
let fld =
S.fold (FL.any (== elm)) (S.fromList $ Prelude.take idx ls)
Stream.fold
(Fold.any (== elm))
(Stream.fromList $ Prelude.take idx ls)
in fld `shouldReturn` False
null :: [Int] -> Expectation
null ls =
S.fold FL.null (S.fromList ls)
Stream.fold Fold.null (Stream.fromList ls)
`shouldReturn`
case ls of
[] -> True
@ -204,42 +209,42 @@ null ls =
elem :: Int -> [Int] -> Expectation
elem elm ls = do
y <- S.fold (FL.elem elm) (S.fromList ls)
let fld = S.fold (FL.any (== elm)) (S.fromList ls)
y <- Stream.fold (Fold.elem elm) (Stream.fromList ls)
let fld = Stream.fold (Fold.any (== elm)) (Stream.fromList ls)
fld `shouldReturn` y
notElem :: Int -> [Int] -> Expectation
notElem elm ls = do
y <- S.fold (FL.notElem elm) (S.fromList ls)
let fld = S.fold (FL.any (== elm)) (S.fromList ls)
y <- Stream.fold (Fold.notElem elm) (Stream.fromList ls)
let fld = Stream.fold (Fold.any (== elm)) (Stream.fromList ls)
fld `shouldReturn` not y
all :: (a -> Bool) -> [a] -> Expectation
all f ls =
S.fold (FL.all f) (S.fromList ls) `shouldReturn` Prelude.all f ls
Stream.fold (Fold.all f) (Stream.fromList ls) `shouldReturn` Prelude.all f ls
any :: (a -> Bool) -> [a] -> Expectation
any f ls = S.fold (FL.any f) (S.fromList ls) `shouldReturn` Prelude.any f ls
any f ls = Stream.fold (Fold.any f) (Stream.fromList ls) `shouldReturn` Prelude.any f ls
and :: [Bool] -> Expectation
and ls = S.fold FL.and (S.fromList ls) `shouldReturn` Prelude.and ls
and ls = Stream.fold Fold.and (Stream.fromList ls) `shouldReturn` Prelude.and ls
or :: [Bool] -> Expectation
or ls = S.fold FL.or (S.fromList ls) `shouldReturn` Prelude.or ls
or ls = Stream.fold Fold.or (Stream.fromList ls) `shouldReturn` Prelude.or ls
take :: [Int] -> Property
take ls =
forAll (chooseInt (-1, Prelude.length ls + 2)) $ \n ->
S.fold (FL.take n FL.toList) (S.fromList ls)
Stream.fold (Fold.take n Fold.toList) (Stream.fromList ls)
`shouldReturn` Prelude.take n ls
takeEndBy_ :: Property
takeEndBy_ =
forAll (listOf (chooseInt (0, 1))) $ \ls ->
let p = (== 1)
f = FL.takeEndBy_ p FL.toList
f = Fold.takeEndBy_ p Fold.toList
ys = Prelude.takeWhile (not . p) ls
in case S.fold f (S.fromList ls) of
in case Stream.fold f (Stream.fromList ls) of
Right xs -> checkListEqual xs ys
Left _ -> property False
@ -248,9 +253,9 @@ takeEndByOrMax =
forAll (chooseInt (min_value, max_value)) $ \n ->
forAll (listOf (chooseInt (0, 1))) $ \ls ->
let p = (== 1)
f = FL.takeEndBy_ p (FL.take n FL.toList)
f = Fold.takeEndBy_ p (Fold.take n Fold.toList)
ys = Prelude.take n (Prelude.takeWhile (not . p) ls)
in case S.fold f (S.fromList ls) of
in case Stream.fold f (Stream.fromList ls) of
Right xs -> checkListEqual xs ys
Left _ -> property False
@ -258,10 +263,10 @@ chooseFloat :: (Float, Float) -> Gen Float
chooseFloat = choose
drain :: [Int] -> Expectation
drain ls = S.fold FL.drain (S.fromList ls) `shouldReturn` ()
drain ls = Stream.fold Fold.drain (Stream.fromList ls) `shouldReturn` ()
drainBy :: [Int] -> Expectation
drainBy ls = S.fold (FL.drainBy return) (S.fromList ls) `shouldReturn` ()
drainBy ls = Stream.fold (Fold.drainBy return) (Stream.fromList ls) `shouldReturn` ()
mean :: Property
mean =
@ -271,7 +276,7 @@ mean =
where
action ls = do
v1 <- run $ S.fold FL.mean (S.fromList ls)
v1 <- run $ Stream.fold Fold.mean (Stream.fromList ls)
let v2 = Prelude.sum ls / fromIntegral (Prelude.length ls)
assert (abs (v1 - v2) < 0.0001)
@ -283,7 +288,7 @@ stdDev =
where
action ls = do
v1 <- run $ S.fold FL.stdDev (S.fromList ls)
v1 <- run $ Stream.fold Fold.stdDev (Stream.fromList ls)
let avg = Prelude.sum ls / fromIntegral (Prelude.length ls)
se = Prelude.sum (fmap (\x -> (x - avg) * (x - avg)) ls)
sd = sqrt $ se / fromIntegral (Prelude.length ls)
@ -297,7 +302,7 @@ variance =
where
action ls = do
v1 <- run $ S.fold FL.variance (S.fromList ls)
v1 <- run $ Stream.fold Fold.variance (Stream.fromList ls)
let avg = Prelude.sum ls / fromIntegral (Prelude.length ls)
se = Prelude.sum (fmap (\x -> (x - avg) * (x - avg)) ls)
vr = se / fromIntegral (Prelude.length ls)
@ -311,7 +316,7 @@ mconcat =
where
action ls = do
v1 <- run $ S.fold FL.mconcat (S.map Sum $ S.fromList ls)
v1 <- run $ Stream.fold Fold.mconcat (fmap Sum $ Stream.fromList ls)
let v2 = Prelude.sum ls
assert (getSum v1 == v2)
@ -323,7 +328,7 @@ foldMap =
where
action ls = do
v1 <- run $ S.fold (FL.foldMap Sum) $ S.fromList ls
v1 <- run $ Stream.fold (Fold.foldMap Sum) $ Stream.fromList ls
let v2 = Prelude.sum ls
assert (getSum v1 == v2)
@ -335,7 +340,7 @@ foldMapM =
where
action ls = do
v1 <- run $ S.fold (FL.foldMapM (return . Sum)) $ S.fromList ls
v1 <- run $ Stream.fold (Fold.foldMapM (return . Sum)) $ Stream.fromList ls
let v2 = Prelude.sum ls
assert (getSum v1 == v2)
@ -352,7 +357,7 @@ lookup =
, (8, "fifth+third"), (9, "fifth+fourth")
, (10, "fifth+fifth")
]
v1 <- run $ S.fold (FL.lookup key) $ S.fromList ls
v1 <- run $ Stream.fold (Fold.lookup key) $ Stream.fromList ls
let v2 = Prelude.lookup key ls
assert (v1 == v2)
@ -365,9 +370,9 @@ rmapM =
action ls = do
let addLen x = return $ x + Prelude.length ls
fld = FL.rmapM addLen FL.sum
fld = Fold.rmapM addLen Fold.sum
v2 = foldl (+) (Prelude.length ls) ls
v1 <- run $ S.fold fld $ S.fromList ls
v1 <- run $ Stream.fold fld $ Stream.fromList ls
assert (v1 == v2)
teeWithLength :: Property
@ -378,7 +383,7 @@ teeWithLength =
where
action ls = do
v1 <- run $ S.fold (FL.tee FL.sum FL.length) $ S.fromList ls
v1 <- run $ Stream.fold (Fold.tee Fold.sum Fold.length) $ Stream.fromList ls
let v2 = Prelude.sum ls
v3 = Prelude.length ls
assert (v1 == (v2, v3))
@ -391,7 +396,10 @@ teeWithFstLength =
where
action ls = do
v1 <- run $ S.fold (F.teeWithFst (,) (FL.take 5 FL.sum) FL.length) $ S.fromList ls
v1 <-
run
$ Stream.fold (Fold.teeWithFst (,) (Fold.take 5 Fold.sum) Fold.length)
$ Stream.fromList ls
let v2 = Prelude.sum (Prelude.take 5 ls)
v3 = Prelude.length (Prelude.take 5 ls)
assert (v1 == (v2, v3))
@ -405,7 +413,10 @@ partitionByM =
action ls = do
let f = \x -> if odd x then return (Left x) else return (Right x)
v1 <- run $ S.fold (F.partitionByM f FL.length FL.length) $ S.fromList ls
v1 <-
run
$ Stream.fold (Fold.partitionByM f Fold.length Fold.length)
$ Stream.fromList ls
let v2 = foldl (\b a -> if odd a then b+1 else b) 0 ls
v3 = foldl (\b a -> if even a then b+1 else b) 0 ls
assert (v1 == (v2, v3))
@ -419,7 +430,11 @@ partitionByFstM =
action _ = do
let f = \x -> if odd x then return (Left x) else return (Right x)
v1 <- run $ S.fold (F.partitionByFstM f (FL.take 25 FL.length) FL.length) (S.fromList ([1..100]:: [Int]))
v1 <-
run
$ Stream.fold
(Fold.partitionByFstM f (Fold.take 25 Fold.length) Fold.length)
(Stream.fromList ([1 .. 100] :: [Int]))
let v2 = foldl (\b a -> if odd a then b+1 else b) 0 ([1..49] :: [Int])
v3 = foldl (\b a -> if even a then b+1 else b) 0 ([1..49] :: [Int])
assert (v1 == (v2, v3))
@ -433,7 +448,11 @@ partitionByMinM1 =
action _ = do
let f = \x -> if odd x then return (Left x) else return (Right x)
v1 <- run $ S.fold (F.partitionByMinM f FL.length (FL.take 25 FL.length)) (S.fromList ([1..100]:: [Int]))
v1 <-
run
$ Stream.fold
(Fold.partitionByMinM f Fold.length (Fold.take 25 Fold.length))
(Stream.fromList ([1 .. 100] :: [Int]))
let v2 = foldl (\b a -> if odd a then b+1 else b) 0 ([1..50] :: [Int])
v3 = foldl (\b a -> if even a then b+1 else b) 0 ([1..50] :: [Int])
assert (v1 == (v2, v3))
@ -447,7 +466,11 @@ partitionByMinM2 =
action _ = do
let f = \x -> if odd x then return (Left x) else return (Right x)
v1 <- run $ S.fold (F.partitionByMinM f (FL.take 25 FL.length) FL.length) (S.fromList ([1..100]:: [Int]))
v1 <-
run
$ Stream.fold
(Fold.partitionByMinM f (Fold.take 25 Fold.length) Fold.length)
(Stream.fromList ([1 .. 100] :: [Int]))
let v2 = foldl (\b a -> if odd a then b+1 else b) 0 ([1..49] :: [Int])
v3 = foldl (\b a -> if even a then b+1 else b) 0 ([1..49] :: [Int])
assert (v1 == (v2, v3))
@ -460,7 +483,10 @@ teeWithMinLength1 =
where
action ls = do
v1 <- run $ S.fold (F.teeWithMin (,) (FL.take 5 FL.sum) FL.length) $ S.fromList ls
v1 <-
run
$ Stream.fold (Fold.teeWithMin (,) (Fold.take 5 Fold.sum) Fold.length)
$ Stream.fromList ls
let v2 = Prelude.sum (Prelude.take 5 ls)
v3 = Prelude.length (Prelude.take 5 ls)
assert (v1 == (v2, v3))
@ -474,10 +500,14 @@ teeWithMinLength2 =
where
action ls = do
v1 <- run $ S.fold (F.teeWithMin (,) FL.sum (FL.take 5 FL.length)) $ S.fromList ls
v1 <-
run
$ Stream.fold (Fold.teeWithMin (,) Fold.sum (Fold.take 5 Fold.length))
$ Stream.fromList ls
let v2 = Prelude.sum (Prelude.take 5 ls)
v3 = Prelude.length (Prelude.take 5 ls)
assert (v1 == (v2, v3))
teeWithMax :: Property
teeWithMax =
forAll (listOf1 (chooseInt (intMin, intMax)))
@ -486,7 +516,7 @@ teeWithMax =
where
action ls = do
v1 <- run $ S.fold (FL.tee FL.sum FL.maximum) $ S.fromList ls
v1 <- run $ Stream.fold (Fold.tee Fold.sum Fold.maximum) $ Stream.fromList ls
let v2 = Prelude.sum ls
v3 = foldMaybe (greater compare) intMin ls
assert (v1 == (v2, v3))
@ -499,7 +529,8 @@ distribute =
where
action ls = do
v1 <- run $ S.fold (FL.distribute [FL.sum, FL.length]) $ S.fromList ls
v1 <-
run $ Stream.fold (Fold.distribute [Fold.sum, Fold.length]) $ Stream.fromList ls
let v2 = Prelude.sum ls
v3 = Prelude.length ls
assert (v1 == [v2, v3])
@ -509,8 +540,8 @@ partition =
monadicIO $ do
v1 :: (Int, [String]) <-
run
$ S.fold (FL.partition FL.sum FL.toList)
$ S.fromList
$ Stream.fold (Fold.partition Fold.sum Fold.toList)
$ Stream.fromList
[Left 1, Right "abc", Left 3, Right "xy", Right "pp2"]
let v2 = (4,["abc","xy","pp2"])
assert (v1 == v2)
@ -520,8 +551,8 @@ unzip =
monadicIO $ do
v1 :: (Int, [String]) <-
run
$ S.fold (FL.unzip FL.sum FL.toList)
$ S.fromList [(1, "aa"), (2, "bb"), (3, "cc")]
$ Stream.fold (Fold.unzip Fold.sum Fold.toList)
$ Stream.fromList [(1, "aa"), (2, "bb"), (3, "cc")]
let v2 = (6, ["aa", "bb", "cc"])
assert (v1 == v2)
@ -530,8 +561,8 @@ postscan = forAll (listOf (chooseInt (intMin, intMax))) $ \ls ->
monadicIO $ do
v1 :: [Int] <-
run
$ S.fold (F.postscan FL.sum FL.toList)
$ S.fromList ls
$ Stream.fold (Fold.postscan Fold.sum Fold.toList)
$ Stream.fromList ls
let v2 = scanl1 (+) ls
assert (v1 == v2)
@ -540,19 +571,19 @@ many =
forAll (listOf (chooseInt (0, 100))) $ \lst ->
forAll (chooseInt (1, 100)) $ \i ->
monadicIO $ do
let strm = S.fromList lst
r1 <- S.fold (FL.many (split i) FL.toList) strm
r2 <- S.toList $ Stream.foldMany (split i) strm
let strm = Stream.fromList lst
r1 <- Stream.fold (Fold.many (split i) Fold.toList) strm
r2 <- Stream.fold Fold.toList $ Stream.foldMany (split i) strm
assert $ r1 == r2
where
split i = FL.take i FL.toList
split i = Fold.take i Fold.toList
foldBreak :: [Int] -> Property
foldBreak ls = monadicIO $ do
(mbh, rest) <- run $ Stream.foldBreak FL.head (S.fromList ls)
rests <- run $ S.toList rest
(mbh, rest) <- run $ Stream.foldBreak Fold.head (Stream.fromList ls)
rests <- run $ Stream.fold Fold.toList rest
assert (mbh == headl ls)
listEquals (==) rests (taill ls)
@ -564,10 +595,10 @@ foldBreak ls = monadicIO $ do
demux :: Expectation
demux =
let table "SUM" = return FL.sum
table "PRODUCT" = return FL.product
table _ = return FL.length
input = Stream.fromList (
let table "SUM" = return Fold.sum
table "PRODUCT" = return Fold.product
table _ = return Fold.length
input = Stream.fromList (
[ ("SUM", 1)
, ("abc", 1)
, ("PRODUCT", 2)
@ -579,7 +610,7 @@ demux =
, ("abc", 2)
] :: [(String, Int)])
in Stream.fold
(F.demux table)
(Fold.demux table)
input
`shouldReturn`
Data.Map.fromList [("PRODUCT", 8),("SUM", 4),("abc",3),("xyz",2)]
@ -590,22 +621,22 @@ demuxWith =
let getKey x | even x = "SUM"
| otherwise = "PRODUCT"
getFold "SUM" = return FL.sum
getFold "PRODUCT" = return FL.product
getFold "SUM" = return Fold.sum
getFold "PRODUCT" = return Fold.product
getFold _ = error "demuxWith: bug"
input = Stream.fromList [1, 2, 3, 4 :: Int]
input = Stream.fromList [1, 2, 3, 4 :: Int]
in Stream.fold
(F.demuxWith getKey (getFold . getKey))
(Fold.demuxWith getKey (getFold . getKey))
input
`shouldReturn`
Data.Map.fromList [("PRODUCT",3),("SUM",6)]
Data.Map.fromList [("PRODUCT",3),("SUM",6)]
classifyWith :: Expectation
classifyWith =
let input = Stream.fromList [("ONE",1),("ONE",1.1),("TWO",2), ("TWO",2.2)]
let input = Stream.fromList [("ONE",1),("ONE",1.1),("TWO",2), ("TWO",2.2)]
in Stream.fold
(F.classifyWith fst (FL.lmap snd FL.toList))
(Fold.classifyWith fst (Fold.lmap snd Fold.toList))
input
`shouldReturn`
Data.Map.fromList
@ -622,7 +653,7 @@ classify =
, ("TWO",(2, 2.2))
]
in Stream.fold
(F.classify (FL.lmap snd FL.toList))
(Fold.classify (Fold.lmap snd Fold.toList))
input
`shouldReturn`
Data.Map.fromList
@ -631,8 +662,8 @@ classify =
splitAt :: Expectation
splitAt =
Stream.fold
(F.splitAt 6 FL.toList FL.toList)
(Stream.fromList "Hello World!")
(Fold.splitAt 6 Fold.toList Fold.toList)
(Stream.fromList "Hello World!")
`shouldReturn`
("Hello ","World!")
@ -641,8 +672,8 @@ scan = forAll (listOf (chooseInt (0, 100))) $ \lst ->
monadicIO $ do
v1 :: [Int] <-
run
$ S.fold (F.scan FL.sum FL.toList)
$ S.fromList lst
$ Stream.fold (Fold.scan Fold.sum Fold.toList)
$ Stream.fromList lst
let v2 = scanl (+) 0 lst
assert (v1 == v2)
@ -658,10 +689,10 @@ topBy isTop = forAll (listOf (chooseInt (-50, 100))) $ \ls0 ->
n <- liftIO $ generate $ chooseInt (-2, n0 + 2)
if isTop
then do
lst <- S.fold (F.top n) (S.fromList ls) >>= MA.toList
lst <- Stream.fold (Fold.top n) (Stream.fromList ls) >>= MArray.toList
assert ((Prelude.take n . Prelude.reverse . sort) ls == lst)
else do
lst <- S.fold (F.bottom n) (S.fromList ls) >>= MA.toList
lst <- Stream.fold (Fold.bottom n) (Stream.fromList ls) >>= MArray.toList
assert ((Prelude.take n . sort) ls == lst)
top :: Property
@ -672,10 +703,10 @@ bottom = topBy False
nub :: Property
nub = monadicIO $ do
vals <- Stream.toList
vals <- Stream.fold Fold.toList
$ Stream.catMaybes
$ Stream.postscan F.nub
$ Stream.fromList [1::Int, 1, 2, 3, 4, 4, 5, 1, 5, 7]
$ Stream.postscan Fold.nub
$ Stream.fromList [1::Int, 1, 2, 3, 4, 4, 5, 1, 5, 7]
assert (vals == [1, 2, 3, 4, 5, 7])
moduleName :: String

View File

@ -3,7 +3,8 @@ module Streamly.Test.Data.Fold.Window (main) where
import Streamly.Internal.Data.Fold.Window
import Test.Hspec (hspec, describe, it, runIO)
import qualified Streamly.Internal.Data.Ring.Foreign as Ring
import qualified Streamly.Prelude as S
import qualified Streamly.Internal.Data.Stream as S
import qualified Streamly.Internal.Data.Fold as Fold
import Prelude hiding (sum, maximum, minimum)
@ -23,7 +24,7 @@ main = hspec $ do
let c = S.fromList testCase
a <- runIO $ S.fold (Ring.slidingWindow winSize f) c
b <- runIO $ S.fold f $ S.drop (numElem - winSize)
$ S.map (, Nothing) c
$ fmap (, Nothing) c
let c1 = a - b
it ("should not deviate more than " ++ show deviationLimit)
$ c1 >= -1 * deviationLimit && c1 <= deviationLimit
@ -40,8 +41,8 @@ main = hspec $ do
testFunc tc f sI sW = do
let c = S.fromList tc
a <- runIO $ S.toList $ S.postscan f $ S.map (, Nothing) c
b <- runIO $ S.toList $ S.postscan
a <- runIO $ S.fold Fold.toList $ S.postscan f $ fmap (, Nothing) c
b <- runIO $ S.fold Fold.toList $ S.postscan
(Ring.slidingWindow winSize f) c
it "Infinite" $ a == sI
it ("Finite " ++ show winSize) $ b == sW

View File

@ -9,10 +9,10 @@ import qualified GHC.Exts as GHC
#ifdef USE_STREAMLY_LIST
import Data.Functor.Identity
import Streamly.Internal.Data.List (List(..), pattern Cons, pattern Nil, ZipList(..),
fromZipList, toZipList)
import Streamly.Prelude (SerialT)
import qualified Streamly.Prelude as S
import Streamly.Internal.Data.List
(List(..), pattern Cons, pattern Nil, ZipList(..), fromZipList, toZipList)
import Streamly.Internal.Data.Stream (Stream)
import qualified Streamly.Internal.Data.Stream as S
#else
import Prelude -- to suppress compiler warning
@ -39,37 +39,37 @@ main :: IO ()
main = hspec $
describe moduleName $ do
#ifdef USE_STREAMLY_LIST
describe "OverloadedLists for 'SerialT Identity' type" $ do
describe "OverloadedLists for 'Stream Identity' type" $ do
it "Overloaded lists" $ do
([1..3] :: SerialT Identity Int) `shouldBe` S.fromList [1..3]
GHC.toList ([1..3] :: SerialT Identity Int) `shouldBe` [1..3]
([1..3] :: Stream Identity Int) `shouldBe` S.fromList [1..3]
GHC.toList ([1..3] :: Stream Identity Int) `shouldBe` [1..3]
it "Show instance" $ do
show (S.fromList [1..3] :: SerialT Identity Int)
show (S.fromList [1..3] :: Stream Identity Int)
`shouldBe` "fromList [1,2,3]"
it "Read instance" $ do
(read "fromList [1,2,3]" :: SerialT Identity Int) `shouldBe` [1..3]
(read "fromList [1,2,3]" :: Stream Identity Int) `shouldBe` [1..3]
it "Eq instance" $ do
([1,2,3] :: SerialT Identity Int) == [1,2,3] `shouldBe` True
([1,2,3] :: Stream Identity Int) == [1,2,3] `shouldBe` True
it "Ord instance" $ do
([1,2,3] :: SerialT Identity Int) > [1,2,1] `shouldBe` True
([1,2,3] :: Stream Identity Int) > [1,2,1] `shouldBe` True
it "Monad comprehension" $ do
[(x,y) | x <- [1..2], y <- [1..2]] `shouldBe`
([(1,1), (1,2), (2,1), (2,2)] :: SerialT Identity (Int, Int))
([(1,1), (1,2), (2,1), (2,2)] :: Stream Identity (Int, Int))
it "Foldable (sum)" $ sum ([1..3] :: SerialT Identity Int)
it "Foldable (sum)" $ sum ([1..3] :: Stream Identity Int)
`shouldBe` 6
it "Traversable (mapM)" $
mapM return ([1..10] :: SerialT Identity Int)
mapM return ([1..10] :: Stream Identity Int)
`shouldReturn` [1..10]
describe "OverloadedStrings for 'SerialT Identity' type" $ do
describe "OverloadedStrings for 'Stream Identity' type" $ do
it "overloaded strings" $ do
("hello" :: SerialT Identity Char) `shouldBe` S.fromList "hello"
("hello" :: Stream Identity Char) `shouldBe` S.fromList "hello"
#endif
describe "OverloadedLists for List type" $ do

View File

@ -18,7 +18,7 @@ import qualified Prelude
import qualified Streamly.Internal.Data.Array.Unboxed as A
import qualified Streamly.Internal.Data.Fold as FL
import qualified Streamly.Internal.Data.Parser as P
import qualified Streamly.Internal.Data.Stream.IsStream as S
import qualified Streamly.Internal.Data.Stream as S
import qualified Test.Hspec as H
#if MIN_VERSION_QuickCheck(2,14,0)
@ -36,7 +36,6 @@ chooseAny = MkGen (\r _ -> let (x,_) = random r in x)
#endif
maxTestCount :: Int
maxTestCount = 100
@ -482,7 +481,7 @@ parseManyWordQuotedBy =
spc _ = False
parser = P.wordQuotedBy kQ esc lQ rQ fromLQ spc FL.toList
result <- H.runIO $ S.toList $ S.parseMany parser inpStrm
result <- H.runIO $ S.fold FL.toList $ S.parseMany parser inpStrm
H.it (showCase c) $ result `H.shouldBe` expected
where
@ -727,7 +726,7 @@ parseMany =
outs <- do
let p = P.fromFold $ FL.take len FL.toList
run
$ S.toList
$ S.fold FL.toList
$ S.parseMany p (S.fromList $ concat ins)
listEquals (==) outs ins
@ -781,7 +780,7 @@ parseMany2Events =
monadicIO $ do
xs <-
( run
$ S.toList
$ S.fold FL.toList
$ S.parseMany readOneEvent
$ S.fromList (concat (replicate 2 event))
)
@ -801,7 +800,7 @@ manyEqParseMany =
monadicIO $ do
let strm = S.fromList lst
r1 <- run $ S.parse (P.many (split i) FL.toList) strm
r2 <- run $ S.toList $ S.parseMany (split i) strm
r2 <- run $ S.fold FL.toList $ S.parseMany (split i) strm
assert $ r1 == r2
where
@ -829,6 +828,11 @@ takeEndBy1 =
else [x]
takeWhileAndFirstFail _ [] = []
splitWithSuffix
:: Monad m
=> (a -> Bool) -> FL.Fold m a b -> S.Stream m a -> S.Stream m b
splitWithSuffix predicate f = S.foldMany (FL.takeEndBy predicate f)
takeEndBy2 :: Property
takeEndBy2 =
forAll (listOf (chooseInt (0, 1))) $ \ls ->
@ -838,7 +842,7 @@ takeEndBy2 =
predicate = (==0)
eitherParsedList =
S.toList $
S.fold FL.toList $
S.parseMany (P.takeEndBy predicate prsr) strm
where
@ -850,12 +854,12 @@ takeEndBy2 =
[] -> return []
_ ->
if last ls == 0
then S.toList $ S.append strm1 (S.fromList [])
else S.toList strm1
then S.fold FL.toList $ S.append strm1 (S.fromList [])
else S.fold FL.toList strm1
where
strm1 = S.splitWithSuffix predicate FL.toList strm
strm1 = splitWithSuffix predicate FL.toList strm
in
case eitherParsedList of
Left _ -> property False

View File

@ -17,7 +17,7 @@ import qualified Streamly.Internal.Data.Fold as FL
import qualified Streamly.Internal.Data.Parser.ParserD as P
import qualified Streamly.Internal.Data.Producer.Source as Source
import qualified Streamly.Internal.Data.Producer as Producer
import qualified Streamly.Internal.Data.Stream.IsStream as S
import qualified Streamly.Internal.Data.Stream as S
import qualified Streamly.Internal.Data.Stream.StreamD as D
import qualified Streamly.Internal.Data.Unfold as Unfold
import qualified Test.Hspec as H
@ -28,6 +28,7 @@ import Prelude hiding (sequence)
import Test.QuickCheck (chooseAny)
#else
import System.Random (Random(random))
@ -54,6 +55,9 @@ max_value = 10000
max_length :: Int
max_length = 1000
toList :: Monad m => S.Stream m a -> m [a]
toList = S.fold FL.toList
-- Accumulator Tests
fromFold :: Property
@ -602,7 +606,7 @@ parseMany =
monadicIO $ do
outs <-
( run
$ S.toList
$ toList
$ S.parseManyD
(P.fromFold $ FL.take len FL.toList) (S.fromList $ concat ins)
)
@ -621,7 +625,7 @@ parseUnfold = do
<*> chooseInt (1, len)
<*> chooseInt (1, len)) $ \(ls, clen, tlen) ->
monadicIO $ do
arrays <- S.toList $ S.arraysOf clen (S.fromList ls)
arrays <- toList $ S.arraysOf clen (S.fromList ls)
let src = Source.source (Just (Producer.OuterLoop arrays))
let parser = P.fromFold (FL.take tlen FL.toList)
let readSrc =
@ -630,7 +634,7 @@ parseUnfold = do
let streamParser =
Producer.simplify (Source.parseManyD parser readSrc)
xs <- run
$ S.toList
$ toList
$ S.unfoldMany Unfold.fromList
$ S.unfold streamParser src
@ -697,7 +701,7 @@ parseMany2Events =
monadicIO $ do
xs <-
( run
$ S.toList
$ toList
$ S.parseManyD readOneEvent
$ S.fromList (concat (replicate 2 event))
)

View File

@ -13,17 +13,15 @@ import Streamly.Internal.Data.Unfold (Unfold)
import qualified Data.List as List
import qualified Prelude
import qualified Streamly.Data.Unfold as UF
import qualified Streamly.Internal.Data.Fold as Fold
import qualified Streamly.Internal.Data.Unfold as UF
import qualified Streamly.Internal.Data.Stream.IsStream as S
import qualified Streamly.Internal.Data.Stream as S
import qualified Streamly.Internal.Data.Stream.StreamD as D
import qualified Streamly.Internal.Data.Stream.StreamK as K
import Control.Monad.Trans.State.Strict
import Data.Functor.Identity
import Prelude hiding (const, take, drop, concat, mapM)
import Streamly.Prelude (SerialT)
import Test.Hspec as H
import Test.Hspec.QuickCheck
import Test.QuickCheck
@ -43,7 +41,7 @@ testUnfoldM unf seed si sf lst = evalState action si
where
action = do
x <- S.toList $ S.unfold unf seed
x <- S.fold Fold.toList $ S.unfold unf seed
y <- get
return $ x == lst && y == sf
@ -57,7 +55,7 @@ testUnfold unf seed lst = runIdentity action
where
action = do
x <- S.toList $ S.unfold unf seed
x <- S.fold Fold.toList $ S.unfold unf seed
return $ x == lst
testUnfoldD :: Unfold Identity a Int -> a -> [Int] -> Bool
@ -112,7 +110,7 @@ fromStream =
$ \list ->
testUnfoldD
UF.fromStream
(S.fromList list :: SerialT Identity Int)
(S.fromList list :: S.Stream Identity Int)
list
fromStreamD :: Property

View File

@ -40,6 +40,11 @@ flag opt
manual: True
default: True
flag test-core
description: Test only core package
manual: True
default: False
-------------------------------------------------------------------------------
-- Common stanzas
-------------------------------------------------------------------------------
@ -139,21 +144,23 @@ common optimization-options
common test-dependencies
build-depends:
streamly
, streamly-core
, base >= 4.9 && < 4.17
, containers >= 0.5 && < 0.7
, exceptions >= 0.8 && < 0.11
, ghc
, hspec >= 2.0 && < 2.10
, mtl >= 2.2 && < 2.3
, random >= 1.0.0 && < 1.3
, transformers >= 0.4 && < 0.7
, QuickCheck >= 2.13 && < 2.15
, directory >= 1.2.2 && < 1.4
, filepath >= 1.4.1 && < 1.5
, temporary >= 1.3 && < 1.4
, network >= 3.1 && < 3.2
streamly-core
, base >= 4.9 && < 4.17
, containers >= 0.5 && < 0.7
, exceptions >= 0.8 && < 0.11
, ghc
, hspec >= 2.0 && < 2.10
, mtl >= 2.2 && < 2.3
, random >= 1.0.0 && < 1.3
, transformers >= 0.4 && < 0.7
, QuickCheck >= 2.13 && < 2.15
, directory >= 1.2.2 && < 1.4
, filepath >= 1.4.1 && < 1.5
, temporary >= 1.3 && < 1.4
, network >= 3.1 && < 3.2
if !flag(test-core)
build-depends: streamly
if flag(fusion-plugin) && !impl(ghcjs) && !impl(ghc < 8.6)
build-depends:
@ -173,7 +180,8 @@ library
import: lib-options, test-dependencies
hs-source-dirs: lib
exposed-modules: Streamly.Test.Common
, Streamly.Test.Prelude.Common
if !flag(test-core)
exposed-modules: Streamly.Test.Prelude.Common
if flag(limit-build-mem)
ghc-options: +RTS -M1500M -RTS
@ -222,23 +230,37 @@ test-suite Data.Array
type: exitcode-stdio-1.0
main-is: Streamly/Test/Data/Array.hs
ghc-options: -main-is Streamly.Test.Data.Array.main
if flag(test-core)
buildable: False
test-suite Data.Array.Unboxed
import: test-options
type: exitcode-stdio-1.0
main-is: Streamly/Test/Data/Array/Unboxed.hs
ghc-options: -main-is Streamly.Test.Data.Array.Unboxed.main
if flag(test-core)
buildable: False
test-suite Data.Array.Unboxed.Mut
import: test-options
type: exitcode-stdio-1.0
main-is: Streamly/Test/Data/Array/Unboxed/Mut.hs
ghc-options: -main-is Streamly.Test.Data.Array.Unboxed.Mut.main
test-suite Data.Ring.Unboxed
import: test-options
type: exitcode-stdio-1.0
main-is: Streamly/Test/Data/Ring/Unboxed.hs
ghc-options: -main-is Streamly.Test.Data.Ring.Unboxed.main
if flag(test-core)
buildable: False
test-suite Data.Array.Stream.Foreign
import: test-options
type: exitcode-stdio-1.0
main-is: Streamly/Test/Data/Array/Stream/Foreign.hs
if flag(test-core)
buildable: False
test-suite Data.Fold
import: test-options
@ -270,6 +292,8 @@ test-suite Data.SmallArray
type: exitcode-stdio-1.0
main-is: Streamly/Test/Data/SmallArray.hs
ghc-options: -main-is Streamly.Test.Data.SmallArray.main
if flag(test-core)
buildable: False
test-suite Data.Unfold
import: test-options
@ -282,6 +306,8 @@ test-suite FileSystem.Event
ghc-options: -main-is Streamly.Test.FileSystem.Event
main-is: Streamly/Test/FileSystem/Event.hs
other-modules: Streamly.Test.FileSystem.Event.Common
if flag(test-core)
buildable: False
test-suite FileSystem.Event.Darwin
import: test-options
@ -292,6 +318,8 @@ test-suite FileSystem.Event.Darwin
ghc-options: -main-is Streamly.Test.FileSystem.Event.Darwin
if !os(darwin)
buildable: False
if flag(test-core)
buildable: False
test-suite FileSystem.Event.Linux
import: test-options
@ -302,6 +330,8 @@ test-suite FileSystem.Event.Linux
ghc-options: -main-is Streamly.Test.FileSystem.Event.Linux
if !os(linux)
buildable: False
if flag(test-core)
buildable: False
test-suite FileSystem.Event.Windows
import: test-options
@ -312,40 +342,54 @@ test-suite FileSystem.Event.Windows
ghc-options: -main-is Streamly.Test.FileSystem.Event.Windows
if !os(windows)
buildable: False
if flag(test-core)
buildable: False
test-suite FileSystem.Handle
import: test-options
type: exitcode-stdio-1.0
main-is: Streamly/Test/FileSystem/Handle.hs
ghc-options: -main-is Streamly.Test.FileSystem.Handle.main
if flag(test-core)
buildable: False
test-suite Network.Inet.TCP
import: test-options
type: exitcode-stdio-1.0
main-is: Streamly/Test/Network/Inet/TCP.hs
if flag(test-core)
buildable: False
test-suite Network.Socket
import: test-options
type: exitcode-stdio-1.0
main-is: Streamly/Test/Network/Socket.hs
if flag(test-core)
buildable: False
test-suite Prelude
import: test-options
type: exitcode-stdio-1.0
main-is: Streamly/Test/Prelude.hs
ghc-options: -main-is Streamly.Test.Prelude.main
if flag(test-core)
buildable: False
test-suite Prelude.Ahead
import: test-options
type: exitcode-stdio-1.0
main-is: Streamly/Test/Prelude/Ahead.hs
ghc-options: -main-is Streamly.Test.Prelude.Ahead.main
if flag(test-core)
buildable: False
test-suite Prelude.Async
import: test-options
type: exitcode-stdio-1.0
main-is: Streamly/Test/Prelude/Async.hs
ghc-options: -main-is Streamly.Test.Prelude.Async.main
if flag(test-core)
buildable: False
test-suite Prelude.Concurrent
import: test-options
@ -354,18 +398,24 @@ test-suite Prelude.Concurrent
ghc-options: -main-is Streamly.Test.Prelude.Concurrent.main
if flag(limit-build-mem)
ghc-options: +RTS -M2000M -RTS
if flag(test-core)
buildable: False
test-suite Prelude.Fold
import: test-options
type: exitcode-stdio-1.0
main-is: Streamly/Test/Prelude/Fold.hs
ghc-options: -main-is Streamly.Test.Prelude.Fold.main
if flag(test-core)
buildable: False
test-suite Prelude.Parallel
import: test-options
type: exitcode-stdio-1.0
main-is: Streamly/Test/Prelude/Parallel.hs
ghc-options: -main-is Streamly.Test.Prelude.Parallel.main
if flag(test-core)
buildable: False
test-suite Prelude.Rate
import:always-optimized
@ -376,6 +426,8 @@ test-suite Prelude.Rate
buildable: True
else
buildable: False
if flag(test-core)
buildable: False
test-suite Prelude.Serial
import: test-options
@ -384,23 +436,31 @@ test-suite Prelude.Serial
ghc-options: -main-is Streamly.Test.Prelude.Serial.main
if flag(limit-build-mem)
ghc-options: +RTS -M1500M -RTS
if flag(test-core)
buildable: False
test-suite Prelude.Top
import: test-options
type: exitcode-stdio-1.0
main-is: Streamly/Test/Prelude/Top.hs
if flag(test-core)
buildable: False
test-suite Prelude.WAsync
import: test-options
type: exitcode-stdio-1.0
main-is: Streamly/Test/Prelude/WAsync.hs
ghc-options: -main-is Streamly.Test.Prelude.WAsync.main
if flag(test-core)
buildable: False
test-suite Prelude.WSerial
import: test-options
type: exitcode-stdio-1.0
main-is: Streamly/Test/Prelude/WSerial.hs
ghc-options: -main-is Streamly.Test.Prelude.WSerial.main
if flag(test-core)
buildable: False
test-suite Prelude.ZipAsync
import: test-options
@ -409,27 +469,31 @@ test-suite Prelude.ZipAsync
ghc-options: -main-is Streamly.Test.Prelude.ZipAsync.main
if flag(limit-build-mem)
ghc-options: +RTS -M750M -RTS
if flag(test-core)
buildable: False
test-suite Prelude.ZipSerial
import: test-options
type: exitcode-stdio-1.0
main-is: Streamly/Test/Prelude/ZipSerial.hs
ghc-options: -main-is Streamly.Test.Prelude.ZipSerial.main
if flag(test-core)
buildable: False
test-suite Unicode.Stream
import: test-options
type: exitcode-stdio-1.0
main-is: Streamly/Test/Unicode/Stream.hs
ghc-options: -main-is Streamly.Test.Unicode.Stream.main
if flag(test-core)
buildable: False
test-suite Unicode.Char
import: test-options
type: exitcode-stdio-1.0
main-is: Streamly/Test/Unicode/Char.hs
ghc-options: -main-is Streamly.Test.Unicode.Char.main
if flag(dev)
buildable: True
else
if flag(test-core) || !flag(dev)
buildable: False
test-suite version-bounds