Plug in common array test code cleanly in Data.Array.Foreign

This commit is contained in:
adithyaov 2021-11-27 02:34:01 +05:30 committed by Adithya Kumar
parent db254e10b7
commit a2f7e570ab
2 changed files with 112 additions and 84 deletions

View File

@ -31,8 +31,7 @@ import Streamly.Test.Common (listEquals)
import qualified Streamly.Prelude as S
#if defined(TEST_ARRAY) ||\
defined(DATA_ARRAY_PRIM) ||\
#if defined(DATA_ARRAY_PRIM) ||\
defined(DATA_ARRAY_PRIM_PINNED)
import qualified Streamly.Internal.Data.Fold as Fold
#endif
@ -40,14 +39,6 @@ import qualified Streamly.Internal.Data.Fold as Fold
#ifdef TEST_SMALL_ARRAY
import qualified Streamly.Internal.Data.SmallArray as A
type Array = A.SmallArray
#elif defined(TEST_ARRAY)
import Data.Word(Word8)
import qualified Streamly.Internal.Data.Array.Foreign as A
import qualified Streamly.Internal.Data.Array.Foreign.Type as A
import qualified Streamly.Internal.Data.Array.Foreign.Mut.Type as MA
import qualified Streamly.Internal.Data.Array.Stream.Foreign as AS
type Array = A.Array
#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
@ -61,8 +52,6 @@ type Array = A.Array
moduleName :: String
#ifdef TEST_SMALL_ARRAY
moduleName = "Data.SmallArray"
#elif defined(TEST_ARRAY)
moduleName = "Data.Array.Foreign"
#elif defined(DATA_ARRAY_PRIM_PINNED)
moduleName = "Data.Array.Prim.Pinned"
#elif defined(DATA_ARRAY_PRIM)
@ -185,55 +174,6 @@ foldManyWith f =
$ S.fromList list
assert (xs == list)
#ifdef TEST_ARRAY
unsafeWriteIndex :: [Int] -> Int -> Int -> IO Bool
unsafeWriteIndex xs i x = do
arr <- MA.fromList xs
MA.putIndexUnsafe arr i x
x1 <- MA.getIndexUnsafe arr i
return $ x1 == x
lastN :: Int -> [a] -> [a]
lastN n l = drop (length l - n) l
testLastN :: Property
testLastN =
forAll (choose (0, maxArrLen)) $ \len ->
forAll (choose (0, len)) $ \n ->
forAll (vectorOf len (arbitrary :: Gen Int)) $ \list ->
monadicIO $ do
xs <- run
$ fmap A.toList
$ S.fold (A.writeLastN n)
$ S.fromList list
assert (xs == lastN n list)
testLastN_LN :: Int -> Int -> IO Bool
testLastN_LN len n = do
let list = [1..len]
l1 <- fmap A.toList $ S.fold (A.writeLastN n) $ S.fromList list
let l2 = lastN n list
return $ l1 == l2
-- 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
#endif
main :: IO ()
main =
hspec $
@ -257,30 +197,10 @@ main =
prop "fromList" testFromList
#endif
#if defined(TEST_ARRAY) ||\
defined(DATA_ARRAY_PRIM) ||\
#if defined(DATA_ARRAY_PRIM) ||\
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)
#ifdef TEST_ARRAY
prop "AS.concat . (A.fromList . (:[]) <$>) === id" $ concatArrayW8
describe "unsafeSlice" $ do
it "partial" $ unsafeSlice 2 4 [1..10]
it "none" $ unsafeSlice 10 0 [1..10]
it "full" $ unsafeSlice 0 10 [1..10]
describe "Mut.unsafeWriteIndex" $ do
it "first" (unsafeWriteIndex [1..10] 0 0 `shouldReturn` True)
it "middle" (unsafeWriteIndex [1..10] 5 0 `shouldReturn` True)
it "last" (unsafeWriteIndex [1..10] 9 0 `shouldReturn` True)
describe "Fold" $ do
prop "writeLastN : 0 <= n <= len" $ testLastN
describe "writeLastN boundary conditions" $ do
it "writeLastN -1" (testLastN_LN 10 (-1) `shouldReturn` True)
it "writeLastN 0" (testLastN_LN 10 0 `shouldReturn` True)
it "writeLastN length" (testLastN_LN 10 10 `shouldReturn` True)
it "writeLastN (length + 1)" (testLastN_LN 10 11 `shouldReturn` True)
#endif

View File

@ -8,5 +8,113 @@
module Streamly.Test.Data.Array.Foreign (main) where
#define TEST_ARRAY
#include "Streamly/Test/Common/Array.hs"
#include "Streamly/Test/Data/Array/CommonImports.hs"
import Data.Word(Word8)
import qualified Streamly.Internal.Data.Fold as Fold
import qualified Streamly.Internal.Data.Array.Foreign as A
import qualified Streamly.Internal.Data.Array.Foreign.Type as A
import qualified Streamly.Internal.Data.Array.Foreign.Mut.Type as MA
import qualified Streamly.Internal.Data.Array.Stream.Foreign as AS
type Array = A.Array
moduleName :: String
moduleName = "Data.Array.Foreign"
#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)
unsafeWriteIndex :: [Int] -> Int -> Int -> IO Bool
unsafeWriteIndex xs i x = do
arr <- MA.fromList xs
MA.putIndexUnsafe arr i x
x1 <- MA.getIndexUnsafe arr i
return $ x1 == x
lastN :: Int -> [a] -> [a]
lastN n l = drop (length l - n) l
testLastN :: Property
testLastN =
forAll (choose (0, maxArrLen)) $ \len ->
forAll (choose (0, len)) $ \n ->
forAll (vectorOf len (arbitrary :: Gen Int)) $ \list ->
monadicIO $ do
xs <- run
$ fmap A.toList
$ S.fold (A.writeLastN n)
$ S.fromList list
assert (xs == lastN n list)
testLastN_LN :: Int -> Int -> IO Bool
testLastN_LN len n = do
let list = [1..len]
l1 <- fmap A.toList $ S.fold (A.writeLastN n) $ S.fromList list
let l2 = lastN n list
return $ l1 == l2
-- 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
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)))
prop "AS.concat . (A.fromList . (:[]) <$>) === id" $ concatArrayW8
describe "unsafeSlice" $ do
it "partial" $ unsafeSlice 2 4 [1..10]
it "none" $ unsafeSlice 10 0 [1..10]
it "full" $ unsafeSlice 0 10 [1..10]
describe "Mut.unsafeWriteIndex" $ do
it "first" (unsafeWriteIndex [1..10] 0 0 `shouldReturn` True)
it "middle" (unsafeWriteIndex [1..10] 5 0 `shouldReturn` True)
it "last" (unsafeWriteIndex [1..10] 9 0 `shouldReturn` True)
describe "Fold" $ do
prop "writeLastN : 0 <= n <= len" $ testLastN
describe "writeLastN boundary conditions" $ do
it "writeLastN -1" (testLastN_LN 10 (-1) `shouldReturn` True)
it "writeLastN 0" (testLastN_LN 10 0 `shouldReturn` True)
it "writeLastN length" (testLastN_LN 10 10 `shouldReturn` True)
it "writeLastN (length + 1)" (testLastN_LN 10 11 `shouldReturn` True)