Skip to content

Commit

Permalink
Move estimateSignedTxSize to separate module (#4037)
Browse files Browse the repository at this point in the history
```haskell
-- |
-- Copyright: © 2023 IOHK, 2023 Cardano Foundation
-- License: Apache-2.0
--
-- Module for 'signTx' and signing-related utilities for balancing.
module Cardano.Wallet.Write.Tx.Sign
    (
    -- * Signing transactions
    -- TODO: Move signTx function here

    -- * Signing-related utilities required for balancing
      estimateSignedTxSize

    , KeyWitnessCount (..)
    , estimateKeyWitnessCount
    )
    where
```

### Comments

- Depends on #4036

### Issue Number

ADP-3081
  • Loading branch information
Anviking authored Jul 20, 2023
2 parents 4477b99 + 46f6c93 commit 40fb32f
Show file tree
Hide file tree
Showing 6 changed files with 270 additions and 217 deletions.
4 changes: 2 additions & 2 deletions lib/wallet/api/http/Cardano/Wallet/Api/Http/Server/Error.hs
Original file line number Diff line number Diff line change
Expand Up @@ -112,8 +112,6 @@ import Cardano.Wallet.Primitive.Types.TokenMap
( Flat (..) )
import Cardano.Wallet.Primitive.Types.Tx.SealedTx
( serialisedTx )
import Cardano.Wallet.Shelley.Transaction
( KeyWitnessCount (..) )
import Cardano.Wallet.Transaction
( ErrSignTx (..) )
import Cardano.Wallet.Write.Tx.Balance
Expand All @@ -122,6 +120,8 @@ import Cardano.Wallet.Write.Tx.Balance
, ErrBalanceTxInternalError (..)
, ErrUpdateSealedTx (..)
)
import Cardano.Wallet.Write.Tx.Sign
( KeyWitnessCount (..) )
import Control.Monad.Except
( ExceptT, lift, withExceptT )
import Control.Monad.Trans.Except
Expand Down
1 change: 1 addition & 0 deletions lib/wallet/cardano-wallet.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -412,6 +412,7 @@ library
Cardano.Wallet.Write.Tx.Balance
Cardano.Wallet.Write.Tx.Gen
Cardano.Wallet.Write.Tx.Redeemers
Cardano.Wallet.Write.Tx.Sign
Cardano.Wallet.Write.Tx.SizeEstimation
Cardano.Wallet.Write.Tx.TimeTranslation
Cardano.Wallet.Write.UTxOAssumptions
Expand Down
214 changes: 3 additions & 211 deletions lib/wallet/src/Cardano/Wallet/Shelley/Transaction.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,6 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE EmptyCase #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE LambdaCase #-}
Expand Down Expand Up @@ -36,9 +35,6 @@ module Cardano.Wallet.Shelley.Transaction
( newTransactionLayer

-- * For balancing (To be moved)
, estimateKeyWitnessCount
, estimateSignedTxSize
, KeyWitnessCount (..)
, distributeSurplus
, distributeSurplusDelta
, sizeOfCoin
Expand Down Expand Up @@ -85,7 +81,7 @@ import Cardano.Binary
import Cardano.Crypto.Wallet
( XPub )
import Cardano.Ledger.Allegra.Core
( inputsTxBodyL, ppMinFeeAL )
( inputsTxBodyL )
import Cardano.Ledger.Crypto
( DSIGN )
import Cardano.Tx.Balance.Internal.CoinSelection
Expand All @@ -99,8 +95,6 @@ import Cardano.Wallet.Address.Derivation.SharedKey
( replaceCosignersWithVerKeys )
import Cardano.Wallet.Address.Derivation.Shelley
( toRewardAccountRaw )
import Cardano.Wallet.Address.Discovery.Shared
( estimateMaxWitnessRequiredPerInput )
import Cardano.Wallet.Address.Keys.WalletKey
( getRawKey )
import Cardano.Wallet.Flavor
Expand All @@ -124,7 +118,6 @@ import Cardano.Wallet.Primitive.Types.Tx
, Tx (..)
, cardanoTxIdeallyNoLaterThan
, sealedTxFromCardano'
, sealedTxFromCardanoBody
)
import Cardano.Wallet.Primitive.Types.Tx.Constraints
( TxSize (..), txOutMaxTokenQuantity )
Expand All @@ -151,7 +144,7 @@ import Cardano.Wallet.Shelley.Compatibility
, toStakePoolDlgCert
)
import Cardano.Wallet.Shelley.Compatibility.Ledger
( Convert (..), toWalletCoin, toWalletScript )
( Convert (toLedger) )
import Cardano.Wallet.Transaction
( AnyExplicitScript (..)
, AnyScript (..)
Expand All @@ -174,7 +167,7 @@ import Cardano.Wallet.TxWitnessTag
import Cardano.Wallet.Util
( HasCallStack, internalError )
import Cardano.Wallet.Write.Tx
( FeePerByte (..), IsRecentEra (..), KeyWitnessCount (..), RecentEra (..) )
( FeePerByte (..) )
import Control.Arrow
( left, second )
import Control.Lens
Expand All @@ -197,8 +190,6 @@ import Data.Maybe
( mapMaybe )
import Data.Type.Equality
( type (==) )
import Numeric.Natural
( Natural )
import Ouroboros.Network.Block
( SlotNo )

Expand All @@ -211,7 +202,6 @@ import qualified Cardano.Crypto as CC
import qualified Cardano.Crypto.DSIGN as DSIGN
import qualified Cardano.Crypto.Hash.Class as Crypto
import qualified Cardano.Crypto.Wallet as Crypto.HD
import qualified Cardano.Ledger.Alonzo.Scripts as Alonzo
import qualified Cardano.Ledger.Api as Ledger
import qualified Cardano.Ledger.Keys.Bootstrap as SL
import qualified Cardano.Wallet.Primitive.Types.Coin as Coin
Expand Down Expand Up @@ -650,199 +640,6 @@ mkDelegationCertificates da cred =
]
Quit -> [toStakeKeyDeregCert cred]

