{-# LANGUAGE DataKinds #-} {-# LANGUAGE ExistentialQuantification #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TypeApplications #-} module Test.Cardano.Chain.Genesis.Example ( exampleGenesisAvvmBalances, exampleGenesisData0, exampleGenesisDelegation, exampleGenesisInitializer, exampleGenesisSpec, ) where import Cardano.Chain.Common ( BlockCount (..), hashKey, mkKnownLovelace, ) import Cardano.Chain.Delegation (unsafeCertificate) import Cardano.Chain.Genesis ( FakeAvvmOptions (..), GenesisAvvmBalances (..), GenesisData (..), GenesisDelegation (..), GenesisInitializer (..), GenesisKeyHashes (..), GenesisNonAvvmBalances (..), GenesisSpec (..), TestnetBalanceOptions (..), ) import Cardano.Chain.Slotting (EpochNumber (..)) import Cardano.Crypto ( AProtocolMagic (..), CompactRedeemVerificationKey, ProtocolMagicId (..), RequiresNetworkMagic (..), Signature (..), redeemDeterministicKeyGen, toCompactRedeemVerificationKey, ) import Cardano.Crypto.Signing (VerificationKey (..)) import qualified Cardano.Crypto.Wallet as CC import Cardano.Ledger.Binary (Annotated (..)) import Cardano.Prelude import qualified Data.ByteString.Base16 as B16 import qualified Data.Map.Strict as M import Data.Maybe (fromJust) import qualified Data.Set as Set import Data.Time (Day (..), UTCTime (..), secondsToDiffTime) import Test.Cardano.Chain.Common.Example ( exampleAddress, exampleAddress1, exampleKeyHash, ) import Test.Cardano.Chain.Update.Example (exampleProtocolParameters) import Test.Cardano.Crypto.CBOR (getBytes) import Test.Cardano.Crypto.Example (exampleProtocolMagicId0) exampleBlockCount :: BlockCount exampleBlockCount :: BlockCount exampleBlockCount = Word64 -> BlockCount BlockCount Word64 12344 exampleGenesisSpec :: GenesisSpec exampleGenesisSpec :: GenesisSpec exampleGenesisSpec = GenesisAvvmBalances -> GenesisDelegation -> ProtocolParameters -> BlockCount -> ProtocolMagic -> GenesisInitializer -> GenesisSpec UnsafeGenesisSpec GenesisAvvmBalances exampleGenesisAvvmBalances GenesisDelegation exampleGenesisDelegation ProtocolParameters exampleProtocolParameters (Word64 -> BlockCount BlockCount Word64 37) (forall a. Annotated ProtocolMagicId a -> RequiresNetworkMagic -> AProtocolMagic a AProtocolMagic (forall b a. b -> a -> Annotated b a Annotated (Word32 -> ProtocolMagicId ProtocolMagicId Word32 1783847074) ()) RequiresNetworkMagic RequiresMagic) GenesisInitializer exampleGenesisInitializer exampleGenesisAvvmBalances :: GenesisAvvmBalances exampleGenesisAvvmBalances :: GenesisAvvmBalances exampleGenesisAvvmBalances = Map CompactRedeemVerificationKey Lovelace -> GenesisAvvmBalances GenesisAvvmBalances forall a b. (a -> b) -> a -> b $ forall k a. Ord k => [(k, a)] -> Map k a M.fromList [ ((Int, Int) -> CompactRedeemVerificationKey exampleCompactRVK' (Int 0, Int 32), forall (n :: Nat). (KnownNat n, n <= 45000000000000000) => Lovelace mkKnownLovelace @36524597913081152) , ((Int, Int) -> CompactRedeemVerificationKey exampleCompactRVK' (Int 32, Int 32), forall (n :: Nat). (KnownNat n, n <= 45000000000000000) => Lovelace mkKnownLovelace @37343863242999412) ] where exampleCompactRVK' :: (Int, Int) -> CompactRedeemVerificationKey exampleCompactRVK' :: (Int, Int) -> CompactRedeemVerificationKey exampleCompactRVK' (Int m, Int n) = RedeemVerificationKey -> CompactRedeemVerificationKey toCompactRedeemVerificationKey forall a b. (a -> b) -> a -> b $ forall a. HasCallStack => Maybe a -> a fromJust (forall a b. (a, b) -> a fst forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> ByteString -> Maybe (RedeemVerificationKey, RedeemSigningKey) redeemDeterministicKeyGen (Int -> Int -> ByteString getBytes Int m Int n)) exampleGenesisData0 :: GenesisData exampleGenesisData0 :: GenesisData exampleGenesisData0 = GenesisData { gdGenesisKeyHashes :: GenesisKeyHashes gdGenesisKeyHashes = GenesisKeyHashes exampleGenesisKeyHashes , gdHeavyDelegation :: GenesisDelegation gdHeavyDelegation = GenesisDelegation exampleGenesisDelegation , gdStartTime :: UTCTime gdStartTime = UTCTime exampleUTCTime0 , gdNonAvvmBalances :: GenesisNonAvvmBalances gdNonAvvmBalances = GenesisNonAvvmBalances exampleGenesisNonAvvmBalances0 , gdProtocolParameters :: ProtocolParameters gdProtocolParameters = ProtocolParameters exampleProtocolParameters , gdK :: BlockCount gdK = BlockCount exampleBlockCount , gdProtocolMagicId :: ProtocolMagicId gdProtocolMagicId = ProtocolMagicId exampleProtocolMagicId0 , gdAvvmDistr :: GenesisAvvmBalances gdAvvmDistr = GenesisAvvmBalances exampleGenesisAvvmBalances } exampleGenesisDelegation :: GenesisDelegation exampleGenesisDelegation :: GenesisDelegation exampleGenesisDelegation = Map KeyHash Certificate -> GenesisDelegation UnsafeGenesisDelegation ( forall k a. Ord k => [(k, a)] -> Map k a M.fromList [ ( VerificationKey -> KeyHash hashKey VerificationKey issueVerKey , EpochNumber -> VerificationKey -> VerificationKey -> Signature EpochNumber -> Certificate unsafeCertificate (Word64 -> EpochNumber EpochNumber Word64 68300481033) VerificationKey issueVerKey ( XPub -> VerificationKey VerificationKey ( CC.XPub { xpubPublicKey :: ByteString CC.xpubPublicKey = ByteString pskDelVerKey , xpubChaincode :: ChainCode CC.xpubChaincode = ChainCode pskDelChainCode } ) ) Signature EpochNumber sig ) ] ) where issueVerKey :: VerificationKey issueVerKey = XPub -> VerificationKey VerificationKey (CC.XPub {xpubPublicKey :: ByteString CC.xpubPublicKey = ByteString pskVerKey, xpubChaincode :: ChainCode CC.xpubChaincode = ChainCode pskChainCode}) sig :: Signature EpochNumber sig :: Signature EpochNumber sig = forall a. XSignature -> Signature a Signature forall a b. (a -> b) -> a -> b $ forall b a. b -> Either a b -> b fromRight (forall a. HasCallStack => Text -> a panic Text "Something went wrong") forall a b. (a -> b) -> a -> b $ ByteString -> Either String XSignature CC.xsignature ( ByteString -> ByteString hexToBS ByteString "bae5422af5405e3803154a4ad986da5d14cf624d670\ \1c5c78a79ec73777f74e13973af83752114d9f18166\ \085997fc81e432cab7fee99a275d8bf138ad04e103" ) pskVerKey :: ByteString pskVerKey = ByteString -> ByteString hexToBS ByteString "e2a1773a2a82d10c30890cbf84eccbdc1aaaee920496424d36e8\ \68039d9cb519" pskChainCode :: ChainCode pskChainCode = ByteString -> ChainCode CC.ChainCode ( ByteString -> ByteString hexToBS ByteString "21b25efe033d9b00d4f02ccd9cdabcec332\ \abbc6fdf883ca5bf3a8aff4aac27e" ) pskDelVerKey :: ByteString pskDelVerKey = ByteString -> ByteString hexToBS ByteString "ddca69bfeac14c013304da88ac032ee63281ab036c1b1b918\ \8e4b174b303f43e" pskDelChainCode :: ChainCode pskDelChainCode = ByteString -> ChainCode CC.ChainCode ( ByteString -> ByteString hexToBS ByteString "55163b178e999b9fd50637b2edab8c85\ \8a879ac3c4bd3e610095419a19696573" ) exampleGenesisInitializer :: GenesisInitializer exampleGenesisInitializer :: GenesisInitializer exampleGenesisInitializer = GenesisInitializer { giTestBalance :: TestnetBalanceOptions giTestBalance = TestnetBalanceOptions { tboPoors :: Word tboPoors = Word 2448641325904532856 , tboRichmen :: Word tboRichmen = Word 14071205313513960321 , tboTotalBalance :: Lovelace tboTotalBalance = forall (n :: Nat). (KnownNat n, n <= 45000000000000000) => Lovelace mkKnownLovelace @10953275486128625 , tboRichmenShare :: Rational tboRichmenShare = Rational 0.366832547637728 :: Rational } , giFakeAvvmBalance :: FakeAvvmOptions giFakeAvvmBalance = FakeAvvmOptions { faoCount :: Word faoCount = Word 17853231730478779264 , faoOneBalance :: Lovelace faoOneBalance = forall (n :: Nat). (KnownNat n, n <= 45000000000000000) => Lovelace mkKnownLovelace @15087947214890024 } , giAvvmBalanceFactor :: Rational giAvvmBalanceFactor = Rational 0.366832547637728 :: Rational , giUseHeavyDlg :: Bool giUseHeavyDlg = Bool False } exampleGenesisNonAvvmBalances0 :: GenesisNonAvvmBalances exampleGenesisNonAvvmBalances0 :: GenesisNonAvvmBalances exampleGenesisNonAvvmBalances0 = Map Address Lovelace -> GenesisNonAvvmBalances GenesisNonAvvmBalances forall a b. (a -> b) -> a -> b $ forall k a. Ord k => [(k, a)] -> Map k a M.fromList [(Address exampleAddress, Lovelace coin), (Address exampleAddress1, Lovelace coin1)] where coin :: Lovelace coin = forall (n :: Nat). (KnownNat n, n <= 45000000000000000) => Lovelace mkKnownLovelace @36524597913081152 coin1 :: Lovelace coin1 = forall (n :: Nat). (KnownNat n, n <= 45000000000000000) => Lovelace mkKnownLovelace @37343863242999412 exampleGenesisKeyHashes :: GenesisKeyHashes exampleGenesisKeyHashes :: GenesisKeyHashes exampleGenesisKeyHashes = Set KeyHash -> GenesisKeyHashes GenesisKeyHashes (forall a. a -> Set a Set.singleton KeyHash exampleKeyHash) exampleUTCTime0 :: UTCTime exampleUTCTime0 :: UTCTime exampleUTCTime0 = Day -> DiffTime -> UTCTime UTCTime (Integer -> Day ModifiedJulianDay Integer 10000) (Integer -> DiffTime secondsToDiffTime Integer 82401) hexToBS :: ByteString -> ByteString hexToBS :: ByteString -> ByteString hexToBS ByteString ts = case ByteString -> Either String ByteString B16.decode ByteString ts of Right ByteString fullyDecoded -> ByteString fullyDecoded Left String msg -> forall a. HasCallStack => Text -> a panic forall a b. (a -> b) -> a -> b $ Text "fail to decode: " forall a. Semigroup a => a -> a -> a <> forall a b. (Show a, ConvertText String b) => a -> b show ByteString ts forall a. Semigroup a => a -> a -> a <> Text " with error: " forall a. Semigroup a => a -> a -> a <> forall a b. (Show a, ConvertText String b) => a -> b show String msg