Skip to content

Commit

Permalink
Merge pull request #642 from IntersectMBO/newhoggy/use-evaluateTransa…
Browse files Browse the repository at this point in the history
…ctionFee-in-calculateMinFee

Use evaluateTransactionFee in calculate-min-fee
  • Loading branch information
newhoggy authored Mar 18, 2024
2 parents fc9386e + b753d9a commit a68f9f7
Show file tree
Hide file tree
Showing 22 changed files with 652 additions and 214 deletions.
3 changes: 2 additions & 1 deletion cardano-cli/cardano-cli.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -356,7 +356,8 @@ test-suite cardano-cli-golden
build-tool-depends: cardano-cli:cardano-cli
, tasty-discover:tasty-discover

other-modules: Test.Golden.Byron.SigningKeys
other-modules: Test.Golden.Babbage.Transaction.CalculateMinFee
Test.Golden.Byron.SigningKeys
Test.Golden.Byron.Tx
Test.Golden.Byron.TxBody
Test.Golden.Byron.UpdateProposal
Expand Down
3 changes: 0 additions & 3 deletions cardano-cli/src/Cardano/CLI/EraBased/Commands/Transaction.hs
Original file line number Diff line number Diff line change
Expand Up @@ -160,10 +160,7 @@ newtype TransactionPolicyIdCmdArgs = TransactionPolicyIdCmdArgs

data TransactionCalculateMinFeeCmdArgs = TransactionCalculateMinFeeCmdArgs
{ txBodyFile :: !(TxBodyFile In)
, networkId :: !NetworkId
, protocolParamsFile :: !ProtocolParamsFile
, txInCount :: !TxInCount
, txOutCount :: !TxOutCount
, txShelleyWitnessCount :: !TxShelleyWitnessCount
, txByronWitnessCount :: !TxByronWitnessCount
} deriving Show
Expand Down
25 changes: 19 additions & 6 deletions cardano-cli/src/Cardano/CLI/EraBased/Options/Common.hs
Original file line number Diff line number Diff line change
Expand Up @@ -76,6 +76,19 @@ prefixFlag prefix longFlag =
Nothing -> longFlag
Just prefix' -> prefix' <> "-" <> longFlag

pNetworkIdDeprecated :: Parser NetworkId
pNetworkIdDeprecated = asum
[ Opt.flag' Mainnet $ mconcat
[ Opt.long "mainnet"
, Opt.help "DEPRECATED. This argument has no effect."
]
, fmap (Testnet . NetworkMagic) $ Opt.option (bounded "TESTNET_MAGIC") $ mconcat
[ Opt.long "testnet-magic"
, Opt.metavar "NATURAL"
, Opt.help "DEPRECATED. This argument has no effect."
]
]

