Skip to content

Commit

Permalink
tx inputs: replace (TxIn, Coin) by (TxIn, Maybe TxOut)
Browse files Browse the repository at this point in the history
  • Loading branch information
Unisay authored and erikd committed Jan 31, 2023
1 parent b3f0218 commit 7b2a479
Show file tree
Hide file tree
Showing 24 changed files with 190 additions and 138 deletions.
5 changes: 2 additions & 3 deletions lib/wallet/api/http/Cardano/Wallet/Api/Http/Shelley/Server.hs
Expand Up @@ -2273,8 +2273,8 @@ mkApiTransactionFromInfo ti wrk wid deposit info metadataSchema = do
MkApiTransactionParams
{ txId = info ^. #txInfoId
, txFee = info ^. #txInfoFee
, txInputs = info ^. #txInfoInputs <&> drop2nd
, txCollateralInputs = info ^. #txInfoCollateralInputs <&> drop2nd
, txInputs = info ^. #txInfoInputs
, txCollateralInputs = info ^. #txInfoCollateralInputs
, txOutputs = info ^. #txInfoOutputs
, txCollateralOutput = info ^. #txInfoCollateralOutput
, txWithdrawals = info ^. #txInfoWithdrawals
Expand All @@ -2291,7 +2291,6 @@ mkApiTransactionFromInfo ti wrk wid deposit info metadataSchema = do
InLedger -> apiTx {depth = Just $ info ^. #txInfoDepth}
Expired -> apiTx
where
drop2nd (a,_,c) = (a,c)
status :: Lens' (ApiTransaction n) (Maybe ApiBlockReference)
status = case info ^. #txInfoMeta . #status of
Pending -> #pendingSince
Expand Down
7 changes: 5 additions & 2 deletions lib/wallet/bench/db-bench.hs
Expand Up @@ -586,15 +586,18 @@ mkTxHistory numTx numInputs numOutputs numAssets range =
where
sl i = SlotNo $ range !! (i `mod` length range)

mkInputs :: Int -> Int -> [(TxIn, Coin)]
mkInputs :: Int -> Int -> [(TxIn, Maybe TxOut)]
mkInputs prefix n =
[ force
( TxIn (Hash (label lbl i)) (fromIntegral i)
, Coin $ fromIntegral n
, Just $ mkTxOut n
)
| !i <- [1..n]]
where
lbl = show prefix <> "in"
mkTxOut i = TxOut
(mkAddress prefix i)
(TokenBundle.TokenBundle (Coin $ fromIntegral i) mempty)

-- | Creates transaction outputs with multi-asset token bundles.
mkOutputs :: Int -> Int -> Int -> [TxOut]
Expand Down
10 changes: 3 additions & 7 deletions lib/wallet/src/Cardano/Wallet/DB/Pure/Implementation.hs
Expand Up @@ -73,7 +73,7 @@ import Prelude
import Cardano.Pool.Types
( PoolId )
import Cardano.Wallet.Primitive.Model
( Wallet, currentTip, utxo )
( Wallet, currentTip )
import Cardano.Wallet.Primitive.Slotting
( TimeInterpreter, epochOf, interpretQuery, slotToUTCTime )
import Cardano.Wallet.Primitive.Types
Expand Down Expand Up @@ -109,8 +109,6 @@ import Cardano.Wallet.Primitive.Types.Tx
, TxMeta (..)
, TxStatus (..)
)
import Cardano.Wallet.Primitive.Types.UTxO
( UTxO (..) )
import Control.DeepSeq
( NFData )
import Control.Monad
Expand Down Expand Up @@ -484,11 +482,9 @@ mReadTxHistory ti wid minWithdrawal order range mstatus db@(Database wallets txs
, txInfoFee =
fee tx
, txInfoInputs =
(\(inp, amt) -> (inp, amt, Map.lookup inp $ unUTxO $ utxo cp))
<$> resolvedInputs tx
resolvedInputs tx
, txInfoCollateralInputs =
(\(inp, amt) -> (inp, amt, Map.lookup inp $ unUTxO $ utxo cp))
<$> resolvedCollateralInputs tx
resolvedCollateralInputs tx
, txInfoOutputs =
outputs tx
, txInfoCollateralOutput =
Expand Down
12 changes: 6 additions & 6 deletions lib/wallet/src/Cardano/Wallet/DB/Store/Transactions/Model.hs
Expand Up @@ -171,26 +171,26 @@ instance Delta DeltaTxSet where
Type conversions
From wallet types -> to database tables
-------------------------------------------------------------------------------}
mkTxIn :: TxId -> (Int, (W.TxIn, W.Coin)) -> TxIn
mkTxIn tid (ix,(txIn,amt)) =
mkTxIn :: TxId -> (Int, (W.TxIn, Maybe W.TxOut)) -> TxIn
mkTxIn tid (ix, (txIn, txOut)) =
TxIn
{ txInputTxId = tid
, txInputOrder = ix
, txInputSourceTxId = TxId (W.TxIn.inputId txIn)
, txInputSourceIndex = W.TxIn.inputIx txIn
, txInputSourceAmount = amt
, txInputSourceAmount = maybe (W.Coin 0) W.TxOut.coin txOut
}

mkTxCollateral :: TxId
-> (Int, (W.TxIn, W.Coin))
-> (Int, (W.TxIn, Maybe W.TxOut))
-> TxCollateral
mkTxCollateral tid (ix,(txCollateral,amt)) =
mkTxCollateral tid (ix, (txCollateral, txOut)) =
TxCollateral
{ txCollateralTxId = tid
, txCollateralOrder = ix
, txCollateralSourceTxId = TxId $ W.TxIn.inputId txCollateral
, txCollateralSourceIndex = W.TxIn.inputIx txCollateral
, txCollateralSourceAmount = amt
, txCollateralSourceAmount = maybe (W.Coin 0) W.TxOut.coin txOut
}

-- The key to sort TxCollateralOutToken
Expand Down
2 changes: 0 additions & 2 deletions lib/wallet/src/Cardano/Wallet/DB/Store/Wallets/Model.hs
Expand Up @@ -201,15 +201,13 @@ mkTransactionInfo ti tip TxRelation{..} decor DB.TxMeta{..} = do
{ inputId = getTxId (txInputSourceTxId tx)
, inputIx = txInputSourceIndex tx
}
, txInputSourceAmount tx
, lookupTxOutForTxIn tx decor
)
mkTxCollateral tx =
( WT.TxIn
{ inputId = getTxId (txCollateralSourceTxId tx)
, inputIx = txCollateralSourceIndex tx
}
, txCollateralSourceAmount tx
, lookupTxOutForTxCollateral tx decor
)
mkTxWithdrawal w = (txWithdrawalAccount w, txWithdrawalAmount w)
Expand Down
6 changes: 3 additions & 3 deletions lib/wallet/src/Cardano/Wallet/Primitive/Model.hs
Expand Up @@ -435,9 +435,9 @@ availableUTxO pending (Wallet u _ _) = u `excluding` used
-- UTxO which have been spent or committed as collateral in a pending
-- transaction are not available to use in future transactions.
getUsedTxIn :: Tx -> Set TxIn
getUsedTxIn tx = Set.fromList $ fst <$> mconcat
[ tx ^. #resolvedInputs
, tx ^. #resolvedCollateralInputs
getUsedTxIn tx = Set.fromList $ mconcat
[ fst <$> tx ^. #resolvedInputs
, fst <$> tx ^. #resolvedCollateralInputs
]

-- | Computes the total 'UTxO' set of a wallet.
Expand Down
12 changes: 6 additions & 6 deletions lib/wallet/src/Cardano/Wallet/Primitive/Types/Tx/Gen.hs
Expand Up @@ -73,8 +73,8 @@ shrinkTx = shrinkMapBy txWithoutIdToTx txToTxWithoutId shrinkTxWithoutId

data TxWithoutId = TxWithoutId
{ fee :: !(Maybe Coin)
, resolvedInputs :: ![(TxIn, Coin)]
, resolvedCollateralInputs :: ![(TxIn, Coin)]
, resolvedInputs :: ![(TxIn, Maybe TxOut)]
, resolvedCollateralInputs :: ![(TxIn, Maybe TxOut)]
, outputs :: ![TxOut]
, collateralOutput :: !(Maybe TxOut)
, metadata :: !(Maybe TxMetadata)
Expand All @@ -86,8 +86,8 @@ data TxWithoutId = TxWithoutId
genTxWithoutId :: Gen TxWithoutId
genTxWithoutId = TxWithoutId
<$> liftArbitrary genCoinPositive
<*> listOf1 (liftArbitrary2 genTxIn genCoinPositive)
<*> listOf1 (liftArbitrary2 genTxIn genCoinPositive)
<*> listOf1 (liftArbitrary2 genTxIn (pure Nothing))
<*> listOf1 (liftArbitrary2 genTxIn (pure Nothing))
<*> listOf genTxOut
<*> liftArbitrary genTxOut
<*> liftArbitrary genNestedTxMetadata
Expand All @@ -97,8 +97,8 @@ genTxWithoutId = TxWithoutId
shrinkTxWithoutId :: TxWithoutId -> [TxWithoutId]
shrinkTxWithoutId = genericRoundRobinShrink
<@> liftShrink shrinkCoinPositive
<:> shrinkList (liftShrink2 shrinkTxIn shrinkCoinPositive)
<:> shrinkList (liftShrink2 shrinkTxIn shrinkCoinPositive)
<:> shrinkList (liftShrink2 shrinkTxIn (liftShrink shrinkTxOut))
<:> shrinkList (liftShrink2 shrinkTxIn (liftShrink shrinkTxOut))
<:> shrinkList shrinkTxOut
<:> liftShrink shrinkTxOut
<:> liftShrink shrinkTxMetadata
Expand Down
Expand Up @@ -60,10 +60,10 @@ data TransactionInfo = TransactionInfo
-- ^ Serialization of this transaction
, txInfoFee :: Maybe Coin
-- ^ Explicit transaction fee
, txInfoInputs :: [(TxIn, Coin, Maybe TxOut)]
, txInfoInputs :: [(TxIn, Maybe TxOut)]
-- ^ Transaction inputs and (maybe) corresponding outputs of the
-- source. Source information can only be provided for outgoing payments.
, txInfoCollateralInputs :: [(TxIn, Coin, Maybe TxOut)]
, txInfoCollateralInputs :: [(TxIn, Maybe TxOut)]
-- ^ Collateral inputs and (maybe) corresponding outputs.
, txInfoOutputs :: [TxOut]
-- ^ Payment destination.
Expand All @@ -87,26 +87,21 @@ data TransactionInfo = TransactionInfo

instance NFData TransactionInfo

-- | Reconstruct a transaction info from a transaction.
-- | Reconstruct a transaction from a transaction info.
fromTransactionInfo :: TransactionInfo -> Tx
fromTransactionInfo info = Tx
{ txId = txInfoId info
, txCBOR = txInfoCBOR info
, fee = txInfoFee info
, resolvedInputs = drop3rd <$> txInfoInputs info
, resolvedCollateralInputs = drop3rd <$> txInfoCollateralInputs info
, resolvedInputs = txInfoInputs info
, resolvedCollateralInputs = txInfoCollateralInputs info
, outputs = txInfoOutputs info
, collateralOutput = txInfoCollateralOutput info
, withdrawals = txInfoWithdrawals info
, metadata = txInfoMetadata info
, scriptValidity = txInfoScriptValidity info
}
where
drop3rd :: (a, b, c) -> (a, b)
drop3rd (a, b, _) = (a, b)


-- | Drop time-specific information
toTxHistory :: TransactionInfo -> (Tx, TxMeta)
toTxHistory info =
(fromTransactionInfo info, txInfoMeta info)
toTxHistory info = (fromTransactionInfo info, txInfoMeta info)
4 changes: 2 additions & 2 deletions lib/wallet/src/Cardano/Wallet/Primitive/Types/Tx/Tx.hs
Expand Up @@ -107,13 +107,13 @@ data Tx = Tx
-- easily be re-computed from the delta between outputs and inputs.

, resolvedInputs
:: ![(TxIn, Coin)]
:: ![(TxIn, Maybe TxOut)]
-- ^ NOTE: Order of inputs matters in the transaction representation.
-- The transaction id is computed from the binary representation of a
-- tx, for which inputs are serialized in a specific order.

, resolvedCollateralInputs
:: ![(TxIn, Coin)]
:: ![(TxIn, Maybe TxOut)]
-- ^ NOTE: The order of collateral inputs matters in the transaction
-- representation. The transaction id is computed from the binary
-- representation of a tx, for which collateral inputs are serialized
Expand Down
13 changes: 8 additions & 5 deletions lib/wallet/src/Cardano/Wallet/Primitive/Types/Tx/TxSeq.hs
Expand Up @@ -111,7 +111,7 @@ import Prelude hiding
import Cardano.Wallet.Primitive.Model
( applyTxToUTxO )
import Cardano.Wallet.Primitive.Types.Coin
( Coin )
( Coin (..) )
import Cardano.Wallet.Primitive.Types.Hash
( Hash (..) )
import Cardano.Wallet.Primitive.Types.StateDeltaSeq
Expand All @@ -124,6 +124,8 @@ import Cardano.Wallet.Primitive.Types.Tx
( Tx (..), txAssetIds, txMapAssetIds, txMapTxIds, txRemoveAssetId )
import Cardano.Wallet.Primitive.Types.Tx.TxIn
( TxIn )
import Cardano.Wallet.Primitive.Types.Tx.TxOut
( TxOut )
import Cardano.Wallet.Primitive.Types.UTxO
( UTxO )
import Data.Bifoldable
Expand Down Expand Up @@ -528,10 +530,11 @@ canApplyTxToUTxO tx u = (&&)
(all inputRefIsValid (Tx.resolvedInputs tx))
(all inputRefIsValid (Tx.resolvedCollateralInputs tx))
where
inputRefIsValid :: (TxIn, Coin) -> Bool
inputRefIsValid (ti, c) = case UTxO.lookup ti u of
Nothing -> False
Just to -> TxOut.coin to == c
inputRefIsValid :: (TxIn, Maybe TxOut) -> Bool
inputRefIsValid (ti, c) =
case UTxO.lookup ti u of
Nothing -> False
Just c' -> TxOut.coin c' == maybe (Coin 0) TxOut.coin c

safeAppendTx :: MonadFail m => UTxO -> Tx -> m UTxO
safeAppendTx = flip safeApplyTxToUTxO
Expand Down
12 changes: 4 additions & 8 deletions lib/wallet/src/Cardano/Wallet/Primitive/Types/Tx/TxSeq/Gen.hs
Expand Up @@ -317,14 +317,10 @@ genTxFromUTxO genAddr u = do
, Just TxScriptInvalid
]
pure $ txWithoutIdToTx TxWithoutId
{ fee =
Just feeCoin
, resolvedInputs =
fmap (TokenBundle.getCoin . tokens) <$> inputs
, resolvedCollateralInputs =
fmap (TokenBundle.getCoin . tokens) <$> collateralInputs
, outputs =
zipWith TxOut outputAddresses outputBundles
{ fee = Just feeCoin
, resolvedInputs = fmap Just <$> inputs
, resolvedCollateralInputs = fmap Just <$> collateralInputs
, outputs = zipWith TxOut outputAddresses outputBundles
, collateralOutput = listToMaybe $
zipWith TxOut collateralOutputAddresses collateralOutputBundles
, metadata = Nothing
Expand Down
3 changes: 1 addition & 2 deletions lib/wallet/src/Cardano/Wallet/Read/Primitive/Tx/Allegra.hs
Expand Up @@ -65,7 +65,6 @@ import qualified Cardano.Ledger.Shelley.Tx as SL
import qualified Cardano.Ledger.ShelleyMA.AuxiliaryData as MA
import qualified Cardano.Ledger.ShelleyMA.TxBody as MA
import qualified Cardano.Wallet.Primitive.Types as W
import qualified Cardano.Wallet.Primitive.Types.Coin as W
import qualified Cardano.Wallet.Primitive.Types.Hash as W
import qualified Cardano.Wallet.Primitive.Types.Tx as W
import qualified Data.Map.Strict as Map
Expand All @@ -91,7 +90,7 @@ fromAllegraTx tx =
, fee =
Just $ fromShelleyCoin fee
, resolvedInputs =
map ((,W.Coin 0) . fromShelleyTxIn) (toList ins)
map ((,Nothing) . fromShelleyTxIn) (toList ins)
, resolvedCollateralInputs =
-- TODO: (ADP-957)
[]
Expand Down
5 changes: 2 additions & 3 deletions lib/wallet/src/Cardano/Wallet/Read/Primitive/Tx/Alonzo.hs
Expand Up @@ -77,7 +77,6 @@ import qualified Cardano.Ledger.Core as SL.Core
import qualified Cardano.Ledger.Mary.Value as SL
import qualified Cardano.Ledger.Shelley.API as SL
import qualified Cardano.Wallet.Primitive.Types as W
import qualified Cardano.Wallet.Primitive.Types.Coin as W
import qualified Cardano.Wallet.Primitive.Types.Hash as W
import qualified Cardano.Wallet.Primitive.Types.Tx as W
import qualified Cardano.Wallet.Primitive.Types.Tx.TxOut as W
Expand All @@ -104,9 +103,9 @@ fromAlonzoTx tx@(Alonzo.ValidatedTx bod wits (Alonzo.IsValid isValid) aux) witCt
, fee =
Just $ fromShelleyCoin fee
, resolvedInputs =
map ((,W.Coin 0) . fromShelleyTxIn) (toList ins)
map ((,Nothing) . fromShelleyTxIn) (toList ins)
, resolvedCollateralInputs =
map ((,W.Coin 0) . fromShelleyTxIn) (toList collateral)
map ((,Nothing) . fromShelleyTxIn) (toList collateral)
, outputs =
map fromAlonzoTxOut (toList outs)
, collateralOutput =
Expand Down
5 changes: 2 additions & 3 deletions lib/wallet/src/Cardano/Wallet/Read/Primitive/Tx/Babbage.hs
Expand Up @@ -80,7 +80,6 @@ import qualified Cardano.Ledger.Core as SL.Core
import qualified Cardano.Ledger.Mary.Value as SL
import qualified Cardano.Ledger.Shelley.API as SL
import qualified Cardano.Wallet.Primitive.Types as W
import qualified Cardano.Wallet.Primitive.Types.Coin as W
import qualified Cardano.Wallet.Primitive.Types.Hash as W
import qualified Cardano.Wallet.Primitive.Types.Tx as W
import qualified Cardano.Wallet.Primitive.Types.Tx.TxOut as W
Expand All @@ -107,9 +106,9 @@ fromBabbageTx tx@(Alonzo.ValidatedTx bod wits (Alonzo.IsValid isValid) aux) witC
, fee =
Just $ fromShelleyCoin fee
, resolvedInputs =
map ((,W.Coin 0) . fromShelleyTxIn) (toList inps)
map ((,Nothing) . fromShelleyTxIn) (toList inps)
, resolvedCollateralInputs =
map ((,W.Coin 0) . fromShelleyTxIn) (toList collateralInps)
map ((,Nothing) . fromShelleyTxIn) (toList collateralInps)
, outputs =
map (fromBabbageTxOut . sizedValue) (toList outs)
, collateralOutput =
Expand Down
3 changes: 1 addition & 2 deletions lib/wallet/src/Cardano/Wallet/Read/Primitive/Tx/Byron.hs
Expand Up @@ -35,7 +35,6 @@ import Control.Monad
import qualified Cardano.Crypto.Hashing as CC
import qualified Cardano.Wallet.Primitive.Types.Address as W
import qualified Cardano.Wallet.Primitive.Types.Coin as Coin
import qualified Cardano.Wallet.Primitive.Types.Coin as W
import qualified Cardano.Wallet.Primitive.Types.Hash as W
import qualified Cardano.Wallet.Primitive.Types.TokenBundle as TokenBundle
import qualified Cardano.Wallet.Primitive.Types.Tx as W
Expand All @@ -58,7 +57,7 @@ fromTxAux txAux = case taTx txAux of

-- TODO: Review 'W.Tx' to not require resolved inputs but only inputs
, resolvedInputs =
(, W.Coin 0) . fromTxIn <$> NE.toList inputs
(, Nothing) . fromTxIn <$> NE.toList inputs

, resolvedCollateralInputs = []

Expand Down
2 changes: 1 addition & 1 deletion lib/wallet/src/Cardano/Wallet/Read/Primitive/Tx/Mary.hs
Expand Up @@ -105,7 +105,7 @@ fromMaryTx tx witCtx =
, fee =
Just $ fromShelleyCoin fee
, resolvedInputs =
map ((,W.Coin 0) . fromShelleyTxIn) (toList ins)
map ((,Nothing) . fromShelleyTxIn) (toList ins)
, resolvedCollateralInputs =
[]
, outputs =
Expand Down
2 changes: 1 addition & 1 deletion lib/wallet/src/Cardano/Wallet/Read/Primitive/Tx/Shelley.hs
Expand Up @@ -137,7 +137,7 @@ fromShelleyTx tx =
, fee =
Just $ fromShelleyCoin fee
, resolvedInputs =
map ((,W.Coin 0) . fromShelleyTxIn) (toList ins)
(,Nothing) . fromShelleyTxIn <$> toList ins
, resolvedCollateralInputs =
[]
, outputs =
Expand Down
2 changes: 1 addition & 1 deletion lib/wallet/src/Cardano/Wallet/Shelley/Transaction.hs
Expand Up @@ -424,7 +424,7 @@ mkTx networkId payload ttl (rewardAcnt, pwdAcnt) addrResolver wdrl cs fees era =
addrResolver inputResolver (unsigned, mkExtraWits unsigned)

let withResolvedInputs (tx, _, _, _, _, _) = tx
{ resolvedInputs = second TxOut.coin <$> F.toList (view #inputs cs)
{ resolvedInputs = second Just <$> F.toList (view #inputs cs)
}
Right ( withResolvedInputs (fromCardanoTx AnyWitnessCountCtx signed)
, sealedTxFromCardano' signed
Expand Down

0 comments on commit 7b2a479

Please sign in to comment.