{-# LANGUAGE MagicHash #-} module Word12BuilderSpec where import Test.Hspec import Test.Hspec.QuickCheck import Test.QuickCheck import Data.Bits import Data.Word12.Internal import Data.ByteString.Lazy.Builder import qualified Data.ByteString.Lazy as BL instance Arbitrary Word12 where arbitrary = arbitrarySizedBoundedIntegral shrink = shrinkIntegral spec :: Spec spec = do describe "split4'8" $ do it "0xabc" $ do split4'8 0xabc `shouldBe` (0x0a, 0xbc) it "0xfff" $ do split4'8 0xfff `shouldBe` (0x0f, 0xff) describe "(x, y) = split4'8 z" $ do prop "x <= 0x0f" $ \z -> let (x, _) = split4'8 z in x <= 0x0f prop "x << 8 | y == z" $ do \z -> let (x, y) = split4'8 z in fromIntegral x `shiftL` 8 .|. fromIntegral y == z describe "split8'4" $ do it "0xabc" $ do split8'4 0xabc `shouldBe` (0xab, 0xc0) it "0xfff" $ do split8'4 0xfff `shouldBe` (0xff, 0xf0) describe "(x, y) = split8'4 z" $ do prop "y == 0 || y >= 0x10" $ \z -> let (_, y) = split8'4 z in y == 0 || y >= 0x10 prop "x << 4 | y >> 4 == z" $ do \z -> let (x, y) = split8'4 z in fromIntegral x `shiftL` 4 .|. fromIntegral y `shiftR` 4 == z describe "fromWord12sle" $ do it "[0xff8, 0xfff, 0x123, 0x456]" $ do let w12s = [0xff8, 0xfff, 0x123, 0x456] toLazyByteString (fromWord12sle w12s) `shouldBe` BL.pack [0xf8, 0xff, 0xff, 0x23, 0x61, 0x45] it "[0x123, 0x456, 0x789, 0xabc, 0xdef]" $ do let w12s = [0x123, 0x456, 0x789, 0xabc, 0xdef] toLazyByteString (fromWord12sle w12s) `shouldBe` BL.pack [0x23, 0x61, 0x45, 0x89, 0xc7, 0xab, 0xef, 0x0d] it "[0x123, 0x456, 0x789]" $ do let w12s = [0x123, 0x456, 0x789] toLazyByteString (fromWord12sle w12s) `shouldBe` BL.pack [0x23, 0x61, 0x45, 0x89, 0x07] it "[]" $ do let w12s = [] toLazyByteString (fromWord12sle w12s) `shouldBe` BL.pack [] it "[0x109]" $ do let w12s = [0x109] toLazyByteString (fromWord12sle w12s) `shouldBe` BL.pack [0x09, 0x01] it "[0x019]" $ do let w12s = [0x019] toLazyByteString (fromWord12sle w12s) `shouldBe` BL.pack [0x19, 0x00] it "[0x000]" $ do let w12s = [0x000] toLazyByteString (fromWord12sle w12s) `shouldBe` BL.pack [0x00, 0x00] it "[0xff8]" $ do let w12s = [0xff8] toLazyByteString (fromWord12sle w12s) `shouldBe` BL.pack [0xf8, 0x0f] it "[0x123,0xff8]" $ do let w12s = [0x123, 0xff8] toLazyByteString (fromWord12sle w12s) `shouldBe` BL.pack [0x23, 0x81, 0xff] prop "odd (length w12s) && last w12s < 0x100 ==> BL.last (toLazyByteString (fromWord12sle w12s)) == 0" $ forAll (choose (0,0x0ff :: Int)) $ \i -> \w12s' -> let w12s = [w12s'] ++ [w12s'] ++ [fromIntegral i] in BL.last (toLazyByteString (fromWord12sle w12s)) == 0 describe "fromWord12sbe" $ do it "[0xff8, 0xfff, 0x123, 0x456]" $ do let w12s = [0xff8, 0xfff, 0x123, 0x456] toLazyByteString (fromWord12sbe w12s) `shouldBe` BL.pack [0xff, 0x8f, 0xff, 0x12, 0x34, 0x56] it "[0x123, 0x456, 0x789, 0xabc, 0xdef]" $ do let w12s = [0x123, 0x456, 0x789, 0xabc, 0xdef] toLazyByteString (fromWord12sbe w12s) `shouldBe` BL.pack [0x12, 0x34, 0x56, 0x78, 0x9a, 0xbc, 0xde, 0xf0] it "[]" $ do let w12s = [] toLazyByteString (fromWord12sbe w12s) `shouldBe` BL.pack [] it "[0x109]" $ do let w12s = [0x109] toLazyByteString (fromWord12sbe w12s) `shouldBe` BL.pack [0x10, 0x90] it "[0x190]" $ do let w12s = [0x190] toLazyByteString (fromWord12sbe w12s) `shouldBe` BL.pack [0x19, 0x00] it "[0x000]" $ do let w12s = [0x000] toLazyByteString (fromWord12sle w12s) `shouldBe` BL.pack [0x00, 0x00]