{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module Test.Consensus.Byron.Generators (
RegularBlock (..)
, epochSlots
, k
, protocolMagicId
) where
import Cardano.Chain.Block (ABlockOrBoundary (..),
ABlockOrBoundaryHdr (..))
import qualified Cardano.Chain.Block as CC.Block
import qualified Cardano.Chain.Byron.API as API
import Cardano.Chain.Common (KeyHash)
import qualified Cardano.Chain.Delegation as CC.Del
import qualified Cardano.Chain.Delegation.Validation.Activation as CC.Act
import qualified Cardano.Chain.Delegation.Validation.Interface as CC.DI
import qualified Cardano.Chain.Delegation.Validation.Scheduling as CC.Sched
import qualified Cardano.Chain.Genesis as CC.Genesis
import Cardano.Chain.Slotting (EpochNumber, EpochSlots (..),
SlotNumber)
import qualified Cardano.Chain.Update as CC.Update
import qualified Cardano.Chain.Update.Validation.Interface as CC.UPI
import qualified Cardano.Chain.Update.Validation.Registration as CC.Reg
import qualified Cardano.Chain.UTxO as CC.UTxO
import Cardano.Crypto (ProtocolMagicId (..))
import Cardano.Crypto.Hashing (Hash)
import Cardano.Ledger.Binary (decCBOR, encCBOR)
import Control.Monad (replicateM)
import Data.Coerce (coerce)
import qualified Data.Map.Strict as Map
import Ouroboros.Consensus.Block
import Ouroboros.Consensus.Byron.Ledger
import Ouroboros.Consensus.Byron.Protocol
import Ouroboros.Consensus.Config.SecurityParam
import Ouroboros.Consensus.HeaderValidation (AnnTip (..))
import Ouroboros.Consensus.Ledger.SupportsMempool (GenTxId)
import Ouroboros.Consensus.Protocol.PBFT.State (PBftState)
import qualified Ouroboros.Consensus.Protocol.PBFT.State as PBftState
import Ouroboros.Network.SizeInBytes
import qualified Test.Cardano.Chain.Block.Gen as CC
import qualified Test.Cardano.Chain.Common.Gen as CC
import qualified Test.Cardano.Chain.Delegation.Gen as CC
import qualified Test.Cardano.Chain.MempoolPayload.Gen as CC
import qualified Test.Cardano.Chain.Slotting.Gen as CC
import qualified Test.Cardano.Chain.Update.Gen as UG
import qualified Test.Cardano.Chain.UTxO.Gen as CC
import qualified Test.Cardano.Crypto.Gen as CC
import Test.Cardano.Ledger.Binary.Arbitrary ()
import Test.QuickCheck hiding (Result)
import Test.QuickCheck.Hedgehog (hedgehog)
import Test.Util.Orphans.Arbitrary ()
import Test.Util.Serialisation.Roundtrip (Coherent (..),
WithVersion (..))
import Test.Util.Serialisation.SomeResult (SomeResult (..))
k :: SecurityParam
k :: SecurityParam
k = Word64 -> SecurityParam
SecurityParam Word64
10
epochSlots :: EpochSlots
epochSlots :: EpochSlots
epochSlots = Word64 -> EpochSlots
EpochSlots Word64
100
protocolMagicId :: ProtocolMagicId
protocolMagicId :: ProtocolMagicId
protocolMagicId = Word32 -> ProtocolMagicId
ProtocolMagicId Word32
100
newtype RegularBlock = RegularBlock { RegularBlock -> ByronBlock
unRegularBlock :: ByronBlock }
deriving (RegularBlock -> RegularBlock -> Bool
(RegularBlock -> RegularBlock -> Bool)
-> (RegularBlock -> RegularBlock -> Bool) -> Eq RegularBlock
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RegularBlock -> RegularBlock -> Bool
== :: RegularBlock -> RegularBlock -> Bool
$c/= :: RegularBlock -> RegularBlock -> Bool
/= :: RegularBlock -> RegularBlock -> Bool
Eq, Int -> RegularBlock -> ShowS
[RegularBlock] -> ShowS
RegularBlock -> String
(Int -> RegularBlock -> ShowS)
-> (RegularBlock -> String)
-> ([RegularBlock] -> ShowS)
-> Show RegularBlock
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RegularBlock -> ShowS
showsPrec :: Int -> RegularBlock -> ShowS
$cshow :: RegularBlock -> String
show :: RegularBlock -> String
$cshowList :: [RegularBlock] -> ShowS
showList :: [RegularBlock] -> ShowS
Show)
instance Arbitrary RegularBlock where
arbitrary :: Gen RegularBlock
arbitrary =
ByronBlock -> RegularBlock
RegularBlock (ByronBlock -> RegularBlock)
-> (Block -> ByronBlock) -> Block -> RegularBlock
forall b c a. (b -> c) -> (a -> b) -> a -> c
.EpochSlots -> Block -> ByronBlock
annotateByronBlock EpochSlots
epochSlots (Block -> RegularBlock) -> Gen Block -> Gen RegularBlock
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
Gen Block -> Gen Block
forall a. Gen a -> Gen a
hedgehog (ProtocolMagicId -> EpochSlots -> Gen Block
CC.genBlock ProtocolMagicId
protocolMagicId EpochSlots
epochSlots)
instance Arbitrary ByronBlock where
arbitrary :: Gen ByronBlock
arbitrary = Coherent ByronBlock -> ByronBlock
forall a. Coherent a -> a
getCoherent (Coherent ByronBlock -> ByronBlock)
-> Gen (Coherent ByronBlock) -> Gen ByronBlock
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen (Coherent ByronBlock)
forall a. Arbitrary a => Gen a
arbitrary
instance Arbitrary (Coherent ByronBlock) where
arbitrary :: Gen (Coherent ByronBlock)
arbitrary = ByronBlock -> Coherent ByronBlock
forall a. a -> Coherent a
Coherent (ByronBlock -> Coherent ByronBlock)
-> Gen ByronBlock -> Gen (Coherent ByronBlock)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(Int, Gen ByronBlock)] -> Gen ByronBlock
forall a. HasCallStack => [(Int, Gen a)] -> Gen a
frequency
[ (Int
3, Gen ByronBlock
genBlock)
, (Int
1, Gen ByronBlock
genBoundaryBlock)
]
where
genBlock :: Gen ByronBlock
genBlock :: Gen ByronBlock
genBlock = RegularBlock -> ByronBlock
unRegularBlock (RegularBlock -> ByronBlock) -> Gen RegularBlock -> Gen ByronBlock
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen RegularBlock
forall a. Arbitrary a => Gen a
arbitrary
genBoundaryBlock :: Gen ByronBlock
genBoundaryBlock :: Gen ByronBlock
genBoundaryBlock =
EpochSlots -> ABlockOrBoundary ByteString -> ByronBlock
mkByronBlock EpochSlots
epochSlots (ABlockOrBoundary ByteString -> ByronBlock)
-> (ABoundaryBlock () -> ABlockOrBoundary ByteString)
-> ABoundaryBlock ()
-> ByronBlock
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ABoundaryBlock ByteString -> ABlockOrBoundary ByteString
forall a. ABoundaryBlock a -> ABlockOrBoundary a
ABOBBoundary (ABoundaryBlock ByteString -> ABlockOrBoundary ByteString)
-> (ABoundaryBlock () -> ABoundaryBlock ByteString)
-> ABoundaryBlock ()
-> ABlockOrBoundary ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ProtocolMagicId -> ABoundaryBlock () -> ABoundaryBlock ByteString
API.reAnnotateBoundary ProtocolMagicId
protocolMagicId (ABoundaryBlock () -> ByronBlock)
-> Gen (ABoundaryBlock ()) -> Gen ByronBlock
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
Gen (ABoundaryBlock ()) -> Gen (ABoundaryBlock ())
forall a. Gen a -> Gen a
hedgehog (Gen (ABoundaryBlock ())
CC.genBoundaryBlock)
instance Arbitrary (Header ByronBlock) where
arbitrary :: Gen (Header ByronBlock)
arbitrary = [(Int, Gen (Header ByronBlock))] -> Gen (Header ByronBlock)
forall a. HasCallStack => [(Int, Gen a)] -> Gen a
frequency
[ (Int
3, Gen (Header ByronBlock)
genHeader)
, (Int
1, Gen (Header ByronBlock)
genBoundaryHeader)
]
where
genHeader :: Gen (Header ByronBlock)
genHeader :: Gen (Header ByronBlock)
genHeader = do
SizeInBytes
blockSize <- Word32 -> SizeInBytes
SizeInBytes (Word32 -> SizeInBytes) -> Gen Word32 -> Gen SizeInBytes
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Word32
forall a. Arbitrary a => Gen a
arbitrary
(ABlockOrBoundaryHdr ByteString
-> SizeInBytes -> Header ByronBlock)
-> SizeInBytes
-> ABlockOrBoundaryHdr ByteString
-> Header ByronBlock
forall a b c. (a -> b -> c) -> b -> a -> c
flip (EpochSlots
-> ABlockOrBoundaryHdr ByteString
-> SizeInBytes
-> Header ByronBlock
mkByronHeader EpochSlots
epochSlots) SizeInBytes
blockSize (ABlockOrBoundaryHdr ByteString -> Header ByronBlock)
-> (AHeader () -> ABlockOrBoundaryHdr ByteString)
-> AHeader ()
-> Header ByronBlock
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AHeader ByteString -> ABlockOrBoundaryHdr ByteString
forall a. AHeader a -> ABlockOrBoundaryHdr a
ABOBBlockHdr (AHeader ByteString -> ABlockOrBoundaryHdr ByteString)
-> (AHeader () -> AHeader ByteString)
-> AHeader ()
-> ABlockOrBoundaryHdr ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
(AHeader () -> Encoding)
-> (forall s. Decoder s (AHeader ByteSpan))
-> AHeader ()
-> AHeader ByteString
forall (f :: * -> *) a.
Functor f =>
(f a -> Encoding)
-> (forall s. Decoder s (f ByteSpan)) -> f a -> f ByteString
API.reAnnotateUsing
(EpochSlots -> AHeader () -> Encoding
CC.Block.encCBORHeader EpochSlots
epochSlots)
(EpochSlots -> Decoder s (AHeader ByteSpan)
forall s. EpochSlots -> Decoder s (AHeader ByteSpan)
CC.Block.decCBORAHeader EpochSlots
epochSlots) (AHeader () -> Header ByronBlock)
-> Gen (AHeader ()) -> Gen (Header ByronBlock)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
Gen (AHeader ()) -> Gen (AHeader ())
forall a. Gen a -> Gen a
hedgehog (ProtocolMagicId -> EpochSlots -> Gen (AHeader ())
CC.genHeader ProtocolMagicId
protocolMagicId EpochSlots
epochSlots)
genBoundaryHeader :: Gen (Header ByronBlock)
genBoundaryHeader :: Gen (Header ByronBlock)
genBoundaryHeader = do
SizeInBytes
blockSize <- Word32 -> SizeInBytes
SizeInBytes (Word32 -> SizeInBytes) -> Gen Word32 -> Gen SizeInBytes
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Word32
forall a. Arbitrary a => Gen a
arbitrary
(ABlockOrBoundaryHdr ByteString
-> SizeInBytes -> Header ByronBlock)
-> SizeInBytes
-> ABlockOrBoundaryHdr ByteString
-> Header ByronBlock
forall a b c. (a -> b -> c) -> b -> a -> c
flip (EpochSlots
-> ABlockOrBoundaryHdr ByteString
-> SizeInBytes
-> Header ByronBlock
mkByronHeader EpochSlots
epochSlots) SizeInBytes
blockSize (ABlockOrBoundaryHdr ByteString -> Header ByronBlock)
-> (ABoundaryHeader () -> ABlockOrBoundaryHdr ByteString)
-> ABoundaryHeader ()
-> Header ByronBlock
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ABoundaryHeader ByteString -> ABlockOrBoundaryHdr ByteString
forall a. ABoundaryHeader a -> ABlockOrBoundaryHdr a
ABOBBoundaryHdr (ABoundaryHeader ByteString -> ABlockOrBoundaryHdr ByteString)
-> (ABoundaryHeader () -> ABoundaryHeader ByteString)
-> ABoundaryHeader ()
-> ABlockOrBoundaryHdr ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
(ABoundaryHeader () -> Encoding)
-> (forall s. Decoder s (ABoundaryHeader ByteSpan))
-> ABoundaryHeader ()
-> ABoundaryHeader ByteString
forall (f :: * -> *) a.
Functor f =>
(f a -> Encoding)
-> (forall s. Decoder s (f ByteSpan)) -> f a -> f ByteString
API.reAnnotateUsing
(ProtocolMagicId -> ABoundaryHeader () -> Encoding
forall a. ProtocolMagicId -> ABoundaryHeader a -> Encoding
CC.Block.encCBORABoundaryHeader ProtocolMagicId
protocolMagicId)
Decoder s (ABoundaryHeader ByteSpan)
forall s. Decoder s (ABoundaryHeader ByteSpan)
CC.Block.decCBORABoundaryHeader (ABoundaryHeader () -> Header ByronBlock)
-> Gen (ABoundaryHeader ()) -> Gen (Header ByronBlock)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
Gen (ABoundaryHeader ()) -> Gen (ABoundaryHeader ())
forall a. Gen a -> Gen a
hedgehog Gen (ABoundaryHeader ())
CC.genBoundaryHeader
instance Arbitrary (Hash a) where
arbitrary :: Gen (Hash a)
arbitrary = Hash Text -> Hash a
forall a b. Coercible a b => a -> b
coerce (Hash Text -> Hash a) -> Gen (Hash Text) -> Gen (Hash a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen (Hash Text) -> Gen (Hash Text)
forall a. Gen a -> Gen a
hedgehog Gen (Hash Text)
CC.genTextHash
instance Arbitrary ByronHash where
arbitrary :: Gen ByronHash
arbitrary = HeaderHash -> ByronHash
ByronHash (HeaderHash -> ByronHash) -> Gen HeaderHash -> Gen ByronHash
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen HeaderHash
forall a. Arbitrary a => Gen a
arbitrary
instance Arbitrary KeyHash where
arbitrary :: Gen KeyHash
arbitrary = Gen KeyHash -> Gen KeyHash
forall a. Gen a -> Gen a
hedgehog Gen KeyHash
CC.genKeyHash
instance Arbitrary (GenTx ByronBlock) where
arbitrary :: Gen (GenTx ByronBlock)
arbitrary =
AMempoolPayload ByteString -> GenTx ByronBlock
fromMempoolPayload (AMempoolPayload ByteString -> GenTx ByronBlock)
-> (AMempoolPayload () -> AMempoolPayload ByteString)
-> AMempoolPayload ()
-> GenTx ByronBlock
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (AMempoolPayload () -> Encoding)
-> (forall s. Decoder s (AMempoolPayload ByteSpan))
-> AMempoolPayload ()
-> AMempoolPayload ByteString
forall (f :: * -> *) a.
Functor f =>
(f a -> Encoding)
-> (forall s. Decoder s (f ByteSpan)) -> f a -> f ByteString
API.reAnnotateUsing AMempoolPayload () -> Encoding
forall a. EncCBOR a => a -> Encoding
encCBOR Decoder s (AMempoolPayload ByteSpan)
forall s. Decoder s (AMempoolPayload ByteSpan)
forall a s. DecCBOR a => Decoder s a
decCBOR (AMempoolPayload () -> GenTx ByronBlock)
-> Gen (AMempoolPayload ()) -> Gen (GenTx ByronBlock)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
Gen (AMempoolPayload ()) -> Gen (AMempoolPayload ())
forall a. Gen a -> Gen a
hedgehog (ProtocolMagicId -> Gen (AMempoolPayload ())
CC.genMempoolPayload ProtocolMagicId
protocolMagicId)
instance Arbitrary (GenTxId ByronBlock) where
arbitrary :: Gen (GenTxId ByronBlock)
arbitrary = [Gen (GenTxId ByronBlock)] -> Gen (GenTxId ByronBlock)
forall a. HasCallStack => [Gen a] -> Gen a
oneof
[ TxId -> GenTxId ByronBlock
ByronTxId (TxId -> GenTxId ByronBlock)
-> Gen TxId -> Gen (GenTxId ByronBlock)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen TxId -> Gen TxId
forall a. Gen a -> Gen a
hedgehog Gen TxId
CC.genTxId
, CertificateId -> GenTxId ByronBlock
ByronDlgId (CertificateId -> GenTxId ByronBlock)
-> Gen CertificateId -> Gen (GenTxId ByronBlock)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen CertificateId -> Gen CertificateId
forall a. Gen a -> Gen a
hedgehog Gen CertificateId
genCertificateId
, UpId -> GenTxId ByronBlock
ByronUpdateProposalId (UpId -> GenTxId ByronBlock)
-> Gen UpId -> Gen (GenTxId ByronBlock)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen UpId -> Gen UpId
forall a. Gen a -> Gen a
hedgehog (ProtocolMagicId -> Gen UpId
UG.genUpId ProtocolMagicId
protocolMagicId)
, VoteId -> GenTxId ByronBlock
ByronUpdateVoteId (VoteId -> GenTxId ByronBlock)
-> Gen VoteId -> Gen (GenTxId ByronBlock)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen VoteId -> Gen VoteId
forall a. Gen a -> Gen a
hedgehog Gen VoteId
genUpdateVoteId
]
where
genCertificateId :: Gen CertificateId
genCertificateId = Gen Certificate -> Gen CertificateId
forall a algo.
(EncCBOR a, HashAlgorithm algo) =>
Gen a -> Gen (AbstractHash algo a)
CC.genAbstractHash (ProtocolMagicId -> Gen Certificate
CC.genCertificate ProtocolMagicId
protocolMagicId)
genUpdateVoteId :: Gen VoteId
genUpdateVoteId = Gen Vote -> Gen VoteId
forall a algo.
(EncCBOR a, HashAlgorithm algo) =>
Gen a -> Gen (AbstractHash algo a)
CC.genAbstractHash (ProtocolMagicId -> Gen Vote
UG.genVote ProtocolMagicId
protocolMagicId)
instance Arbitrary API.ApplyMempoolPayloadErr where
arbitrary :: Gen ApplyMempoolPayloadErr
arbitrary = [Gen ApplyMempoolPayloadErr] -> Gen ApplyMempoolPayloadErr
forall a. HasCallStack => [Gen a] -> Gen a
oneof
[ UTxOValidationError -> ApplyMempoolPayloadErr
API.MempoolTxErr (UTxOValidationError -> ApplyMempoolPayloadErr)
-> Gen UTxOValidationError -> Gen ApplyMempoolPayloadErr
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen UTxOValidationError -> Gen UTxOValidationError
forall a. Gen a -> Gen a
hedgehog Gen UTxOValidationError
CC.genUTxOValidationError
, Error -> ApplyMempoolPayloadErr
API.MempoolDlgErr (Error -> ApplyMempoolPayloadErr)
-> Gen Error -> Gen ApplyMempoolPayloadErr
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Error -> Gen Error
forall a. Gen a -> Gen a
hedgehog Gen Error
CC.genError
]
instance Arbitrary (SomeSecond BlockQuery ByronBlock) where
arbitrary :: Gen (SomeSecond BlockQuery ByronBlock)
arbitrary = SomeSecond BlockQuery ByronBlock
-> Gen (SomeSecond BlockQuery ByronBlock)
forall a. a -> Gen a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SomeSecond BlockQuery ByronBlock
-> Gen (SomeSecond BlockQuery ByronBlock))
-> SomeSecond BlockQuery ByronBlock
-> Gen (SomeSecond BlockQuery ByronBlock)
forall a b. (a -> b) -> a -> b
$ BlockQuery ByronBlock State -> SomeSecond BlockQuery ByronBlock
forall {k1} {k2} (f :: k1 -> k2 -> *) (a :: k1) (b :: k2).
f a b -> SomeSecond f a
SomeSecond BlockQuery ByronBlock State
GetUpdateInterfaceState
instance Arbitrary EpochNumber where
arbitrary :: Gen EpochNumber
arbitrary = Gen EpochNumber -> Gen EpochNumber
forall a. Gen a -> Gen a
hedgehog Gen EpochNumber
CC.genEpochNumber
instance Arbitrary SlotNumber where
arbitrary :: Gen SlotNumber
arbitrary = Gen SlotNumber -> Gen SlotNumber
forall a. Gen a -> Gen a
hedgehog Gen SlotNumber
CC.genSlotNumber
instance Arbitrary CC.Update.ApplicationName where
arbitrary :: Gen ApplicationName
arbitrary = Gen ApplicationName -> Gen ApplicationName
forall a. Gen a -> Gen a
hedgehog Gen ApplicationName
UG.genApplicationName
instance Arbitrary CC.Update.SystemTag where
arbitrary :: Gen SystemTag
arbitrary = Gen SystemTag -> Gen SystemTag
forall a. Gen a -> Gen a
hedgehog Gen SystemTag
UG.genSystemTag
instance Arbitrary CC.Update.InstallerHash where
arbitrary :: Gen InstallerHash
arbitrary = Gen InstallerHash -> Gen InstallerHash
forall a. Gen a -> Gen a
hedgehog Gen InstallerHash
UG.genInstallerHash
instance Arbitrary CC.Update.ProtocolVersion where
arbitrary :: Gen ProtocolVersion
arbitrary = Gen ProtocolVersion -> Gen ProtocolVersion
forall a. Gen a -> Gen a
hedgehog Gen ProtocolVersion
UG.genProtocolVersion
instance Arbitrary CC.Update.ProtocolParameters where
arbitrary :: Gen ProtocolParameters
arbitrary = Gen ProtocolParameters -> Gen ProtocolParameters
forall a. Gen a -> Gen a
hedgehog Gen ProtocolParameters
UG.genProtocolParameters
instance Arbitrary CC.Update.SoftwareVersion where
arbitrary :: Gen SoftwareVersion
arbitrary = Gen SoftwareVersion -> Gen SoftwareVersion
forall a. Gen a -> Gen a
hedgehog Gen SoftwareVersion
UG.genSoftwareVersion
instance Arbitrary CC.Reg.ProtocolUpdateProposal where
arbitrary :: Gen ProtocolUpdateProposal
arbitrary = ProtocolVersion -> ProtocolParameters -> ProtocolUpdateProposal
CC.Reg.ProtocolUpdateProposal
(ProtocolVersion -> ProtocolParameters -> ProtocolUpdateProposal)
-> Gen ProtocolVersion
-> Gen (ProtocolParameters -> ProtocolUpdateProposal)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen ProtocolVersion
forall a. Arbitrary a => Gen a
arbitrary
Gen (ProtocolParameters -> ProtocolUpdateProposal)
-> Gen ProtocolParameters -> Gen ProtocolUpdateProposal
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen ProtocolParameters
forall a. Arbitrary a => Gen a
arbitrary
instance Arbitrary CC.Reg.SoftwareUpdateProposal where
arbitrary :: Gen SoftwareUpdateProposal
arbitrary = SoftwareVersion -> Metadata -> SoftwareUpdateProposal
CC.Reg.SoftwareUpdateProposal
(SoftwareVersion -> Metadata -> SoftwareUpdateProposal)
-> Gen SoftwareVersion -> Gen (Metadata -> SoftwareUpdateProposal)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen SoftwareVersion
forall a. Arbitrary a => Gen a
arbitrary
Gen (Metadata -> SoftwareUpdateProposal)
-> Gen Metadata -> Gen SoftwareUpdateProposal
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Metadata
forall a. Arbitrary a => Gen a
arbitrary
instance Arbitrary CC.Reg.ApplicationVersion where
arbitrary :: Gen ApplicationVersion
arbitrary = Word32 -> SlotNumber -> Metadata -> ApplicationVersion
CC.Reg.ApplicationVersion
(Word32 -> SlotNumber -> Metadata -> ApplicationVersion)
-> Gen Word32 -> Gen (SlotNumber -> Metadata -> ApplicationVersion)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Word32
forall a. Arbitrary a => Gen a
arbitrary
Gen (SlotNumber -> Metadata -> ApplicationVersion)
-> Gen SlotNumber -> Gen (Metadata -> ApplicationVersion)
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen SlotNumber
forall a. Arbitrary a => Gen a
arbitrary
Gen (Metadata -> ApplicationVersion)
-> Gen Metadata -> Gen ApplicationVersion
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Metadata
forall a. Arbitrary a => Gen a
arbitrary
instance Arbitrary CC.UPI.State where
arbitrary :: Gen State
arbitrary = EpochNumber
-> ProtocolVersion
-> ProtocolParameters
-> [CandidateProtocolUpdate]
-> ApplicationVersions
-> ProtocolUpdateProposals
-> SoftwareUpdateProposals
-> Map UpId SlotNumber
-> Map UpId (Set KeyHash)
-> Set Endorsement
-> Map UpId SlotNumber
-> State
CC.UPI.State
(EpochNumber
-> ProtocolVersion
-> ProtocolParameters
-> [CandidateProtocolUpdate]
-> ApplicationVersions
-> ProtocolUpdateProposals
-> SoftwareUpdateProposals
-> Map UpId SlotNumber
-> Map UpId (Set KeyHash)
-> Set Endorsement
-> Map UpId SlotNumber
-> State)
-> Gen EpochNumber
-> Gen
(ProtocolVersion
-> ProtocolParameters
-> [CandidateProtocolUpdate]
-> ApplicationVersions
-> ProtocolUpdateProposals
-> SoftwareUpdateProposals
-> Map UpId SlotNumber
-> Map UpId (Set KeyHash)
-> Set Endorsement
-> Map UpId SlotNumber
-> State)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen EpochNumber
forall a. Arbitrary a => Gen a
arbitrary
Gen
(ProtocolVersion
-> ProtocolParameters
-> [CandidateProtocolUpdate]
-> ApplicationVersions
-> ProtocolUpdateProposals
-> SoftwareUpdateProposals
-> Map UpId SlotNumber
-> Map UpId (Set KeyHash)
-> Set Endorsement
-> Map UpId SlotNumber
-> State)
-> Gen ProtocolVersion
-> Gen
(ProtocolParameters
-> [CandidateProtocolUpdate]
-> ApplicationVersions
-> ProtocolUpdateProposals
-> SoftwareUpdateProposals
-> Map UpId SlotNumber
-> Map UpId (Set KeyHash)
-> Set Endorsement
-> Map UpId SlotNumber
-> State)
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen ProtocolVersion
forall a. Arbitrary a => Gen a
arbitrary
Gen
(ProtocolParameters
-> [CandidateProtocolUpdate]
-> ApplicationVersions
-> ProtocolUpdateProposals
-> SoftwareUpdateProposals
-> Map UpId SlotNumber
-> Map UpId (Set KeyHash)
-> Set Endorsement
-> Map UpId SlotNumber
-> State)
-> Gen ProtocolParameters
-> Gen
([CandidateProtocolUpdate]
-> ApplicationVersions
-> ProtocolUpdateProposals
-> SoftwareUpdateProposals
-> Map UpId SlotNumber
-> Map UpId (Set KeyHash)
-> Set Endorsement
-> Map UpId SlotNumber
-> State)
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen ProtocolParameters
forall a. Arbitrary a => Gen a
arbitrary
Gen
([CandidateProtocolUpdate]
-> ApplicationVersions
-> ProtocolUpdateProposals
-> SoftwareUpdateProposals
-> Map UpId SlotNumber
-> Map UpId (Set KeyHash)
-> Set Endorsement
-> Map UpId SlotNumber
-> State)
-> Gen [CandidateProtocolUpdate]
-> Gen
(ApplicationVersions
-> ProtocolUpdateProposals
-> SoftwareUpdateProposals
-> Map UpId SlotNumber
-> Map UpId (Set KeyHash)
-> Set Endorsement
-> Map UpId SlotNumber
-> State)
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> [CandidateProtocolUpdate] -> Gen [CandidateProtocolUpdate]
forall a. a -> Gen a
forall (f :: * -> *) a. Applicative f => a -> f a
pure [CandidateProtocolUpdate]
forall a. Monoid a => a
mempty
Gen
(ApplicationVersions
-> ProtocolUpdateProposals
-> SoftwareUpdateProposals
-> Map UpId SlotNumber
-> Map UpId (Set KeyHash)
-> Set Endorsement
-> Map UpId SlotNumber
-> State)
-> Gen ApplicationVersions
-> Gen
(ProtocolUpdateProposals
-> SoftwareUpdateProposals
-> Map UpId SlotNumber
-> Map UpId (Set KeyHash)
-> Set Endorsement
-> Map UpId SlotNumber
-> State)
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen ApplicationVersions
forall a. Arbitrary a => Gen a
arbitrary
Gen
(ProtocolUpdateProposals
-> SoftwareUpdateProposals
-> Map UpId SlotNumber
-> Map UpId (Set KeyHash)
-> Set Endorsement
-> Map UpId SlotNumber
-> State)
-> Gen ProtocolUpdateProposals
-> Gen
(SoftwareUpdateProposals
-> Map UpId SlotNumber
-> Map UpId (Set KeyHash)
-> Set Endorsement
-> Map UpId SlotNumber
-> State)
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen ProtocolUpdateProposals
forall a. Arbitrary a => Gen a
arbitrary
Gen
(SoftwareUpdateProposals
-> Map UpId SlotNumber
-> Map UpId (Set KeyHash)
-> Set Endorsement
-> Map UpId SlotNumber
-> State)
-> Gen SoftwareUpdateProposals
-> Gen
(Map UpId SlotNumber
-> Map UpId (Set KeyHash)
-> Set Endorsement
-> Map UpId SlotNumber
-> State)
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen SoftwareUpdateProposals
forall a. Arbitrary a => Gen a
arbitrary
Gen
(Map UpId SlotNumber
-> Map UpId (Set KeyHash)
-> Set Endorsement
-> Map UpId SlotNumber
-> State)
-> Gen (Map UpId SlotNumber)
-> Gen
(Map UpId (Set KeyHash)
-> Set Endorsement -> Map UpId SlotNumber -> State)
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen (Map UpId SlotNumber)
forall a. Arbitrary a => Gen a
arbitrary
Gen
(Map UpId (Set KeyHash)
-> Set Endorsement -> Map UpId SlotNumber -> State)
-> Gen (Map UpId (Set KeyHash))
-> Gen (Set Endorsement -> Map UpId SlotNumber -> State)
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen (Map UpId (Set KeyHash))
forall a. Arbitrary a => Gen a
arbitrary
Gen (Set Endorsement -> Map UpId SlotNumber -> State)
-> Gen (Set Endorsement) -> Gen (Map UpId SlotNumber -> State)
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Set Endorsement -> Gen (Set Endorsement)
forall a. a -> Gen a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Set Endorsement
forall a. Monoid a => a
mempty
Gen (Map UpId SlotNumber -> State)
-> Gen (Map UpId SlotNumber) -> Gen State
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen (Map UpId SlotNumber)
forall a. Arbitrary a => Gen a
arbitrary
instance Arbitrary CC.Genesis.GenesisHash where
arbitrary :: Gen GenesisHash
arbitrary = Hash Raw -> GenesisHash
CC.Genesis.GenesisHash (Hash Raw -> GenesisHash) -> Gen (Hash Raw) -> Gen GenesisHash
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen (Hash Raw)
forall a. Arbitrary a => Gen a
arbitrary
instance Arbitrary CC.UTxO.UTxO where
arbitrary :: Gen UTxO
arbitrary = Gen UTxO -> Gen UTxO
forall a. Gen a -> Gen a
hedgehog Gen UTxO
CC.genUTxO
instance Arbitrary CC.Act.State where
arbitrary :: Gen State
arbitrary = Map -> Map KeyHash SlotNumber -> State
CC.Act.State
(Map -> Map KeyHash SlotNumber -> State)
-> Gen Map -> Gen (Map KeyHash SlotNumber -> State)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Map
forall a. Arbitrary a => Gen a
arbitrary
Gen (Map KeyHash SlotNumber -> State)
-> Gen (Map KeyHash SlotNumber) -> Gen State
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen (Map KeyHash SlotNumber)
forall a. Arbitrary a => Gen a
arbitrary
instance Arbitrary CC.Sched.ScheduledDelegation where
arbitrary :: Gen ScheduledDelegation
arbitrary = SlotNumber -> KeyHash -> KeyHash -> ScheduledDelegation
CC.Sched.ScheduledDelegation
(SlotNumber -> KeyHash -> KeyHash -> ScheduledDelegation)
-> Gen SlotNumber
-> Gen (KeyHash -> KeyHash -> ScheduledDelegation)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen SlotNumber
forall a. Arbitrary a => Gen a
arbitrary
Gen (KeyHash -> KeyHash -> ScheduledDelegation)
-> Gen KeyHash -> Gen (KeyHash -> ScheduledDelegation)
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen KeyHash
forall a. Arbitrary a => Gen a
arbitrary
Gen (KeyHash -> ScheduledDelegation)
-> Gen KeyHash -> Gen ScheduledDelegation
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen KeyHash
forall a. Arbitrary a => Gen a
arbitrary
instance Arbitrary CC.Sched.State where
arbitrary :: Gen State
arbitrary = Seq ScheduledDelegation -> Set (EpochNumber, KeyHash) -> State
CC.Sched.State
(Seq ScheduledDelegation -> Set (EpochNumber, KeyHash) -> State)
-> Gen (Seq ScheduledDelegation)
-> Gen (Set (EpochNumber, KeyHash) -> State)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen (Seq ScheduledDelegation)
forall a. Arbitrary a => Gen a
arbitrary
Gen (Set (EpochNumber, KeyHash) -> State)
-> Gen (Set (EpochNumber, KeyHash)) -> Gen State
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen (Set (EpochNumber, KeyHash))
forall a. Arbitrary a => Gen a
arbitrary
instance Arbitrary CC.DI.State where
arbitrary :: Gen State
arbitrary = State -> State -> State
CC.DI.State
(State -> State -> State) -> Gen State -> Gen (State -> State)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen State
forall a. Arbitrary a => Gen a
arbitrary
Gen (State -> State) -> Gen State -> Gen State
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen State
forall a. Arbitrary a => Gen a
arbitrary
instance Arbitrary CC.Block.ChainValidationState where
arbitrary :: Gen ChainValidationState
arbitrary = SlotNumber
-> Either GenesisHash HeaderHash
-> UTxO
-> State
-> State
-> ChainValidationState
CC.Block.ChainValidationState
(SlotNumber
-> Either GenesisHash HeaderHash
-> UTxO
-> State
-> State
-> ChainValidationState)
-> Gen SlotNumber
-> Gen
(Either GenesisHash HeaderHash
-> UTxO -> State -> State -> ChainValidationState)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen SlotNumber
forall a. Arbitrary a => Gen a
arbitrary
Gen
(Either GenesisHash HeaderHash
-> UTxO -> State -> State -> ChainValidationState)
-> Gen (Either GenesisHash HeaderHash)
-> Gen (UTxO -> State -> State -> ChainValidationState)
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen (Either GenesisHash HeaderHash)
forall a. Arbitrary a => Gen a
arbitrary
Gen (UTxO -> State -> State -> ChainValidationState)
-> Gen UTxO -> Gen (State -> State -> ChainValidationState)
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen UTxO
forall a. Arbitrary a => Gen a
arbitrary
Gen (State -> State -> ChainValidationState)
-> Gen State -> Gen (State -> ChainValidationState)
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen State
forall a. Arbitrary a => Gen a
arbitrary
Gen (State -> ChainValidationState)
-> Gen State -> Gen ChainValidationState
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen State
forall a. Arbitrary a => Gen a
arbitrary
instance Arbitrary ByronNodeToNodeVersion where
arbitrary :: Gen ByronNodeToNodeVersion
arbitrary = Gen ByronNodeToNodeVersion
forall a. (Bounded a, Enum a) => Gen a
arbitraryBoundedEnum
instance Arbitrary ByronNodeToClientVersion where
arbitrary :: Gen ByronNodeToClientVersion
arbitrary = Gen ByronNodeToClientVersion
forall a. (Bounded a, Enum a) => Gen a
arbitraryBoundedEnum
instance Arbitrary CC.Del.Map where
arbitrary :: Gen Map
arbitrary = [(KeyHash, KeyHash)] -> Map
CC.Del.fromList ([(KeyHash, KeyHash)] -> Map)
-> Gen [(KeyHash, KeyHash)] -> Gen Map
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen [(KeyHash, KeyHash)]
forall a. Arbitrary a => Gen a
arbitrary
instance Arbitrary ByronTransition where
arbitrary :: Gen ByronTransition
arbitrary = Map ProtocolVersion BlockNo -> ByronTransition
ByronTransitionInfo (Map ProtocolVersion BlockNo -> ByronTransition)
-> ([(ProtocolVersion, BlockNo)] -> Map ProtocolVersion BlockNo)
-> [(ProtocolVersion, BlockNo)]
-> ByronTransition
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(ProtocolVersion, BlockNo)] -> Map ProtocolVersion BlockNo
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList ([(ProtocolVersion, BlockNo)] -> ByronTransition)
-> Gen [(ProtocolVersion, BlockNo)] -> Gen ByronTransition
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen [(ProtocolVersion, BlockNo)]
forall a. Arbitrary a => Gen a
arbitrary
instance Arbitrary (LedgerState ByronBlock) where
arbitrary :: Gen (LedgerState ByronBlock)
arbitrary = WithOrigin BlockNo
-> ChainValidationState
-> ByronTransition
-> LedgerState ByronBlock
ByronLedgerState (WithOrigin BlockNo
-> ChainValidationState
-> ByronTransition
-> LedgerState ByronBlock)
-> Gen (WithOrigin BlockNo)
-> Gen
(ChainValidationState -> ByronTransition -> LedgerState ByronBlock)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen (WithOrigin BlockNo)
forall a. Arbitrary a => Gen a
arbitrary Gen
(ChainValidationState -> ByronTransition -> LedgerState ByronBlock)
-> Gen ChainValidationState
-> Gen (ByronTransition -> LedgerState ByronBlock)
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen ChainValidationState
forall a. Arbitrary a => Gen a
arbitrary Gen (ByronTransition -> LedgerState ByronBlock)
-> Gen ByronTransition -> Gen (LedgerState ByronBlock)
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen ByronTransition
forall a. Arbitrary a => Gen a
arbitrary
instance Arbitrary (TipInfoIsEBB ByronBlock) where
arbitrary :: Gen (TipInfoIsEBB ByronBlock)
arbitrary = HeaderHash ByronBlock -> IsEBB -> TipInfoIsEBB ByronBlock
ByronHash -> IsEBB -> TipInfoIsEBB ByronBlock
forall blk. HeaderHash blk -> IsEBB -> TipInfoIsEBB blk
TipInfoIsEBB (ByronHash -> IsEBB -> TipInfoIsEBB ByronBlock)
-> Gen ByronHash -> Gen (IsEBB -> TipInfoIsEBB ByronBlock)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen ByronHash
forall a. Arbitrary a => Gen a
arbitrary Gen (IsEBB -> TipInfoIsEBB ByronBlock)
-> Gen IsEBB -> Gen (TipInfoIsEBB ByronBlock)
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> [IsEBB] -> Gen IsEBB
forall a. HasCallStack => [a] -> Gen a
elements [IsEBB
IsEBB, IsEBB
IsNotEBB]
instance Arbitrary (AnnTip ByronBlock) where
arbitrary :: Gen (AnnTip ByronBlock)
arbitrary = SlotNo -> BlockNo -> TipInfoIsEBB ByronBlock -> AnnTip ByronBlock
SlotNo -> BlockNo -> TipInfo ByronBlock -> AnnTip ByronBlock
forall blk. SlotNo -> BlockNo -> TipInfo blk -> AnnTip blk
AnnTip
(SlotNo -> BlockNo -> TipInfoIsEBB ByronBlock -> AnnTip ByronBlock)
-> Gen SlotNo
-> Gen (BlockNo -> TipInfoIsEBB ByronBlock -> AnnTip ByronBlock)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Word64 -> SlotNo
SlotNo (Word64 -> SlotNo) -> Gen Word64 -> Gen SlotNo
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Word64
forall a. Arbitrary a => Gen a
arbitrary)
Gen (BlockNo -> TipInfoIsEBB ByronBlock -> AnnTip ByronBlock)
-> Gen BlockNo
-> Gen (TipInfoIsEBB ByronBlock -> AnnTip ByronBlock)
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Word64 -> BlockNo
BlockNo (Word64 -> BlockNo) -> Gen Word64 -> Gen BlockNo
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Word64
forall a. Arbitrary a => Gen a
arbitrary)
Gen (TipInfoIsEBB ByronBlock -> AnnTip ByronBlock)
-> Gen (TipInfoIsEBB ByronBlock) -> Gen (AnnTip ByronBlock)
forall a b. Gen (a -> b) -> Gen a -> Gen b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen (TipInfoIsEBB ByronBlock)
forall a. Arbitrary a => Gen a
arbitrary
instance Arbitrary (PBftState PBftByronCrypto) where
arbitrary :: Gen (PBftState PBftByronCrypto)
arbitrary = do
Word64
slots <- (Word64, Word64) -> Gen Word64
forall a. Random a => (a, a) -> Gen a
choose (Word64
0, Word64
10)
[KeyHash]
keys <- Int -> Gen KeyHash -> Gen [KeyHash]
forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM Int
3 Gen KeyHash
forall a. Arbitrary a => Gen a
arbitrary
let signers :: [PBftSigner PBftByronCrypto]
signers = (SlotNo -> KeyHash -> PBftSigner PBftByronCrypto)
-> [SlotNo] -> [KeyHash] -> [PBftSigner PBftByronCrypto]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith SlotNo -> KeyHash -> PBftSigner PBftByronCrypto
SlotNo
-> PBftVerKeyHash PBftByronCrypto -> PBftSigner PBftByronCrypto
forall c. SlotNo -> PBftVerKeyHash c -> PBftSigner c
PBftState.PBftSigner ((Word64 -> SlotNo) -> [Word64] -> [SlotNo]
forall a b. (a -> b) -> [a] -> [b]
map Word64 -> SlotNo
SlotNo [Word64
0..Word64
slots]) ([KeyHash] -> [KeyHash]
forall a. HasCallStack => [a] -> [a]
cycle [KeyHash]
keys)
PBftState PBftByronCrypto -> Gen (PBftState PBftByronCrypto)
forall a. a -> Gen a
forall (m :: * -> *) a. Monad m => a -> m a
return (PBftState PBftByronCrypto -> Gen (PBftState PBftByronCrypto))
-> PBftState PBftByronCrypto -> Gen (PBftState PBftByronCrypto)
forall a b. (a -> b) -> a -> b
$ [PBftSigner PBftByronCrypto] -> PBftState PBftByronCrypto
forall c. PBftCrypto c => [PBftSigner c] -> PBftState c
PBftState.fromList [PBftSigner PBftByronCrypto]
signers
instance Arbitrary (SomeResult ByronBlock) where
arbitrary :: Gen (SomeResult ByronBlock)
arbitrary = BlockQuery ByronBlock State -> State -> SomeResult ByronBlock
forall result blk.
(Eq result, Show result, Typeable result) =>
BlockQuery blk result -> result -> SomeResult blk
SomeResult BlockQuery ByronBlock State
GetUpdateInterfaceState (State -> SomeResult ByronBlock)
-> Gen State -> Gen (SomeResult ByronBlock)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen State
forall a. Arbitrary a => Gen a
arbitrary
instance Arbitrary (WithVersion ByronNodeToNodeVersion (Header ByronBlock)) where
arbitrary :: Gen (WithVersion ByronNodeToNodeVersion (Header ByronBlock))
arbitrary = do
ByronNodeToNodeVersion
version <- Gen ByronNodeToNodeVersion
forall a. Arbitrary a => Gen a
arbitrary
Header ByronBlock
hdr <- Gen (Header ByronBlock)
forall a. Arbitrary a => Gen a
arbitrary
let hdr' :: Header ByronBlock
hdr' = case ByronNodeToNodeVersion
version of
ByronNodeToNodeVersion
ByronNodeToNodeVersion1 ->
Header ByronBlock
hdr { byronHeaderBlockSizeHint = fakeByronBlockSizeHint }
ByronNodeToNodeVersion
ByronNodeToNodeVersion2 ->
Header ByronBlock
hdr
WithVersion ByronNodeToNodeVersion (Header ByronBlock)
-> Gen (WithVersion ByronNodeToNodeVersion (Header ByronBlock))
forall a. a -> Gen a
forall (m :: * -> *) a. Monad m => a -> m a
return (ByronNodeToNodeVersion
-> Header ByronBlock
-> WithVersion ByronNodeToNodeVersion (Header ByronBlock)
forall v a. v -> a -> WithVersion v a
WithVersion ByronNodeToNodeVersion
version Header ByronBlock
hdr')
instance Arbitrary (WithVersion ByronNodeToNodeVersion (SomeSecond (NestedCtxt Header) ByronBlock)) where
arbitrary :: Gen
(WithVersion
ByronNodeToNodeVersion (SomeSecond (NestedCtxt Header) ByronBlock))
arbitrary = do
ByronNodeToNodeVersion
version <- Gen ByronNodeToNodeVersion
forall a. Arbitrary a => Gen a
arbitrary
SizeInBytes
size <- case ByronNodeToNodeVersion
version of
ByronNodeToNodeVersion
ByronNodeToNodeVersion1 -> SizeInBytes -> Gen SizeInBytes
forall a. a -> Gen a
forall (m :: * -> *) a. Monad m => a -> m a
return SizeInBytes
fakeByronBlockSizeHint
ByronNodeToNodeVersion
ByronNodeToNodeVersion2 -> Word32 -> SizeInBytes
SizeInBytes (Word32 -> SizeInBytes) -> Gen Word32 -> Gen SizeInBytes
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Word32
forall a. Arbitrary a => Gen a
arbitrary
SomeSecond (NestedCtxt Header) ByronBlock
ctxt <- [SomeSecond (NestedCtxt Header) ByronBlock]
-> Gen (SomeSecond (NestedCtxt Header) ByronBlock)
forall a. HasCallStack => [a] -> Gen a
elements [
NestedCtxt Header ByronBlock (AHeader ByteString)
-> SomeSecond (NestedCtxt Header) ByronBlock
forall {k1} {k2} (f :: k1 -> k2 -> *) (a :: k1) (b :: k2).
f a b -> SomeSecond f a
SomeSecond (NestedCtxt Header ByronBlock (AHeader ByteString)
-> SomeSecond (NestedCtxt Header) ByronBlock)
-> (NestedCtxt_ ByronBlock Header (AHeader ByteString)
-> NestedCtxt Header ByronBlock (AHeader ByteString))
-> NestedCtxt_ ByronBlock Header (AHeader ByteString)
-> SomeSecond (NestedCtxt Header) ByronBlock
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NestedCtxt_ ByronBlock Header (AHeader ByteString)
-> NestedCtxt Header ByronBlock (AHeader ByteString)
forall (f :: * -> *) blk a.
NestedCtxt_ blk f a -> NestedCtxt f blk a
NestedCtxt (NestedCtxt_ ByronBlock Header (AHeader ByteString)
-> SomeSecond (NestedCtxt Header) ByronBlock)
-> NestedCtxt_ ByronBlock Header (AHeader ByteString)
-> SomeSecond (NestedCtxt Header) ByronBlock
forall a b. (a -> b) -> a -> b
$ SizeInBytes -> NestedCtxt_ ByronBlock Header (AHeader ByteString)
CtxtByronRegular SizeInBytes
size
, NestedCtxt Header ByronBlock (SlotNo, ABoundaryHeader ByteString)
-> SomeSecond (NestedCtxt Header) ByronBlock
forall {k1} {k2} (f :: k1 -> k2 -> *) (a :: k1) (b :: k2).
f a b -> SomeSecond f a
SomeSecond (NestedCtxt Header ByronBlock (SlotNo, ABoundaryHeader ByteString)
-> SomeSecond (NestedCtxt Header) ByronBlock)
-> (NestedCtxt_
ByronBlock Header (SlotNo, ABoundaryHeader ByteString)
-> NestedCtxt
Header ByronBlock (SlotNo, ABoundaryHeader ByteString))
-> NestedCtxt_
ByronBlock Header (SlotNo, ABoundaryHeader ByteString)
-> SomeSecond (NestedCtxt Header) ByronBlock
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NestedCtxt_ ByronBlock Header (SlotNo, ABoundaryHeader ByteString)
-> NestedCtxt
Header ByronBlock (SlotNo, ABoundaryHeader ByteString)
forall (f :: * -> *) blk a.
NestedCtxt_ blk f a -> NestedCtxt f blk a
NestedCtxt (NestedCtxt_ ByronBlock Header (SlotNo, ABoundaryHeader ByteString)
-> SomeSecond (NestedCtxt Header) ByronBlock)
-> NestedCtxt_
ByronBlock Header (SlotNo, ABoundaryHeader ByteString)
-> SomeSecond (NestedCtxt Header) ByronBlock
forall a b. (a -> b) -> a -> b
$ SizeInBytes
-> NestedCtxt_
ByronBlock Header (SlotNo, ABoundaryHeader ByteString)
CtxtByronBoundary SizeInBytes
size
]
WithVersion
ByronNodeToNodeVersion (SomeSecond (NestedCtxt Header) ByronBlock)
-> Gen
(WithVersion
ByronNodeToNodeVersion (SomeSecond (NestedCtxt Header) ByronBlock))
forall a. a -> Gen a
forall (m :: * -> *) a. Monad m => a -> m a
return (ByronNodeToNodeVersion
-> SomeSecond (NestedCtxt Header) ByronBlock
-> WithVersion
ByronNodeToNodeVersion (SomeSecond (NestedCtxt Header) ByronBlock)
forall v a. v -> a -> WithVersion v a
WithVersion ByronNodeToNodeVersion
version SomeSecond (NestedCtxt Header) ByronBlock
ctxt)