{-# LANGUAGE TemplateHaskell #-}
module Test.Cardano.Chain.Genesis.CBOR (
tests,
)
where
import Cardano.Prelude
import Test.Cardano.Chain.Genesis.Gen
import Test.Cardano.Crypto.Gen (genProtocolMagicId)
import Test.Cardano.Ledger.Binary.Vintage.Helpers.GoldenRoundTrip (
roundTripsCBORBuildable,
roundTripsCBORShow,
)
import Test.Cardano.Prelude (discoverRoundTripArg)
import Test.Options (TSGroup, TSProperty, concatTSGroups, eachOfTS)
ts_roundTripGenesisKeyHashesCBOR :: TSProperty
ts_roundTripGenesisKeyHashesCBOR :: TSProperty
ts_roundTripGenesisKeyHashesCBOR =
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS TestLimit
1000 Gen GenesisKeyHashes
genGenesisKeyHashes forall a (m :: * -> *).
(DecCBOR a, EncCBOR a, Eq a, MonadTest m, Buildable a,
HasCallStack) =>
a -> m ()
roundTripsCBORBuildable
tests :: TSGroup
tests :: TSGroup
tests =
[TSGroup] -> TSGroup
concatTSGroups
[$$discoverRoundTripArg]
ts_roundTripGenesisAvvmBalances :: TSProperty
ts_roundTripGenesisAvvmBalances :: TSProperty
ts_roundTripGenesisAvvmBalances =
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS TestLimit
1000 Gen GenesisAvvmBalances
genGenesisAvvmBalances forall a (m :: * -> *).
(DecCBOR a, EncCBOR a, Eq a, MonadTest m, Show a, HasCallStack) =>
a -> m ()
roundTripsCBORShow
ts_roundTripGenesisNonAvvmBalances :: TSProperty
ts_roundTripGenesisNonAvvmBalances :: TSProperty
ts_roundTripGenesisNonAvvmBalances =
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS TestLimit
1000 Gen GenesisNonAvvmBalances
genGenesisNonAvvmBalances forall a (m :: * -> *).
(DecCBOR a, EncCBOR a, Eq a, MonadTest m, Show a, HasCallStack) =>
a -> m ()
roundTripsCBORShow
ts_roundTripGenesisDelegation :: TSProperty
ts_roundTripGenesisDelegation :: TSProperty
ts_roundTripGenesisDelegation =
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS TestLimit
1000 (ProtocolMagicId -> GenT Identity GenesisDelegation
genGenesisDelegation forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Gen ProtocolMagicId
genProtocolMagicId) forall a (m :: * -> *).
(DecCBOR a, EncCBOR a, Eq a, MonadTest m, Show a, HasCallStack) =>
a -> m ()
roundTripsCBORShow
ts_roundTripGenesisData :: TSProperty
ts_roundTripGenesisData :: TSProperty
ts_roundTripGenesisData =
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS TestLimit
1000 (ProtocolMagicId -> GenT Identity Config
genConfig forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Gen ProtocolMagicId
genProtocolMagicId) forall a (m :: * -> *).
(DecCBOR a, EncCBOR a, Eq a, MonadTest m, Show a, HasCallStack) =>
a -> m ()
roundTripsCBORShow