pNetworkId :: EnvCli -> Parser NetworkId
pNetworkId envCli = asum $ mconcat
[ [ Opt.flag' Mainnet $ mconcat
Expand Down Expand Up @@ -2226,20 +2239,20 @@ pInputTxOrTxBodyFile =
, InputTxFile <$> pTxFileIn
]

pTxInCount :: Parser TxInCount
pTxInCount =
pTxInCountDeprecated :: Parser TxInCount
pTxInCountDeprecated =
fmap TxInCount $ Opt.option Opt.auto $ mconcat
[ Opt.long "tx-in-count"
, Opt.metavar "NATURAL"
, Opt.help "The number of transaction inputs."
, Opt.help "DEPRECATED. This argument has no effect."
]

pTxOutCount :: Parser TxOutCount
pTxOutCount =
pTxOutCountDeprecated :: Parser TxOutCount
pTxOutCountDeprecated =
fmap TxOutCount $ Opt.option Opt.auto $ mconcat
[ Opt.long "tx-out-count"
, Opt.metavar "NATURAL"
, Opt.help "The number of transaction outputs."
, Opt.help "DEPRECATED. This argument has no effect."
]

pTxShelleyWitnessCount :: Parser TxShelleyWitnessCount
Expand Down
13 changes: 7 additions & 6 deletions cardano-cli/src/Cardano/CLI/EraBased/Options/Transaction.hs
Original file line number Diff line number Diff line change
Expand Up @@ -76,7 +76,7 @@ pTransactionCmds era envCli =
$ Opt.progDesc "Calculate the PolicyId from the monetary policy script."
, Just
$ subParser "calculate-min-fee"
$ Opt.info (pTransactionCalculateMinFee envCli)
$ Opt.info pTransactionCalculateMinFee
$ Opt.progDesc "Calculate the minimum fee for a transaction."
, Just $ subParser "calculate-min-required-utxo"
$ Opt.info (pTransactionCalculateMinReqUTxO era)
Expand Down Expand Up @@ -260,17 +260,18 @@ pTransactionPolicyId =
TransactionPolicyIdCmdArgs
<$> pScript

pTransactionCalculateMinFee :: EnvCli -> Parser (TransactionCmds era)
pTransactionCalculateMinFee envCli =
pTransactionCalculateMinFee :: Parser (TransactionCmds era)
pTransactionCalculateMinFee =
fmap TransactionCalculateMinFeeCmd $
TransactionCalculateMinFeeCmdArgs
<$> pTxBodyFileIn
<*> pNetworkId envCli
<*> pProtocolParamsFile
<*> pTxInCount
<*> pTxOutCount
<*> pTxShelleyWitnessCount
<*> pTxByronWitnessCount
-- Deprecated options:
<* optional pNetworkIdDeprecated
<* optional pTxInCountDeprecated
<* optional pTxOutCountDeprecated

pTransactionCalculateMinReqUTxO :: ShelleyBasedEra era -> Parser (TransactionCmds era)
pTransactionCalculateMinReqUTxO era =
Expand Down
108 changes: 75 additions & 33 deletions cardano-cli/src/Cardano/CLI/EraBased/Run/Transaction.hs
Original file line number Diff line number Diff line change
Expand Up @@ -37,6 +37,8 @@ import Cardano.Api.Byron hiding (SomeByronSigningKey (..))
import qualified Cardano.Api.Ledger as L
import Cardano.Api.Shelley

import qualified Cardano.Binary as CBOR
import qualified Cardano.Chain.Common as Byron
import qualified Cardano.CLI.EraBased.Commands.Transaction as Cmd
import Cardano.CLI.EraBased.Run.Genesis
import Cardano.CLI.Json.Friendly (FriendlyFormat (..), friendlyTx, friendlyTxBody)
Expand All @@ -54,6 +56,7 @@ import qualified Ouroboros.Network.Protocol.LocalTxSubmission.Client as Net.Tx
import Control.Monad (forM)
import Data.Aeson.Encode.Pretty (encodePretty)
import Data.Bifunctor (Bifunctor (..))
import qualified Data.ByteString as Data.Bytestring
import qualified Data.ByteString.Char8 as BS
import qualified Data.ByteString.Lazy.Char8 as LBS
import Data.Data ((:~:) (..))
Expand Down Expand Up @@ -1009,45 +1012,84 @@ runTransactionCalculateMinFeeCmd :: ()
runTransactionCalculateMinFeeCmd
Cmd.TransactionCalculateMinFeeCmdArgs
{ txBodyFile = File txbodyFilePath
, networkId = networkId
, protocolParamsFile = protocolParamsFile
, txInCount = TxInCount nInputs
, txOutCount = TxOutCount nOutputs
, txShelleyWitnessCount = TxShelleyWitnessCount nShelleyKeyWitnesses
, txByronWitnessCount = TxByronWitnessCount nByronKeyWitnesses
} = do

txbodyFile <- liftIO $ fileOrPipe txbodyFilePath
unwitnessed <- firstExceptT TxCmdCddlError . newExceptT $ readFileTxBody txbodyFile
pparams <- firstExceptT TxCmdProtocolParamsError $ readProtocolParameters protocolParamsFile
case unwitnessed of
IncompleteCddlFormattedTx anyTx -> do
InAnyShelleyBasedEra sbe unwitTx <- pure anyTx
let txbody = getTxBody unwitTx
let tx = makeSignedTransaction [] txbody
L.Coin fee = estimateTransactionFee sbe
networkId
(protocolParamTxFeeFixed pparams)
(protocolParamTxFeePerByte pparams)
tx
nInputs nOutputs
nShelleyKeyWitnesses nByronKeyWitnesses

liftIO $ putStrLn $ (show fee :: String) <> " Lovelace"

UnwitnessedCliFormattedTxBody anyTxBody -> do
InAnyShelleyBasedEra sbe txbody <- pure anyTxBody

let tx = makeSignedTransaction [] txbody
L.Coin fee = estimateTransactionFee sbe
networkId
(protocolParamTxFeeFixed pparams)
(protocolParamTxFeePerByte pparams)
tx
nInputs nOutputs
nByronKeyWitnesses nShelleyKeyWitnesses

liftIO $ putStrLn $ (show fee :: String) <> " Lovelace"
unwitnessed <-
firstExceptT TxCmdCddlError . newExceptT
$ readFileTxBody txbodyFile
pparams <-
firstExceptT TxCmdProtocolParamsError
$ readProtocolParameters protocolParamsFile

let nShelleyKeyWitW32 = fromIntegral nShelleyKeyWitnesses

InAnyShelleyBasedEra sbe txbody <- case unwitnessed of
IncompleteCddlFormattedTx (InAnyShelleyBasedEra sbe unwitTx) -> do
pure $ InAnyShelleyBasedEra sbe $ getTxBody unwitTx

UnwitnessedCliFormattedTxBody (InAnyShelleyBasedEra sbe txbody) -> do
pure $ InAnyShelleyBasedEra sbe txbody

lpparams <- getLedgerPParams sbe pparams

let shelleyfee = evaluateTransactionFee sbe lpparams txbody nShelleyKeyWitW32 0

let byronfee = calculateByronWitnessFees (protocolParamTxFeePerByte pparams) nByronKeyWitnesses

let L.Coin fee = shelleyfee + byronfee

liftIO $ putStrLn $ (show fee :: String) <> " Lovelace"

getLedgerPParams :: forall era. ()
=> ShelleyBasedEra era
-> ProtocolParameters
-> ExceptT TxCmdError IO (L.PParams (ShelleyLedgerEra era))
getLedgerPParams sbe pparams =
firstExceptT TxCmdProtocolParamsConverstionError $
hoistEither $ toLedgerPParams sbe pparams

-- Extra logic to handle byron witnesses.
-- TODO: move this to Cardano.API.Fee.evaluateTransactionFee.
calculateByronWitnessFees :: ()
=> L.Coin -- ^ The tx fee per byte (from protocol parameters)
-> Int -- ^ The number of Byron key witnesses
-> L.Coin
calculateByronWitnessFees txFeePerByte byronwitcount =
L.Coin
$ toInteger txFeePerByte
* toInteger byronwitcount
* toInteger sizeByronKeyWitnesses
where
sizeByronKeyWitnesses = smallArray + keyObj + sigObj + ccodeObj + attrsObj

smallArray = 1

keyObj = 2 + keyLen
keyLen = 32

sigObj = 2 + sigLen
sigLen = 64

ccodeObj = 2 + ccodeLen
ccodeLen = 32

attrsObj = 2 + Data.Bytestring.length attributes

-- We assume testnet network magic here to avoid having
-- to thread the actual network ID into this function
-- merely to calculate the fees of byron witnesses more accurately.
-- This may slightly over-estimate min fees for byron witnesses
-- in mainnet transaction by one Word32 per witness.
attributes = CBOR.serialize' $
Byron.mkAttributes Byron.AddrAttributes {
Byron.aaVKDerivationPath = Nothing,
Byron.aaNetworkMagic = Byron.NetworkTestnet maxBound
}


-- ----------------------------------------------------------------------------
-- Transaction fee calculation
Expand Down
3 changes: 0 additions & 3 deletions cardano-cli/src/Cardano/CLI/Legacy/Commands/Transaction.hs
Original file line number Diff line number Diff line change
Expand Up @@ -117,10 +117,7 @@ data LegacyTransactionCmds
ScriptFile
| TransactionCalculateMinFeeCmd
(TxBodyFile In)
NetworkId
ProtocolParamsFile
TxInCount
TxOutCount
TxShelleyWitnessCount
TxByronWitnessCount
| TransactionCalculateMinValueCmd
Expand Down
7 changes: 4 additions & 3 deletions cardano-cli/src/Cardano/CLI/Legacy/Options.hs
Original file line number Diff line number Diff line change
Expand Up @@ -414,12 +414,13 @@ pTransaction envCli =
pTransactionCalculateMinFee =
TransactionCalculateMinFeeCmd
<$> pTxBodyFileIn
<*> pNetworkId envCli
<*> pProtocolParamsFile
<*> pTxInCount
<*> pTxOutCount
<*> pTxShelleyWitnessCount
<*> pTxByronWitnessCount
-- Deprecated options:
<* optional pNetworkIdDeprecated
<* optional pTxInCountDeprecated
<* optional pTxOutCountDeprecated

pTransactionCalculateMinReqUTxO :: Parser LegacyTransactionCmds
pTransactionCalculateMinReqUTxO =
Expand Down
13 changes: 2 additions & 11 deletions cardano-cli/src/Cardano/CLI/Legacy/Run/Transaction.hs
Original file line number Diff line number Diff line change
Expand Up @@ -43,8 +43,8 @@ runLegacyTransactionCmds = \case
runLegacyTransactionSignCmd txinfile skfiles network txoutfile
TransactionSubmitCmd mNodeSocketPath consensusModeParams network txFp ->
runLegacyTransactionSubmitCmd mNodeSocketPath consensusModeParams network txFp
TransactionCalculateMinFeeCmd txbody nw pParamsFile nInputs nOutputs nShelleyKeyWitnesses nByronKeyWitnesses ->
runLegacyTransactionCalculateMinFeeCmd txbody nw pParamsFile nInputs nOutputs nShelleyKeyWitnesses nByronKeyWitnesses
TransactionCalculateMinFeeCmd txbody pParamsFile nShelleyKeyWitnesses nByronKeyWitnesses ->
runLegacyTransactionCalculateMinFeeCmd txbody pParamsFile nShelleyKeyWitnesses nByronKeyWitnesses
TransactionCalculateMinValueCmd (EraInEon sbe) pParamsFile txOuts' ->
runLegacyTransactionCalculateMinValueCmd (AnyShelleyBasedEra sbe) pParamsFile txOuts'
TransactionHashScriptDataCmd scriptDataOrFile ->
Expand Down Expand Up @@ -222,28 +222,19 @@ runLegacyTransactionSubmitCmd

runLegacyTransactionCalculateMinFeeCmd :: ()
=> TxBodyFile In
-> NetworkId
-> ProtocolParamsFile
-> TxInCount
-> TxOutCount
-> TxShelleyWitnessCount
-> TxByronWitnessCount
-> ExceptT TxCmdError IO ()
runLegacyTransactionCalculateMinFeeCmd
txbodyFile
nw
pParamsFile
txInCount
txOutCount
txShelleyWitnessCount
txByronWitnessCount =
runTransactionCalculateMinFeeCmd
( Cmd.TransactionCalculateMinFeeCmdArgs
txbodyFile
nw
pParamsFile
txInCount
txOutCount
txShelleyWitnessCount
txByronWitnessCount
)
Expand Down
Original file line number Diff line number Diff line change
@@ -0,0 +1,26 @@
{-# LANGUAGE OverloadedStrings #-}

module Test.Golden.Babbage.Transaction.CalculateMinFee
( hprop_golden_babbage_transaction_calculate_min_fee
) where

import Test.Cardano.CLI.Util

import Hedgehog (Property)
import qualified Hedgehog as H

{- HLINT ignore "Use camelCase" -}

hprop_golden_babbage_transaction_calculate_min_fee :: Property
hprop_golden_babbage_transaction_calculate_min_fee = propertyOnce $ do
protocolParamsJsonFile <- noteInputFile "test/cardano-cli-golden/files/input/babbage/transaction-calculate-min-fee/protocol-params.json"
txBodyFile <- noteInputFile "test/cardano-cli-golden/files/input/babbage/tx/txbody"

minFeeTxt <- execCardanoCLI
[ "transaction","calculate-min-fee"
, "--witness-count", "1"
, "--protocol-params-file", protocolParamsJsonFile
, "--tx-body-file", txBodyFile
]

H.diff minFeeTxt (==) "165633 Lovelace\n"
Original file line number Diff line number Diff line change
Expand Up @@ -17,13 +17,10 @@ hprop_golden_shelley_transaction_calculate_min_fee = propertyOnce $ do

minFeeTxt <- execCardanoCLI
[ "transaction","calculate-min-fee"
, "--tx-in-count", "32"
, "--tx-out-count", "27"
, "--byron-witness-count", "10"
, "--witness-count", "5"
, "--testnet-magic", "4036000900"
, "--protocol-params-file", protocolParamsJsonFile
, "--tx-body-file", txBodyFile
]

H.diff minFeeTxt (==) "5083100 Lovelace\n"
H.diff minFeeTxt (==) "2050100 Lovelace\n"
Loading

0 comments on commit a68f9f7

Please sign in to comment.