Skip to content

Commit

Permalink
Add test cases for custom data types TH instances
Browse files Browse the repository at this point in the history
  • Loading branch information
rnjtranjan committed Jun 30, 2023
1 parent 0c3661a commit 84d6623
Showing 1 changed file with 42 additions and 6 deletions.
48 changes: 42 additions & 6 deletions test/Streamly/Test/Data/Unbox.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
{-# LANGUAGE StandaloneDeriving, DeriveAnyClass #-}
{-# LANGUAGE StandaloneDeriving, DeriveAnyClass, TemplateHaskell #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeApplications #-}
{-# HLINT ignore "Use newtype instead of data" #-}
Expand All @@ -24,6 +24,7 @@ import Data.Complex (Complex ((:+)))
import Data.Functor.Const (Const (..))
import Data.Functor.Identity (Identity (..))
import Data.Proxy (Proxy(..))
import Data.Word (Word8)
import GHC.Generics (Generic, Rep(..))
import GHC.Real (Ratio(..))
import Streamly.Internal.Data.Unbox.TH
Expand Down Expand Up @@ -148,6 +149,17 @@ testGenericConsistency val = do
checkSizeOf :: forall a. Unbox a => Proxy a -> Int -> IO ()
checkSizeOf _ size = sizeOf (Proxy :: Proxy a) `shouldBe` size

data Foo =
Foo Bool Bool
| Bar Word8 Bool
deriving (Unbox, Show, Eq, Generic)

data CustomData a b = CS1 | CS2 | CS3 a a b deriving (Show, Eq)

data CustomDataPhantom a = CD1 | CD2 deriving (Show, Eq)

$(makeUnbox ''CustomDataPhantom)
$(makeUnbox ''CustomData)
--------------------------------------------------------------------------------
-- CPP helpers
--------------------------------------------------------------------------------
Expand All @@ -174,26 +186,50 @@ checkTHSizeOf_UnarySum :: Int -> Expectation
checkTHSizeOf_UnarySum size = $(exprGetSize (ConT ''UnarySum)) `shouldBe` size

checkTHSizeOf_UnarySum2 :: Int -> Expectation
checkTHSizeOf_UnarySum2 size = $(exprGetSize (ConT ''UnarySum2)) `shouldBe` size
checkTHSizeOf_UnarySum2 size =
$(exprGetSize (ConT ''UnarySum2)) `shouldBe` size

checkTHSizeOf_Single :: Int -> Expectation
checkTHSizeOf_Single size = $(exprGetSize (ConT ''Single)) `shouldBe` size
checkTHSizeOf_Single size =
$(exprGetSize (ConT ''Single)) `shouldBe` size

checkTHSizeOf_Product2 :: Int -> Expectation
checkTHSizeOf_Product2 size = $(exprGetSize (ConT ''Product2)) `shouldBe` size
checkTHSizeOf_Product2 size =
$(exprGetSize (ConT ''Product2)) `shouldBe` size

checkTHSizeOf_SumOfProducts :: Int -> Expectation
checkTHSizeOf_SumOfProducts size = $(exprGetSize (ConT ''SumOfProducts)) `shouldBe` size
checkTHSizeOf_SumOfProducts size =
$(exprGetSize (ConT ''SumOfProducts)) `shouldBe` size

checkTHSizeOf_NestedSOP :: Int -> Expectation
checkTHSizeOf_NestedSOP size = $(exprGetSize (ConT ''NestedSOP)) `shouldBe` size
checkTHSizeOf_NestedSOP size =
$(exprGetSize (ConT ''NestedSOP)) `shouldBe` size

#define CHECK_SIZE_TH(type, expectation) \
it "checkTHSizeOf_Custom type" $ checkSizeOf (Proxy :: Proxy type) expectation

--------------------------------------------------------------------------------
-- Tests
--------------------------------------------------------------------------------

testCases :: Spec
testCases = do
CHECK_SIZE_TH ((CustomDataPhantom Foo), 1)
CHECK_SIZE_TH ((CustomData Unit Unit), 4)
CHECK_SIZE_TH ((CustomData Word8 Foo), 6)
CHECK_SIZE_TH ((CustomData Foo Foo), 10)
CHECK_SIZE_TH ((CustomData Product2 Foo), 28)

it "CustomData" $
testSerialization
@(CustomData Foo Foo)
(CS3 (Foo True True) (Foo True True) (Foo True True))

it "CustomDataPhantom" $
testSerialization
@(CustomDataPhantom Foo)
(CD1)

it "Unit TH" $ checkTHSizeOf_Unit 1
it "Unit1 TH" $ checkTHSizeOf_Unit1 1
it "Unit2 TH" $ checkTHSizeOf_Unit2 2
Expand Down

0 comments on commit 84d6623

Please sign in to comment.