Skip to content

Commit

Permalink
Replace C.ProtocolParameters with Write.mockPParams in wallet tests
Browse files Browse the repository at this point in the history
  • Loading branch information
Anviking committed Jul 15, 2024
1 parent b7ee099 commit 383205b
Show file tree
Hide file tree
Showing 4 changed files with 22 additions and 197 deletions.
11 changes: 3 additions & 8 deletions lib/benchmarks/exe/api-bench.hs
Original file line number Diff line number Diff line change
Expand Up @@ -98,8 +98,8 @@ import Cardano.Wallet.DB.Layer
( PersistAddressBook
)
import Cardano.Wallet.DummyTarget.Primitive.Types
( dummyNetworkLayer
, dummyNodeProtocolParameters
( dummyLedgerProtocolParameters
, dummyNetworkLayer
, dummyProtocolParameters
, dummySlottingParameters
, dummyTimeInterpreter
Expand Down Expand Up @@ -622,12 +622,7 @@ mockNetworkLayer = dummyNetworkLayer
{ timeInterpreter = hoistTimeInterpreter liftIO mockTimeInterpreter
, currentSlottingParameters = pure dummySlottingParameters
, currentProtocolParameters = pure dummyProtocolParameters
, currentProtocolParametersInRecentEras = pure
$ Write.InRecentEraBabbage $
either (error . show) id $
C.toLedgerPParams
C.ShelleyBasedEraBabbage
dummyNodeProtocolParameters
, currentProtocolParametersInRecentEras = dummyLedgerProtocolParameters
, currentNodeEra = pure $ Cardano.anyCardanoEra Cardano.BabbageEra
, currentNodeTip = pure Read.BlockTip
{ Read.slotNo = Read.SlotNo 123456789
Expand Down
1 change: 1 addition & 0 deletions lib/unit/cardano-wallet-unit.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -49,6 +49,7 @@ library test-common
, cardano-wallet-network-layer
, cardano-wallet-primitive
, cardano-wallet-read
, cardano-balance-tx:internal
, containers
, time

Expand Down
144 changes: 14 additions & 130 deletions lib/unit/test-common/Cardano/Wallet/DummyTarget/Primitive/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,18 +2,15 @@
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NumericUnderscores #-}

-- TODO [ADP-3385] Stop using deprecated 'Cardano.ProtocolParameters'
--https://cardanofoundation.atlassian.net/browse/ADP-3385
{-# OPTIONS_GHC -fno-warn-deprecations #-}
{-# LANGUAGE TypeApplications #-}

module Cardano.Wallet.DummyTarget.Primitive.Types
( -- * Dummy values
block0
, dummyNetworkParameters
, dummyGenesisParameters
, dummyNodeProtocolParameters
, dummyProtocolParameters
, dummyLedgerProtocolParameters
, dummySlottingParameters
, dummyTimeInterpreter
, dummyGenesisHash
Expand All @@ -22,16 +19,16 @@ module Cardano.Wallet.DummyTarget.Primitive.Types

-- * Mocks
, dummyNetworkLayer

-- * Realistic values
, babbageMainnetProtocolParameters
) where

import Prelude

import Cardano.Wallet.Network
( NetworkLayer (..)
)
import Cardano.Wallet.Primitive.Ledger.Shelley
( fromConwayPParams
)
import Cardano.Wallet.Primitive.Slotting
( TimeInterpreter
, hoistTimeInterpreter
Expand All @@ -42,19 +39,13 @@ import Cardano.Wallet.Primitive.Types
, Block (..)
, BlockHeader (..)
, EpochLength (..)
, ExecutionUnitPrices (..)
, ExecutionUnits (..)
, FeePolicy (..)
, GenesisParameters (..)
, LinearFunction (..)
, NetworkParameters (..)
, ProtocolParameters (..)
, SlotLength (..)
, SlotNo (..)
, SlottingParameters (..)
, StartTime (..)
, TokenBundleMaxSize (..)
, TxParameters (..)
, emptyEraInfo
)
import Cardano.Wallet.Primitive.Types.Coin
Expand All @@ -72,9 +63,6 @@ import Cardano.Wallet.Primitive.Types.Tx
, TxMetadata (..)
, TxScriptValidity (..)
)
import Cardano.Wallet.Primitive.Types.Tx.Constraints
( TxSize (..)
)
import Cardano.Wallet.Primitive.Types.Tx.TxIn
( TxIn (..)
)
Expand All @@ -99,10 +87,12 @@ import Data.Time.Clock.POSIX
import GHC.Stack
( HasCallStack
)
import Internal.Cardano.Write.Tx.Gen
( mockPParams
)

import qualified Cardano.Api.Ledger as C
import qualified Cardano.Api.Shelley as C
import qualified Data.ByteString.Char8 as B8
import qualified Internal.Cardano.Write.Tx as Write

{-----------------------------------------------------------------------------
Dummy values
Expand Down Expand Up @@ -142,14 +132,6 @@ dummyTimeInterpreter = hoistTimeInterpreter (pure . runIdentity)
(getGenesisBlockDate dummyGenesisParameters)
dummySlottingParameters

dummyTxParameters :: TxParameters
dummyTxParameters = TxParameters
{ getFeePolicy = LinearFee $ LinearFunction { intercept = 14, slope = 42 }
, getTxMaxSize = Quantity 8_192
, getTokenBundleMaxSize = TokenBundleMaxSize (TxSize 2_000)
, getMaxExecutionUnits = ExecutionUnits 10 14
}

dummyNetworkParameters :: NetworkParameters
dummyNetworkParameters = NetworkParameters
{ genesisParameters = dummyGenesisParameters
Expand All @@ -158,62 +140,12 @@ dummyNetworkParameters = NetworkParameters
}

dummyProtocolParameters :: ProtocolParameters
dummyProtocolParameters = ProtocolParameters
{ decentralizationLevel = minBound
, txParameters = dummyTxParameters
, desiredNumberOfStakePools = 100
, stakeKeyDeposit = Coin 0
, eras = emptyEraInfo
, maximumCollateralInputCount = 3
, minimumCollateralPercentage = 150
, executionUnitPrices =
Just $ ExecutionUnitPrices
{ pricePerStep = 7.21e-5
, pricePerMemoryUnit = 0.057_7
}
}
dummyProtocolParameters = fromConwayPParams
emptyEraInfo
(mockPParams @Write.ConwayEra)

-- | Dummy parameters that are consistent with the @dummy*@ parameters.
dummyNodeProtocolParameters :: C.ProtocolParameters
dummyNodeProtocolParameters = C.ProtocolParameters
{ C.protocolParamProtocolVersion = (8,0)
, C.protocolParamDecentralization =Just 1
, C.protocolParamExtraPraosEntropy = Nothing
, C.protocolParamMaxBlockHeaderSize = 1_100
, C.protocolParamMaxBlockBodySize = 90_112
, C.protocolParamMaxTxSize = 8_192
, C.protocolParamTxFeeFixed = 14 -- B
, C.protocolParamTxFeePerByte = 42 -- A
, C.protocolParamMinUTxOValue = Nothing
, C.protocolParamStakeAddressDeposit = C.Coin 0
, C.protocolParamStakePoolDeposit = C.Coin 500_000_000
, C.protocolParamMinPoolCost = C.Coin 340_000_000
, C.protocolParamPoolRetireMaxEpoch = C.EpochInterval 18
, C.protocolParamStakePoolTargetNum = 100
, C.protocolParamPoolPledgeInfluence = 0.3 -- a0
, C.protocolParamMonetaryExpansion = 0.003 -- rho
, C.protocolParamTreasuryCut = 0.20 -- tau
, C.protocolParamUTxOCostPerByte = Just $ C.Coin 43_10
, C.protocolParamCostModels = mempty
, C.protocolParamPrices =
Just $ C.ExecutionUnitPrices
{ C.priceExecutionSteps = 7.21e-5
, C.priceExecutionMemory = 0.057_7
}
, C.protocolParamMaxTxExUnits =
Just $ C.ExecutionUnits
{ C.executionSteps = 10
, C.executionMemory = 14
}
, C.protocolParamMaxBlockExUnits =
Just $ C.ExecutionUnits
{ C.executionSteps = 20
, C.executionMemory = 62
}
, C.protocolParamMaxValueSize = Just 2_000
, C.protocolParamCollateralPercent = Just 150
, C.protocolParamMaxCollateralInputs = Just 3
}
dummyLedgerProtocolParameters :: Write.IsRecentEra era => Write.PParams era
dummyLedgerProtocolParameters = mockPParams

dummyNetworkLayer :: HasCallStack => NetworkLayer m a
dummyNetworkLayer = NetworkLayer
Expand Down Expand Up @@ -274,51 +206,3 @@ mkTxId
-> Map RewardAccount Coin
-> Maybe TxMetadata -> Hash "Tx"
mkTxId ins outs wdrls md = mockHash (ins, outs, wdrls, md)

{-----------------------------------------------------------------------------
Realistic values
------------------------------------------------------------------------------}
-- | Data from mainnet on 2023-03-17.
-- NOTE: Does not include Plutus cost model (todo).
babbageMainnetProtocolParameters :: C.ProtocolParameters
babbageMainnetProtocolParameters = C.ProtocolParameters
{ C.protocolParamProtocolVersion = (8,0)
, C.protocolParamDecentralization = Just 0
, C.protocolParamExtraPraosEntropy = Nothing
, C.protocolParamMaxBlockHeaderSize = 1_100
, C.protocolParamMaxBlockBodySize = 90_112
, C.protocolParamMaxTxSize = 16_384
, C.protocolParamTxFeeFixed = 155_381 -- B
, C.protocolParamTxFeePerByte = 44 -- A
, C.protocolParamMinUTxOValue = Just $ C.Coin 1_000_000
, C.protocolParamStakeAddressDeposit = C.Coin 2_000_000
, C.protocolParamStakePoolDeposit = C.Coin 500_000_000
, C.protocolParamMinPoolCost = C.Coin 340_000_000
, C.protocolParamPoolRetireMaxEpoch = C.EpochInterval 18
, C.protocolParamStakePoolTargetNum = 500
, C.protocolParamPoolPledgeInfluence = 0.3 -- a0
, C.protocolParamMonetaryExpansion = 0.003 -- rho
, C.protocolParamTreasuryCut = 0.20 -- tau
, C.protocolParamUTxOCostPerByte = Just $ C.Coin 4_310
, C.protocolParamCostModels =
mempty
-- TODO: Include a Plutus cost model here.
, C.protocolParamPrices =
Just $ C.ExecutionUnitPrices
{ C.priceExecutionSteps = 7.21e-5
, C.priceExecutionMemory = 0.057_7
}
, C.protocolParamMaxTxExUnits =
Just $ C.ExecutionUnits
{ C.executionSteps = 10_000_000_000
, C.executionMemory = 14_000_000
}
, C.protocolParamMaxBlockExUnits =
Just $ C.ExecutionUnits
{ C.executionSteps = 20_000_000_000
, C.executionMemory = 62_000_000
}
, C.protocolParamMaxValueSize = Just 5_000
, C.protocolParamCollateralPercent = Just 150
, C.protocolParamMaxCollateralInputs = Just 3
}
63 changes: 4 additions & 59 deletions lib/unit/test/unit/Cardano/Wallet/Shelley/TransactionSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -20,10 +20,6 @@

{-# OPTIONS_GHC -fno-warn-orphans #-}

-- TODO [ADP-3385] Stop using deprecated 'Cardano.ProtocolParameters'
--https://cardanofoundation.atlassian.net/browse/ADP-3385
{-# OPTIONS_GHC -fno-warn-deprecations #-}

-- TODO: https://cardanofoundation.atlassian.net/browse/ADP-2841
{-# LANGUAGE CPP #-}
#if __GLASGOW_HASKELL__ >= 902
Expand Down Expand Up @@ -253,9 +249,6 @@ import Data.Proxy
import Data.Quantity
( Quantity (..)
)
import Data.Ratio
( (%)
)
import Data.Semigroup
( mtimesDefault
)
Expand All @@ -282,6 +275,9 @@ import Internal.Cardano.Write.Tx
, ShelleyLedgerEra
, cardanoEraFromRecentEra
)
import Internal.Cardano.Write.Tx.Gen
( mockPParams
)
import Internal.Cardano.Write.Tx.SizeEstimation
( TxSkeleton (..)
, estimateTxSize
Expand Down Expand Up @@ -349,8 +345,6 @@ import qualified Cardano.Api.Ledger as L
import qualified Cardano.Api.Shelley as Cardano
import qualified Cardano.Crypto.Hash.Blake2b as Crypto
import qualified Cardano.Crypto.Hash.Class as Crypto
import qualified Cardano.Ledger.Babbage.Core as Babbage
import qualified Cardano.Ledger.Babbage.Core as Ledger
import qualified Cardano.Ledger.Coin as Ledger
import qualified Cardano.Ledger.Crypto as Crypto
import qualified Cardano.Ledger.Shelley.API as SL
Expand All @@ -371,10 +365,8 @@ import qualified Internal.Cardano.Write.Tx as Write
( BabbageEra
, CardanoApiEra
, IsRecentEra
, PParams
, RecentEra (RecentEraBabbage, RecentEraConway)
, cardanoEraFromRecentEra
, shelleyBasedEra
, shelleyBasedEraFromRecentEra
)

Expand Down Expand Up @@ -1393,55 +1385,8 @@ emptyTxSkeleton =
mockTxConstraints :: TxConstraints
mockTxConstraints =
txConstraints
(mockPParamsForTxConstraints @Write.BabbageEra)
(mockPParams @Write.BabbageEra)
TxWitnessShelleyUTxO
where
mockPParamsForTxConstraints
:: forall era . Write.IsRecentEra era => Write.PParams era
mockPParamsForTxConstraints = either (error . show) id $
Cardano.toLedgerPParams
Write.shelleyBasedEra
mockCardanoApiPParamsForTxConstraints

mockCardanoApiPParamsForTxConstraints :: Cardano.ProtocolParameters
mockCardanoApiPParamsForTxConstraints = Cardano.ProtocolParameters
{ Cardano.protocolParamTxFeeFixed = 155_381
, Cardano.protocolParamTxFeePerByte = 44
, Cardano.protocolParamMaxTxSize = 16_384
, Cardano.protocolParamMinUTxOValue = Nothing
, Cardano.protocolParamMaxTxExUnits =
Just $ Cardano.ExecutionUnits 10_000_000_000 14_000_000
, Cardano.protocolParamMaxValueSize = Just 4_000
, Cardano.protocolParamProtocolVersion = (6, 0)
, Cardano.protocolParamDecentralization = Just 0
, Cardano.protocolParamExtraPraosEntropy = Nothing
, Cardano.protocolParamMaxBlockHeaderSize = 100_000 -- Dummy value
, Cardano.protocolParamMaxBlockBodySize = 100_000
, Cardano.protocolParamStakeAddressDeposit = L.Coin 2_000_000
, Cardano.protocolParamStakePoolDeposit = L.Coin 500_000_000
, Cardano.protocolParamMinPoolCost = L.Coin 32_000_000
, Cardano.protocolParamPoolRetireMaxEpoch = L.EpochInterval 2
, Cardano.protocolParamStakePoolTargetNum = 100
, Cardano.protocolParamPoolPledgeInfluence = 0
, Cardano.protocolParamMonetaryExpansion = 0
, Cardano.protocolParamTreasuryCut = 0
, Cardano.protocolParamUTxOCostPerByte =
Just $ Babbage.unCoinPerByte testParameter_coinsPerUTxOByte_Babbage
-- Note: since 'txConstraints' does not make use of cost models, here
-- we use the simplest possible value, which is 'mempty'.
, Cardano.protocolParamCostModels = mempty
, Cardano.protocolParamPrices =
Just $ Cardano.ExecutionUnitPrices (721 % 10_000_000) (577 % 10_000)
, Cardano.protocolParamMaxBlockExUnits =
Just $ Cardano.ExecutionUnits 10_000_000_000 14_000_000
, Cardano.protocolParamCollateralPercent = Just 150
, Cardano.protocolParamMaxCollateralInputs = Just 3
}

testParameter_coinsPerUTxOByte_Babbage :: Ledger.CoinPerByte
testParameter_coinsPerUTxOByte_Babbage
= Ledger.CoinPerByte $ Ledger.Coin 4_310

data MockSelection = MockSelection
{ txInputCount :: Int
, txOutputs :: [TxOut]
Expand Down

0 comments on commit 383205b

Please sign in to comment.