{-# OPTIONS_GHC -fno-warn-orphans #-}
{-# LANGUAGE DeriveGeneric       #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StrictData          #-}
{-# LANGUAGE Trustworthy         #-}
module Test.MessagePack.Spec where

import           Test.Hspec
import           Test.QuickCheck
import qualified Test.QuickCheck.Gen         as Gen
import           Test.QuickCheck.Instances   ()

import qualified Data.ByteString.Char8       as S
import qualified Data.ByteString.Lazy        as L8
import qualified Data.ByteString.Lazy.Char8  as L
import qualified Data.HashMap.Strict         as HashMap
import           Data.Int                    (Int16, Int32, Int64, Int8)
import qualified Data.IntMap                 as IntMap
import qualified Data.Map                    as Map
import qualified Data.Maybe                  as Maybe
import           Data.MessagePack.Arbitrary  ()
import qualified Data.Text.Lazy              as LT
import qualified Data.Vector                 as V
import qualified Data.Vector.Storable        as VS
import qualified Data.Vector.Unboxed         as VU
import           Data.Word                   (Word16, Word32, Word64, Word8)
import           GHC.Generics                (Generic)

import           Data.MessagePack.Types
import           Test.MessagePack.BytePacker (BytePacker)
import qualified Test.MessagePack.BytePacker as BytePacker


data Unit = Unit
  deriving (Unit -> Unit -> Bool
(Unit -> Unit -> Bool) -> (Unit -> Unit -> Bool) -> Eq Unit
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Unit -> Unit -> Bool
$c/= :: Unit -> Unit -> Bool
== :: Unit -> Unit -> Bool
$c== :: Unit -> Unit -> Bool
Eq, Int -> Unit -> ShowS
[Unit] -> ShowS
Unit -> String
(Int -> Unit -> ShowS)
-> (Unit -> String) -> ([Unit] -> ShowS) -> Show Unit
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Unit] -> ShowS
$cshowList :: [Unit] -> ShowS
show :: Unit -> String
$cshow :: Unit -> String
showsPrec :: Int -> Unit -> ShowS
$cshowsPrec :: Int -> Unit -> ShowS
Show, (forall x. Unit -> Rep Unit x)
-> (forall x. Rep Unit x -> Unit) -> Generic Unit
forall x. Rep Unit x -> Unit
forall x. Unit -> Rep Unit x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Unit x -> Unit
$cfrom :: forall x. Unit -> Rep Unit x
Generic)

instance MessagePack Unit


data TyConArgs = TyConArgs Int Int Int
  deriving (TyConArgs -> TyConArgs -> Bool
(TyConArgs -> TyConArgs -> Bool)
-> (TyConArgs -> TyConArgs -> Bool) -> Eq TyConArgs
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TyConArgs -> TyConArgs -> Bool
$c/= :: TyConArgs -> TyConArgs -> Bool
== :: TyConArgs -> TyConArgs -> Bool
$c== :: TyConArgs -> TyConArgs -> Bool
Eq, Int -> TyConArgs -> ShowS
[TyConArgs] -> ShowS
TyConArgs -> String
(Int -> TyConArgs -> ShowS)
-> (TyConArgs -> String)
-> ([TyConArgs] -> ShowS)
-> Show TyConArgs
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TyConArgs] -> ShowS
$cshowList :: [TyConArgs] -> ShowS
show :: TyConArgs -> String
$cshow :: TyConArgs -> String
showsPrec :: Int -> TyConArgs -> ShowS
$cshowsPrec :: Int -> TyConArgs -> ShowS
Show, (forall x. TyConArgs -> Rep TyConArgs x)
-> (forall x. Rep TyConArgs x -> TyConArgs) -> Generic TyConArgs
forall x. Rep TyConArgs x -> TyConArgs
forall x. TyConArgs -> Rep TyConArgs x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TyConArgs x -> TyConArgs
$cfrom :: forall x. TyConArgs -> Rep TyConArgs x
Generic)

instance MessagePack TyConArgs


data Record = Record
  { Record -> Int
recordField1 :: Int
  , Record -> Double
recordField2 :: Double
  , Record -> String
recordField3 :: String
  }
  deriving (Record -> Record -> Bool
(Record -> Record -> Bool)
-> (Record -> Record -> Bool) -> Eq Record
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Record -> Record -> Bool
$c/= :: Record -> Record -> Bool
== :: Record -> Record -> Bool
$c== :: Record -> Record -> Bool
Eq, Int -> Record -> ShowS
[Record] -> ShowS
Record -> String
(Int -> Record -> ShowS)
-> (Record -> String) -> ([Record] -> ShowS) -> Show Record
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Record] -> ShowS
$cshowList :: [Record] -> ShowS
show :: Record -> String
$cshow :: Record -> String
showsPrec :: Int -> Record -> ShowS
$cshowsPrec :: Int -> Record -> ShowS
Show, (forall x. Record -> Rep Record x)
-> (forall x. Rep Record x -> Record) -> Generic Record
forall x. Rep Record x -> Record
forall x. Record -> Rep Record x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Record x -> Record
$cfrom :: forall x. Record -> Rep Record x
Generic)

instance MessagePack Record


data Foo
  = Foo1
  | Foo2 Int
  | Foo3 Int
  | Foo4 Int
  | Foo5 Int
  | Foo6 { Foo -> Int
unFoo3 :: Int }
  | Foo7 Int
  | Foo8 Int Int
  | Foo9 Int Int Int
  deriving (Foo -> Foo -> Bool
(Foo -> Foo -> Bool) -> (Foo -> Foo -> Bool) -> Eq Foo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Foo -> Foo -> Bool
$c/= :: Foo -> Foo -> Bool
== :: Foo -> Foo -> Bool
$c== :: Foo -> Foo -> Bool
Eq, Int -> Foo -> ShowS
[Foo] -> ShowS
Foo -> String
(Int -> Foo -> ShowS)
-> (Foo -> String) -> ([Foo] -> ShowS) -> Show Foo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Foo] -> ShowS
$cshowList :: [Foo] -> ShowS
show :: Foo -> String
$cshow :: Foo -> String
showsPrec :: Int -> Foo -> ShowS
$cshowsPrec :: Int -> Foo -> ShowS
Show, (forall x. Foo -> Rep Foo x)
-> (forall x. Rep Foo x -> Foo) -> Generic Foo
forall x. Rep Foo x -> Foo
forall x. Foo -> Rep Foo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Foo x -> Foo
$cfrom :: forall x. Foo -> Rep Foo x
Generic)

instance MessagePack Foo

instance Arbitrary Foo where
  arbitrary :: Gen Foo
