Skip to content

Commit

Permalink
txsize now just counts the serialized bytes
Browse files Browse the repository at this point in the history
  • Loading branch information
Jared Corduan committed Jul 9, 2020
1 parent 47e2075 commit 34f3ddf
Show file tree
Hide file tree
Showing 4 changed files with 32 additions and 67 deletions.
Original file line number Diff line number Diff line change
Expand Up @@ -705,25 +705,11 @@ genesisState genDelegs0 utxo0 =
dState = emptyDState {_genDelegs = GenDelegs genDelegs0}

-- | Implementation of abstract transaction size
txsize :: forall crypto. (Crypto crypto) => Tx crypto -> Integer
txsize tx = numInputs * inputSize + numOutputs * outputSize + rest
where
uint = 5
smallArray = 1
hashLen = 32
hashObj = 2 + hashLen
addrHashLen = 28
addrHeader = 1
address = 2 + addrHeader + 2 * addrHashLen
txbody = _body tx
numInputs = toInteger . length . _inputs $ txbody
inputSize = smallArray + uint + hashObj
numOutputs = toInteger . length . _outputs $ txbody
outputSize = smallArray + uint + address
rest = fromIntegral $ BSL.length (txFullBytes tx) - extraSize txbody
txsize :: Tx crypto -> Integer
txsize = fromIntegral . BSL.length . txFullBytes

-- | Minimum fee calculation
minfee :: forall crypto. (Crypto crypto) => PParams -> Tx crypto -> Coin
minfee :: PParams -> Tx crypto -> Coin
minfee pp tx = Coin $ fromIntegral (_minfeeA pp) * txsize tx + fromIntegral (_minfeeB pp)

