@@ -432,6 +432,8 @@ import Cardano.Api.Internal.SerialiseJSON
432432import Cardano.Api.Internal.Tx.BuildTxWith
433433import Cardano.Api.Internal.Tx.Output
434434import Cardano.Api.Internal.Tx.Sign
435+ import Cardano.Api.Internal.Tx.UTxO (UTxO )
436+ import Cardano.Api.Internal.Tx.UTxO qualified as UTxO
435437import Cardano.Api.Internal.TxIn
436438import Cardano.Api.Internal.TxMetadata
437439import Cardano.Api.Internal.Utils
@@ -476,6 +478,7 @@ import Ouroboros.Consensus.Shelley.Eras qualified as E
476478 , ShelleyEra
477479 )
478480
481+ import Control.Applicative
479482import Control.Monad
480483import Data.Aeson (object , (.=) )
481484import Data.Aeson qualified as Aeson
@@ -575,6 +578,10 @@ data TxInsReference era where
575578 TxInsReference
576579 :: BabbageEraOnwards era
577580 -> [TxIn ]
581+ -- ^ A list of reference inputs
582+ -> Set HashableScriptData
583+ -- ^ A set of datums, which hashes are referenced in UTXO of reference inputs. Those datums will be inserted
584+ -- to the datum map available to the scripts.
578585 -> TxInsReference era
579586
580587deriving instance Eq (TxInsReference era )
@@ -1083,17 +1090,18 @@ modTxInsReference
10831090modTxInsReference f txBodyContent = txBodyContent{txInsReference = f (txInsReference txBodyContent)}
10841091
10851092addTxInsReference
1086- :: IsBabbageBasedEra era => [TxIn ] -> TxBodyContent build era -> TxBodyContent build era
1087- addTxInsReference txInsReference =
1093+ :: IsBabbageBasedEra era
1094+ => [TxIn ] -> Set HashableScriptData -> TxBodyContent build era -> TxBodyContent build era
1095+ addTxInsReference txInsReference scriptData =
10881096 modTxInsReference
10891097 ( \ case
1090- TxInsReferenceNone -> TxInsReference babbageBasedEra txInsReference
1091- TxInsReference era xs -> TxInsReference era (xs <> txInsReference)
1098+ TxInsReferenceNone -> TxInsReference babbageBasedEra txInsReference scriptData
1099+ TxInsReference era xs scriptData' -> TxInsReference era (xs <> txInsReference) (scriptData' <> scriptData )
10921100 )
10931101
10941102addTxInReference
10951103 :: IsBabbageBasedEra era => TxIn -> TxBodyContent build era -> TxBodyContent build era
1096- addTxInReference txInReference = addTxInsReference [txInReference]
1104+ addTxInReference txInReference = addTxInsReference [txInReference] mempty
10971105
10981106setTxOuts :: [TxOut CtxTx era ] -> TxBodyContent build era -> TxBodyContent build era
10991107setTxOuts v txBodyContent = txBodyContent{txOuts = v}
@@ -1366,13 +1374,20 @@ instance Error TxBodyError where
13661374 TxBodyProtocolParamsConversionError ppces ->
13671375 " Errors in protocol parameters conversion: " <> prettyError ppces
13681376
1377+ -- TxIn
1378+ -- -> (TxIn -> UTXO -> Hash ScriptData)
1379+ -- -> (Hash ScriptData -> HashableScriptData)
1380+ -- -> HashableScriptData
1381+
13691382createTransactionBody
13701383 :: forall era
13711384 . HasCallStack
13721385 => ShelleyBasedEra era
1386+ -> UTxO era
1387+ -- ^ UTXO for reference inputs
13731388 -> TxBodyContent BuildTx era
13741389 -> Either TxBodyError (TxBody era )
1375- createTransactionBody sbe bc =
1390+ createTransactionBody sbe utxo bc =
13761391 shelleyBasedEraConstraints sbe $ do
13771392 (sData, mScriptIntegrityHash, scripts) <-
13781393 caseShelleyToMaryOrAlonzoEraOnwards
@@ -1387,7 +1402,7 @@ createTransactionBody sbe bc =
13871402 )
13881403 ( \ aeon -> do
13891404 TxScriptWitnessRequirements languages scripts dats redeemers <-
1390- collectTxBodyScriptWitnessRequirements aeon bc
1405+ collectTxBodyScriptWitnessRequirements aeon utxo bc
13911406
13921407 let pparams = txProtocolParams bc
13931408 sData = TxBodyScriptData aeon dats redeemers
@@ -1746,7 +1761,7 @@ fromLedgerTxInsReference
17461761fromLedgerTxInsReference sbe txBody =
17471762 caseShelleyToAlonzoOrBabbageEraOnwards
17481763 (const TxInsReferenceNone )
1749- (\ w -> TxInsReference w $ map fromShelleyTxIn . toList $ txBody ^. L. referenceInputsTxBodyL)
1764+ (\ w -> TxInsReference w ( map fromShelleyTxIn . toList $ txBody ^. L. referenceInputsTxBodyL) mempty )
17501765 sbe
17511766
17521767fromLedgerTxTotalCollateral
@@ -2108,11 +2123,11 @@ convPParamsToScriptIntegrityHash
21082123 -> Alonzo. TxDats (ShelleyLedgerEra era )
21092124 -> Set Plutus. Language
21102125 -> StrictMaybe L. ScriptIntegrityHash
2111- convPParamsToScriptIntegrityHash w txProtocolParams redeemers datums languages =
2126+ convPParamsToScriptIntegrityHash w ( BuildTxWith mTxProtocolParams) redeemers datums languages =
21122127 alonzoEraOnwardsConstraints w $
2113- case txProtocolParams of
2114- BuildTxWith Nothing -> SNothing
2115- BuildTxWith ( Just (LedgerProtocolParameters pp) ) ->
2128+ case mTxProtocolParams of
2129+ Nothing -> SNothing
2130+ Just (LedgerProtocolParameters pp) ->
21162131 Alonzo. hashScriptIntegrity (Set. map (L. getLanguageView pp) languages) redeemers datums
21172132
21182133convLanguages :: [(ScriptWitnessIndex , AnyScriptWitness era )] -> Set Plutus. Language
@@ -2126,7 +2141,7 @@ convReferenceInputs :: TxInsReference era -> Set Ledger.TxIn
21262141convReferenceInputs txInsReference =
21272142 case txInsReference of
21282143 TxInsReferenceNone -> mempty
2129- TxInsReference _ refTxins -> fromList $ map toShelleyTxIn refTxins
2144+ TxInsReference _ refTxins _ -> fromList $ map toShelleyTxIn refTxins
21302145
21312146-- | Returns an OSet of proposals from 'TxProposalProcedures'.
21322147convProposalProcedures
@@ -2986,18 +3001,27 @@ collectTxBodyScriptWitnessRequirements
29863001 :: forall era
29873002 . IsShelleyBasedEra era
29883003 => AlonzoEraOnwards era
3004+ -> UTxO era
3005+ -- ^ UTXO for reference inputs
29893006 -> TxBodyContent BuildTx era
29903007 -> Either
29913008 TxBodyError
29923009 (TxScriptWitnessRequirements (ShelleyLedgerEra era ))
29933010collectTxBodyScriptWitnessRequirements
29943011 aEon
3012+ utxo
29953013 bc@ TxBodyContent
2996- { txOuts
3014+ { txInsReference
3015+ , txOuts
29973016 } =
29983017 obtainAlonzoScriptPurposeConstraints aEon $ do
29993018 let sbe = shelleyBasedEra @ era
3000- supplementaldatums = TxScriptWitnessRequirements mempty mempty (getSupplementalDatums aEon txOuts) mempty
3019+ supplementaldatums =
3020+ TxScriptWitnessRequirements
3021+ mempty
3022+ mempty
3023+ (getSupplementalDatums aEon txInsReference utxo txOuts)
3024+ mempty
30013025 txInWits <-
30023026 first TxBodyPlutusScriptDecodeError $
30033027 legacyWitnessToScriptRequirements aEon $
@@ -3053,17 +3077,30 @@ collectTxBodyScriptWitnessRequirements
30533077
30543078getSupplementalDatums
30553079 :: AlonzoEraOnwards era
3080+ -> TxInsReference era
3081+ -- ^ reference inputs
3082+ -> UTxO era
3083+ -- ^ UTxO for reference inputs
30563084 -> [TxOut CtxTx era ]
30573085 -> L. TxDats (ShelleyLedgerEra era )
3058- getSupplementalDatums eon [] = alonzoEraOnwardsConstraints eon mempty
3059- getSupplementalDatums eon txouts =
3060- alonzoEraOnwardsConstraints eon $
3061- L. TxDats $
3062- fromList
3063- [ (L. hashData ledgerData, ledgerData)
3064- | TxOut _ _ (TxOutSupplementalDatum _ d) _ <- txouts
3065- , let ledgerData = toAlonzoData d
3086+ getSupplementalDatums eon txInsRef utxo txOutsFromTx = alonzoEraOnwardsConstraints eon $ do
3087+ let refTxInsDats =
3088+ [ d
3089+ | TxInsReference _ txIns datumSet <- [txInsRef]
3090+ , let datumMap = fromList $ map (\ h -> (hashScriptDataBytes h, h)) $ toList datumSet
3091+ , txIn <- txIns
3092+ , -- resolve only hashes
3093+ TxOut _ _ (TxOutDatumHash _ datumHash) _ <- maybeToList $ UTxO. lookup txIn utxo
3094+ , d <- maybeToList $ Map. lookup datumHash datumMap
30663095 ]
3096+ -- use only supplemental datum
3097+ txOutsDats = [d | TxOut _ _ (TxOutSupplementalDatum _ d) _ <- txOutsFromTx]
3098+ L. TxDats $
3099+ fromList $
3100+ [ (L. hashData ledgerData, ledgerData)
3101+ | d <- refTxInsDats <> txOutsDats
3102+ , let ledgerData = toAlonzoData d
3103+ ]
30673104
30683105extractWitnessableTxIns
30693106 :: AlonzoEraOnwards era
0 commit comments