Add test cases for Unbox Generic derived instances (#2207)

Co-authored-by: Harendra Kumar <harendra@composewell.com>
This commit is contained in:
Ranjeet Ranjan 2023-01-07 19:05:30 +05:30 committed by GitHub
parent 8adf0c3c3d
commit deb16f8670
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
5 changed files with 91 additions and 2 deletions

View File

@ -13,6 +13,7 @@ test/Streamly/Test/Prelude/Fold.hs
test/Streamly/Test/Prelude/Rate.hs
test/Streamly/Test/Prelude/Serial.hs
test/Streamly/Test/Unicode/Stream.hs
test/Streamly/Test/Data/Unbox.hs
benchmark/lib/Streamly/Benchmark/Common.hs
benchmark/lib/Streamly/Benchmark/Common/Handle.hs
benchmark/lib/Streamly/Benchmark/Prelude.hs

View File

@ -84,8 +84,8 @@ cradle:
cabal:
- path: "./test/Streamly/Test/Data/Array.hs"
component: "test:Data.Array"
- path: "./test/Streamly/Test/Data/Array.hs"
component: "test:Data.Array"
- path: "./test/Streamly/Test/Data/Unbox.hs"
component: "test:Data.Unbox"
- path: "./test/Streamly/Test/Data/Array/Mut.hs"
component: "test:Data.Array.Mut"
- path: "./test/Streamly/Test/Data/Array/Stream.hs"

View File

@ -118,6 +118,7 @@ extra-source-files:
test/version-bounds.hs
test/Streamly/Test/Unicode/ucd/NormalizationTest.txt
test/Streamly/Test/Unicode/extra/NormalizationTest.txt
test/Streamly/Test/Data/Unbox.hs
benchmark/Streamly/Benchmark/Unicode/data/AllChars.txt
benchmark/Streamly/Benchmark/Unicode/data/Devanagari.txt
benchmark/Streamly/Benchmark/Unicode/data/Japanese.txt

View File

@ -0,0 +1,79 @@
{-# LANGUAGE DeriveAnyClass #-}
-- |
-- Module : Streamly.Test.Data.Unbox
-- Copyright : (c) 2022 Composewell technologies
-- License : BSD-3-Clause
-- Maintainer : streamly@composewell.com
-- Stability : experimental
-- Portability : GHC
module Streamly.Test.Data.Unbox (main) where
import Data.Proxy (Proxy(..))
import GHC.Generics (Generic)
import Streamly.Internal.Data.Unboxed (Unbox(..))
import qualified Streamly.Internal.Data.IORef.Unboxed as IORef
import Test.Hspec as H
import Test.Hspec.QuickCheck
import Test.QuickCheck (Property)
import Test.QuickCheck.Monadic (monadicIO, assert, run)
data Unit = Unit deriving (Unbox, Show, Generic, Eq)
{-# ANN Single "HLint: ignore" #-}
data Single = Single Int deriving (Unbox, Show, Generic, Eq)
data Product2 = Product2 Int Char deriving (Unbox, Show, Generic, Eq)
data SumOfProducts =
SOP0
| SOP1 Int
| SOP2 Int Char
| SOP3 Int Int Int deriving (Unbox, Show, Generic, Eq)
data NestedSOP =
NSOP0 SumOfProducts
| NSOP1 SumOfProducts deriving (Unbox, Show, Generic, Eq)
test ::(Unbox a, Eq a) => a -> a -> Property
test v1 v2 = monadicIO $ do
ref <- run $ IORef.newIORef v1
x1 <- run $ IORef.readIORef ref
run $ IORef.writeIORef ref v2
x2 <- run $ IORef.readIORef ref
assert (x2 == v2)
assert (x1 == v1)
checkSizeOf :: forall a. Unbox a => Proxy a -> Int -> Property
checkSizeOf _ size = monadicIO $
assert (sizeOf (undefined :: a) == size)
moduleName :: String
moduleName = "Data.Unbox"
tests :: Spec
tests = do
prop "test Unit Unit" $ test Unit Unit
prop "(Single 0) (Single 1)" $ test (Single 0) (Single 1)
prop "(Product2 0 'a') (Product2 1 'b')"
$ test (Product2 0 'a') (Product2 1 'b')
prop "(SOP0) (SOP1 1)" $ test SOP0 (SOP1 1)
prop "(SOP0) (SOP2 1 'a')" $ test SOP0 (SOP2 1 'a')
prop "(SOP0) (SOP3 1 2 3)" $ test SOP0 (SOP3 1 2 3)
prop "checkSizeOf Unit" $ checkSizeOf (Proxy :: Proxy Unit) 1
prop "checkSizeOf Single" $ checkSizeOf (Proxy :: Proxy Single) 8
prop "checkSizeOf Product2" $ checkSizeOf (Proxy :: Proxy Product2) 12
prop "checkSizeOf SumOfProducts"
$ checkSizeOf (Proxy :: Proxy SumOfProducts) 25
prop "checkSizeOf NestedSOP" $ checkSizeOf (Proxy :: Proxy NestedSOP) 26
main :: IO ()
main =
hspec $
H.parallel $
modifyMaxSuccess (const 1) $ do
describe moduleName $ do
describe "Generic Unboxed Type" tests

View File

@ -253,6 +253,14 @@ test-suite Data.Ring.Unboxed
if flag(use-streamly-core)
buildable: False
test-suite Data.Unbox
import: test-options
type: exitcode-stdio-1.0
main-is: Streamly/Test/Data/Unbox.hs
ghc-options: -main-is Streamly.Test.Data.Unbox.main
if flag(use-streamly-core)
buildable: False
test-suite Data.Array.Stream
import: test-options
type: exitcode-stdio-1.0