{-# LANGUAGE TemplateHaskell #-}
module Test.Cardano.Chain.Buildable (
tests,
) where
import Cardano.Chain.Common (
Attributes (Attributes),
UnparsedFields (UnparsedFields),
)
import Cardano.Prelude
import Formatting (Buildable, build, sformat)
import Hedgehog (PropertyT, eval, property)
import Test.Cardano.Chain.Block.Gen (
genBlockSignature,
genBlockWithEpochSlots,
genHeader,
)
import qualified Test.Cardano.Chain.Block.Gen as Block
import qualified Test.Cardano.Chain.Common.Gen as Common
import qualified Test.Cardano.Chain.Delegation.Gen as Delegation
import qualified Test.Cardano.Chain.Genesis.Gen as Genesis
import Test.Cardano.Chain.Slotting.Gen (feedPMEpochSlots)
import qualified Test.Cardano.Chain.Slotting.Gen as Slotting
import qualified Test.Cardano.Chain.UTxO.Gen as UTxO
import qualified Test.Cardano.Chain.Update.Gen as Update
import Test.Cardano.Crypto.Gen (feedPM)
import Test.Cardano.Prelude
import Test.Options (TSGroup, TSProperty, eachOfTS)
tests :: TSGroup
tests :: TSGroup
tests = $$discoverPropArg
isBuildable :: Buildable a => a -> PropertyT IO ()
isBuildable :: forall a. Buildable a => a -> PropertyT IO ()
isBuildable = PropertyT IO Text -> PropertyT IO ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (PropertyT IO Text -> PropertyT IO ())
-> (a -> PropertyT IO Text) -> a -> PropertyT IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Text -> PropertyT IO Text
forall (m :: * -> *) a. (MonadTest m, HasCallStack) => a -> m a
eval (Text -> PropertyT IO Text)
-> (a -> Text) -> a -> PropertyT IO Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Format Text (a -> Text) -> a -> Text
forall a. Format Text a -> a
sformat Format Text (a -> Text)
forall a r. Buildable a => Format r (a -> r)
build
ts_prop_blockIsBuildable :: TSProperty
ts_prop_blockIsBuildable :: TSProperty
ts_prop_blockIsBuildable =
TestLimit
-> Gen (WithEpochSlots Block)
-> (WithEpochSlots Block -> PropertyT IO ())
-> TSProperty
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS TestLimit
100 ((ProtocolMagicId -> Gen (WithEpochSlots Block))
-> Gen (WithEpochSlots Block)
forall a. (ProtocolMagicId -> Gen a) -> Gen a
feedPM ProtocolMagicId -> Gen (WithEpochSlots Block)
genBlockWithEpochSlots) WithEpochSlots Block -> PropertyT IO ()
forall a. Buildable a => a -> PropertyT IO ()
isBuildable
ts_prop_blockProofIsBuildable :: TSProperty
ts_prop_blockProofIsBuildable :: TSProperty
ts_prop_blockProofIsBuildable = TestLimit -> Gen Proof -> (Proof -> PropertyT IO ()) -> TSProperty
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS TestLimit
100 ((ProtocolMagicId -> Gen Proof) -> Gen Proof
forall a. (ProtocolMagicId -> Gen a) -> Gen a
feedPM ProtocolMagicId -> Gen Proof
Block.genProof) Proof -> PropertyT IO ()
forall a. Buildable a => a -> PropertyT IO ()
isBuildable
ts_prop_headerIsBuildable :: TSProperty
=
TestLimit
-> Gen (WithEpochSlots Header)
-> (WithEpochSlots Header -> PropertyT IO ())
-> TSProperty
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS
TestLimit
100
((ProtocolMagicId -> EpochSlots -> Gen (WithEpochSlots Header))
-> Gen (WithEpochSlots Header)
forall a. (ProtocolMagicId -> EpochSlots -> Gen a) -> Gen a
feedPMEpochSlots ((ProtocolMagicId -> EpochSlots -> Gen Header)
-> ProtocolMagicId -> EpochSlots -> Gen (WithEpochSlots Header)
forall a.
(ProtocolMagicId -> EpochSlots -> Gen a)
-> ProtocolMagicId -> EpochSlots -> Gen (WithEpochSlots a)
Slotting.genWithEpochSlots ProtocolMagicId -> EpochSlots -> Gen Header
genHeader))
WithEpochSlots Header -> PropertyT IO ()
forall a. Buildable a => a -> PropertyT IO ()
isBuildable
ts_prop_blockSignatureIsBuildable :: TSProperty
ts_prop_blockSignatureIsBuildable :: TSProperty
ts_prop_blockSignatureIsBuildable =
TestLimit
-> Gen BlockSignature
-> (BlockSignature -> PropertyT IO ())
-> TSProperty
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS TestLimit
100 ((ProtocolMagicId -> EpochSlots -> Gen BlockSignature)
-> Gen BlockSignature
forall a. (ProtocolMagicId -> EpochSlots -> Gen a) -> Gen a
feedPMEpochSlots ProtocolMagicId -> EpochSlots -> Gen BlockSignature
genBlockSignature) BlockSignature -> PropertyT IO ()
forall a. Buildable a => a -> PropertyT IO ()
isBuildable
ts_prop_addrAttributesIsBuildable :: TSProperty
ts_prop_addrAttributesIsBuildable :: TSProperty
ts_prop_addrAttributesIsBuildable =
TestLimit
-> Gen AddrAttributes
-> (AddrAttributes -> PropertyT IO ())
-> TSProperty
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS TestLimit
100 Gen AddrAttributes
Common.genAddrAttributes AddrAttributes -> PropertyT IO ()
forall a. Buildable a => a -> PropertyT IO ()
isBuildable
ts_prop_addrSpendingData :: TSProperty
ts_prop_addrSpendingData :: TSProperty
ts_prop_addrSpendingData = TestLimit
-> Gen AddrSpendingData
-> (AddrSpendingData -> PropertyT IO ())
-> TSProperty
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS TestLimit
100 Gen AddrSpendingData
Common.genAddrSpendingData AddrSpendingData -> PropertyT IO ()
forall a. Buildable a => a -> PropertyT IO ()
isBuildable
ts_prop_addressIsBuildable :: TSProperty
ts_prop_addressIsBuildable :: TSProperty
ts_prop_addressIsBuildable = TestLimit
-> Gen Address -> (Address -> PropertyT IO ()) -> TSProperty
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS TestLimit
100 Gen Address
Common.genAddress Address -> PropertyT IO ()
forall a. Buildable a => a -> PropertyT IO ()
isBuildable
ts_prop_attributesUnitIsBuildable :: TSProperty
ts_prop_attributesUnitIsBuildable :: TSProperty
ts_prop_attributesUnitIsBuildable =
Property -> TSProperty
forall a b. a -> b -> a
const (Property -> TSProperty)
-> (PropertyT IO () -> Property) -> PropertyT IO () -> TSProperty
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. HasCallStack => PropertyT IO () -> Property
PropertyT IO () -> Property
property (PropertyT IO () -> TSProperty) -> PropertyT IO () -> TSProperty
forall a b. (a -> b) -> a -> b
$ Attributes () -> PropertyT IO ()
forall a. Buildable a => a -> PropertyT IO ()
isBuildable (() -> UnparsedFields -> Attributes ()
forall h. h -> UnparsedFields -> Attributes h
Attributes () (Map Word8 ByteString -> UnparsedFields
UnparsedFields Map Word8 ByteString
forall a. Monoid a => a
mempty))
ts_prop_blockCountIsBuildable :: TSProperty
ts_prop_blockCountIsBuildable :: TSProperty
ts_prop_blockCountIsBuildable = TestLimit
-> Gen BlockCount -> (BlockCount -> PropertyT IO ()) -> TSProperty
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS TestLimit
100 Gen BlockCount
Common.genBlockCount BlockCount -> PropertyT IO ()
forall a. Buildable a => a -> PropertyT IO ()
isBuildable
ts_prop_chainDifficultyIsBuildable :: TSProperty
ts_prop_chainDifficultyIsBuildable :: TSProperty
ts_prop_chainDifficultyIsBuildable =
TestLimit
-> Gen ChainDifficulty
-> (ChainDifficulty -> PropertyT IO ())
-> TSProperty
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS TestLimit
100 Gen ChainDifficulty
Common.genChainDifficulty ChainDifficulty -> PropertyT IO ()
forall a. Buildable a => a -> PropertyT IO ()
isBuildable
ts_prop_keyHashIsBuildable :: TSProperty
ts_prop_keyHashIsBuildable :: TSProperty
ts_prop_keyHashIsBuildable = TestLimit
-> Gen KeyHash -> (KeyHash -> PropertyT IO ()) -> TSProperty
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS TestLimit
100 Gen KeyHash
Common.genKeyHash KeyHash -> PropertyT IO ()
forall a. Buildable a => a -> PropertyT IO ()
isBuildable
ts_prop_lovelaceIsBuildable :: TSProperty
ts_prop_lovelaceIsBuildable :: TSProperty
ts_prop_lovelaceIsBuildable = TestLimit
-> Gen Lovelace -> (Lovelace -> PropertyT IO ()) -> TSProperty
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS TestLimit
100 Gen Lovelace
Common.genLovelace Lovelace -> PropertyT IO ()
forall a. Buildable a => a -> PropertyT IO ()
isBuildable
ts_prop_lovelacePortionIsBuildable :: TSProperty
ts_prop_lovelacePortionIsBuildable :: TSProperty
ts_prop_lovelacePortionIsBuildable =
TestLimit
-> Gen LovelacePortion
-> (LovelacePortion -> PropertyT IO ())
-> TSProperty
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS TestLimit
100 Gen LovelacePortion
Common.genLovelacePortion LovelacePortion -> PropertyT IO ()
forall a. Buildable a => a -> PropertyT IO ()
isBuildable
ts_prop_merkleRootIsBuildable :: TSProperty
ts_prop_merkleRootIsBuildable :: TSProperty
ts_prop_merkleRootIsBuildable =
TestLimit
-> Gen (MerkleRoot ())
-> (MerkleRoot () -> PropertyT IO ())
-> TSProperty
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS TestLimit
100 (Gen () -> Gen (MerkleRoot ())
forall a. EncCBOR a => Gen a -> Gen (MerkleRoot a)
Common.genMerkleRoot (() -> Gen ()
forall a. a -> GenT Identity a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())) MerkleRoot () -> PropertyT IO ()
forall a. Buildable a => a -> PropertyT IO ()
isBuildable
ts_prop_networkMagicIsBuildable :: TSProperty
ts_prop_networkMagicIsBuildable :: TSProperty
ts_prop_networkMagicIsBuildable =
TestLimit
-> Gen NetworkMagic
-> (NetworkMagic -> PropertyT IO ())
-> TSProperty
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS TestLimit
100 Gen NetworkMagic
Common.genNetworkMagic NetworkMagic -> PropertyT IO ()
forall a. Buildable a => a -> PropertyT IO ()
isBuildable
ts_prop_txFeePolicyIsBuildable :: TSProperty
ts_prop_txFeePolicyIsBuildable :: TSProperty
ts_prop_txFeePolicyIsBuildable = TestLimit
-> Gen TxFeePolicy
-> (TxFeePolicy -> PropertyT IO ())
-> TSProperty
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS TestLimit
100 Gen TxFeePolicy
Common.genTxFeePolicy TxFeePolicy -> PropertyT IO ()
forall a. Buildable a => a -> PropertyT IO ()
isBuildable
ts_prop_txSizeLinearIsBuildable :: TSProperty
ts_prop_txSizeLinearIsBuildable :: TSProperty
ts_prop_txSizeLinearIsBuildable =
TestLimit
-> Gen TxSizeLinear
-> (TxSizeLinear -> PropertyT IO ())
-> TSProperty
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS TestLimit
100 Gen TxSizeLinear
Common.genTxSizeLinear TxSizeLinear -> PropertyT IO ()
forall a. Buildable a => a -> PropertyT IO ()
isBuildable
ts_prop_delegationCertificateIsBuildable :: TSProperty
ts_prop_delegationCertificateIsBuildable :: TSProperty
ts_prop_delegationCertificateIsBuildable =
TestLimit
-> Gen Certificate
-> (Certificate -> PropertyT IO ())
-> TSProperty
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS TestLimit
100 ((ProtocolMagicId -> Gen Certificate) -> Gen Certificate
forall a. (ProtocolMagicId -> Gen a) -> Gen a
feedPM ProtocolMagicId -> Gen Certificate
Delegation.genCertificate) Certificate -> PropertyT IO ()
forall a. Buildable a => a -> PropertyT IO ()
isBuildable
ts_prop_delegationPayloadIsBuildable :: TSProperty
ts_prop_delegationPayloadIsBuildable :: TSProperty
ts_prop_delegationPayloadIsBuildable =
TestLimit
-> Gen Payload -> (Payload -> PropertyT IO ()) -> TSProperty
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS TestLimit
100 ((ProtocolMagicId -> Gen Payload) -> Gen Payload
forall a. (ProtocolMagicId -> Gen a) -> Gen a
feedPM ProtocolMagicId -> Gen Payload
Delegation.genPayload) Payload -> PropertyT IO ()
forall a. Buildable a => a -> PropertyT IO ()
isBuildable
ts_prop_genesisKeyHashesIsBuildable :: TSProperty
ts_prop_genesisKeyHashesIsBuildable :: TSProperty
ts_prop_genesisKeyHashesIsBuildable =
TestLimit
-> Gen GenesisKeyHashes
-> (GenesisKeyHashes -> PropertyT IO ())
-> TSProperty
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS TestLimit
100 Gen GenesisKeyHashes
Genesis.genGenesisKeyHashes GenesisKeyHashes -> PropertyT IO ()
forall a. Buildable a => a -> PropertyT IO ()
isBuildable
ts_prop_genesisNonAvvmBalancesIsBuildable :: TSProperty
ts_prop_genesisNonAvvmBalancesIsBuildable :: TSProperty
ts_prop_genesisNonAvvmBalancesIsBuildable =
TestLimit
-> Gen GenesisNonAvvmBalances
-> (GenesisNonAvvmBalances -> PropertyT IO ())
-> TSProperty
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS TestLimit
100 Gen GenesisNonAvvmBalances
Genesis.genGenesisNonAvvmBalances GenesisNonAvvmBalances -> PropertyT IO ()
forall a. Buildable a => a -> PropertyT IO ()
isBuildable
ts_prop_epochAndSlotCountIsBuildable :: TSProperty
ts_prop_epochAndSlotCountIsBuildable :: TSProperty
ts_prop_epochAndSlotCountIsBuildable =
TestLimit
-> Gen EpochAndSlotCount
-> (EpochAndSlotCount -> PropertyT IO ())
-> TSProperty
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS
TestLimit
100
(Gen EpochSlots
Slotting.genEpochSlots Gen EpochSlots
-> (EpochSlots -> Gen EpochAndSlotCount) -> Gen EpochAndSlotCount
forall a b.
GenT Identity a -> (a -> GenT Identity b) -> GenT Identity b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= EpochSlots -> Gen EpochAndSlotCount
Slotting.genEpochAndSlotCount)
EpochAndSlotCount -> PropertyT IO ()
forall a. Buildable a => a -> PropertyT IO ()
isBuildable
ts_prop_epochNumberIsBuildable :: TSProperty
ts_prop_epochNumberIsBuildable :: TSProperty
ts_prop_epochNumberIsBuildable =
TestLimit
-> Gen EpochNumber
-> (EpochNumber -> PropertyT IO ())
-> TSProperty
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS TestLimit
100 Gen EpochNumber
Slotting.genEpochNumber EpochNumber -> PropertyT IO ()
forall a. Buildable a => a -> PropertyT IO ()
isBuildable
ts_prop_epochSlotsIsBuildable :: TSProperty
ts_prop_epochSlotsIsBuildable :: TSProperty
ts_prop_epochSlotsIsBuildable = TestLimit
-> Gen EpochSlots -> (EpochSlots -> PropertyT IO ()) -> TSProperty
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS TestLimit
100 Gen EpochSlots
Slotting.genEpochSlots EpochSlots -> PropertyT IO ()
forall a. Buildable a => a -> PropertyT IO ()
isBuildable
ts_prop_slotCountIsBuildable :: TSProperty
ts_prop_slotCountIsBuildable :: TSProperty
ts_prop_slotCountIsBuildable = TestLimit
-> Gen SlotCount -> (SlotCount -> PropertyT IO ()) -> TSProperty
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS TestLimit
100 Gen SlotCount
Slotting.genSlotCount SlotCount -> PropertyT IO ()
forall a. Buildable a => a -> PropertyT IO ()
isBuildable
ts_prop_slotNumberIsBuilable :: TSProperty
ts_prop_slotNumberIsBuilable :: TSProperty
ts_prop_slotNumberIsBuilable = TestLimit
-> Gen SlotNumber -> (SlotNumber -> PropertyT IO ()) -> TSProperty
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS TestLimit
100 Gen SlotNumber
Slotting.genSlotNumber SlotNumber -> PropertyT IO ()
forall a. Buildable a => a -> PropertyT IO ()
isBuildable
ts_prop_applicationNameIsBuildable :: TSProperty
ts_prop_applicationNameIsBuildable :: TSProperty
ts_prop_applicationNameIsBuildable =
TestLimit
-> Gen ApplicationName
-> (ApplicationName -> PropertyT IO ())
-> TSProperty
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS TestLimit
100 Gen ApplicationName
Update.genApplicationName ApplicationName -> PropertyT IO ()
forall a. Buildable a => a -> PropertyT IO ()
isBuildable
ts_prop_installerHashIsBuildable :: TSProperty
ts_prop_installerHashIsBuildable :: TSProperty
ts_prop_installerHashIsBuildable =
TestLimit
-> Gen InstallerHash
-> (InstallerHash -> PropertyT IO ())
-> TSProperty
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS TestLimit
100 Gen InstallerHash
Update.genInstallerHash InstallerHash -> PropertyT IO ()
forall a. Buildable a => a -> PropertyT IO ()
isBuildable
ts_prop_updatePayloadIsBuildable :: TSProperty
ts_prop_updatePayloadIsBuildable :: TSProperty
ts_prop_updatePayloadIsBuildable =
TestLimit
-> Gen Payload -> (Payload -> PropertyT IO ()) -> TSProperty
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS TestLimit
100 ((ProtocolMagicId -> Gen Payload) -> Gen Payload
forall a. (ProtocolMagicId -> Gen a) -> Gen a
feedPM ProtocolMagicId -> Gen Payload
Update.genPayload) Payload -> PropertyT IO ()
forall a. Buildable a => a -> PropertyT IO ()
isBuildable
ts_prop_proposalIsBuiladble :: TSProperty
ts_prop_proposalIsBuiladble :: TSProperty
ts_prop_proposalIsBuiladble =
TestLimit
-> Gen Proposal -> (Proposal -> PropertyT IO ()) -> TSProperty
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS TestLimit
100 ((ProtocolMagicId -> Gen Proposal) -> Gen Proposal
forall a. (ProtocolMagicId -> Gen a) -> Gen a
feedPM ProtocolMagicId -> Gen Proposal
Update.genProposal) Proposal -> PropertyT IO ()
forall a. Buildable a => a -> PropertyT IO ()
isBuildable
ts_prop_protocolParametersIsBuildable :: TSProperty
ts_prop_protocolParametersIsBuildable :: TSProperty
ts_prop_protocolParametersIsBuildable =
TestLimit
-> Gen ProtocolParameters
-> (ProtocolParameters -> PropertyT IO ())
-> TSProperty
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS TestLimit
100 Gen ProtocolParameters
Update.genProtocolParameters ProtocolParameters -> PropertyT IO ()
forall a. Buildable a => a -> PropertyT IO ()
isBuildable
ts_prop_protocolParametersUpdateIsBuildable :: TSProperty
ts_prop_protocolParametersUpdateIsBuildable :: TSProperty
ts_prop_protocolParametersUpdateIsBuildable =
TestLimit
-> Gen ProtocolParametersUpdate
-> (ProtocolParametersUpdate -> PropertyT IO ())
-> TSProperty
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS TestLimit
100 Gen ProtocolParametersUpdate
Update.genProtocolParametersUpdate ProtocolParametersUpdate -> PropertyT IO ()
forall a. Buildable a => a -> PropertyT IO ()
isBuildable
ts_prop_protocolVersionIsBuildable :: TSProperty
ts_prop_protocolVersionIsBuildable :: TSProperty
ts_prop_protocolVersionIsBuildable =
TestLimit
-> Gen ProtocolVersion
-> (ProtocolVersion -> PropertyT IO ())
-> TSProperty
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS TestLimit
100 Gen ProtocolVersion
Update.genProtocolVersion ProtocolVersion -> PropertyT IO ()
forall a. Buildable a => a -> PropertyT IO ()
isBuildable
ts_prop_softforkRuleIsBuildable :: TSProperty
ts_prop_softforkRuleIsBuildable :: TSProperty
ts_prop_softforkRuleIsBuildable =
TestLimit
-> Gen SoftforkRule
-> (SoftforkRule -> PropertyT IO ())
-> TSProperty
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS TestLimit
100 Gen SoftforkRule
Update.genSoftforkRule SoftforkRule -> PropertyT IO ()
forall a. Buildable a => a -> PropertyT IO ()
isBuildable
ts_prop_softwareVersionIsBuildable :: TSProperty
ts_prop_softwareVersionIsBuildable :: TSProperty
ts_prop_softwareVersionIsBuildable =
TestLimit
-> Gen SoftforkRule
-> (SoftforkRule -> PropertyT IO ())
-> TSProperty
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS TestLimit
100 Gen SoftforkRule
Update.genSoftforkRule SoftforkRule -> PropertyT IO ()
forall a. Buildable a => a -> PropertyT IO ()
isBuildable
ts_prop_systemTagIsBuildable :: TSProperty
ts_prop_systemTagIsBuildable :: TSProperty
ts_prop_systemTagIsBuildable = TestLimit
-> Gen SystemTag -> (SystemTag -> PropertyT IO ()) -> TSProperty
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS TestLimit
100 Gen SystemTag
Update.genSystemTag SystemTag -> PropertyT IO ()
forall a. Buildable a => a -> PropertyT IO ()
isBuildable
ts_prop_voteIsBuildable :: TSProperty
ts_prop_voteIsBuildable :: TSProperty
ts_prop_voteIsBuildable = TestLimit -> Gen Vote -> (Vote -> PropertyT IO ()) -> TSProperty
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS TestLimit
100 ((ProtocolMagicId -> Gen Vote) -> Gen Vote
forall a. (ProtocolMagicId -> Gen a) -> Gen a
feedPM ProtocolMagicId -> Gen Vote
Update.genVote) Vote -> PropertyT IO ()
forall a. Buildable a => a -> PropertyT IO ()
isBuildable
ts_prop_txIsBuildable :: TSProperty
ts_prop_txIsBuildable :: TSProperty
ts_prop_txIsBuildable = TestLimit -> Gen Tx -> (Tx -> PropertyT IO ()) -> TSProperty
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS TestLimit
100 Gen Tx
UTxO.genTx Tx -> PropertyT IO ()
forall a. Buildable a => a -> PropertyT IO ()
isBuildable
ts_prop_txInIsBuildable :: TSProperty
ts_prop_txInIsBuildable :: TSProperty
ts_prop_txInIsBuildable = TestLimit -> Gen TxIn -> (TxIn -> PropertyT IO ()) -> TSProperty
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS TestLimit
100 Gen TxIn
UTxO.genTxIn TxIn -> PropertyT IO ()
forall a. Buildable a => a -> PropertyT IO ()
isBuildable
ts_prop_txOutIsBuildable :: TSProperty
ts_prop_txOutIsBuildable :: TSProperty
ts_prop_txOutIsBuildable = TestLimit -> Gen TxOut -> (TxOut -> PropertyT IO ()) -> TSProperty
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS TestLimit
100 Gen TxOut
UTxO.genTxOut TxOut -> PropertyT IO ()
forall a. Buildable a => a -> PropertyT IO ()
isBuildable
ts_prop_txAuxIsBuildable :: TSProperty
ts_prop_txAuxIsBuildable :: TSProperty
ts_prop_txAuxIsBuildable = TestLimit -> Gen TxAux -> (TxAux -> PropertyT IO ()) -> TSProperty
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS TestLimit
100 ((ProtocolMagicId -> Gen TxAux) -> Gen TxAux
forall a. (ProtocolMagicId -> Gen a) -> Gen a
feedPM ProtocolMagicId -> Gen TxAux
UTxO.genTxAux) TxAux -> PropertyT IO ()
forall a. Buildable a => a -> PropertyT IO ()
isBuildable
ts_prop_txProofIsBuildable :: TSProperty
ts_prop_txProofIsBuildable :: TSProperty
ts_prop_txProofIsBuildable = TestLimit
-> Gen TxProof -> (TxProof -> PropertyT IO ()) -> TSProperty
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS TestLimit
100 ((ProtocolMagicId -> Gen TxProof) -> Gen TxProof
forall a. (ProtocolMagicId -> Gen a) -> Gen a
feedPM ProtocolMagicId -> Gen TxProof
UTxO.genTxProof) TxProof -> PropertyT IO ()
forall a. Buildable a => a -> PropertyT IO ()
isBuildable
ts_prop_txInWitnessIsBuildable :: TSProperty
ts_prop_txInWitnessIsBuildable :: TSProperty
ts_prop_txInWitnessIsBuildable =
TestLimit
-> Gen TxInWitness
-> (TxInWitness -> PropertyT IO ())
-> TSProperty
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> TSProperty
eachOfTS TestLimit
100 ((ProtocolMagicId -> Gen TxInWitness) -> Gen TxInWitness
forall a. (ProtocolMagicId -> Gen a) -> Gen a
feedPM ProtocolMagicId -> Gen TxInWitness
UTxO.genTxInWitness) TxInWitness -> PropertyT IO ()
forall a. Buildable a => a -> PropertyT IO ()
isBuildable