module Test.Cardano.Chain.Genesis.Gen (
genCanonicalGenesisData,
genCanonicalGenesisDelegation,
genGenesisData,
genGenesisHash,
genConfig,
genFakeAvvmOptions,
genGenesisAvvmBalances,
genGenesisDelegation,
genGenesisInitializer,
genGenesisNonAvvmBalances,
genGenesisSpec,
genGenesisKeyHashes,
genSignatureEpochNumber,
genTestnetBalanceOptions,
) where
import Cardano.Chain.Common (BlockCount (..))
import Cardano.Chain.Genesis (
Config (..),
FakeAvvmOptions (..),
GenesisAvvmBalances (..),
GenesisData (..),
GenesisDelegation (..),
GenesisHash (..),
GenesisInitializer (..),
GenesisKeyHashes (..),
GenesisNonAvvmBalances (..),
GenesisSpec (..),
TestnetBalanceOptions (..),
mkGenesisDelegation,
mkGenesisSpec,
)
import Cardano.Chain.Slotting (EpochNumber)
import Cardano.Crypto (ProtocolMagicId, Signature (..))
import qualified Cardano.Crypto.Wallet as CC
import Cardano.Prelude
import Data.Coerce (coerce)
import qualified Data.Map.Strict as M
import qualified Data.Text as T
import Data.Time (Day (..), UTCTime (..), secondsToDiffTime)
import Formatting (build, sformat)
import Hedgehog
import qualified Hedgehog.Gen as Gen
import qualified Hedgehog.Range as Range
import Test.Cardano.Chain.Common.Gen (
genAddress,
genBlockCount,
genKeyHash,
genLovelace,
)
import Test.Cardano.Chain.Delegation.Gen (
genCanonicalCertificateDistinctList,
genCertificateDistinctList,
)
import Test.Cardano.Chain.UTxO.Gen (genUTxOConfiguration)
import Test.Cardano.Chain.Update.Gen (
genCanonicalProtocolParameters,
genProtocolParameters,
)
import Test.Cardano.Crypto.Gen (
genCompactRedeemVerificationKey,
genProtocolMagic,
genProtocolMagicId,
genRequiresNetworkMagic,
genTextHash,
)
genConfig :: ProtocolMagicId -> Gen Config
genConfig :: ProtocolMagicId -> Gen Config
genConfig ProtocolMagicId
pm =
GenesisData
-> GenesisHash
-> RequiresNetworkMagic
-> UTxOConfiguration
-> Config
Config
(GenesisData
-> GenesisHash
-> RequiresNetworkMagic
-> UTxOConfiguration
-> Config)
-> GenT Identity GenesisData
-> GenT
Identity
(GenesisHash
-> RequiresNetworkMagic -> UTxOConfiguration -> Config)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ProtocolMagicId -> GenT Identity GenesisData
genGenesisData ProtocolMagicId
pm
GenT
Identity
(GenesisHash
-> RequiresNetworkMagic -> UTxOConfiguration -> Config)
-> GenT Identity GenesisHash
-> GenT
Identity (RequiresNetworkMagic -> UTxOConfiguration -> Config)
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
<*> GenT Identity GenesisHash
genGenesisHash
GenT Identity (RequiresNetworkMagic -> UTxOConfiguration -> Config)
-> GenT Identity RequiresNetworkMagic
-> GenT Identity (UTxOConfiguration -> Config)
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
<*> GenT Identity RequiresNetworkMagic
genRequiresNetworkMagic
GenT Identity (UTxOConfiguration -> Config)
-> GenT Identity UTxOConfiguration -> Gen Config
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
<*> GenT Identity UTxOConfiguration
genUTxOConfiguration
genCanonicalGenesisData :: ProtocolMagicId -> Gen GenesisData
genCanonicalGenesisData :: ProtocolMagicId -> GenT Identity GenesisData
genCanonicalGenesisData ProtocolMagicId
pm =
GenesisKeyHashes
-> GenesisDelegation
-> UTCTime
-> GenesisNonAvvmBalances
-> ProtocolParameters
-> BlockCount
-> ProtocolMagicId
-> GenesisAvvmBalances
-> GenesisData
GenesisData
(GenesisKeyHashes
-> GenesisDelegation
-> UTCTime
-> GenesisNonAvvmBalances
-> ProtocolParameters
-> BlockCount
-> ProtocolMagicId
-> GenesisAvvmBalances
-> GenesisData)
-> GenT Identity GenesisKeyHashes
-> GenT
Identity
(GenesisDelegation
-> UTCTime
-> GenesisNonAvvmBalances
-> ProtocolParameters
-> BlockCount
-> ProtocolMagicId
-> GenesisAvvmBalances
-> GenesisData)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenT Identity GenesisKeyHashes
genGenesisKeyHashes
GenT
Identity
(GenesisDelegation
-> UTCTime
-> GenesisNonAvvmBalances
-> ProtocolParameters
-> BlockCount
-> ProtocolMagicId
-> GenesisAvvmBalances
-> GenesisData)
-> GenT Identity GenesisDelegation
-> GenT
Identity
(UTCTime
-> GenesisNonAvvmBalances
-> ProtocolParameters
-> BlockCount
-> ProtocolMagicId
-> GenesisAvvmBalances
-> GenesisData)
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
<*> ProtocolMagicId -> GenT Identity GenesisDelegation
genCanonicalGenesisDelegation ProtocolMagicId
pm
GenT
Identity
(UTCTime
-> GenesisNonAvvmBalances
-> ProtocolParameters
-> BlockCount
-> ProtocolMagicId
-> GenesisAvvmBalances
-> GenesisData)
-> GenT Identity UTCTime
-> GenT
Identity
(GenesisNonAvvmBalances
-> ProtocolParameters
-> BlockCount
-> ProtocolMagicId
-> GenesisAvvmBalances
-> GenesisData)
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
<*> GenT Identity UTCTime
genUTCTime
GenT
Identity
(GenesisNonAvvmBalances
-> ProtocolParameters
-> BlockCount
-> ProtocolMagicId
-> GenesisAvvmBalances
-> GenesisData)
-> GenT Identity GenesisNonAvvmBalances
-> GenT
Identity
(ProtocolParameters
-> BlockCount
-> ProtocolMagicId
-> GenesisAvvmBalances
-> GenesisData)
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
<*> GenT Identity GenesisNonAvvmBalances
genGenesisNonAvvmBalances
GenT
Identity
(ProtocolParameters
-> BlockCount
-> ProtocolMagicId
-> GenesisAvvmBalances
-> GenesisData)
-> GenT Identity ProtocolParameters
-> GenT
Identity
(BlockCount
-> ProtocolMagicId -> GenesisAvvmBalances -> GenesisData)
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
<*> GenT Identity ProtocolParameters
genCanonicalProtocolParameters
GenT
Identity
(BlockCount
-> ProtocolMagicId -> GenesisAvvmBalances -> GenesisData)
-> GenT Identity BlockCount
-> GenT
Identity (ProtocolMagicId -> GenesisAvvmBalances -> GenesisData)
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
<*> GenT Identity BlockCount
genBlockCount'
GenT
Identity (ProtocolMagicId -> GenesisAvvmBalances -> GenesisData)
-> GenT Identity ProtocolMagicId
-> GenT Identity (GenesisAvvmBalances -> GenesisData)
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
<*> GenT Identity ProtocolMagicId
genProtocolMagicId
GenT Identity (GenesisAvvmBalances -> GenesisData)
-> GenT Identity GenesisAvvmBalances -> GenT Identity GenesisData
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
<*> GenT Identity GenesisAvvmBalances
genGenesisAvvmBalances
where
genBlockCount' :: Gen BlockCount
genBlockCount' :: GenT Identity BlockCount
genBlockCount' = Word64 -> BlockCount
BlockCount (Word64 -> BlockCount)
-> GenT Identity Word64 -> GenT Identity BlockCount
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Range Word64 -> GenT Identity Word64
forall (m :: * -> *). MonadGen m => Range Word64 -> m Word64
Gen.word64 (Word64 -> Word64 -> Range Word64
forall a. Integral a => a -> a -> Range a
Range.linear Word64
0 Word64
1000000000)
genCanonicalGenesisDelegation :: ProtocolMagicId -> Gen GenesisDelegation
genCanonicalGenesisDelegation :: ProtocolMagicId -> GenT Identity GenesisDelegation
genCanonicalGenesisDelegation ProtocolMagicId
pm =
[Certificate] -> GenesisDelegation
mkGenesisDelegation' ([Certificate] -> GenesisDelegation)
-> GenT Identity [Certificate] -> GenT Identity GenesisDelegation
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ProtocolMagicId -> GenT Identity [Certificate]
genCanonicalCertificateDistinctList ProtocolMagicId
pm
where
mkGenesisDelegation' :: [Certificate] -> GenesisDelegation
mkGenesisDelegation' =
(GenesisDelegationError -> GenesisDelegation)
-> (GenesisDelegation -> GenesisDelegation)
-> Either GenesisDelegationError GenesisDelegation
-> GenesisDelegation
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Text -> GenesisDelegation
forall a. HasCallStack => Text -> a
panic (Text -> GenesisDelegation)
-> (GenesisDelegationError -> Text)
-> GenesisDelegationError
-> GenesisDelegation
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 (GenesisDelegationError -> Text)
-> GenesisDelegationError -> Text
forall a. Format Text a -> a
sformat Format Text (GenesisDelegationError -> Text)
forall a r. Buildable a => Format r (a -> r)
build) GenesisDelegation -> GenesisDelegation
forall (cat :: * -> * -> *) a. Category cat => cat a a
identity (Either GenesisDelegationError GenesisDelegation
-> GenesisDelegation)
-> ([Certificate]
-> Either GenesisDelegationError GenesisDelegation)
-> [Certificate]
-> GenesisDelegation
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
. [Certificate] -> Either GenesisDelegationError GenesisDelegation
forall (m :: * -> *).
MonadError GenesisDelegationError m =>
[Certificate] -> m GenesisDelegation
mkGenesisDelegation
genGenesisData :: ProtocolMagicId -> Gen GenesisData
genGenesisData :: ProtocolMagicId -> GenT Identity GenesisData
genGenesisData ProtocolMagicId
pm =
GenesisKeyHashes
-> GenesisDelegation
-> UTCTime
-> GenesisNonAvvmBalances
-> ProtocolParameters
-> BlockCount
-> ProtocolMagicId
-> GenesisAvvmBalances
-> GenesisData
GenesisData
(GenesisKeyHashes
-> GenesisDelegation
-> UTCTime
-> GenesisNonAvvmBalances
-> ProtocolParameters
-> BlockCount
-> ProtocolMagicId
-> GenesisAvvmBalances
-> GenesisData)
-> GenT Identity GenesisKeyHashes
-> GenT
Identity
(GenesisDelegation
-> UTCTime
-> GenesisNonAvvmBalances
-> ProtocolParameters
-> BlockCount
-> ProtocolMagicId
-> GenesisAvvmBalances
-> GenesisData)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenT Identity GenesisKeyHashes
genGenesisKeyHashes
GenT
Identity
(GenesisDelegation
-> UTCTime
-> GenesisNonAvvmBalances
-> ProtocolParameters
-> BlockCount
-> ProtocolMagicId
-> GenesisAvvmBalances
-> GenesisData)
-> GenT Identity GenesisDelegation
-> GenT
Identity
(UTCTime
-> GenesisNonAvvmBalances
-> ProtocolParameters
-> BlockCount
-> ProtocolMagicId
-> GenesisAvvmBalances
-> GenesisData)
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
<*> ProtocolMagicId -> GenT Identity GenesisDelegation
genGenesisDelegation ProtocolMagicId
pm
GenT
Identity
(UTCTime
-> GenesisNonAvvmBalances
-> ProtocolParameters
-> BlockCount
-> ProtocolMagicId
-> GenesisAvvmBalances
-> GenesisData)
-> GenT Identity UTCTime
-> GenT
Identity
(GenesisNonAvvmBalances
-> ProtocolParameters
-> BlockCount
-> ProtocolMagicId
-> GenesisAvvmBalances
-> GenesisData)
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
<*> GenT Identity UTCTime
genUTCTime
GenT
Identity
(GenesisNonAvvmBalances
-> ProtocolParameters
-> BlockCount
-> ProtocolMagicId
-> GenesisAvvmBalances
-> GenesisData)
-> GenT Identity GenesisNonAvvmBalances
-> GenT
Identity
(ProtocolParameters
-> BlockCount
-> ProtocolMagicId
-> GenesisAvvmBalances
-> GenesisData)
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
<*> GenT Identity GenesisNonAvvmBalances
genGenesisNonAvvmBalances
GenT
Identity
(ProtocolParameters
-> BlockCount
-> ProtocolMagicId
-> GenesisAvvmBalances
-> GenesisData)
-> GenT Identity ProtocolParameters
-> GenT
Identity
(BlockCount
-> ProtocolMagicId -> GenesisAvvmBalances -> GenesisData)
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
<*> GenT Identity ProtocolParameters
genProtocolParameters
GenT
Identity
(BlockCount
-> ProtocolMagicId -> GenesisAvvmBalances -> GenesisData)
-> GenT Identity BlockCount
-> GenT
Identity (ProtocolMagicId -> GenesisAvvmBalances -> GenesisData)
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
<*> GenT Identity BlockCount
genBlockCount
GenT
Identity (ProtocolMagicId -> GenesisAvvmBalances -> GenesisData)
-> GenT Identity ProtocolMagicId
-> GenT Identity (GenesisAvvmBalances -> GenesisData)
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
<*> GenT Identity ProtocolMagicId
genProtocolMagicId
GenT Identity (GenesisAvvmBalances -> GenesisData)
-> GenT Identity GenesisAvvmBalances -> GenT Identity GenesisData
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
<*> GenT Identity GenesisAvvmBalances
genGenesisAvvmBalances
genGenesisHash :: Gen GenesisHash
genGenesisHash :: GenT Identity GenesisHash
genGenesisHash = AbstractHash Blake2b_256 Raw -> GenesisHash
GenesisHash (AbstractHash Blake2b_256 Raw -> GenesisHash)
-> (Hash Text -> AbstractHash Blake2b_256 Raw)
-> Hash Text
-> GenesisHash
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
. Hash Text -> AbstractHash Blake2b_256 Raw
forall a b. Coercible a b => a -> b
coerce (Hash Text -> GenesisHash)
-> GenT Identity (Hash Text) -> GenT Identity GenesisHash
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenT Identity (Hash Text)
genTextHash
genFakeAvvmOptions :: Gen FakeAvvmOptions
genFakeAvvmOptions :: Gen FakeAvvmOptions
genFakeAvvmOptions =
Word -> Lovelace -> FakeAvvmOptions
FakeAvvmOptions (Word -> Lovelace -> FakeAvvmOptions)
-> GenT Identity Word
-> GenT Identity (Lovelace -> FakeAvvmOptions)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Range Word -> GenT Identity Word
forall (m :: * -> *). MonadGen m => Range Word -> m Word
Gen.word Range Word
forall a. (Bounded a, Num a) => Range a
Range.constantBounded GenT Identity (Lovelace -> FakeAvvmOptions)
-> GenT Identity Lovelace -> Gen FakeAvvmOptions
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
<*> GenT Identity Lovelace
genLovelace
genGenesisDelegation :: ProtocolMagicId -> Gen GenesisDelegation
genGenesisDelegation :: ProtocolMagicId -> GenT Identity GenesisDelegation
genGenesisDelegation ProtocolMagicId
pm = [Certificate] -> GenesisDelegation
mkGenesisDelegation' ([Certificate] -> GenesisDelegation)
-> GenT Identity [Certificate] -> GenT Identity GenesisDelegation
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ProtocolMagicId -> GenT Identity [Certificate]
genCertificateDistinctList ProtocolMagicId
pm
where
mkGenesisDelegation' :: [Certificate] -> GenesisDelegation
mkGenesisDelegation' =
(GenesisDelegationError -> GenesisDelegation)
-> (GenesisDelegation -> GenesisDelegation)
-> Either GenesisDelegationError GenesisDelegation
-> GenesisDelegation
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Text -> GenesisDelegation
forall a. HasCallStack => Text -> a
panic (Text -> GenesisDelegation)
-> (GenesisDelegationError -> Text)
-> GenesisDelegationError
-> GenesisDelegation
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 (GenesisDelegationError -> Text)
-> GenesisDelegationError -> Text
forall a. Format Text a -> a
sformat Format Text (GenesisDelegationError -> Text)
forall a r. Buildable a => Format r (a -> r)
build) GenesisDelegation -> GenesisDelegation
forall (cat :: * -> * -> *) a. Category cat => cat a a
identity (Either GenesisDelegationError GenesisDelegation
-> GenesisDelegation)
-> ([Certificate]
-> Either GenesisDelegationError GenesisDelegation)
-> [Certificate]
-> GenesisDelegation
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
. [Certificate] -> Either GenesisDelegationError GenesisDelegation
forall (m :: * -> *).
MonadError GenesisDelegationError m =>
[Certificate] -> m GenesisDelegation
mkGenesisDelegation
genGenesisInitializer :: Gen GenesisInitializer
genGenesisInitializer :: Gen GenesisInitializer
genGenesisInitializer =
TestnetBalanceOptions
-> FakeAvvmOptions -> Rational -> Bool -> GenesisInitializer
GenesisInitializer
(TestnetBalanceOptions
-> FakeAvvmOptions -> Rational -> Bool -> GenesisInitializer)
-> GenT Identity TestnetBalanceOptions
-> GenT
Identity
(FakeAvvmOptions -> Rational -> Bool -> GenesisInitializer)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenT Identity TestnetBalanceOptions
genTestnetBalanceOptions
GenT
Identity
(FakeAvvmOptions -> Rational -> Bool -> GenesisInitializer)
-> Gen FakeAvvmOptions
-> GenT Identity (Rational -> Bool -> GenesisInitializer)
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
<*> Gen FakeAvvmOptions
genFakeAvvmOptions
GenT Identity (Rational -> Bool -> GenesisInitializer)
-> GenT Identity Rational
-> GenT Identity (Bool -> GenesisInitializer)
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
<*> (Double -> Rational
forall a b. (Real a, Fractional b) => a -> b
realToFrac (Double -> Rational)
-> GenT Identity Double -> GenT Identity Rational
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Range Double -> GenT Identity Double
forall (m :: * -> *). MonadGen m => Range Double -> m Double
Gen.double (Double -> Double -> Range Double
forall a. a -> a -> Range a
Range.constant Double
0 Double
1))
GenT Identity (Bool -> GenesisInitializer)
-> GenT Identity Bool -> Gen GenesisInitializer
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
<*> GenT Identity Bool
forall (m :: * -> *). MonadGen m => m Bool
Gen.bool
genGenesisNonAvvmBalances :: Gen GenesisNonAvvmBalances
genGenesisNonAvvmBalances :: GenT Identity GenesisNonAvvmBalances
genGenesisNonAvvmBalances =
Map Address Lovelace -> GenesisNonAvvmBalances
GenesisNonAvvmBalances
(Map Address Lovelace -> GenesisNonAvvmBalances)
-> ([(Address, Lovelace)] -> Map Address Lovelace)
-> [(Address, Lovelace)]
-> GenesisNonAvvmBalances
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
. [(Address, Lovelace)] -> Map Address Lovelace
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList
([(Address, Lovelace)] -> GenesisNonAvvmBalances)
-> GenT Identity [(Address, Lovelace)]
-> GenT Identity GenesisNonAvvmBalances
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Range Int
-> GenT Identity (Address, Lovelace)
-> GenT Identity [(Address, Lovelace)]
forall (m :: * -> *) a. MonadGen m => Range Int -> m a -> m [a]
Gen.list
(Int -> Int -> Range Int
forall a. Integral a => a -> a -> Range a
Range.linear Int
1 Int
10)
((,) (Address -> Lovelace -> (Address, Lovelace))
-> GenT Identity Address
-> GenT Identity (Lovelace -> (Address, Lovelace))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenT Identity Address
genAddress GenT Identity (Lovelace -> (Address, Lovelace))
-> GenT Identity Lovelace -> GenT Identity (Address, Lovelace)
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
<*> GenT Identity Lovelace
genLovelace)
genGenesisSpec :: ProtocolMagicId -> Gen GenesisSpec
genGenesisSpec :: ProtocolMagicId -> Gen GenesisSpec
genGenesisSpec ProtocolMagicId
pm = (Text -> GenesisSpec)
-> (GenesisSpec -> GenesisSpec)
-> Either Text GenesisSpec
-> GenesisSpec
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Text -> GenesisSpec
forall a. HasCallStack => Text -> a
panic (Text -> GenesisSpec) -> (Text -> Text) -> Text -> GenesisSpec
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 -> Text
forall a b. ConvertText a b => a -> b
toS) GenesisSpec -> GenesisSpec
forall (cat :: * -> * -> *) a. Category cat => cat a a
identity (Either Text GenesisSpec -> GenesisSpec)
-> GenT Identity (Either Text GenesisSpec) -> Gen GenesisSpec
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenT Identity (Either Text GenesisSpec)
mkGenSpec
where
mkGenSpec :: GenT Identity (Either Text GenesisSpec)
mkGenSpec =
GenesisAvvmBalances
-> GenesisDelegation
-> ProtocolParameters
-> BlockCount
-> ProtocolMagic
-> GenesisInitializer
-> Either Text GenesisSpec
mkGenesisSpec
(GenesisAvvmBalances
-> GenesisDelegation
-> ProtocolParameters
-> BlockCount
-> ProtocolMagic
-> GenesisInitializer
-> Either Text GenesisSpec)
-> GenT Identity GenesisAvvmBalances
-> GenT
Identity
(GenesisDelegation
-> ProtocolParameters
-> BlockCount
-> ProtocolMagic
-> GenesisInitializer
-> Either Text GenesisSpec)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenT Identity GenesisAvvmBalances
genGenesisAvvmBalances
GenT
Identity
(GenesisDelegation
-> ProtocolParameters
-> BlockCount
-> ProtocolMagic
-> GenesisInitializer
-> Either Text GenesisSpec)
-> GenT Identity GenesisDelegation
-> GenT
Identity
(ProtocolParameters
-> BlockCount
-> ProtocolMagic
-> GenesisInitializer
-> Either Text GenesisSpec)
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
<*> ProtocolMagicId -> GenT Identity GenesisDelegation
genGenesisDelegation ProtocolMagicId
pm
GenT
Identity
(ProtocolParameters
-> BlockCount
-> ProtocolMagic
-> GenesisInitializer
-> Either Text GenesisSpec)
-> GenT Identity ProtocolParameters
-> GenT
Identity
(BlockCount
-> ProtocolMagic -> GenesisInitializer -> Either Text GenesisSpec)
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
<*> GenT Identity ProtocolParameters
genProtocolParameters
GenT
Identity
(BlockCount
-> ProtocolMagic -> GenesisInitializer -> Either Text GenesisSpec)
-> GenT Identity BlockCount
-> GenT
Identity
(ProtocolMagic -> GenesisInitializer -> Either Text GenesisSpec)
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
<*> GenT Identity BlockCount
genBlockCount
GenT
Identity
(ProtocolMagic -> GenesisInitializer -> Either Text GenesisSpec)
-> GenT Identity ProtocolMagic
-> GenT Identity (GenesisInitializer -> Either Text GenesisSpec)
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
<*> GenT Identity ProtocolMagic
genProtocolMagic
GenT Identity (GenesisInitializer -> Either Text GenesisSpec)
-> Gen GenesisInitializer
-> GenT Identity (Either Text GenesisSpec)
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
<*> Gen GenesisInitializer
genGenesisInitializer
genTestnetBalanceOptions :: Gen TestnetBalanceOptions
genTestnetBalanceOptions :: GenT Identity TestnetBalanceOptions
genTestnetBalanceOptions =
Word -> Word -> Lovelace -> Rational -> TestnetBalanceOptions
TestnetBalanceOptions
(Word -> Word -> Lovelace -> Rational -> TestnetBalanceOptions)
-> GenT Identity Word
-> GenT
Identity (Word -> Lovelace -> Rational -> TestnetBalanceOptions)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Range Word -> GenT Identity Word
forall (m :: * -> *). MonadGen m => Range Word -> m Word
Gen.word Range Word
forall a. (Bounded a, Num a) => Range a
Range.constantBounded
GenT
Identity (Word -> Lovelace -> Rational -> TestnetBalanceOptions)
-> GenT Identity Word
-> GenT Identity (Lovelace -> Rational -> TestnetBalanceOptions)
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 Word -> GenT Identity Word
forall (m :: * -> *). MonadGen m => Range Word -> m Word
Gen.word Range Word
forall a. (Bounded a, Num a) => Range a
Range.constantBounded
GenT Identity (Lovelace -> Rational -> TestnetBalanceOptions)
-> GenT Identity Lovelace
-> GenT Identity (Rational -> TestnetBalanceOptions)
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
<*> GenT Identity Lovelace
genLovelace
GenT Identity (Rational -> TestnetBalanceOptions)
-> GenT Identity Rational -> GenT Identity TestnetBalanceOptions
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
<*> (Double -> Rational
forall a b. (Real a, Fractional b) => a -> b
realToFrac (Double -> Rational)
-> GenT Identity Double -> GenT Identity Rational
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Range Double -> GenT Identity Double
forall (m :: * -> *). MonadGen m => Range Double -> m Double
Gen.double (Double -> Double -> Range Double
forall a. a -> a -> Range a
Range.constant Double
0 Double
1))
genGenesisAvvmBalances :: Gen GenesisAvvmBalances
genGenesisAvvmBalances :: GenT Identity GenesisAvvmBalances
genGenesisAvvmBalances =
Map CompactRedeemVerificationKey Lovelace -> GenesisAvvmBalances
GenesisAvvmBalances
(Map CompactRedeemVerificationKey Lovelace -> GenesisAvvmBalances)
-> GenT Identity (Map CompactRedeemVerificationKey Lovelace)
-> GenT Identity GenesisAvvmBalances
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen CompactRedeemVerificationKey
-> GenT Identity Lovelace
-> GenT Identity (Map CompactRedeemVerificationKey Lovelace)
forall k v. Ord k => Gen k -> Gen v -> Gen (Map k v)
customMapGen Gen CompactRedeemVerificationKey
genCompactRedeemVerificationKey GenT Identity Lovelace
genLovelace
genGenesisKeyHashes :: Gen GenesisKeyHashes
genGenesisKeyHashes :: GenT Identity GenesisKeyHashes
genGenesisKeyHashes =
Set KeyHash -> GenesisKeyHashes
GenesisKeyHashes (Set KeyHash -> GenesisKeyHashes)
-> GenT Identity (Set KeyHash) -> GenT Identity GenesisKeyHashes
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Range Int -> GenT Identity KeyHash -> GenT Identity (Set KeyHash)
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
10 Int
25) GenT Identity KeyHash
genKeyHash
genSignatureEpochNumber :: Gen (Signature EpochNumber)
genSignatureEpochNumber :: Gen (Signature EpochNumber)
genSignatureEpochNumber =
(String -> Signature EpochNumber)
-> (XSignature -> Signature EpochNumber)
-> Either String XSignature
-> Signature EpochNumber
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Text -> Signature EpochNumber
forall a. HasCallStack => Text -> a
panic (Text -> Signature EpochNumber)
-> (String -> Text) -> String -> Signature EpochNumber
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
. String -> Text
T.pack) XSignature -> Signature EpochNumber
forall a. XSignature -> Signature a
Signature
(Either String XSignature -> Signature EpochNumber)
-> (ByteString -> Either String XSignature)
-> ByteString
-> Signature EpochNumber
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
. ByteString -> Either String XSignature
CC.xsignature
(ByteString -> Signature EpochNumber)
-> GenT Identity ByteString -> Gen (Signature EpochNumber)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Range Int -> GenT Identity Char -> GenT Identity ByteString
forall (m :: * -> *).
MonadGen m =>
Range Int -> m Char -> m ByteString
Gen.utf8 (Int -> Int -> Range Int
forall a. a -> a -> Range a
Range.constant Int
64 Int
64) GenT Identity Char
forall (m :: * -> *). MonadGen m => m Char
Gen.hexit
genUTCTime :: Gen UTCTime
genUTCTime :: GenT Identity UTCTime
genUTCTime =
( \Integer
jday Integer
seconds ->
Day -> DiffTime -> UTCTime
UTCTime (Integer -> Day
ModifiedJulianDay Integer
jday) (Integer -> DiffTime
secondsToDiffTime Integer
seconds)
)
(Integer -> Integer -> UTCTime)
-> GenT Identity Integer -> GenT Identity (Integer -> UTCTime)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Range Integer -> GenT Identity Integer
forall (m :: * -> *) a. (MonadGen m, Integral a) => Range a -> m a
Gen.integral (Integer -> Integer -> Range Integer
forall a. Integral a => a -> a -> Range a
Range.linear Integer
0 Integer
1000000)
GenT Identity (Integer -> UTCTime)
-> GenT Identity Integer -> GenT Identity UTCTime
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 -> GenT Identity Integer
forall (m :: * -> *) a. (MonadGen m, Integral a) => Range a -> m a
Gen.integral (Integer -> Integer -> Range Integer
forall a. Integral a => a -> a -> Range a
Range.linear Integer
0 Integer
86401)
customMapGen :: Ord k => Gen k -> Gen v -> Gen (Map k v)
customMapGen :: forall k v. Ord k => Gen k -> Gen v -> Gen (Map k v)
customMapGen Gen k
keyGen Gen v
valGen =
[(k, v)] -> Map k v
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList ([(k, v)] -> Map k v)
-> GenT Identity [(k, v)] -> GenT Identity (Map k v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Range Int -> GenT Identity (k, v) -> GenT Identity [(k, v)]
forall (m :: * -> *) a. MonadGen m => Range Int -> m a -> m [a]
Gen.list (Int -> Int -> Range Int
forall a. Integral a => a -> a -> Range a
Range.linear Int
1 Int
10) ((,) (k -> v -> (k, v)) -> Gen k -> GenT Identity (v -> (k, v))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen k
keyGen GenT Identity (v -> (k, v)) -> Gen v -> GenT Identity (k, v)
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
<*> Gen v
valGen)