Skip to content

Commit

Permalink
neededTxInsForBlock now accounts for all inputs (#2715)
Browse files Browse the repository at this point in the history
I've add a new class method to Era, getAllTxInputs, which collects
all the various inputs in the transaction body in each era.

* For Shelley through Mary this is just the spending inputs.
* Alonzo adds collateral inputs.
* Babbage adds reference inputs.
  • Loading branch information
Jared Corduan authored Mar 31, 2022
1 parent 16040b3 commit 28632ee
Show file tree
Hide file tree
Showing 8 changed files with 38 additions and 14 deletions.
5 changes: 5 additions & 0 deletions eras/alonzo/impl/src/Cardano/Ledger/Alonzo.hs
Original file line number Diff line number Diff line change
Expand Up @@ -104,6 +104,11 @@ instance CC.Crypto c => EraModule.Era (AlonzoEra c) where
type Crypto (AlonzoEra c) = c
getTxOutEitherAddr = getAlonzoTxOutEitherAddr

getAllTxInputs txb = spending `Set.union` collateral
where
spending = getField @"inputs" txb
collateral = getField @"collateral" txb

instance API.ShelleyEraCrypto c => API.ApplyTx (AlonzoEra c) where
reapplyTx globals env state vtx =
let res =
Expand Down
6 changes: 6 additions & 0 deletions eras/babbage/impl/src/Cardano/Ledger/Babbage.hs
Original file line number Diff line number Diff line change
Expand Up @@ -123,6 +123,12 @@ instance

getTxOutEitherAddr = getBabbageTxOutEitherAddr

getAllTxInputs txb = spending `Set.union` collateral `Set.union` reference
where
spending = getField @"inputs" txb
collateral = getField @"collateral" txb
reference = getField @"referenceInputs" txb

instance (CC.Crypto c) => Shelley.ValidateScript (BabbageEra c) where
isNativeScript x = not (isPlutusScript x)
scriptPrefixTag script =
Expand Down
2 changes: 2 additions & 0 deletions eras/shelley-ma/impl/src/Cardano/Ledger/ShelleyMA.hs
Original file line number Diff line number Diff line change
Expand Up @@ -109,6 +109,8 @@ instance

getTxOutEitherAddr (TxOutCompact a _) = Right a

getAllTxInputs = getField @"inputs"

instance CryptoClass.Crypto c => UsesValue (ShelleyMAEra 'Mary c)

instance CryptoClass.Crypto c => UsesValue (ShelleyMAEra 'Allegra c)
Expand Down
4 changes: 4 additions & 0 deletions eras/shelley/impl/src/Cardano/Ledger/Shelley.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
Expand Down Expand Up @@ -58,6 +59,7 @@ import Cardano.Ledger.Shelley.Tx
import qualified Cardano.Ledger.Shelley.Tx as STx (Tx, TxBody, TxOut (..))
import qualified Data.ByteString as BS
import Data.Proxy
import GHC.Records (HasField (..))

data ShelleyEra c

Expand All @@ -66,6 +68,8 @@ instance CryptoClass.Crypto c => E.Era (ShelleyEra c) where

getTxOutEitherAddr (STx.TxOutCompact a _) = Right a

getAllTxInputs = getField @"inputs"

instance CryptoClass.Crypto c => UsesValue (ShelleyEra c)

instance CryptoClass.Crypto c => UsesTxOut (ShelleyEra c) where
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -737,8 +737,7 @@ preserveOutputsTx SourceSignalTarget {source = chainSt, signal = block} =
canRestrictUTxO ::
forall era ledger.
( ChainProperty era,
TestingLedger era ledger,
HasField "inputs" (Core.TxBody era) (Set (TxIn (Crypto era)))
TestingLedger era ledger
) =>
SourceSignalTarget (CHAIN era) ->
Property
Expand Down Expand Up @@ -1080,8 +1079,7 @@ ledgerTraceFromBlock chainSt block =
ledgerTraceFromBlockWithRestrictedUTxO ::
forall era ledger.
( ChainProperty era,
TestingLedger era ledger,
HasField "inputs" (Core.TxBody era) (Set (TxIn (Crypto era)))
TestingLedger era ledger
) =>
ChainState era ->
Block (BHeader (Crypto era)) era ->
Expand Down
8 changes: 3 additions & 5 deletions libs/cardano-ledger-core/src/Cardano/Ledger/Block.hs
Original file line number Diff line number Diff line change
Expand Up @@ -33,7 +33,7 @@ import Cardano.Binary
serializeEncoding,
)
import qualified Cardano.Ledger.Core as Core
import Cardano.Ledger.Era (Crypto, Era, ValidateScript (..))
import Cardano.Ledger.Era (Crypto, Era (getAllTxInputs), ValidateScript (..))
import qualified Cardano.Ledger.Era as Era
import Cardano.Ledger.Serialization
( ToCBORGroup (..),
Expand Down Expand Up @@ -169,14 +169,12 @@ bbody (Block' _ txs _) = txs
-- will use 'neededTxInsForBlock' to retrieve the needed UTxO from disk
-- and present only those to the ledger.
neededTxInsForBlock ::
( Era era,
HasField "inputs" (Core.TxBody era) (Set (TxIn (Crypto era)))
) =>
Era era =>
Block h era ->
Set (TxIn (Crypto era))
neededTxInsForBlock (Block' _ txsSeq _) = Set.filter isNotNewInput allTxIns
where
txBodies = map (getField @"body") $ toList $ Era.fromTxSeq txsSeq
allTxIns = Set.unions $ map (getField @"inputs") txBodies
allTxIns = Set.unions $ map getAllTxInputs txBodies
newTxIds = Set.fromList $ map txid txBodies
isNotNewInput (TxIn txID _) = txID `Set.notMember` newTxIds
9 changes: 9 additions & 0 deletions libs/cardano-ledger-core/src/Cardano/Ledger/Era.hs
Original file line number Diff line number Diff line change
Expand Up @@ -42,6 +42,7 @@ import Cardano.Ledger.SafeHash
( HashAnnotated (..),
SafeToHash (..),
)
import Cardano.Ledger.TxIn (TxIn (..))
import Cardano.Ledger.Val (Val)
import Control.Monad.Except (Except, runExcept)
import qualified Data.ByteString as BS
Expand Down Expand Up @@ -94,6 +95,14 @@ class
Left a -> compactAddr a
Right ca -> ca

-- | The validity of any individual block depends only on a subset
-- of the UTxO stored in the ledger state. The consensus layer makes
-- use of this fact, and uses the function below to to retrieve the
-- needed UTxO from disk and present only those to the ledger.
-- It is therefore neccessary that this function account for all the
-- different types of inputs inside a transaction.
getAllTxInputs :: Core.TxBody e -> Set (TxIn (Crypto e))

-- TODO - figure out a dedicated module for things that will create helper
-- functions from this module:

Expand Down
12 changes: 7 additions & 5 deletions libs/cardano-ledger-core/src/Cardano/Ledger/TxIn.hs
Original file line number Diff line number Diff line change
Expand Up @@ -25,12 +25,12 @@ module Cardano.Ledger.TxIn
where

import Cardano.Binary (FromCBOR (fromCBOR), ToCBOR (..), encodeListLen)
import Cardano.Crypto.Hash.Class (HashAlgorithm)
import Cardano.Ledger.BaseTypes (TxIx (..), mkTxIxPartial)
import Cardano.Ledger.Core (TxBody)
import qualified Cardano.Ledger.Crypto as CC
import Cardano.Ledger.Era (Crypto, Era)
import Cardano.Ledger.Hashes (EraIndependentTxBody)
import Cardano.Ledger.SafeHash (SafeHash, hashAnnotated)
import Cardano.Ledger.SafeHash (HashAnnotated, SafeHash, hashAnnotated)
import Cardano.Ledger.Serialization (decodeRecordNamed)
import Cardano.Prelude (HeapWords (..), NFData)
import qualified Cardano.Prelude as HW
Expand All @@ -40,10 +40,12 @@ import NoThunks.Class (NoThunks (..))

-- | Compute the id of a transaction.
txid ::
forall era.
Era era =>
forall era c.
( HashAlgorithm (CC.HASH c),
HashAnnotated (TxBody era) EraIndependentTxBody c
) =>
TxBody era ->
TxId (Crypto era)
TxId c
txid = TxId . hashAnnotated

-- ===================================================================================
Expand Down

0 comments on commit 28632ee

Please sign in to comment.