{-# LANGUAGE TypeApplications #-} module Main (main) where import Control.Monad (void) import qualified Data.ByteString as B import Data.Serialize ( runPut , put , putWord64be , runGet ) import Data.Serialize.Versioned ( runVersionedPut , putVersioned , runVersionedGet , getVersioned ) import Data.Word ( Word8 , Word64 ) import Test.HUnit ( Test( TestLabel , TestList ) , (~=?) , runTestTT ) import Common import V0 testValue :: Foo testValue = Foo (Bar 1) (Baz "abc" (BazSub 2)) encoded :: B.ByteString encoded = runPut $ runVersionedPut @TestDomain $ putVersioned testValue encodingIdentityTest :: Test encodingIdentityTest = Right testValue ~=? decoded where decoded = runGet (runVersionedGet $ getVersioned @TestDomain) encoded encodingIsExpected :: Test encodingIsExpected = expectedEncoding ~=? encoded where expectedEncoding = runPut $ putWord64be 0 <> -- Version number put (1 :: Word64) <> -- (Bar 1) put "abc" <> -- (Baz "abc" _) put (0 :: Word8) <> -- BazSub put (2 :: Integer) -- (BazSub 2) main :: IO () main = void $ runTestTT $ TestList [ TestLabel "encoding identity" encodingIdentityTest , TestLabel "encoding is as expected" encodingIsExpected ]