-- | Compute the lovelace which are created by the transaction
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -41,8 +41,7 @@ module Shelley.Spec.Ledger.TxData
_txfee,
_ttl,
_txUpdate,
_mdHash,
extraSize
_mdHash
),
TxId (..),
TxIn (..),
Expand Down Expand Up @@ -78,7 +77,6 @@ import Cardano.Binary
serializeEncoding,
serializeEncoding',
szCases,
withSlice,
)
import Cardano.Prelude
( AllowThunksIn (..),
Expand All @@ -95,13 +93,11 @@ import Data.Aeson (FromJSON (..), ToJSON (..), (.!=), (.:), (.:?), (.=))
import qualified Data.Aeson as Aeson
import Data.Aeson.Types (explicitParseField)
import Data.ByteString (ByteString)
import qualified Data.ByteString as BS
import qualified Data.ByteString.Base16 as Base16
import qualified Data.ByteString.Char8 as Char8
import qualified Data.ByteString.Lazy as BSL
import Data.Foldable (fold)
import Data.IP (IPv4, IPv6)
import Data.Int (Int64)
import Data.Map.Strict (Map)
import qualified Data.Map.Strict as Map
import Data.Ord (comparing)
Expand Down Expand Up @@ -465,8 +461,7 @@ data TxBody crypto = TxBody'
_ttl' :: !SlotNo,
_txUpdate' :: !(StrictMaybe (Update crypto)),
_mdHash' :: !(StrictMaybe (MetaDataHash crypto)),
bodyBytes :: LByteString,
extraSize :: Int64 -- This is the contribution of inputs, outputs, and fees to the size of the transaction
bodyBytes :: LByteString
}
deriving (Show, Eq, Generic)
deriving
Expand Down Expand Up @@ -516,10 +511,9 @@ pattern TxBody {_inputs, _outputs, _certs, _wdrls, _txfee, _ttl, _txUpdate, _mdH
inputBytes = serializeEncoding' $ encodeFoldable _inputs
outputBytes = serializeEncoding' $ encodeFoldable _outputs
feeBytes = serializeEncoding' $ toCBOR _txfee
es = fromIntegral $ BS.length inputBytes + BS.length outputBytes + BS.length feeBytes
n = fromIntegral $ length l
bytes = serializeEncoding $ encodeMapLen n <> fold l
in TxBody' _inputs _outputs _certs _wdrls _txfee _ttl _txUpdate _mdHash bytes es
in TxBody' _inputs _outputs _certs _wdrls _txfee _ttl _txUpdate _mdHash bytes

{-# COMPLETE TxBody #-}

Expand Down Expand Up @@ -719,26 +713,14 @@ instance
mapParts <-
decodeMapContents $
decodeWord >>= \case
0 -> f 0 (decodeSet fromCBOR) $ \bytes x t ->
t
{ _inputs' = x,
extraSize = extraSize t + BSL.length bytes
}
1 -> f 1 (decodeStrictSeq fromCBOR) $ \bytes x t ->
t
{ _outputs' = x,
extraSize = extraSize t + BSL.length bytes
}
2 -> f 2 fromCBOR $ \bytes x t ->
t
{ _txfee' = x,
extraSize = extraSize t + BSL.length bytes
}
3 -> f 3 fromCBOR $ \_ x t -> t {_ttl' = x}
4 -> f 4 (decodeStrictSeq fromCBOR) $ \_ x t -> t {_certs' = x}
5 -> f 5 fromCBOR $ \_ x t -> t {_wdrls' = x}
6 -> f 6 fromCBOR $ \_ x t -> t {_txUpdate' = SJust x}
7 -> f 7 fromCBOR $ \_ x t -> t {_mdHash' = SJust x}
0 -> f 0 (decodeSet fromCBOR) $ \x t -> t {_inputs' = x}
1 -> f 1 (decodeStrictSeq fromCBOR) $ \x t -> t {_outputs' = x}
2 -> f 2 fromCBOR $ \x t -> t {_txfee' = x}
3 -> f 3 fromCBOR $ \x t -> t {_ttl' = x}
4 -> f 4 (decodeStrictSeq fromCBOR) $ \x t -> t {_certs' = x}
5 -> f 5 fromCBOR $ \x t -> t {_wdrls' = x}
6 -> f 6 fromCBOR $ \x t -> t {_txUpdate' = SJust x}
7 -> f 7 fromCBOR $ \x t -> t {_mdHash' = SJust x}
k -> invalidKey k
let requiredFields :: Map Int String
requiredFields =
Expand All @@ -754,19 +736,17 @@ instance
(null missingFields)
(fail $ "missing required transaction component(s): " <> show missingFields)
pure $
Annotator $ \fullbytes bytes ->
(foldr ($) basebody (flip runAnnotator fullbytes . snd <$> mapParts)) {bodyBytes = bytes}
Annotator $ \_fullbytes bytes ->
(foldr ($) basebody (snd <$> mapParts)) {bodyBytes = bytes}
where
f ::
Int ->
Decoder s a ->
(LByteString -> a -> TxBody crypto -> TxBody crypto) ->
Decoder s (Int, Annotator (TxBody crypto -> TxBody crypto))
(a -> TxBody crypto -> TxBody crypto) ->
Decoder s (Int, TxBody crypto -> TxBody crypto)
f key decoder updater = do
(x, annBytes) <- withSlice decoder
let result = Annotator $ \fullbytes txbody ->
updater (runAnnotator annBytes fullbytes) x txbody
pure (key, result)
x <- decoder
pure (key, updater x)
basebody =
TxBody'
{ _inputs' = Set.empty,
Expand All @@ -777,8 +757,7 @@ instance
_wdrls' = Wdrl Map.empty,
_txUpdate' = SNothing,
_mdHash' = SNothing,
bodyBytes = mempty,
extraSize = 0
bodyBytes = mempty
}

instance ToCBOR PoolMetaData where
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -499,16 +499,16 @@ sizeTests :: TestTree
sizeTests =
testGroup
"Fee Tests"
[ testCase "simple utxo" $ sizeTest p txSimpleUTxOBytes16 txSimpleUTxO 139,
testCase "multiple utxo" $ sizeTest p txMutiUTxOBytes16 txMutiUTxO 462,
testCase "register stake key" $ sizeTest p txRegisterStakeBytes16 txRegisterStake 150,
testCase "delegate stake key" $ sizeTest p txDelegateStakeBytes16 txDelegateStake 178,
testCase "deregister stake key" $ sizeTest p txDeregisterStakeBytes16 txDeregisterStake 150,
testCase "register stake pool" $ sizeTest p txRegisterPoolBytes16 txRegisterPool 200,
testCase "retire stake pool" $ sizeTest p txRetirePoolBytes16 txRetirePool 149,
testCase "metadata" $ sizeTest p txWithMDBytes16 txWithMD 154,
testCase "multisig" $ sizeTest p txWithMultiSigBytes16 (txWithMultiSig p) 189,
testCase "reward withdrawal" $ sizeTest p txWithWithdrawalBytes16 txWithWithdrawal 172
[ testCase "simple utxo" $ sizeTest p txSimpleUTxOBytes16 txSimpleUTxO 57,
testCase "multiple utxo" $ sizeTest p txMutiUTxOBytes16 txMutiUTxO 138,
testCase "register stake key" $ sizeTest p txRegisterStakeBytes16 txRegisterStake 68,
testCase "delegate stake key" $ sizeTest p txDelegateStakeBytes16 txDelegateStake 96,
testCase "deregister stake key" $ sizeTest p txDeregisterStakeBytes16 txDeregisterStake 68,
testCase "register stake pool" $ sizeTest p txRegisterPoolBytes16 txRegisterPool 118,
testCase "retire stake pool" $ sizeTest p txRetirePoolBytes16 txRetirePool 67,
testCase "metadata" $ sizeTest p txWithMDBytes16 txWithMD 72,
testCase "multisig" $ sizeTest p txWithMultiSigBytes16 (txWithMultiSig p) 107,
testCase "reward withdrawal" $ sizeTest p txWithWithdrawalBytes16 txWithWithdrawal 90
]
where
p :: Proxy ShortHash
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -515,7 +515,7 @@ testEmptyInputSet =
testFeeTooSmall :: Assertion
testFeeTooSmall =
testInvalidTx
[UtxowFailure (UtxoFailure (FeeTooSmallUTxO (Coin 206) (Coin 1)))]
[UtxowFailure (UtxoFailure (FeeTooSmallUTxO (Coin 74) (Coin 1)))]
$ aliceGivesBobLovelace
AliceToBob
{ input = (TxIn genesisId 0),
Expand Down

0 comments on commit 34f3ddf

Please sign in to comment.