arbitrary = [Gen Foo] -> Gen Foo
forall a. [Gen a] -> Gen a
Gen.oneof
    [ Foo -> Gen Foo
forall (m :: * -> *) a. Monad m => a -> m a
return Foo
Foo1
    , Int -> Foo
Foo2 (Int -> Foo) -> Gen Int -> Gen Foo
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Int
forall a. Arbitrary a => Gen a
arbitrary
    , Int -> Foo
Foo3 (Int -> Foo) -> Gen Int -> Gen Foo
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Int
forall a. Arbitrary a => Gen a
arbitrary
    , Int -> Foo
Foo4 (Int -> Foo) -> Gen Int -> Gen Foo
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Int
forall a. Arbitrary a => Gen a
arbitrary
    , Int -> Foo
Foo5 (Int -> Foo) -> Gen Int -> Gen Foo
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Int
forall a. Arbitrary a => Gen a
arbitrary
    , Int -> Foo
Foo6 (Int -> Foo) -> Gen Int -> Gen Foo
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Int
forall a. Arbitrary a => Gen a
arbitrary
    , Int -> Foo
Foo7 (Int -> Foo) -> Gen Int -> Gen Foo
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Int
forall a. Arbitrary a => Gen a
arbitrary
    , Int -> Int -> Foo
Foo8 (Int -> Int -> Foo) -> Gen Int -> Gen (Int -> Foo)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Int
forall a. Arbitrary a => Gen a
arbitrary Gen (Int -> Foo) -> Gen Int -> Gen Foo
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Int
forall a. Arbitrary a => Gen a
arbitrary
    , Int -> Int -> Int -> Foo
Foo9 (Int -> Int -> Int -> Foo) -> Gen Int -> Gen (Int -> Int -> Foo)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Int
forall a. Arbitrary a => Gen a
arbitrary Gen (Int -> Int -> Foo) -> Gen Int -> Gen (Int -> Foo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Int
forall a. Arbitrary a => Gen a
arbitrary Gen (Int -> Foo) -> Gen Int -> Gen Foo
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Int
forall a. Arbitrary a => Gen a
arbitrary
    ]


type UnpackResult a = Either DecodeError a

checkMessage :: Show a => UnpackResult a -> Expectation
checkMessage :: UnpackResult a -> Expectation
checkMessage (Right a
res) =
  HasCallStack => String -> Expectation
String -> Expectation
expectationFailure (String -> Expectation) -> String -> Expectation
forall a b. (a -> b) -> a -> b
$ String
"unexpected success: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ a -> String
forall a. Show a => a -> String
show a
res
checkMessage (Left DecodeError
msgs) =
  DecodeError -> String
forall a. Show a => a -> String
show DecodeError
msgs String -> String -> Expectation
forall a. (HasCallStack, Show a, Eq a) => [a] -> [a] -> Expectation
`shouldContain` String
"invalid encoding for "


spec :: BytePacker p => p -> Spec
spec :: p -> Spec
spec p
p = do
  String -> Spec -> Spec
forall a. HasCallStack => String -> SpecWith a -> SpecWith a
describe String
"unpack" (Spec -> Spec) -> Spec -> Spec
forall a b. (a -> b) -> a -> b
$
    String -> Property -> SpecWith (Arg Property)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"does not throw exceptions on arbitrary data" (Property -> SpecWith (Arg Property))
-> Property -> SpecWith (Arg Property)
forall a b. (a -> b) -> a -> b
$
      (ByteString -> Expectation) -> Property
forall prop. Testable prop => prop -> Property
property ((ByteString -> Expectation) -> Property)
-> (ByteString -> Expectation) -> Property
forall a b. (a -> b) -> a -> b
$ \ByteString
bs ->
        case ByteString -> Maybe String
forall (m :: * -> *) a.
(MonadFail m, MessagePack a) =>
ByteString -> m a
unpack ByteString
bs of
          Just String
"" -> () -> Expectation
forall (m :: * -> *) a. Monad m => a -> m a
return () :: IO ()
          Maybe String
_       -> () -> Expectation
forall (m :: * -> *) a. Monad m => a -> m a
return () :: IO ()

  String -> Spec -> Spec
forall a. HasCallStack => String -> SpecWith a -> SpecWith a
describe String
"Assoc" (Spec -> Spec) -> Spec -> Spec
forall a b. (a -> b) -> a -> b
$ do
    String -> Property -> SpecWith (Arg Property)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"supports read/show" (Property -> SpecWith (Arg Property))
-> Property -> SpecWith (Arg Property)
forall a b. (a -> b) -> a -> b
$
      (Assoc [(Int, Int)] -> Expectation) -> Property
forall prop. Testable prop => prop -> Property
property ((Assoc [(Int, Int)] -> Expectation) -> Property)
-> (Assoc [(Int, Int)] -> Expectation) -> Property
forall a b. (a -> b) -> a -> b
$ \(Assoc [(Int, Int)]
a :: Assoc [(Int, Int)]) ->
        String -> Assoc [(Int, Int)]
forall a. Read a => String -> a
read (Assoc [(Int, Int)] -> String
forall a. Show a => a -> String
show Assoc [(Int, Int)]
a) Assoc [(Int, Int)] -> Assoc [(Int, Int)] -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` Assoc [(Int, Int)]
a

    String -> Property -> SpecWith (Arg Property)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"inherits ordering from its contained type" (Property -> SpecWith (Arg Property))
-> Property -> SpecWith (Arg Property)
forall a b. (a -> b) -> a -> b
$
      (Assoc Int -> Assoc Int -> Expectation) -> Property
forall prop. Testable prop => prop -> Property
property ((Assoc Int -> Assoc Int -> Expectation) -> Property)
-> (Assoc Int -> Assoc Int -> Expectation) -> Property
forall a b. (a -> b) -> a -> b
$ \(Assoc Int
a :: Assoc Int) Assoc Int
b ->
        (Assoc Int -> Int
forall a. Assoc a -> a
unAssoc Assoc Int
a Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Assoc Int -> Int
forall a. Assoc a -> a
unAssoc Assoc Int
b) Bool -> Bool -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` (Assoc Int
a Assoc Int -> Assoc Int -> Bool
forall a. Ord a => a -> a -> Bool
< Assoc Int
b)

  String -> Spec -> Spec
forall a. HasCallStack => String -> SpecWith a -> SpecWith a
describe String
"failures" (Spec -> Spec) -> Spec -> Spec
forall a b. (a -> b) -> a -> b
$
    String -> Expectation -> SpecWith (Arg Expectation)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"should contain the same start of the failure message for all types" (Expectation -> SpecWith (Arg Expectation))
-> Expectation -> SpecWith (Arg Expectation)
forall a b. (a -> b) -> a -> b
$ do
      UnpackResult Foo -> Expectation
forall a. Show a => UnpackResult a -> Expectation
checkMessage (ByteString -> UnpackResult Foo
forall a. MessagePack a => ByteString -> Either DecodeError a
unpackEither (Object -> ByteString
forall a. MessagePack a => a -> ByteString
pack (Object -> ByteString) -> Object -> ByteString
forall a b. (a -> b) -> a -> b
$ Int64 -> Object
ObjectInt (-Int64
1)) :: UnpackResult Foo)
      UnpackResult Foo -> Expectation
forall a. Show a => UnpackResult a -> Expectation
checkMessage (ByteString -> UnpackResult Foo
forall a. MessagePack a => ByteString -> Either DecodeError a
unpackEither ([Object] -> ByteString
forall a. MessagePack a => a -> ByteString
pack [Int64 -> Object
ObjectInt (-Int64
1), Int64 -> Object
ObjectInt Int64
0]) :: UnpackResult Foo)
      UnpackResult TyConArgs -> Expectation
forall a. Show a => UnpackResult a -> Expectation
checkMessage (ByteString -> UnpackResult TyConArgs
forall a. MessagePack a => ByteString -> Either DecodeError a
unpackEither (Object -> ByteString
forall a. MessagePack a => a -> ByteString
pack (Object -> ByteString) -> Object -> ByteString
forall a b. (a -> b) -> a -> b
$ Vector Object -> Object
ObjectArray Vector Object
forall a. Vector a
V.empty) :: UnpackResult TyConArgs)
      UnpackResult Record -> Expectation
forall a. Show a => UnpackResult a -> Expectation
checkMessage (ByteString -> UnpackResult Record
forall a. MessagePack a => ByteString -> Either DecodeError a
unpackEither (Object -> ByteString
forall a. MessagePack a => a -> ByteString
pack (Object -> ByteString) -> Object -> ByteString
forall a b. (a -> b) -> a -> b
$ Vector Object -> Object
ObjectArray Vector Object
forall a. Vector a
V.empty) :: UnpackResult Record)
      UnpackResult Record -> Expectation
forall a. Show a => UnpackResult a -> Expectation
checkMessage (ByteString -> UnpackResult Record
forall a. MessagePack a => ByteString -> Either DecodeError a
unpackEither ([Int] -> ByteString
forall a. MessagePack a => a -> ByteString
pack [Int
0 :: Int, Int
1, Int
2, Int
3]) :: UnpackResult Record)
      UnpackResult Unit -> Expectation
forall a. Show a => UnpackResult a -> Expectation
checkMessage (ByteString -> UnpackResult Unit
forall a. MessagePack a => ByteString -> Either DecodeError a
unpackEither (String -> ByteString
forall a. MessagePack a => a -> ByteString
pack String
"") :: UnpackResult Unit)
      UnpackResult TyConArgs -> Expectation
forall a. Show a => UnpackResult a -> Expectation
checkMessage (ByteString -> UnpackResult TyConArgs
forall a. MessagePack a => ByteString -> Either DecodeError a
unpackEither (String -> ByteString
forall a. MessagePack a => a -> ByteString
pack String
"") :: UnpackResult TyConArgs)
      UnpackResult Record -> Expectation
forall a. Show a => UnpackResult a -> Expectation
checkMessage (ByteString -> UnpackResult Record
forall a. MessagePack a => ByteString -> Either DecodeError a
unpackEither (String -> ByteString
forall a. MessagePack a => a -> ByteString
pack String
"") :: UnpackResult Record)
      UnpackResult () -> Expectation
forall a. Show a => UnpackResult a -> Expectation
checkMessage (ByteString -> UnpackResult ()
forall a. MessagePack a => ByteString -> Either DecodeError a
unpackEither (String -> ByteString
forall a. MessagePack a => a -> ByteString
pack String
"") :: UnpackResult ())
      UnpackResult Int -> Expectation
forall a. Show a => UnpackResult a -> Expectation
checkMessage (ByteString -> UnpackResult Int
forall a. MessagePack a => ByteString -> Either DecodeError a
unpackEither (() -> ByteString
forall a. MessagePack a => a -> ByteString
pack ()) :: UnpackResult Int)
      UnpackResult Bool -> Expectation
forall a. Show a => UnpackResult a -> Expectation
checkMessage (ByteString -> UnpackResult Bool
forall a. MessagePack a => ByteString -> Either DecodeError a
unpackEither (() -> ByteString
forall a. MessagePack a => a -> ByteString
pack ()) :: UnpackResult Bool)
      UnpackResult Float -> Expectation
forall a. Show a => UnpackResult a -> Expectation
checkMessage (ByteString -> UnpackResult Float
forall a. MessagePack a => ByteString -> Either DecodeError a
unpackEither (() -> ByteString
forall a. MessagePack a => a -> ByteString
pack ()) :: UnpackResult Float)
      UnpackResult Double -> Expectation
forall a. Show a => UnpackResult a -> Expectation
checkMessage (ByteString -> UnpackResult Double
forall a. MessagePack a => ByteString -> Either DecodeError a
unpackEither (() -> ByteString
forall a. MessagePack a => a -> ByteString
pack ()) :: UnpackResult Double)
      UnpackResult ByteString -> Expectation
forall a. Show a => UnpackResult a -> Expectation
checkMessage (ByteString -> UnpackResult ByteString
forall a. MessagePack a => ByteString -> Either DecodeError a
unpackEither (() -> ByteString
forall a. MessagePack a => a -> ByteString
pack ()) :: UnpackResult S.ByteString)
      UnpackResult Text -> Expectation
forall a. Show a => UnpackResult a -> Expectation
checkMessage (ByteString -> UnpackResult Text
forall a. MessagePack a => ByteString -> Either DecodeError a
unpackEither (() -> ByteString
forall a. MessagePack a => a -> ByteString
pack ()) :: UnpackResult LT.Text)
      UnpackResult [String] -> Expectation
forall a. Show a => UnpackResult a -> Expectation
checkMessage (ByteString -> UnpackResult [String]
forall a. MessagePack a => ByteString -> Either DecodeError a
unpackEither (String -> ByteString
forall a. MessagePack a => a -> ByteString
pack String
"") :: UnpackResult [String])
      UnpackResult (Vector Int) -> Expectation
forall a. Show a => UnpackResult a -> Expectation
checkMessage (ByteString -> UnpackResult (Vector Int)
forall a. MessagePack a => ByteString -> Either DecodeError a
unpackEither (() -> ByteString
forall a. MessagePack a => a -> ByteString
pack ()) :: UnpackResult (V.Vector Int))
      UnpackResult (Vector Int) -> Expectation
forall a. Show a => UnpackResult a -> Expectation
checkMessage (ByteString -> UnpackResult (Vector Int)
forall a. MessagePack a => ByteString -> Either DecodeError a
unpackEither (() -> ByteString
forall a. MessagePack a => a -> ByteString
pack ()) :: UnpackResult (VS.Vector Int))
      UnpackResult (Vector Int) -> Expectation
forall a. Show a => UnpackResult a -> Expectation
checkMessage (ByteString -> UnpackResult (Vector Int)
forall a. MessagePack a => ByteString -> Either DecodeError a
unpackEither (() -> ByteString
forall a. MessagePack a => a -> ByteString
pack ()) :: UnpackResult (VU.Vector Int))
      UnpackResult (Assoc [(Int, Int)]) -> Expectation
forall a. Show a => UnpackResult a -> Expectation
checkMessage (ByteString -> UnpackResult (Assoc [(Int, Int)])
forall a. MessagePack a => ByteString -> Either DecodeError a
unpackEither (String -> ByteString
forall a. MessagePack a => a -> ByteString
pack String
"") :: UnpackResult (Assoc [(Int, Int)]))
      UnpackResult (Int, Int) -> Expectation
forall a. Show a => UnpackResult a -> Expectation
checkMessage (ByteString -> UnpackResult (Int, Int)
forall a. MessagePack a => ByteString -> Either DecodeError a
unpackEither (() -> ByteString
forall a. MessagePack a => a -> ByteString
pack ()) :: UnpackResult (Int, Int))
      UnpackResult (Int, Int, Int) -> Expectation
forall a. Show a => UnpackResult a -> Expectation
checkMessage (ByteString -> UnpackResult (Int, Int, Int)
forall a. MessagePack a => ByteString -> Either DecodeError a
unpackEither (() -> ByteString
forall a. MessagePack a => a -> ByteString
pack ()) :: UnpackResult (Int, Int, Int))
      UnpackResult (Int, Int, Int, Int) -> Expectation
forall a. Show a => UnpackResult a -> Expectation
checkMessage (ByteString -> UnpackResult (Int, Int, Int, Int)
forall a. MessagePack a => ByteString -> Either DecodeError a
unpackEither (() -> ByteString
forall a. MessagePack a => a -> ByteString
pack ()) :: UnpackResult (Int, Int, Int, Int))
      UnpackResult (Int, Int, Int, Int, Int) -> Expectation
forall a. Show a => UnpackResult a -> Expectation
checkMessage (ByteString -> UnpackResult (Int, Int, Int, Int, Int)
forall a. MessagePack a => ByteString -> Either DecodeError a
unpackEither (() -> ByteString
forall a. MessagePack a => a -> ByteString
pack ()) :: UnpackResult (Int, Int, Int, Int, Int))
      UnpackResult (Int, Int, Int, Int, Int, Int) -> Expectation
forall a. Show a => UnpackResult a -> Expectation
checkMessage (ByteString -> UnpackResult (Int, Int, Int, Int, Int, Int)
forall a. MessagePack a => ByteString -> Either DecodeError a
unpackEither (() -> ByteString
forall a. MessagePack a => a -> ByteString
pack ()) :: UnpackResult (Int, Int, Int, Int, Int, Int))
      UnpackResult (Int, Int, Int, Int, Int, Int, Int) -> Expectation
forall a. Show a => UnpackResult a -> Expectation
checkMessage (ByteString -> UnpackResult (Int, Int, Int, Int, Int, Int, Int)
forall a. MessagePack a => ByteString -> Either DecodeError a
unpackEither (() -> ByteString
forall a. MessagePack a => a -> ByteString
pack ()) :: UnpackResult (Int, Int, Int, Int, Int, Int, Int))
      UnpackResult (Int, Int, Int, Int, Int, Int, Int, Int)
-> Expectation
forall a. Show a => UnpackResult a -> Expectation
checkMessage (ByteString -> UnpackResult (Int, Int, Int, Int, Int, Int, Int, Int)
forall a. MessagePack a => ByteString -> Either DecodeError a
unpackEither (() -> ByteString
forall a. MessagePack a => a -> ByteString
pack ()) :: UnpackResult (Int, Int, Int, Int, Int, Int, Int, Int))
      UnpackResult (Int, Int, Int, Int, Int, Int, Int, Int, Int)
-> Expectation
forall a. Show a => UnpackResult a -> Expectation
checkMessage (ByteString
-> UnpackResult (Int, Int, Int, Int, Int, Int, Int, Int, Int)
forall a. MessagePack a => ByteString -> Either DecodeError a
unpackEither (() -> ByteString
forall a. MessagePack a => a -> ByteString
pack ()) :: UnpackResult (Int, Int, Int, Int, Int, Int, Int, Int, Int))

  String -> Spec -> Spec
forall a. HasCallStack => String -> SpecWith a -> SpecWith a
describe String
"type coercion" (Spec -> Spec) -> Spec -> Spec
forall a b. (a -> b) -> a -> b
$ do
    String -> Property -> SpecWith (Arg Property)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"bool<-int" (Property -> SpecWith (Arg Property))
-> Property -> SpecWith (Arg Property)
forall a b. (a -> b) -> a -> b
$
      (Int -> Expectation) -> Property
forall prop. Testable prop => prop -> Property
property ((Int -> Expectation) -> Property)
-> (Int -> Expectation) -> Property
forall a b. (a -> b) -> a -> b
$ \(Int
a :: Int) -> Int -> Maybe Bool
forall a b. (MessagePack a, MessagePack b) => a -> Maybe b
coerce Int
a Maybe Bool -> Maybe Bool -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` (Maybe Bool
forall a. Maybe a
Nothing :: Maybe Bool)

    String -> Property -> SpecWith (Arg Property)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"int<-bool" (Property -> SpecWith (Arg Property))
-> Property -> SpecWith (Arg Property)
forall a b. (a -> b) -> a -> b
$
      (Bool -> Expectation) -> Property
forall prop. Testable prop => prop -> Property
property ((Bool -> Expectation) -> Property)
-> (Bool -> Expectation) -> Property
forall a b. (a -> b) -> a -> b
$ \(Bool
a :: Bool) -> Bool -> Maybe Int
forall a b. (MessagePack a, MessagePack b) => a -> Maybe b
coerce Bool
a Maybe Int -> Maybe Int -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` (Maybe Int
forall a. Maybe a
Nothing :: Maybe Int)

    String -> Property -> SpecWith (Arg Property)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"float<-int" (Property -> SpecWith (Arg Property))
-> Property -> SpecWith (Arg Property)
forall a b. (a -> b) -> a -> b
$
      (Int -> Expectation) -> Property
forall prop. Testable prop => prop -> Property
property ((Int -> Expectation) -> Property)
-> (Int -> Expectation) -> Property
forall a b. (a -> b) -> a -> b
$ \(Int
a :: Int) -> Int -> Maybe Float
forall a b. (MessagePack a, MessagePack b) => a -> Maybe b
coerce Int
a Maybe Float -> Maybe Float -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` Float -> Maybe Float
forall a. a -> Maybe a
Just (Int -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
a :: Float)
    String -> Property -> SpecWith (Arg Property)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"float<-double" (Property -> SpecWith (Arg Property))
-> Property -> SpecWith (Arg Property)
forall a b. (a -> b) -> a -> b
$
      (Double -> Expectation) -> Property
forall prop. Testable prop => prop -> Property
property ((Double -> Expectation) -> Property)
-> (Double -> Expectation) -> Property
forall a b. (a -> b) -> a -> b
$ \(Double
a :: Double) -> Double -> Maybe Float
forall a b. (MessagePack a, MessagePack b) => a -> Maybe b
coerce Double
a Maybe Float -> Maybe Float -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` Float -> Maybe Float
forall a. a -> Maybe a
Just (Double -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
a :: Float)
    String -> Property -> SpecWith (Arg Property)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"float<-string" (Property -> SpecWith (Arg Property))
-> Property -> SpecWith (Arg Property)
forall a b. (a -> b) -> a -> b
$
      (String -> Expectation) -> Property
forall prop. Testable prop => prop -> Property
property ((String -> Expectation) -> Property)
-> (String -> Expectation) -> Property
forall a b. (a -> b) -> a -> b
$ \(String
a :: String) -> String -> Maybe Float
forall a b. (MessagePack a, MessagePack b) => a -> Maybe b
coerce String
a Maybe Float -> Maybe Float -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` (Maybe Float
forall a. Maybe a
Nothing :: Maybe Float)

    String -> Property -> SpecWith (Arg Property)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"double<-int" (Property -> SpecWith (Arg Property))
-> Property -> SpecWith (Arg Property)
forall a b. (a -> b) -> a -> b
$
      (Int -> Expectation) -> Property
forall prop. Testable prop => prop -> Property
property ((Int -> Expectation) -> Property)
-> (Int -> Expectation) -> Property
forall a b. (a -> b) -> a -> b
$ \(Int
a :: Int) -> Int -> Maybe Double
forall a b. (MessagePack a, MessagePack b) => a -> Maybe b
coerce Int
a Maybe Double -> Maybe Double -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` Double -> Maybe Double
forall a. a -> Maybe a
Just (Int -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
a :: Double)
    String -> Property -> SpecWith (Arg Property)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"double<-float" (Property -> SpecWith (Arg Property))
-> Property -> SpecWith (Arg Property)
forall a b. (a -> b) -> a -> b
$
      (Float -> Expectation) -> Property
forall prop. Testable prop => prop -> Property
property ((Float -> Expectation) -> Property)
-> (Float -> Expectation) -> Property
forall a b. (a -> b) -> a -> b
$ \(Float
a :: Float) -> Float -> Maybe Double
forall a b. (MessagePack a, MessagePack b) => a -> Maybe b
coerce Float
a Maybe Double -> Maybe Double -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` Double -> Maybe Double
forall a. a -> Maybe a
Just (Float -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
a :: Double)
    String -> Property -> SpecWith (Arg Property)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"double<-string" (Property -> SpecWith (Arg Property))
-> Property -> SpecWith (Arg Property)
forall a b. (a -> b) -> a -> b
$
      (String -> Expectation) -> Property
forall prop. Testable prop => prop -> Property
property ((String -> Expectation) -> Property)
-> (String -> Expectation) -> Property
forall a b. (a -> b) -> a -> b
$ \(String
a :: String) -> String -> Maybe Double
forall a b. (MessagePack a, MessagePack b) => a -> Maybe b
coerce String
a Maybe Double -> Maybe Double -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` (Maybe Double
forall a. Maybe a
Nothing :: Maybe Double)

    String -> Property -> SpecWith (Arg Property)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"bin<-string" (Property -> SpecWith (Arg Property))
-> Property -> SpecWith (Arg Property)
forall a b. (a -> b) -> a -> b
$
      (ByteString -> Expectation) -> Property
forall prop. Testable prop => prop -> Property
property ((ByteString -> Expectation) -> Property)
-> (ByteString -> Expectation) -> Property
forall a b. (a -> b) -> a -> b
$ \(ByteString
a :: S.ByteString) -> ByteString -> Maybe String
forall a b. (MessagePack a, MessagePack b) => a -> Maybe b
coerce ByteString
a Maybe String -> Maybe String -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` (Maybe String
forall a. Maybe a
Nothing :: Maybe String)

    String -> Property -> SpecWith (Arg Property)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"string<-bin" (Property -> SpecWith (Arg Property))
-> Property -> SpecWith (Arg Property)
forall a b. (a -> b) -> a -> b
$
      (String -> Expectation) -> Property
forall prop. Testable prop => prop -> Property
property ((String -> Expectation) -> Property)
-> (String -> Expectation) -> Property
forall a b. (a -> b) -> a -> b
$ \(String
a :: String) -> String -> Maybe ByteString
forall a b. (MessagePack a, MessagePack b) => a -> Maybe b
coerce String
a Maybe ByteString -> Maybe ByteString -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` (Maybe ByteString
forall a. Maybe a
Nothing :: Maybe S.ByteString)

  String -> Spec -> Spec
forall a. HasCallStack => String -> SpecWith a -> SpecWith a
describe String
"Identity Properties" (Spec -> Spec) -> Spec -> Spec
forall a b. (a -> b) -> a -> b
$ do
    let sizes :: [Int]
sizes = [Int
0xf, Int
0x10, Int
0x1f, Int
0x20, Int
0xff, Int
0x100, Int
0xffff, Int
0x10000]

    String -> Expectation -> SpecWith (Arg Expectation)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"unit encoding" (Expectation -> SpecWith (Arg Expectation))
-> Expectation -> SpecWith (Arg Expectation)
forall a b. (a -> b) -> a -> b
$
      Unit
Unit Unit -> Unit -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` Unit -> Unit
forall a. MessagePack a => a -> a
mid Unit
Unit

    String -> Expectation -> SpecWith (Arg Expectation)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"map encodings" (Expectation -> SpecWith (Arg Expectation))
-> Expectation -> SpecWith (Arg Expectation)
forall a b. (a -> b) -> a -> b
$ do
      let rt :: Int -> Expectation
rt Int
n = let a :: IntMap Int
a = [(Int, Int)] -> IntMap Int
forall a. [(Int, a)] -> IntMap a
IntMap.fromList [(Int
x, -Int
x) | Int
x <- [Int
0..Int
n]] in IntMap Int
a IntMap Int -> IntMap Int -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` IntMap Int -> IntMap Int
forall a. MessagePack a => a -> a
mid IntMap Int
a
      (Int -> Expectation) -> [Int] -> Expectation
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ Int -> Expectation
rt [Int]
sizes

    String -> Expectation -> SpecWith (Arg Expectation)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"list encodings" (Expectation -> SpecWith (Arg Expectation))
-> Expectation -> SpecWith (Arg Expectation)
forall a b. (a -> b) -> a -> b
$ do
      let rt :: Int -> Expectation
rt Int
n = let a :: [String]
a = Int -> String -> [String]
forall a. Int -> a -> [a]
replicate Int
n String
"hello" in [String]
a [String] -> [String] -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` [String] -> [String]
forall a. MessagePack a => a -> a
mid [String]
a
      (Int -> Expectation) -> [Int] -> Expectation
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ Int -> Expectation
rt [Int]
sizes

    String -> Expectation -> SpecWith (Arg Expectation)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"vector encodings" (Expectation -> SpecWith (Arg Expectation))
-> Expectation -> SpecWith (Arg Expectation)
forall a b. (a -> b) -> a -> b
$ do
      let rt :: a -> Expectation
rt a
n = let a :: Vector a
a = [a] -> Vector a
forall a. [a] -> Vector a
V.fromList [a
0..a
n] in Vector a
a Vector a -> Vector a -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` Vector a -> Vector a
forall a. MessagePack a => a -> a
mid Vector a
a
      (Int -> Expectation) -> [Int] -> Expectation
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ Int -> Expectation
forall a.
(Show a, Eq a, MessagePack a, Num a, Enum a) =>
a -> Expectation
rt [Int]
sizes

    String -> Expectation -> SpecWith (Arg Expectation)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"storable-vector encodings" (Expectation -> SpecWith (Arg Expectation))
-> Expectation -> SpecWith (Arg Expectation)
forall a b. (a -> b) -> a -> b
$ do
      let rt :: a -> Expectation
rt a
n = let a :: Vector a
a = [a] -> Vector a
forall a. Storable a => [a] -> Vector a
VS.fromList [a
0..a
n] in Vector a
a Vector a -> Vector a -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` Vector a -> Vector a
forall a. MessagePack a => a -> a
mid Vector a
a
      (Int -> Expectation) -> [Int] -> Expectation
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ Int -> Expectation
forall a.
(Show a, Eq a, MessagePack a, Storable a, Num a, Enum a) =>
a -> Expectation
rt [Int]
sizes

    String -> Expectation -> SpecWith (Arg Expectation)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"unboxed-vector encodings" (Expectation -> SpecWith (Arg Expectation))
-> Expectation -> SpecWith (Arg Expectation)
forall a b. (a -> b) -> a -> b
$ do
      let rt :: a -> Expectation
rt a
n = let a :: Vector a
a = [a] -> Vector a
forall a. Unbox a => [a] -> Vector a
VU.fromList [a
0..a
n] in Vector a
a Vector a -> Vector a -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` Vector a -> Vector a
forall a. MessagePack a => a -> a
mid Vector a
a
      (Int -> Expectation) -> [Int] -> Expectation
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ Int -> Expectation
forall a.
(Show a, Eq a, MessagePack a, Unbox a, Num a, Enum a) =>
a -> Expectation
rt [Int]
sizes

    String -> Expectation -> SpecWith (Arg Expectation)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"string encodings" (Expectation -> SpecWith (Arg Expectation))
-> Expectation -> SpecWith (Arg Expectation)
forall a b. (a -> b) -> a -> b
$ do
      let rt :: Int -> Expectation
rt Int
n = let a :: String
a = Int -> Char -> String
forall a. Int -> a -> [a]
replicate Int
n Char
'a' in String
a String -> String -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` ShowS
forall a. MessagePack a => a -> a
mid String
a
      (Int -> Expectation) -> [Int] -> Expectation
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ Int -> Expectation
rt [Int]
sizes

    String -> Expectation -> SpecWith (Arg Expectation)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"bytestring encodings" (Expectation -> SpecWith (Arg Expectation))
-> Expectation -> SpecWith (Arg Expectation)
forall a b. (a -> b) -> a -> b
$ do
      let rt :: Int -> Expectation
rt Int
n = let a :: ByteString
a = String -> ByteString
S.pack (String -> ByteString) -> String -> ByteString
forall a b. (a -> b) -> a -> b
$ Int -> Char -> String
forall a. Int -> a -> [a]
replicate Int
n Char
'a' in ByteString
a ByteString -> ByteString -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` ByteString -> ByteString
forall a. MessagePack a => a -> a
mid ByteString
a
      (Int -> Expectation) -> [Int] -> Expectation
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ Int -> Expectation
rt [Int]
sizes

    String -> Expectation -> SpecWith (Arg Expectation)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"ext encodings" (Expectation -> SpecWith (Arg Expectation))
-> Expectation -> SpecWith (Arg Expectation)
forall a b. (a -> b) -> a -> b
$ do
      let rt :: Int -> Expectation
rt Int
n = let a :: Object
a = Word8 -> ByteString -> Object
ObjectExt Word8
0 (ByteString -> Object) -> ByteString -> Object
forall a b. (a -> b) -> a -> b
$ String -> ByteString
S.pack (String -> ByteString) -> String -> ByteString
forall a b. (a -> b) -> a -> b
$ Int -> Char -> String
forall a. Int -> a -> [a]
replicate Int
n Char
'a' in Object
a Object -> Object -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` Object -> Object
forall a. MessagePack a => a -> a
mid Object
a
      (Int -> Expectation) -> [Int] -> Expectation
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ Int -> Expectation
rt [Int
0..Int
20]
      (Int -> Expectation) -> [Int] -> Expectation
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ Int -> Expectation
rt [Int]
sizes

    String -> Expectation -> SpecWith (Arg Expectation)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"int encodings" (Expectation -> SpecWith (Arg Expectation))
-> Expectation -> SpecWith (Arg Expectation)
forall a b. (a -> b) -> a -> b
$ do
      (-Int64
0x7fffffffffffffff) Int64 -> Int64 -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` Int64 -> Int64
intMid (-Int64
0x7fffffffffffffff)
      (-Int64
0x80000000) Int64 -> Int64 -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` Int64 -> Int64
intMid (-Int64
0x80000000)
      (-Int64
0x7fffffff) Int64 -> Int64 -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` Int64 -> Int64
intMid (-Int64
0x7fffffff)
      (-Int64
0x8000) Int64 -> Int64 -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` Int64 -> Int64
intMid (-Int64
0x8000)
      (-Int64
0x7fff) Int64 -> Int64 -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` Int64 -> Int64
intMid (-Int64
0x7fff)
      (-Int64
1) Int64 -> Int64 -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` Int64 -> Int64
intMid (-Int64
1)
      Int64
0 Int64 -> Int64 -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` Int64 -> Int64
intMid Int64
0
      Int64
1 Int64 -> Int64 -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` Int64 -> Int64
intMid Int64
1
      Int64
0x7fff Int64 -> Int64 -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` Int64 -> Int64
intMid Int64
0x7fff
      Int64
0x8000 Int64 -> Int64 -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` Int64 -> Int64
intMid Int64
0x8000
      Int64
0x7fffffff Int64 -> Int64 -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` Int64 -> Int64
intMid Int64
0x7fffffff
      Int64
0x80000000 Int64 -> Int64 -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` Int64 -> Int64
intMid Int64
0x80000000
      Int64
0x7fffffffffffffff Int64 -> Int64 -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` Int64 -> Int64
intMid Int64
0x7fffffffffffffff

    String -> Property -> SpecWith (Arg Property)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"int"    (Property -> SpecWith (Arg Property))
-> Property -> SpecWith (Arg Property)
forall a b. (a -> b) -> a -> b
$ (Int -> Expectation) -> Property
forall prop. Testable prop => prop -> Property
property ((Int -> Expectation) -> Property)
-> (Int -> Expectation) -> Property
forall a b. (a -> b) -> a -> b
$ \(Int
a :: Int   ) -> Int
a Int -> Int -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` Int -> Int
forall a. MessagePack a => a -> a
mid Int
a
    String -> Property -> SpecWith (Arg Property)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"int8"   (Property -> SpecWith (Arg Property))
-> Property -> SpecWith (Arg Property)
forall a b. (a -> b) -> a -> b
$ (Int8 -> Expectation) -> Property
forall prop. Testable prop => prop -> Property
property ((Int8 -> Expectation) -> Property)
-> (Int8 -> Expectation) -> Property
forall a b. (a -> b) -> a -> b
$ \(Int8
a :: Int8  ) -> Int8
a Int8 -> Int8 -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` Int8 -> Int8
forall a. MessagePack a => a -> a
mid Int8
a
    String -> Property -> SpecWith (Arg Property)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"int16"  (Property -> SpecWith (Arg Property))
-> Property -> SpecWith (Arg Property)
forall a b. (a -> b) -> a -> b
$ (Int16 -> Expectation) -> Property
forall prop. Testable prop => prop -> Property
property ((Int16 -> Expectation) -> Property)
-> (Int16 -> Expectation) -> Property
forall a b. (a -> b) -> a -> b
$ \(Int16
a :: Int16 ) -> Int16
a Int16 -> Int16 -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` Int16 -> Int16
forall a. MessagePack a => a -> a
mid Int16
a
    String -> Property -> SpecWith (Arg Property)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"int32"  (Property -> SpecWith (Arg Property))
-> Property -> SpecWith (Arg Property)
forall a b. (a -> b) -> a -> b
$ (Int32 -> Expectation) -> Property
forall prop. Testable prop => prop -> Property
property ((Int32 -> Expectation) -> Property)
-> (Int32 -> Expectation) -> Property
forall a b. (a -> b) -> a -> b
$ \(Int32
a :: Int32 ) -> Int32
a Int32 -> Int32 -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` Int32 -> Int32
forall a. MessagePack a => a -> a
mid Int32
a
    String -> Property -> SpecWith (Arg Property)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"int64"  (Property -> SpecWith (Arg Property))
-> Property -> SpecWith (Arg Property)
forall a b. (a -> b) -> a -> b
$ (Int64 -> Expectation) -> Property
forall prop. Testable prop => prop -> Property
property ((Int64 -> Expectation) -> Property)
-> (Int64 -> Expectation) -> Property
forall a b. (a -> b) -> a -> b
$ \(Int64
a :: Int64 ) -> Int64
a Int64 -> Int64 -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` Int64 -> Int64
forall a. MessagePack a => a -> a
mid Int64
a
    String -> Property -> SpecWith (Arg Property)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"word"   (Property -> SpecWith (Arg Property))
-> Property -> SpecWith (Arg Property)
forall a b. (a -> b) -> a -> b
$ (Word -> Expectation) -> Property
forall prop. Testable prop => prop -> Property
property ((Word -> Expectation) -> Property)
-> (Word -> Expectation) -> Property
forall a b. (a -> b) -> a -> b
$ \(Word
a :: Word  ) -> Word
a Word -> Word -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` Word -> Word
forall a. MessagePack a => a -> a
mid Word
a
    String -> Property -> SpecWith (Arg Property)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"word8"  (Property -> SpecWith (Arg Property))
-> Property -> SpecWith (Arg Property)
forall a b. (a -> b) -> a -> b
$ (Word8 -> Expectation) -> Property
forall prop. Testable prop => prop -> Property
property ((Word8 -> Expectation) -> Property)
-> (Word8 -> Expectation) -> Property
forall a b. (a -> b) -> a -> b
$ \(Word8
a :: Word8 ) -> Word8
a Word8 -> Word8 -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` Word8 -> Word8
forall a. MessagePack a => a -> a
mid Word8
a
    String -> Property -> SpecWith (Arg Property)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"word16" (Property -> SpecWith (Arg Property))
-> Property -> SpecWith (Arg Property)
forall a b. (a -> b) -> a -> b
$ (Word16 -> Expectation) -> Property
forall prop. Testable prop => prop -> Property
property ((Word16 -> Expectation) -> Property)
-> (Word16 -> Expectation) -> Property
forall a b. (a -> b) -> a -> b
$ \(Word16
a :: Word16) -> Word16
a Word16 -> Word16 -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` Word16 -> Word16
forall a. MessagePack a => a -> a
mid Word16
a
    String -> Property -> SpecWith (Arg Property)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"word32" (Property -> SpecWith (Arg Property))
-> Property -> SpecWith (Arg Property)
forall a b. (a -> b) -> a -> b
$ (Word32 -> Expectation) -> Property
forall prop. Testable prop => prop -> Property
property ((Word32 -> Expectation) -> Property)
-> (Word32 -> Expectation) -> Property
forall a b. (a -> b) -> a -> b
$ \(Word32
a :: Word32) -> Word32
a Word32 -> Word32 -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` Word32 -> Word32
forall a. MessagePack a => a -> a
mid Word32
a
    String -> Property -> SpecWith (Arg Property)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"word64" (Property -> SpecWith (Arg Property))
-> Property -> SpecWith (Arg Property)
forall a b. (a -> b) -> a -> b
$ (Word64 -> Expectation) -> Property
forall prop. Testable prop => prop -> Property
property ((Word64 -> Expectation) -> Property)
-> (Word64 -> Expectation) -> Property
forall a b. (a -> b) -> a -> b
$ \(Word64
a :: Word64) -> Word64
a Word64 -> Word64 -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` Word64 -> Word64
forall a. MessagePack a => a -> a
mid Word64
a

    String -> Property -> SpecWith (Arg Property)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"ext" (Property -> SpecWith (Arg Property))
-> Property -> SpecWith (Arg Property)
forall a b. (a -> b) -> a -> b
$
      ((Word8, ByteString) -> Expectation) -> Property
forall prop. Testable prop => prop -> Property
property (((Word8, ByteString) -> Expectation) -> Property)
-> ((Word8, ByteString) -> Expectation) -> Property
forall a b. (a -> b) -> a -> b
$ \(Word8
n, ByteString
a) -> Word8 -> ByteString -> Object
ObjectExt Word8
n ByteString
a Object -> Object -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` Object -> Object
forall a. MessagePack a => a -> a
mid (Word8 -> ByteString -> Object
ObjectExt Word8
n ByteString
a)
    String -> Property -> SpecWith (Arg Property)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"nil" (Property -> SpecWith (Arg Property))
-> Property -> SpecWith (Arg Property)
forall a b. (a -> b) -> a -> b
$
      (() -> Expectation) -> Property
forall prop. Testable prop => prop -> Property
property ((() -> Expectation) -> Property)
-> (() -> Expectation) -> Property
forall a b. (a -> b) -> a -> b
$ \(()
a :: ()) -> ()
a () -> () -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` () -> ()
forall a. MessagePack a => a -> a
mid ()
a
    String -> Property -> SpecWith (Arg Property)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"bool" (Property -> SpecWith (Arg Property))
-> Property -> SpecWith (Arg Property)
forall a b. (a -> b) -> a -> b
$
      (Bool -> Expectation) -> Property
forall prop. Testable prop => prop -> Property
property ((Bool -> Expectation) -> Property)
-> (Bool -> Expectation) -> Property
forall a b. (a -> b) -> a -> b
$ \(Bool
a :: Bool) -> Bool
a Bool -> Bool -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` Bool -> Bool
forall a. MessagePack a => a -> a
mid Bool
a
    String -> Property -> SpecWith (Arg Property)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"float" (Property -> SpecWith (Arg Property))
-> Property -> SpecWith (Arg Property)
forall a b. (a -> b) -> a -> b
$
      (Float -> Expectation) -> Property
forall prop. Testable prop => prop -> Property
property ((Float -> Expectation) -> Property)
-> (Float -> Expectation) -> Property
forall a b. (a -> b) -> a -> b
$ \(Float
a :: Float) -> Float
a Float -> Float -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` Float -> Float
forall a. MessagePack a => a -> a
mid Float
a
    String -> Property -> SpecWith (Arg Property)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"double" (Property -> SpecWith (Arg Property))
-> Property -> SpecWith (Arg Property)
forall a b. (a -> b) -> a -> b
$
      (Double -> Expectation) -> Property
forall prop. Testable prop => prop -> Property
property ((Double -> Expectation) -> Property)
-> (Double -> Expectation) -> Property
forall a b. (a -> b) -> a -> b
$ \(Double
a :: Double) -> Double
a Double -> Double -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` Double -> Double
forall a. MessagePack a => a -> a
mid Double
a
    String -> Property -> SpecWith (Arg Property)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"string" (Property -> SpecWith (Arg Property))
-> Property -> SpecWith (Arg Property)
forall a b. (a -> b) -> a -> b
$
      (String -> Expectation) -> Property
forall prop. Testable prop => prop -> Property
property ((String -> Expectation) -> Property)
-> (String -> Expectation) -> Property
forall a b. (a -> b) -> a -> b
$ \(String
a :: String) -> String
a String -> String -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` ShowS
forall a. MessagePack a => a -> a
mid String
a
    String -> Property -> SpecWith (Arg Property)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"bytestring" (Property -> SpecWith (Arg Property))
-> Property -> SpecWith (Arg Property)
forall a b. (a -> b) -> a -> b
$
      (ByteString -> Expectation) -> Property
forall prop. Testable prop => prop -> Property
property ((ByteString -> Expectation) -> Property)
-> (ByteString -> Expectation) -> Property
forall a b. (a -> b) -> a -> b
$ \(ByteString
a :: S.ByteString) -> ByteString
a ByteString -> ByteString -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` ByteString -> ByteString
forall a. MessagePack a => a -> a
mid ByteString
a
    String -> Property -> SpecWith (Arg Property)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"lazy-bytestring" (Property -> SpecWith (Arg Property))
-> Property -> SpecWith (Arg Property)
forall a b. (a -> b) -> a -> b
$
      (ByteString -> Expectation) -> Property
forall prop. Testable prop => prop -> Property
property ((ByteString -> Expectation) -> Property)
-> (ByteString -> Expectation) -> Property
forall a b. (a -> b) -> a -> b
$ \(ByteString
a :: L.ByteString) -> ByteString
a ByteString -> ByteString -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` ByteString -> ByteString
forall a. MessagePack a => a -> a
mid ByteString
a
    String -> Property -> SpecWith (Arg Property)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"lazy-text" (Property -> SpecWith (Arg Property))
-> Property -> SpecWith (Arg Property)
forall a b. (a -> b) -> a -> b
$
      (Text -> Expectation) -> Property
forall prop. Testable prop => prop -> Property
property ((Text -> Expectation) -> Property)
-> (Text -> Expectation) -> Property
forall a b. (a -> b) -> a -> b
$ \(Text
a :: LT.Text) -> Text
a Text -> Text -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` Text -> Text
forall a. MessagePack a => a -> a
mid Text
a
    String -> Property -> SpecWith (Arg Property)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"[int]" (Property -> SpecWith (Arg Property))
-> Property -> SpecWith (Arg Property)
forall a b. (a -> b) -> a -> b
$
      ([Int] -> Expectation) -> Property
forall prop. Testable prop => prop -> Property
property (([Int] -> Expectation) -> Property)
-> ([Int] -> Expectation) -> Property
forall a b. (a -> b) -> a -> b
$ \([Int]
a :: [Int]) -> [Int]
a [Int] -> [Int] -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` [Int] -> [Int]
forall a. MessagePack a => a -> a
mid [Int]
a
    String -> Property -> SpecWith (Arg Property)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"vector int" (Property -> SpecWith (Arg Property))
-> Property -> SpecWith (Arg Property)
forall a b. (a -> b) -> a -> b
$
      (Vector Int -> Expectation) -> Property
forall prop. Testable prop => prop -> Property
property ((Vector Int -> Expectation) -> Property)
-> (Vector Int -> Expectation) -> Property
forall a b. (a -> b) -> a -> b
$ \(Vector Int
a :: V.Vector Int) -> Vector Int
a Vector Int -> Vector Int -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` Vector Int -> Vector Int
forall a. MessagePack a => a -> a
mid Vector Int
a
    String -> Property -> SpecWith (Arg Property)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"storable-vector int" (Property -> SpecWith (Arg Property))
-> Property -> SpecWith (Arg Property)
forall a b. (a -> b) -> a -> b
$
      (Vector Int -> Expectation) -> Property
forall prop. Testable prop => prop -> Property
property ((Vector Int -> Expectation) -> Property)
-> (Vector Int -> Expectation) -> Property
forall a b. (a -> b) -> a -> b
$ \(Vector Int
a :: VS.Vector Int) -> Vector Int
a Vector Int -> Vector Int -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` Vector Int -> Vector Int
forall a. MessagePack a => a -> a
mid Vector Int
a
    String -> Property -> SpecWith (Arg Property)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"unboxed-vector int" (Property -> SpecWith (Arg Property))
-> Property -> SpecWith (Arg Property)
forall a b. (a -> b) -> a -> b
$
      (Vector Int -> Expectation) -> Property
forall prop. Testable prop => prop -> Property
property ((Vector Int -> Expectation) -> Property)
-> (Vector Int -> Expectation) -> Property
forall a b. (a -> b) -> a -> b
$ \(Vector Int
a :: VU.Vector Int) -> Vector Int
a Vector Int -> Vector Int -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` Vector Int -> Vector Int
forall a. MessagePack a => a -> a
mid Vector Int
a
    String -> Property -> SpecWith (Arg Property)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"[string]" (Property -> SpecWith (Arg Property))
-> Property -> SpecWith (Arg Property)
forall a b. (a -> b) -> a -> b
$
      ([String] -> Expectation) -> Property
forall prop. Testable prop => prop -> Property
property (([String] -> Expectation) -> Property)
-> ([String] -> Expectation) -> Property
forall a b. (a -> b) -> a -> b
$ \([String]
a :: [String]) -> [String]
a [String] -> [String] -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` [String] -> [String]
forall a. MessagePack a => a -> a
mid [String]
a
    String -> Property -> SpecWith (Arg Property)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"(int, int)" (Property -> SpecWith (Arg Property))
-> Property -> SpecWith (Arg Property)
forall a b. (a -> b) -> a -> b
$
      ((Int, Int) -> Expectation) -> Property
forall prop. Testable prop => prop -> Property
property (((Int, Int) -> Expectation) -> Property)
-> ((Int, Int) -> Expectation) -> Property
forall a b. (a -> b) -> a -> b
$ \((Int, Int)
a :: (Int, Int)) -> (Int, Int)
a (Int, Int) -> (Int, Int) -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` (Int, Int) -> (Int, Int)
forall a. MessagePack a => a -> a
mid (Int, Int)
a
    String -> Property -> SpecWith (Arg Property)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"(int, int, int)" (Property -> SpecWith (Arg Property))
-> Property -> SpecWith (Arg Property)
forall a b. (a -> b) -> a -> b
$
      ((Int, Int, Int) -> Expectation) -> Property
forall prop. Testable prop => prop -> Property
property (((Int, Int, Int) -> Expectation) -> Property)
-> ((Int, Int, Int) -> Expectation) -> Property
forall a b. (a -> b) -> a -> b
$ \((Int, Int, Int)
a :: (Int, Int, Int)) -> (Int, Int, Int)
a (Int, Int, Int) -> (Int, Int, Int) -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` (Int, Int, Int) -> (Int, Int, Int)
forall a. MessagePack a => a -> a
mid (Int, Int, Int)
a
    String -> Property -> SpecWith (Arg Property)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"(int, int, int, int)" (Property -> SpecWith (Arg Property))
-> Property -> SpecWith (Arg Property)
forall a b. (a -> b) -> a -> b
$
      ((Int, Int, Int, Int) -> Expectation) -> Property
forall prop. Testable prop => prop -> Property
property (((Int, Int, Int, Int) -> Expectation) -> Property)
-> ((Int, Int, Int, Int) -> Expectation) -> Property
forall a b. (a -> b) -> a -> b
$ \((Int, Int, Int, Int)
a :: (Int, Int, Int, Int)) -> (Int, Int, Int, Int)
a (Int, Int, Int, Int) -> (Int, Int, Int, Int) -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` (Int, Int, Int, Int) -> (Int, Int, Int, Int)
forall a. MessagePack a => a -> a
mid (Int, Int, Int, Int)
a
    String -> Property -> SpecWith (Arg Property)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"(int, int, int, int, int)" (Property -> SpecWith (Arg Property))
-> Property -> SpecWith (Arg Property)
forall a b. (a -> b) -> a -> b
$
      ((Int, Int, Int, Int, Int) -> Expectation) -> Property
forall prop. Testable prop => prop -> Property
property (((Int, Int, Int, Int, Int) -> Expectation) -> Property)
-> ((Int, Int, Int, Int, Int) -> Expectation) -> Property
forall a b. (a -> b) -> a -> b
$ \((Int, Int, Int, Int, Int)
a :: (Int, Int, Int, Int, Int)) -> (Int, Int, Int, Int, Int)
a (Int, Int, Int, Int, Int)
-> (Int, Int, Int, Int, Int) -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` (Int, Int, Int, Int, Int) -> (Int, Int, Int, Int, Int)
forall a. MessagePack a => a -> a
mid (Int, Int, Int, Int, Int)
a
    String -> Property -> SpecWith (Arg Property)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"(int, int, int, int, int, int)" (Property -> SpecWith (Arg Property))
-> Property -> SpecWith (Arg Property)
forall a b. (a -> b) -> a -> b
$
      ((Int, Int, Int, Int, Int, Int) -> Expectation) -> Property
forall prop. Testable prop => prop -> Property
property (((Int, Int, Int, Int, Int, Int) -> Expectation) -> Property)
-> ((Int, Int, Int, Int, Int, Int) -> Expectation) -> Property
forall a b. (a -> b) -> a -> b
$ \((Int, Int, Int, Int, Int, Int)
a :: (Int, Int, Int, Int, Int, Int)) -> (Int, Int, Int, Int, Int, Int)
a (Int, Int, Int, Int, Int, Int)
-> (Int, Int, Int, Int, Int, Int) -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` (Int, Int, Int, Int, Int, Int) -> (Int, Int, Int, Int, Int, Int)
forall a. MessagePack a => a -> a
mid (Int, Int, Int, Int, Int, Int)
a
    String -> Property -> SpecWith (Arg Property)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"(int, int, int, int, int, int, int)" (Property -> SpecWith (Arg Property))
-> Property -> SpecWith (Arg Property)
forall a b. (a -> b) -> a -> b
$
      ((Int, Int, Int, Int, Int, Int, Int) -> Expectation) -> Property
forall prop. Testable prop => prop -> Property
property (((Int, Int, Int, Int, Int, Int, Int) -> Expectation) -> Property)
-> ((Int, Int, Int, Int, Int, Int, Int) -> Expectation) -> Property
forall a b. (a -> b) -> a -> b
$ \((Int, Int, Int, Int, Int, Int, Int)
a :: (Int, Int, Int, Int, Int, Int, Int)) -> (Int, Int, Int, Int, Int, Int, Int)
a (Int, Int, Int, Int, Int, Int, Int)
-> (Int, Int, Int, Int, Int, Int, Int) -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` (Int, Int, Int, Int, Int, Int, Int)
-> (Int, Int, Int, Int, Int, Int, Int)
forall a. MessagePack a => a -> a
mid (Int, Int, Int, Int, Int, Int, Int)
a
    String -> Property -> SpecWith (Arg Property)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"(int, int, int, int, int, int, int, int)" (Property -> SpecWith (Arg Property))
-> Property -> SpecWith (Arg Property)
forall a b. (a -> b) -> a -> b
$
      ((Int, Int, Int, Int, Int, Int, Int, Int) -> Expectation)
-> Property
forall prop. Testable prop => prop -> Property
property (((Int, Int, Int, Int, Int, Int, Int, Int) -> Expectation)
 -> Property)
-> ((Int, Int, Int, Int, Int, Int, Int, Int) -> Expectation)
-> Property
forall a b. (a -> b) -> a -> b
$ \((Int, Int, Int, Int, Int, Int, Int, Int)
a :: (Int, Int, Int, Int, Int, Int, Int, Int)) -> (Int, Int, Int, Int, Int, Int, Int, Int)
a (Int, Int, Int, Int, Int, Int, Int, Int)
-> (Int, Int, Int, Int, Int, Int, Int, Int) -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` (Int, Int, Int, Int, Int, Int, Int, Int)
-> (Int, Int, Int, Int, Int, Int, Int, Int)
forall a. MessagePack a => a -> a
mid (Int, Int, Int, Int, Int, Int, Int, Int)
a
    String -> Property -> SpecWith (Arg Property)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"(int, int, int, int, int, int, int, int, int)" (Property -> SpecWith (Arg Property))
-> Property -> SpecWith (Arg Property)
forall a b. (a -> b) -> a -> b
$
      ((Int, Int, Int, Int, Int, Int, Int, Int, Int) -> Expectation)
-> Property
forall prop. Testable prop => prop -> Property
property (((Int, Int, Int, Int, Int, Int, Int, Int, Int) -> Expectation)
 -> Property)
-> ((Int, Int, Int, Int, Int, Int, Int, Int, Int) -> Expectation)
-> Property
forall a b. (a -> b) -> a -> b
$ \((Int, Int, Int, Int, Int, Int, Int, Int, Int)
a :: (Int, Int, Int, Int, Int, Int, Int, Int, Int)) -> (Int, Int, Int, Int, Int, Int, Int, Int, Int)
a (Int, Int, Int, Int, Int, Int, Int, Int, Int)
-> (Int, Int, Int, Int, Int, Int, Int, Int, Int) -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` (Int, Int, Int, Int, Int, Int, Int, Int, Int)
-> (Int, Int, Int, Int, Int, Int, Int, Int, Int)
forall a. MessagePack a => a -> a
mid (Int, Int, Int, Int, Int, Int, Int, Int, Int)
a
    String -> Property -> SpecWith (Arg Property)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"[(int, double)]" (Property -> SpecWith (Arg Property))
-> Property -> SpecWith (Arg Property)
forall a b. (a -> b) -> a -> b
$
      ([(Int, Double)] -> Expectation) -> Property
forall prop. Testable prop => prop -> Property
property (([(Int, Double)] -> Expectation) -> Property)
-> ([(Int, Double)] -> Expectation) -> Property
forall a b. (a -> b) -> a -> b
$ \([(Int, Double)]
a :: [(Int, Double)]) -> [(Int, Double)]
a [(Int, Double)] -> [(Int, Double)] -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` [(Int, Double)] -> [(Int, Double)]
forall a. MessagePack a => a -> a
mid [(Int, Double)]
a
    String -> Property -> SpecWith (Arg Property)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"[(string, string)]" (Property -> SpecWith (Arg Property))
-> Property -> SpecWith (Arg Property)
forall a b. (a -> b) -> a -> b
$
      ([(String, String)] -> Expectation) -> Property
forall prop. Testable prop => prop -> Property
property (([(String, String)] -> Expectation) -> Property)
-> ([(String, String)] -> Expectation) -> Property
forall a b. (a -> b) -> a -> b
$ \([(String, String)]
a :: [(String, String)]) -> [(String, String)]
a [(String, String)] -> [(String, String)] -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` [(String, String)] -> [(String, String)]
forall a. MessagePack a => a -> a
mid [(String, String)]
a
    String -> Property -> SpecWith (Arg Property)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"Assoc [(string, int)]" (Property -> SpecWith (Arg Property))
-> Property -> SpecWith (Arg Property)
forall a b. (a -> b) -> a -> b
$
      (Assoc [(String, Int)] -> Expectation) -> Property
forall prop. Testable prop => prop -> Property
property ((Assoc [(String, Int)] -> Expectation) -> Property)
-> (Assoc [(String, Int)] -> Expectation) -> Property
forall a b. (a -> b) -> a -> b
$ \(Assoc [(String, Int)]
a :: Assoc [(String, Int)]) -> Assoc [(String, Int)]
a Assoc [(String, Int)] -> Assoc [(String, Int)] -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` Assoc [(String, Int)] -> Assoc [(String, Int)]
forall a. MessagePack a => a -> a
mid Assoc [(String, Int)]
a
    String -> Property -> SpecWith (Arg Property)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"Map String Int" (Property -> SpecWith (Arg Property))
-> Property -> SpecWith (Arg Property)
forall a b. (a -> b) -> a -> b
$
      (Map String Int -> Expectation) -> Property
forall prop. Testable prop => prop -> Property
property ((Map String Int -> Expectation) -> Property)
-> (Map String Int -> Expectation) -> Property
forall a b. (a -> b) -> a -> b
$ \(Map String Int
a :: Map.Map String Int) -> Map String Int
a Map String Int -> Map String Int -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` Map String Int -> Map String Int
forall a. MessagePack a => a -> a
mid Map String Int
a
    String -> Property -> SpecWith (Arg Property)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"IntMap Int" (Property -> SpecWith (Arg Property))
-> Property -> SpecWith (Arg Property)
forall a b. (a -> b) -> a -> b
$
      (IntMap Int -> Expectation) -> Property
forall prop. Testable prop => prop -> Property
property ((IntMap Int -> Expectation) -> Property)
-> (IntMap Int -> Expectation) -> Property
forall a b. (a -> b) -> a -> b
$ \(IntMap Int
a :: IntMap.IntMap Int) -> IntMap Int
a IntMap Int -> IntMap Int -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` IntMap Int -> IntMap Int
forall a. MessagePack a => a -> a
mid IntMap Int
a
    String -> Property -> SpecWith (Arg Property)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"HashMap String Int" (Property -> SpecWith (Arg Property))
-> Property -> SpecWith (Arg Property)
forall a b. (a -> b) -> a -> b
$
      (HashMap String Int -> Expectation) -> Property
forall prop. Testable prop => prop -> Property
property ((HashMap String Int -> Expectation) -> Property)
-> (HashMap String Int -> Expectation) -> Property
forall a b. (a -> b) -> a -> b
$ \(HashMap String Int
a :: HashMap.HashMap String Int) -> HashMap String Int
a HashMap String Int -> HashMap String Int -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` HashMap String Int -> HashMap String Int
forall a. MessagePack a => a -> a
mid HashMap String Int
a

    String -> Property -> SpecWith (Arg Property)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"generics" (Property -> SpecWith (Arg Property))
-> Property -> SpecWith (Arg Property)
forall a b. (a -> b) -> a -> b
$
      (Foo -> Expectation) -> Property
forall prop. Testable prop => prop -> Property
property ((Foo -> Expectation) -> Property)
-> (Foo -> Expectation) -> Property
forall a b. (a -> b) -> a -> b
$ \(Foo
a :: Foo) -> Foo
a Foo -> Foo -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` Foo -> Foo
forall a. MessagePack a => a -> a
mid Foo
a
    String -> Property -> SpecWith (Arg Property)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"arbitrary message" (Property -> SpecWith (Arg Property))
-> Property -> SpecWith (Arg Property)
forall a b. (a -> b) -> a -> b
$
      (Object -> Expectation) -> Property
forall prop. Testable prop => prop -> Property
property ((Object -> Expectation) -> Property)
-> (Object -> Expectation) -> Property
forall a b. (a -> b) -> a -> b
$ \(Object
a :: Object) -> Object
a Object -> Object -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` Object -> Object
forall a. MessagePack a => a -> a
mid Object
a

  String -> Spec -> Spec
forall a. HasCallStack => String -> SpecWith a -> SpecWith a
describe String
"encoding validation" (Spec -> Spec) -> Spec -> Spec
forall a b. (a -> b) -> a -> b
$ do
    String -> Expectation -> SpecWith (Arg Expectation)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"word64 2^64-1" (Expectation -> SpecWith (Arg Expectation))
-> Expectation -> SpecWith (Arg Expectation)
forall a b. (a -> b) -> a -> b
$
      Word64 -> ByteString
forall a. MessagePack a => a -> ByteString
pack (Word64
0xffffffffffffffff :: Word64) ByteString -> ByteString -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` [Word8] -> ByteString
L8.pack [Word8
0xCF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF]

    String -> Expectation -> SpecWith (Arg Expectation)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"decodes empty array as ()" (Expectation -> SpecWith (Arg Expectation))
-> Expectation -> SpecWith (Arg Expectation)
forall a b. (a -> b) -> a -> b
$
      ByteString -> Maybe ()
forall (m :: * -> *) a.
(MonadFail m, MessagePack a) =>
ByteString -> m a
unpack ([Int] -> ByteString
forall a. MessagePack a => a -> ByteString
pack ([] :: [Int])) Maybe () -> Maybe () -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` () -> Maybe ()
forall a. a -> Maybe a
Just ()

  where
    mid :: MessagePack a => a -> a
    mid :: a -> a
mid = Maybe a -> a
forall a. HasCallStack => Maybe a -> a
Maybe.fromJust (Maybe a -> a) -> (a -> Maybe a) -> a -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Maybe a
forall (m :: * -> *) a.
(MonadFail m, MessagePack a) =>
ByteString -> m a
unpack (ByteString -> Maybe a) -> (a -> ByteString) -> a -> Maybe a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> ByteString
forall a. MessagePack a => a -> ByteString
pack

    intMid :: Int64 -> Int64
    intMid :: Int64 -> Int64
intMid = Int64 -> Int64
forall a. MessagePack a => a -> a
mid

    unpackEither :: MessagePack a => L.ByteString -> Either DecodeError a
    unpackEither :: ByteString -> Either DecodeError a
unpackEither = p -> ByteString -> Either DecodeError a
forall p a.
(BytePacker p, MessagePack a) =>
p -> ByteString -> Either DecodeError a
BytePacker.unpackEither p
p

    pack :: MessagePack a => a -> L.ByteString
    pack :: a -> ByteString
pack = p -> a -> ByteString
forall p a. (BytePacker p, MessagePack a) => p -> a -> ByteString
BytePacker.pack p
p

    unpack :: (MonadFail m, MessagePack a) => L.ByteString -> m a
    unpack :: ByteString -> m a
unpack = p -> ByteString -> m a
forall p (m :: * -> *) a.
(BytePacker p, Monad m, MonadFail m, MessagePack a) =>
p -> ByteString -> m a
BytePacker.unpack p
p

    coerce :: (MessagePack a, MessagePack b) => a -> Maybe b
    coerce :: a -> Maybe b
coerce = ByteString -> Maybe b
forall (m :: * -> *) a.
(MonadFail m, MessagePack a) =>
ByteString -> m a
unpack (ByteString -> Maybe b) -> (a -> ByteString) -> a -> Maybe b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> ByteString
forall a. MessagePack a => a -> ByteString
pack