-- | Estimate the size of the transaction (body) when fully signed.
estimateSignedTxSize
:: forall era. Write.IsRecentEra era
=> Write.PParams (Write.ShelleyLedgerEra era)
-> KeyWitnessCount
-> Cardano.TxBody era
-> TxSize
estimateSignedTxSize pparams nWits body =
let
-- Hack which allows us to rely on the ledger to calculate the size of
-- witnesses:
feeOfWits :: Coin
feeOfWits = minfee nWits `Coin.difference` minfee mempty

sizeOfWits :: TxSize
sizeOfWits =
case feeOfWits `coinQuotRem` feePerByte of
(n, 0) -> 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 :: TxSize
sizeOfTx = TxSize
. fromIntegral
. BS.length
. serialisedTx
$ sealedTxFromCardanoBody body
in
sizeOfTx <> sizeOfWits
where
coinQuotRem :: Coin -> Coin -> (Natural, Natural)
coinQuotRem (Coin p) (Coin q) = quotRem p q

minfee :: KeyWitnessCount -> Coin
minfee witCount = toWalletCoin $ Write.evaluateMinimumFee
(Write.recentEra @era) pparams (toLedgerTx body) witCount

toLedgerTx :: Cardano.TxBody era -> Write.Tx (Write.ShelleyLedgerEra era)
toLedgerTx b = case Cardano.Tx b [] of
Byron.ByronTx {} -> case Write.recentEra @era of {}
Cardano.ShelleyTx _era ledgerTx -> ledgerTx

feePerByte :: Coin
feePerByte = toWalletCoin $
case Write.recentEra @era of
Write.RecentEraBabbage -> pparams ^. ppMinFeeAL
Write.RecentEraConway -> pparams ^. ppMinFeeAL

