{-# LANGUAGE NumDecimals #-}
{-# LANGUAGE NumericUnderscores #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeApplications #-}
module Test.Cardano.Ledger.Binary.Vintage.RoundTrip (tests) where
import Data.Fixed (E9, Fixed (..))
import Data.Ratio ((%))
import Hedgehog (Property, Range, checkParallel)
import qualified Hedgehog.Gen as Gen
import qualified Hedgehog.Range as Range
import Test.Cardano.Ledger.Binary.Vintage.Helpers.GoldenRoundTrip (
roundTripsCBORBuildable,
roundTripsCBORShow,
)
import Test.Cardano.Prelude (discoverRoundTrip, eachOf)
tests :: IO Bool
tests :: IO Bool
tests = Group -> IO Bool
forall (m :: * -> *). MonadIO m => Group -> m Bool
checkParallel $$String
[(PropertyName, Property)]
Property
String -> GroupName
String -> PropertyName
GroupName -> [(PropertyName, Property)] -> Group
roundTripUnitBi :: Property
roundTripBoolBi :: Property
roundTripIntegerBi :: Property
roundTripWordBi :: Property
roundTripWord8Bi :: Property
roundTripWord16Bi :: Property
roundTripWord32Bi :: Property
roundTripWord64Bi :: Property
roundTripIntBi :: Property
roundTripFloatBi :: Property
roundTripInt32Bi :: Property
roundTripInt64Bi :: Property
roundTripRatioBi :: Property
roundTripNanoBi :: Property
roundTripMapBi :: Property
roundTripSetBi :: Property
roundTripByteStringBi :: Property
roundTripTextBi :: Property
discoverRoundTrip
roundTripUnitBi :: Property
roundTripUnitBi :: Property
roundTripUnitBi = TestLimit -> Gen () -> (() -> PropertyT IO ()) -> Property
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> Property
eachOf TestLimit
1 (() -> Gen ()
forall a. a -> GenT Identity a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()) () -> PropertyT IO ()
forall a (m :: * -> *).
(DecCBOR a, EncCBOR a, Eq a, MonadTest m, Buildable a,
HasCallStack) =>
a -> m ()
roundTripsCBORBuildable
roundTripBoolBi :: Property
roundTripBoolBi :: Property
roundTripBoolBi = TestLimit -> Gen Bool -> (Bool -> PropertyT IO ()) -> Property
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> Property
eachOf TestLimit
10 Gen Bool
forall (m :: * -> *). MonadGen m => m Bool
Gen.bool Bool -> PropertyT IO ()
forall a (m :: * -> *).
(DecCBOR a, EncCBOR a, Eq a, MonadTest m, Buildable a,
HasCallStack) =>
a -> m ()
roundTripsCBORBuildable
roundTripIntegerBi :: Property
roundTripIntegerBi :: Property
roundTripIntegerBi =
TestLimit
-> Gen Integer -> (Integer -> PropertyT IO ()) -> Property
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> Property
eachOf
TestLimit
1000
(Range Integer -> Gen Integer
forall (m :: * -> *) a. (MonadGen m, Integral a) => Range a -> m a
Gen.integral (Integer -> Integer -> Integer -> Range Integer
forall a. Integral a => a -> a -> a -> Range a
Range.linearFrom Integer
0 (-Integer
1e40) Integer
1e40 :: Range Integer))
Integer -> PropertyT IO ()
forall a (m :: * -> *).
(DecCBOR a, EncCBOR a, Eq a, MonadTest m, Buildable a,
HasCallStack) =>
a -> m ()
roundTripsCBORBuildable
roundTripWordBi :: Property
roundTripWordBi :: Property
roundTripWordBi =
TestLimit -> Gen Word -> (Word -> PropertyT IO ()) -> Property
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> Property
eachOf TestLimit
1000 (Range Word -> Gen Word
forall (m :: * -> *). MonadGen m => Range Word -> m Word
Gen.word Range Word
forall a. (Bounded a, Num a) => Range a
Range.constantBounded) Word -> PropertyT IO ()
forall a (m :: * -> *).
(DecCBOR a, EncCBOR a, Eq a, MonadTest m, Buildable a,
HasCallStack) =>
a -> m ()
roundTripsCBORBuildable
roundTripWord8Bi :: Property
roundTripWord8Bi :: Property
roundTripWord8Bi =
TestLimit -> Gen Word8 -> (Word8 -> PropertyT IO ()) -> Property
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> Property
eachOf TestLimit
1000 (Range Word8 -> Gen Word8
forall (m :: * -> *). MonadGen m => Range Word8 -> m Word8
Gen.word8 Range Word8
forall a. (Bounded a, Num a) => Range a
Range.constantBounded) Word8 -> PropertyT IO ()
forall a (m :: * -> *).
(DecCBOR a, EncCBOR a, Eq a, MonadTest m, Buildable a,
HasCallStack) =>
a -> m ()
roundTripsCBORBuildable
roundTripWord16Bi :: Property
roundTripWord16Bi :: Property
roundTripWord16Bi =
TestLimit -> Gen Word16 -> (Word16 -> PropertyT IO ()) -> Property
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> Property
eachOf TestLimit
1000 (Range Word16 -> Gen Word16
forall (m :: * -> *). MonadGen m => Range Word16 -> m Word16
Gen.word16 Range Word16
forall a. (Bounded a, Num a) => Range a
Range.constantBounded) Word16 -> PropertyT IO ()
forall a (m :: * -> *).
(DecCBOR a, EncCBOR a, Eq a, MonadTest m, Buildable a,
HasCallStack) =>
a -> m ()
roundTripsCBORBuildable
roundTripWord32Bi :: Property
roundTripWord32Bi :: Property
roundTripWord32Bi =
TestLimit -> Gen Word32 -> (Word32 -> PropertyT IO ()) -> Property
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> Property
eachOf TestLimit
1000 (Range Word32 -> Gen Word32
forall (m :: * -> *). MonadGen m => Range Word32 -> m Word32
Gen.word32 Range Word32
forall a. (Bounded a, Num a) => Range a
Range.constantBounded) Word32 -> PropertyT IO ()
forall a (m :: * -> *).
(DecCBOR a, EncCBOR a, Eq a, MonadTest m, Buildable a,
HasCallStack) =>
a -> m ()
roundTripsCBORBuildable
roundTripWord64Bi :: Property
roundTripWord64Bi :: Property
roundTripWord64Bi =
TestLimit -> Gen Word64 -> (Word64 -> PropertyT IO ()) -> Property
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> Property
eachOf TestLimit
1000 (Range Word64 -> Gen Word64
forall (m :: * -> *). MonadGen m => Range Word64 -> m Word64
Gen.word64 Range Word64
forall a. (Bounded a, Num a) => Range a
Range.constantBounded) Word64 -> PropertyT IO ()
forall a (m :: * -> *).
(DecCBOR a, EncCBOR a, Eq a, MonadTest m, Buildable a,
HasCallStack) =>
a -> m ()
roundTripsCBORBuildable
roundTripIntBi :: Property
roundTripIntBi :: Property
roundTripIntBi =
TestLimit -> Gen Int -> (Int -> PropertyT IO ()) -> Property
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> Property
eachOf TestLimit
1000 (Range Int -> Gen Int
forall (m :: * -> *). MonadGen m => Range Int -> m Int
Gen.int Range Int
forall a. (Bounded a, Num a) => Range a
Range.constantBounded) Int -> PropertyT IO ()
forall a (m :: * -> *).
(DecCBOR a, EncCBOR a, Eq a, MonadTest m, Buildable a,
HasCallStack) =>
a -> m ()
roundTripsCBORBuildable
roundTripFloatBi :: Property
roundTripFloatBi :: Property
roundTripFloatBi =
TestLimit -> Gen Float -> (Float -> PropertyT IO ()) -> Property
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> Property
eachOf TestLimit
1000 (Range Float -> Gen Float
forall (m :: * -> *). MonadGen m => Range Float -> m Float
Gen.float (Float -> Float -> Range Float
forall a. a -> a -> Range a
Range.constant (-Float
1e12) Float
1e12)) Float -> PropertyT IO ()
forall a (m :: * -> *).
(DecCBOR a, EncCBOR a, Eq a, MonadTest m, Buildable a,
HasCallStack) =>
a -> m ()
roundTripsCBORBuildable
roundTripInt32Bi :: Property
roundTripInt32Bi :: Property
roundTripInt32Bi =
TestLimit -> Gen Int32 -> (Int32 -> PropertyT IO ()) -> Property
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> Property
eachOf TestLimit
1000 (Range Int32 -> Gen Int32
forall (m :: * -> *). MonadGen m => Range Int32 -> m Int32
Gen.int32 Range Int32
forall a. (Bounded a, Num a) => Range a
Range.constantBounded) Int32 -> PropertyT IO ()
forall a (m :: * -> *).
(DecCBOR a, EncCBOR a, Eq a, MonadTest m, Buildable a,
HasCallStack) =>
a -> m ()
roundTripsCBORBuildable
roundTripInt64Bi :: Property
roundTripInt64Bi :: Property
roundTripInt64Bi =
TestLimit -> Gen Int64 -> (Int64 -> PropertyT IO ()) -> Property
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> Property
eachOf TestLimit
1000 (Range Int64 -> Gen Int64
forall (m :: * -> *). MonadGen m => Range Int64 -> m Int64
Gen.int64 Range Int64
forall a. (Bounded a, Num a) => Range a
Range.constantBounded) Int64 -> PropertyT IO ()
forall a (m :: * -> *).
(DecCBOR a, EncCBOR a, Eq a, MonadTest m, Buildable a,
HasCallStack) =>
a -> m ()
roundTripsCBORBuildable
roundTripRatioBi :: Property
roundTripRatioBi :: Property
roundTripRatioBi =
let r :: Range.Range Integer
r :: Range Integer
r = Integer -> Integer -> Range Integer
forall a. a -> a -> Range a
Range.constant (-Integer
1_000_000_000_000_0000_000) Integer
1_000_000_000_000_0000_000
in TestLimit
-> Gen (Ratio Integer)
-> (Ratio Integer -> PropertyT IO ())
-> Property
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> Property
eachOf
TestLimit
1000
(Integer -> Integer -> Ratio Integer
forall a. Integral a => a -> a -> Ratio a
(%) (Integer -> Integer -> Ratio Integer)
-> Gen Integer -> GenT Identity (Integer -> Ratio Integer)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Range Integer -> Gen Integer
forall (m :: * -> *) a. (MonadGen m, Integral a) => Range a -> m a
Gen.integral Range Integer
r GenT Identity (Integer -> Ratio Integer)
-> Gen Integer -> Gen (Ratio Integer)
forall a b.
GenT Identity (a -> b) -> GenT Identity a -> GenT Identity b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Range Integer -> Gen Integer
forall (m :: * -> *) a. (MonadGen m, Integral a) => Range a -> m a
Gen.integral Range Integer
r)
Ratio Integer -> PropertyT IO ()
forall a (m :: * -> *).
(DecCBOR a, EncCBOR a, Eq a, MonadTest m, Buildable a,
HasCallStack) =>
a -> m ()
roundTripsCBORBuildable
roundTripNanoBi :: Property
roundTripNanoBi :: Property
roundTripNanoBi =
TestLimit
-> Gen (Fixed E9) -> (Fixed E9 -> PropertyT IO ()) -> Property
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> Property
eachOf
TestLimit
1000
((Integer -> Fixed E9
forall k (a :: k). Integer -> Fixed a
MkFixed :: Integer -> Fixed E9) (Integer -> Fixed E9) -> Gen Integer -> Gen (Fixed E9)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Range Integer -> Gen Integer
forall (m :: * -> *) a. (MonadGen m, Integral a) => Range a -> m a
Gen.integral (Integer -> Integer -> Integer -> Range Integer
forall a. a -> a -> a -> Range a
Range.constantFrom Integer
0 (-Integer
1e12) Integer
1e12))
Fixed E9 -> PropertyT IO ()
forall a (m :: * -> *).
(DecCBOR a, EncCBOR a, Eq a, MonadTest m, Show a, HasCallStack) =>
a -> m ()
roundTripsCBORShow
roundTripMapBi :: Property
roundTripMapBi :: Property
roundTripMapBi =
TestLimit
-> Gen (Map Int Int)
-> (Map Int Int -> PropertyT IO ())
-> Property
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> Property
eachOf
TestLimit
100
( Range Int -> GenT Identity (Int, Int) -> Gen (Map Int Int)
forall (m :: * -> *) k v.
(MonadGen m, Ord k) =>
Range Int -> m (k, v) -> m (Map k v)
Gen.map
(Int -> Int -> Range Int
forall a. a -> a -> Range a
Range.constant Int
0 Int
50)
((,) (Int -> Int -> (Int, Int))
-> Gen Int -> GenT Identity (Int -> (Int, Int))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Range Int -> Gen Int
forall (m :: * -> *). MonadGen m => Range Int -> m Int
Gen.int Range Int
forall a. (Bounded a, Num a) => Range a
Range.constantBounded GenT Identity (Int -> (Int, Int))
-> Gen Int -> GenT Identity (Int, Int)
forall a b.
GenT Identity (a -> b) -> GenT Identity a -> GenT Identity b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Range Int -> Gen Int
forall (m :: * -> *). MonadGen m => Range Int -> m Int
Gen.int Range Int
forall a. (Bounded a, Num a) => Range a
Range.constantBounded)
)
Map Int Int -> PropertyT IO ()
forall a (m :: * -> *).
(DecCBOR a, EncCBOR a, Eq a, MonadTest m, Show a, HasCallStack) =>
a -> m ()
roundTripsCBORShow
roundTripSetBi :: Property
roundTripSetBi :: Property
roundTripSetBi =
TestLimit
-> Gen (Set Int) -> (Set Int -> PropertyT IO ()) -> Property
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> Property
eachOf
TestLimit
100
(Range Int -> Gen Int -> Gen (Set Int)
forall (m :: * -> *) a.
(MonadGen m, Ord a) =>
Range Int -> m a -> m (Set a)
Gen.set (Int -> Int -> Range Int
forall a. a -> a -> Range a
Range.constant Int
0 Int
50) (Range Int -> Gen Int
forall (m :: * -> *). MonadGen m => Range Int -> m Int
Gen.int Range Int
forall a. (Bounded a, Num a) => Range a
Range.constantBounded))
Set Int -> PropertyT IO ()
forall a (m :: * -> *).
(DecCBOR a, EncCBOR a, Eq a, MonadTest m, Show a, HasCallStack) =>
a -> m ()
roundTripsCBORShow
roundTripByteStringBi :: Property
roundTripByteStringBi :: Property
roundTripByteStringBi =
TestLimit
-> Gen ByteString -> (ByteString -> PropertyT IO ()) -> Property
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> Property
eachOf TestLimit
100 (Range Int -> Gen ByteString
forall (m :: * -> *). MonadGen m => Range Int -> m ByteString
Gen.bytes (Range Int -> Gen ByteString) -> Range Int -> Gen ByteString
forall a b. (a -> b) -> a -> b
$ Int -> Int -> Range Int
forall a. a -> a -> Range a
Range.constant Int
0 Int
100) ByteString -> PropertyT IO ()
forall a (m :: * -> *).
(DecCBOR a, EncCBOR a, Eq a, MonadTest m, Show a, HasCallStack) =>
a -> m ()
roundTripsCBORShow
roundTripTextBi :: Property
roundTripTextBi :: Property
roundTripTextBi =
TestLimit -> Gen Text -> (Text -> PropertyT IO ()) -> Property
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> Property
eachOf
TestLimit
100
(Range Int -> GenT Identity Char -> Gen Text
forall (m :: * -> *). MonadGen m => Range Int -> m Char -> m Text
Gen.text (Int -> Int -> Range Int
forall a. a -> a -> Range a
Range.constant Int
0 Int
100) GenT Identity Char
forall (m :: * -> *). MonadGen m => m Char
Gen.unicode)
Text -> PropertyT IO ()
forall a (m :: * -> *).
(DecCBOR a, EncCBOR a, Eq a, MonadTest m, Buildable a,
HasCallStack) =>
a -> m ()
roundTripsCBORBuildable