Plug in common array test code cleanly in Data.Array.Prim.Pinned

This commit is contained in:
adithyaov 2021-11-27 02:47:55 +05:30 committed by Adithya Kumar
parent 561ec1edf1
commit 420ee10869
2 changed files with 45 additions and 17 deletions

View File

@ -31,24 +31,14 @@ import Streamly.Test.Common (listEquals)
import qualified Streamly.Prelude as S
#if defined(DATA_ARRAY_PRIM_PINNED)
import qualified Streamly.Internal.Data.Fold as Fold
#endif
#ifdef TEST_SMALL_ARRAY
import qualified Streamly.Internal.Data.SmallArray as A
type Array = A.SmallArray
#elif defined(DATA_ARRAY_PRIM_PINNED)
import qualified Streamly.Internal.Data.Array.Prim.Pinned as A
import qualified Streamly.Internal.Data.Array.Prim.Pinned.Type as A
type Array = A.Array
#endif
moduleName :: String
#ifdef TEST_SMALL_ARRAY
moduleName = "Data.SmallArray"
#elif defined(DATA_ARRAY_PRIM_PINNED)
moduleName = "Data.Array.Prim.Pinned"
#endif
-- Coverage build takes too long with default number of tests
@ -189,10 +179,5 @@ main =
prop "read . write === id" testFoldUnfold
prop "fromList" testFromList
#endif
#if defined(DATA_ARRAY_PRIM_PINNED)
prop "foldMany with writeNUnsafe concats to original"
(foldManyWith (\n -> Fold.take n (A.writeNUnsafe n)))
#endif
prop "foldMany with writeN concats to original"
(foldManyWith A.writeN)

View File

@ -8,5 +8,48 @@
module Streamly.Test.Data.Array.Prim.Pinned where
#define DATA_ARRAY_PRIM_PINNED
#include "Streamly/Test/Common/Array.hs"
#include "Streamly/Test/Data/Array/CommonImports.hs"
import qualified Streamly.Internal.Data.Fold as Fold
import qualified Streamly.Internal.Data.Array.Prim as A
import qualified Streamly.Internal.Data.Array.Prim.Type as A
type Array = A.Array
moduleName :: String
moduleName = "Data.Array.Prim.Pinned"
#include "Streamly/Test/Data/Array/Common.hs"
testFromStreamToStream :: Property
testFromStreamToStream = genericTestFromTo (const A.fromStream) A.toStream (==)
testFoldUnfold :: Property
testFoldUnfold = genericTestFromTo (const (S.fold A.write)) (S.unfold A.read) (==)
testFromList :: Property
testFromList =
forAll (choose (0, maxArrLen)) $ \len ->
forAll (vectorOf len (arbitrary :: Gen Int)) $ \list ->
monadicIO $ do
let arr = A.fromList list
xs <- run $ S.toList $ (S.unfold A.read) arr
assert (xs == list)
testLengthFromStream :: Property
testLengthFromStream = genericTestFrom (const A.fromStream)
main :: IO ()
main =
hspec $
H.parallel $
modifyMaxSuccess (const maxTestCount) $ do
describe moduleName $ do
commonMain
describe "Construction" $ do
prop "length . fromStream === n" testLengthFromStream
prop "toStream . fromStream === id" testFromStreamToStream
prop "read . write === id" testFoldUnfold
prop "fromList" testFromList
prop "foldMany with writeNUnsafe concats to original"
(foldManyWith (\n -> Fold.take n (A.writeNUnsafe n)))