Skip to content

Commit

Permalink
Replace deprecated evaluateTransactionFee with getMinFeeTx (#4631)
Browse files Browse the repository at this point in the history
- [x] Replace deprecated evaluateTransactionFee with getMinFeeTx in a
minimal way (keep using our own `sizeOf_BootstrapWitnesses`)

### Comments

### Issue Number

ADP-3334
  • Loading branch information
Anviking authored Jun 28, 2024
2 parents 5aa4a5b + 5802258 commit b61a19a
Show file tree
Hide file tree
Showing 4 changed files with 109 additions and 119 deletions.
41 changes: 0 additions & 41 deletions lib/balance-tx/lib/internal/Internal/Cardano/Write/Tx.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,6 @@
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE RankNTypes #-}
Expand All @@ -16,10 +15,6 @@
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE UndecidableSuperClasses #-}

{-# OPTIONS_GHC -Wno-warnings-deprecations #-}
-- For 'Shelley.evaluateTransactionFee', see ADP-3334
-- https://cardanofoundation.atlassian.net/browse/ADP-3334

-- |
-- Copyright: © 2022 IOHK
-- License: Apache-2.0
Expand Down Expand Up @@ -149,7 +144,6 @@ module Internal.Cardano.Write.Tx
, AssetName

-- * Balancing
, evaluateMinimumFee
, evaluateTransactionBalance
)
where
Expand Down Expand Up @@ -294,7 +288,6 @@ import qualified Cardano.Ledger.Credential as Core
import qualified Cardano.Ledger.Keys as Ledger
import qualified Cardano.Ledger.Mary.Value as Value
import qualified Cardano.Ledger.Plutus.Data as Alonzo
import qualified Cardano.Ledger.Shelley.API.Wallet as Shelley
import qualified Cardano.Ledger.Shelley.UTxO as Shelley
import qualified Cardano.Ledger.TxIn as Ledger
import qualified Cardano.Wallet.Primitive.Ledger.Convert as Convert
Expand Down Expand Up @@ -782,8 +775,6 @@ toCardanoApiUTxO =
. Map.mapKeys CardanoApi.fromShelleyTxIn
. Map.map (CardanoApi.fromShelleyTxOut (shelleyBasedEra @era))
. unUTxO
where
unUTxO (Shelley.UTxO m) = m

fromCardanoApiUTxO
:: forall era. IsRecentEra era
Expand Down Expand Up @@ -868,38 +859,6 @@ stakeKeyDeposit pp = pp ^. Core.ppKeyDepositL
-- Balancing
--------------------------------------------------------------------------------

-- | Computes the minimal fee amount necessary to pay for a given transaction.
--
evaluateMinimumFee
:: IsRecentEra era
=> PParams era
-> Core.Tx era
-> KeyWitnessCounts
-> Coin
evaluateMinimumFee pp tx kwc =
mainFee <> bootWitnessFee
where
KeyWitnessCounts {nKeyWits, nBootstrapWits} = kwc

mainFee :: Coin
mainFee = Shelley.evaluateTransactionFee pp tx nKeyWits
-- TODO [ADP-3334] Stop using deprecated ledger function
-- https://cardanofoundation.atlassian.net/browse/ADP-3334

FeePerByte feePerByte = getFeePerByte pp

bootWitnessFee :: Coin
bootWitnessFee = Coin $ intCast $ feePerByte * byteCount
where
byteCount :: Natural
byteCount = sizeOf_BootstrapWitnesses $ intCast nBootstrapWits

-- Matching implementation in "Cardano.Wallet.Shelley.Transaction".
-- Equivalence is tested in property.
sizeOf_BootstrapWitnesses :: Natural -> Natural
sizeOf_BootstrapWitnesses 0 = 0
sizeOf_BootstrapWitnesses n = 4 + 180 * n

-- | Evaluate the /balance/ of a transaction using the ledger.
--
-- The balance is defined as:
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -198,7 +198,6 @@ import Internal.Cardano.Write.Tx
, UTxO (..)
, Value
, computeMinimumCoinForTxOut
, evaluateMinimumFee
, evaluateTransactionBalance
, feeOfBytes
, getFeePerByte
Expand Down Expand Up @@ -236,6 +235,7 @@ import Internal.Cardano.Write.Tx.Redeemers
import Internal.Cardano.Write.Tx.Sign
( TimelockKeyWitnessCounts (..)
, estimateKeyWitnessCounts
, estimateSignedTxMinFee
, estimateSignedTxSize
)
import Internal.Cardano.Write.Tx.SizeEstimation
Expand Down Expand Up @@ -866,7 +866,8 @@ balanceTxInner
utxoReference
tx
timelockKeyWitnessCounts
minfee = Convert.toWalletCoin $ evaluateMinimumFee pp tx witCount
minfee = Convert.toWalletCoin
$ estimateSignedTxMinFee pp utxoReference tx witCount
update = TxUpdate
{ extraInputs = mempty
, extraCollateral = mempty
Expand Down
131 changes: 77 additions & 54 deletions lib/balance-tx/lib/internal/Internal/Cardano/Write/Tx/Sign.hs
Original file line number Diff line number Diff line change
@@ -1,10 +1,12 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeApplications #-}
{-# OPTIONS_GHC -Wno-unrecognised-pragmas #-}
{-# HLINT ignore "Use camelCase" #-}

-- |
-- Copyright: © 2023 IOHK, 2023 Cardano Foundation
Expand All @@ -18,6 +20,7 @@ module Internal.Cardano.Write.Tx.Sign

-- * Signing-related utilities required for balancing
estimateSignedTxSize
, estimateSignedTxMinFee

, KeyWitnessCounts (..)
, TimelockKeyWitnessCounts (..)
Expand All @@ -30,6 +33,9 @@ module Internal.Cardano.Write.Tx.Sign

import Prelude

import Cardano.Api.Ledger
( Coin
)
import Cardano.Ledger.Allegra.Scripts
( Timelock
)
Expand All @@ -41,7 +47,7 @@ import Cardano.Ledger.Api
, addrTxWitsL
, bodyTxL
, bootAddrTxWitsL
, ppMinFeeAL
, getMinFeeTx
, scriptTxWitsL
, sizeTxF
, witsTxL
Expand All @@ -50,24 +56,32 @@ import Cardano.Ledger.Credential
( Credential (..)
, StakeCredential
)
import Cardano.Ledger.Tools
( addDummyWitsTx
)
import Cardano.Ledger.UTxO
( EraUTxO (getScriptsHashesNeeded, getScriptsNeeded)
, txinLookup
)
import Cardano.Wallet.Primitive.Types.Tx.Constraints
( TxSize (..)
)
import Control.Lens
( view
, (&)
, (.~)
, (^.)
)
import Data.IntCast
( intCast
, intCastMaybe
)
import Data.Map.Strict
( Map
)
import Data.Maybe
( mapMaybe
)
import Data.Monoid.Monus
( Monus ((<\>))
( fromMaybe
, mapMaybe
)
import Data.Set
( Set
Expand All @@ -80,6 +94,8 @@ import Internal.Cardano.Write.Tx
, Tx
, TxIn
, UTxO
, feeOfBytes
, getFeePerByte
, toCardanoApiTx
)
import Numeric.Natural
Expand All @@ -94,9 +110,6 @@ import qualified Cardano.Ledger.Api as Ledger
import qualified Cardano.Ledger.Api.Tx.Cert as Conway
import qualified Cardano.Ledger.Shelley.TxCert as Shelley
import qualified Cardano.Wallet.Primitive.Ledger.Convert as Convert
import qualified Cardano.Wallet.Primitive.Types.Coin as W
( Coin (..)
)
import qualified Cardano.Wallet.Primitive.Types.Tx.Constraints as W
( TxSize (..)
)
Expand All @@ -114,52 +127,15 @@ estimateSignedTxSize
-> KeyWitnessCounts
-> Tx era -- ^ existing wits in tx are ignored
-> W.TxSize
estimateSignedTxSize pparams nWits txWithWits =
let
-- Hack which allows us to rely on the ledger to calculate the size of
-- witnesses:
feeOfWits :: W.Coin
feeOfWits = minfee nWits <\> minfee mempty

sizeOfWits :: W.TxSize
sizeOfWits =
case feeOfWits `coinQuotRem` feePerByte of
(n, 0) -> W.TxSize n
(_, _) -> error $ unwords
[ "estimateSignedTxSize:"
, "the impossible happened!"
, "Couldn't divide"
, show feeOfWits
, "lovelace (the fee contribution of"
, show nWits
, "witnesses) with"
, show feePerByte
, "lovelace/byte"
]

sizeOfTx :: W.TxSize
sizeOfTx =
fromIntegral @Integer @W.TxSize
$ unsignedTx ^. sizeTxF
in
sizeOfTx <> sizeOfWits
estimateSignedTxSize pparams (KeyWitnessCounts nWit nBoot)tx =
TxSize
. (+ sizeOf_BootstrapWitnesses (intCast nBoot))
. integerToNatural
. view sizeTxF
$ mockWitnesses nWit pparams tx
where
unsignedTx :: Tx era
unsignedTx =
txWithWits
& (witsTxL . addrTxWitsL) .~ mempty
& (witsTxL . bootAddrTxWitsL) .~ mempty

coinQuotRem :: W.Coin -> W.Coin -> (Natural, Natural)
coinQuotRem (W.Coin p) (W.Coin q) = quotRem p q

minfee :: KeyWitnessCounts -> W.Coin
minfee witCount = Convert.toWalletCoin $ Write.evaluateMinimumFee
pparams unsignedTx witCount

feePerByte :: W.Coin
feePerByte = Convert.toWalletCoin $
pparams ^. ppMinFeeAL
integerToNatural = fromMaybe (error "estimateSignedTxSize: negative size")
. intCastMaybe

numberOfShelleyWitnesses :: Word -> KeyWitnessCounts
numberOfShelleyWitnesses n = KeyWitnessCounts n 0
Expand Down Expand Up @@ -418,3 +394,50 @@ estimateMaxWitnessRequiredPerInput = \case
-- https://cardanofoundation.atlassian.net/browse/ADP-2676
CA.ActiveFromSlot _ -> 0
CA.ActiveUntilSlot _ -> 0

estimateSignedTxMinFee
:: forall era. IsRecentEra era
=> PParams era
-> UTxO era
-> Tx era
-> KeyWitnessCounts
-> Coin
estimateSignedTxMinFee pp _utxoNeededSoon tx (KeyWitnessCounts nWit nBoot) =
-- NOTE: We don't use mock bootstrap witnesses, but rely on the same
-- size estimation as coin selection does through 'estimateTxSize'
getMinFeeTx pp (mockWitnesses nWit pp tx)
<> bootWitFee
where
bootWitFee =
feeOfBytes
(getFeePerByte pp)
(sizeOf_BootstrapWitnesses $ intCast nBoot)

-- Matching the corresponding implementation in "Cardano.Write.Tx.SizeEstimation".
-- Their equivalence is tested in a property test.
sizeOf_BootstrapWitnesses :: Natural -> Natural
sizeOf_BootstrapWitnesses 0 = 0
sizeOf_BootstrapWitnesses n = 4 + 180 * n

-- | Adds 'n' number of mock key witnesses to the tx. Any preexisting witnesses
-- will first be removed.
mockWitnesses
:: forall era. IsRecentEra era
=> Word -- Key witnesses
-> PParams era
-> Tx era
-> Tx era
mockWitnesses nWits pp tx =
addDummyWitsTx
pp
(dropWits tx)
(wordToInt nWits)
[] -- no byron witnesses
where
wordToInt :: Word -> Int
wordToInt = fromMaybe (error "addDummyKeyWitnesses") . intCastMaybe

dropWits :: Tx era -> Tx era
dropWits x = x
& (witsTxL . bootAddrTxWitsL) .~ mempty
& (witsTxL . addrTxWitsL) .~ mempty
Loading

0 comments on commit b61a19a

Please sign in to comment.