numberOfShelleyWitnesses :: Word -> KeyWitnessCount
numberOfShelleyWitnesses n = KeyWitnessCount n 0

-- | Estimates the required number of Shelley-era witnesses.
--
-- Because we don't take into account whether two pieces of tx content will need
-- the same key for signing, the result may be an overestimate.
--
-- For instance, this may happen if:
-- 1. Multiple inputs share the same payment key (like in a single address
-- wallet)
-- 2. We are updating our delegation and withdrawing rewards at the same time.
--
-- FIXME [ADP-1515] Improve estimation
--
-- NOTE: Similar to 'estimateTransactionKeyWitnessCount' from cardano-api, which
-- we cannot use because it requires a 'TxBodyContent BuildTx era'.
estimateKeyWitnessCount
:: forall era. IsRecentEra era
=> Cardano.UTxO era
-- ^ Must contain all inputs from the 'TxBody' or
-- 'estimateKeyWitnessCount will 'error'.
-> Cardano.TxBody era
-> KeyWitnessCount
estimateKeyWitnessCount utxo txbody@(Cardano.TxBody txbodycontent) =
let txIns = map fst $ Cardano.txIns txbodycontent
txInsCollateral =
case Cardano.txInsCollateral txbodycontent of
Cardano.TxInsCollateral _ ins -> ins
Cardano.TxInsCollateralNone -> []
vkInsUnique = L.nub $ filter (hasVkPaymentCred utxo) $
txIns ++ txInsCollateral
txExtraKeyWits = Cardano.txExtraKeyWits txbodycontent
txExtraKeyWits' = case txExtraKeyWits of
Cardano.TxExtraKeyWitnesses _ khs -> khs
_ -> []
txWithdrawals = Cardano.txWithdrawals txbodycontent
txWithdrawals' = case txWithdrawals of
Cardano.TxWithdrawals _ wdls ->
[ () | (_, _, Cardano.ViewTx) <- wdls ]
_ -> []
txUpdateProposal = Cardano.txUpdateProposal txbodycontent
txUpdateProposal' = case txUpdateProposal of
Cardano.TxUpdateProposal _
(Cardano.UpdateProposal updatePerGenesisKey _) ->
Map.size updatePerGenesisKey
_ -> 0
txCerts = case Cardano.txCertificates txbodycontent of
Cardano.TxCertificatesNone -> 0
Cardano.TxCertificates _ certs _ ->
sumVia estimateDelegSigningKeys certs
scriptVkWitsUpperBound =
fromIntegral
$ sumVia estimateMaxWitnessRequiredPerInput
$ mapMaybe toTimelockScript scripts
nonInputWits = numberOfShelleyWitnesses $ fromIntegral $
length txExtraKeyWits' +
length txWithdrawals' +
txUpdateProposal' +
fromIntegral txCerts +
scriptVkWitsUpperBound
inputWits = KeyWitnessCount
{ nKeyWits = fromIntegral
. length
$ filter (not . hasBootstrapAddr utxo) vkInsUnique
, nBootstrapWits = fromIntegral
. length
$ filter (hasBootstrapAddr utxo) vkInsUnique
}
in
nonInputWits <> inputWits
where
scripts = case txbody of
Cardano.ShelleyTxBody _ _ shelleyBodyScripts _ _ _ -> shelleyBodyScripts
Byron.ByronTxBody {} -> error "estimateKeyWitnessCount: ByronTxBody"

dummyKeyRole = Payment


estimateDelegSigningKeys :: Cardano.Certificate -> Integer
estimateDelegSigningKeys = \case
Cardano.StakeAddressRegistrationCertificate _ -> 0
Cardano.StakeAddressDeregistrationCertificate cred ->
estimateWitNumForCred cred
Cardano.StakeAddressPoolDelegationCertificate cred _ ->
estimateWitNumForCred cred
_ -> 1
where
-- Does not include the key witness needed for script credentials.
-- They are accounted for separately in @scriptVkWitsUpperBound@.
estimateWitNumForCred = \case
Cardano.StakeCredentialByKey _ -> 1
Cardano.StakeCredentialByScript _ -> 0


