{-# LANGUAGE NegativeLiterals #-} {-# LANGUAGE OverloadedStrings #-} module Pinch.Internal.BuilderSpec (spec) where import Data.Monoid import Data.Word (Word8) import Test.Hspec import Test.Hspec.QuickCheck import qualified Data.ByteString as B import Pinch.Arbitrary import qualified Pinch.Internal.Builder as BB builderCases :: (Show a, Eq a) => (a -> BB.Builder) -> [([Word8], a)] -> Expectation builderCases build = mapM_ . uncurry $ \expected a -> B.unpack (BB.runBuilder (build a)) `shouldBe` expected spec :: Spec spec = describe "Builder" $ do it "can serialize 8-bit integers (1)" $ builderCases BB.int8 [ ([0x01], 1) , ([0x05], 5) , ([0x7f], 127) , ([0xff], -1) , ([0x80], -128) ] prop "can serialize 8-bit integers (2)" $ \b -> B.unpack (BB.runBuilder (BB.int8 b)) `shouldBe` [fromIntegral b] it "can serialize 16-bit integers" $ builderCases BB.int16BE [ ([0x00, 0x01], 1) , ([0x00, 0xff], 255) , ([0x01, 0x00], 256) , ([0x01, 0x01], 257) , ([0x7f, 0xff], 32767) , ([0xff, 0xff], -1) , ([0xff, 0xfe], -2) , ([0xff, 0x00], -256) , ([0xff, 0x01], -255) , ([0x80, 0x00], -32768) ] it "can serialize 32-bit integers" $ builderCases BB.int32BE [ ([0x00, 0x00, 0x00, 0x01], 1) , ([0x00, 0x00, 0x00, 0xff], 255) , ([0x00, 0x00, 0xff, 0xff], 65535) , ([0x00, 0xff, 0xff, 0xff], 16777215) , ([0x7f, 0xff, 0xff, 0xff], 2147483647) , ([0xff, 0xff, 0xff, 0xff], -1) , ([0xff, 0xff, 0xff, 0x00], -256) , ([0xff, 0xff, 0x00, 0x00], -65536) , ([0xff, 0x00, 0x00, 0x00], -16777216) , ([0x80, 0x00, 0x00, 0x00], -2147483648) ] it "can serialize 64-bit integers" $ builderCases BB.int64BE [ ([0x00, 0x00, 0x00, 0x00, 0x00, 0x00, 0x00, 0x01], 1) , ([0x00, 0x00, 0x00, 0x00, 0xff, 0xff, 0xff, 0xff], 4294967295) , ([0x00, 0x00, 0x00, 0xff, 0xff, 0xff, 0xff, 0xff], 1099511627775) , ([0x00, 0x00, 0xff, 0xff, 0xff, 0xff, 0xff, 0xff], 281474976710655) , ([0x00, 0xff, 0xff, 0xff, 0xff, 0xff, 0xff, 0xff], 72057594037927935) , ([0x7f, 0xff, 0xff, 0xff, 0xff, 0xff, 0xff, 0xff], 9223372036854775807) , ([0xff, 0xff, 0xff, 0xff, 0xff, 0xff, 0xff, 0xff], -1) , ([0xff, 0xff, 0xff, 0xff, 0x00, 0x00, 0x00, 0x00], -4294967296) , ([0xff, 0xff, 0xff, 0x00, 0x00, 0x00, 0x00, 0x00], -1099511627776) , ([0xff, 0xff, 0x00, 0x00, 0x00, 0x00, 0x00, 0x00], -281474976710656) , ([0xff, 0x00, 0x00, 0x00, 0x00, 0x00, 0x00, 0x00], -72057594037927936) , ([0x80, 0x00, 0x00, 0x00, 0x00, 0x00, 0x00, 0x00], -9223372036854775808) ] it "can serialize 64-bit little endian integers" $ builderCases BB.int64LE [ ([0x01, 0x00, 0x00, 0x00, 0x00, 0x00, 0x00, 0x00], 1) , ([0xff, 0xff, 0xff, 0xff, 0x00, 0x00, 0x00, 0x00], 4294967295) , ([0xff, 0xff, 0xff, 0xff, 0xff, 0x00, 0x00, 0x00], 1099511627775) , ([0xff, 0xff, 0xff, 0xff, 0xff, 0xff, 0x00, 0x00], 281474976710655) , ([0xff, 0xff, 0xff, 0xff, 0xff, 0xff, 0xff, 0x00], 72057594037927935) , ([0xff, 0xff, 0xff, 0xff, 0xff, 0xff, 0xff, 0x7f], 9223372036854775807) , ([0xff, 0xff, 0xff, 0xff, 0xff, 0xff, 0xff, 0xff], -1) , ([0x00, 0x00, 0x00, 0x00, 0xff, 0xff, 0xff, 0xff], -4294967296) , ([0x00, 0x00, 0x00, 0x00, 0x00, 0xff, 0xff, 0xff], -1099511627776) , ([0x00, 0x00, 0x00, 0x00, 0x00, 0x00, 0xff, 0xff], -281474976710656) , ([0x00, 0x00, 0x00, 0x00, 0x00, 0x00, 0x00, 0xff], -72057594037927936) , ([0x00, 0x00, 0x00, 0x00, 0x00, 0x00, 0x00, 0x80], -9223372036854775808) ] it "can serialize doubles" $ builderCases BB.doubleBE [ ([0x00, 0x00, 0x00, 0x00, 0x00, 0x00, 0x00, 0x00], 0.0) , ([0x3f, 0xf0, 0x00, 0x00, 0x00, 0x00, 0x00, 0x00], 1.0) , ([0x3f, 0xf0, 0x00, 0x00, 0x00, 0x06, 0xdf, 0x38], 1.0000000001) , ([0x3f, 0xf1, 0x99, 0x99, 0x99, 0x99, 0x99, 0x9a], 1.1) , ([0xbf, 0xf1, 0x99, 0x99, 0x99, 0x99, 0x99, 0x9a], -1.1) , ([0x40, 0x09, 0x21, 0xfb, 0x54, 0x44, 0x2d, 0x18], 3.141592653589793) , ([0xbf, 0xf0, 0x00, 0x00, 0x00, 0x06, 0xdf, 0x38], -1.0000000001) ] it "can serialize little endian doubles" $ builderCases BB.doubleLE [ ([0x00, 0x00, 0x00, 0x00, 0x00, 0x00, 0x00, 0x00], 0.0) , ([0x00, 0x00, 0x00, 0x00, 0x00, 0x00, 0xf0, 0x3f], 1.0) , ([0x38, 0xdf, 0x06, 0x00, 0x00, 0x00, 0xf0, 0x3f], 1.0000000001) , ([0x9a, 0x99, 0x99, 0x99, 0x99, 0x99, 0xf1, 0x3f], 1.1) , ([0x9a, 0x99, 0x99, 0x99, 0x99, 0x99, 0xf1, 0xbf], -1.1) , ([0x18, 0x2d, 0x44, 0x54, 0xfb, 0x21, 0x09, 0x40], 3.141592653589793) , ([0x38, 0xdf, 0x06, 0x00, 0x00, 0x00, 0xf0, 0xbf], -1.0000000001) ] prop "can serialize byte strings" $ \(SomeByteString bs) -> BB.runBuilder (BB.byteString bs) `shouldBe` bs prop "can append primitives" $ BB.runBuilder (BB.int8 1 <> BB.int32BE 2) `shouldBe` B.pack [1, 0, 0, 0, 2] prop "can append byte strings" $ \(SomeByteString l) (SomeByteString r) -> BB.runBuilder (BB.byteString l <> BB.byteString r) `shouldBe` (l <> r) prop "can append primitives with bytestrings" $ \(SomeByteString r) -> B.unpack (BB.runBuilder (BB.int32BE 5 <> BB.byteString r)) `shouldBe` (0:0:0:5:B.unpack r)