toTimelockScript
:: Ledger.Script (Cardano.ShelleyLedgerEra era)
-> Maybe (Script KeyHash)
toTimelockScript anyScript = case recentEra @era of
RecentEraConway ->
case anyScript of
Alonzo.TimelockScript timelock ->
Just $ toWalletScript (const dummyKeyRole) timelock
Alonzo.PlutusScript _ _ -> Nothing
RecentEraBabbage ->
case anyScript of
Alonzo.TimelockScript timelock ->
Just $ toWalletScript (const dummyKeyRole) timelock
Alonzo.PlutusScript _ _ -> Nothing

hasVkPaymentCred
:: Cardano.UTxO era
-> Cardano.TxIn
-> Bool
hasVkPaymentCred (Cardano.UTxO u) inp = case Map.lookup inp u of
Just (Cardano.TxOut addrInEra _ _ _) -> Cardano.isKeyAddress addrInEra
Nothing ->
error $ unwords
[ "estimateMaxWitnessRequiredPerInput: input not in utxo."
, "Caller is expected to ensure this does not happen."
]

hasBootstrapAddr
:: Cardano.UTxO era
-> Cardano.TxIn
-> Bool
hasBootstrapAddr (Cardano.UTxO u) inp = case Map.lookup inp u of
Just (Cardano.TxOut addrInEra _ _ _) ->
case addrInEra of
Cardano.AddressInEra Cardano.ByronAddressInAnyEra _ -> True
_ -> False
Nothing ->
error $ unwords
[ "estimateMaxWitnessRequiredPerInput: input not in utxo."
, "Caller is expected to ensure this does not happen."
]

-- | Calculate the cost of increasing a CBOR-encoded Coin-value by another Coin
-- with the lovelace/byte cost given by the 'FeePolicy'.
--
Expand Down Expand Up @@ -1426,8 +1223,3 @@ explicitFees era = case era of
Cardano.TxFeeExplicit Cardano.TxFeesExplicitInBabbageEra
ShelleyBasedEraConway ->
Cardano.TxFeeExplicit Cardano.TxFeesExplicitInConwayEra

-- Small helper function for summing values. Given a list of values, get the sum
-- of the values, after the given function has been applied to each value.
sumVia :: (Foldable t, Num m) => (a -> m) -> t a -> m
sumVia f = F.foldl' (\t -> (t +) . f) 0
4 changes: 3 additions & 1 deletion lib/wallet/src/Cardano/Wallet/Write/Tx/Balance.hs
Original file line number Diff line number Diff line change
Expand Up @@ -109,7 +109,7 @@ import Cardano.Wallet.Read.Primitive.Tx.Features.Outputs
import Cardano.Wallet.Shelley.Compatibility
( fromCardanoTxIn, fromCardanoTxOut, toCardanoSimpleScript, toCardanoUTxO )
import Cardano.Wallet.Shelley.Transaction
( distributeSurplus, estimateKeyWitnessCount, estimateSignedTxSize )
( distributeSurplus )
import Cardano.Wallet.Transaction
( ErrMoreSurplusNeeded (..), TxFeeAndChange (..) )
import Cardano.Wallet.Write.ProtocolParameters
Expand Down Expand Up @@ -140,6 +140,8 @@ import Cardano.Wallet.Write.Tx
)
import Cardano.Wallet.Write.Tx.Redeemers
( ErrAssignRedeemers (..), assignScriptRedeemers )
import Cardano.Wallet.Write.Tx.Sign
( estimateKeyWitnessCount, estimateSignedTxSize )
import Cardano.Wallet.Write.Tx.SizeEstimation
( TxSkeleton (..), estimateTxCost )
import Cardano.Wallet.Write.Tx.TimeTranslation
Expand Down
Loading

0 comments on commit 40fb32f

Please sign in to comment.