44{-# LANGUAGE FlexibleInstances #-}
55{-# LANGUAGE GADTs #-}
66{-# LANGUAGE LambdaCase #-}
7+ {-# LANGUAGE MultiWayIf #-}
78{-# LANGUAGE NamedFieldPuns #-}
89{-# LANGUAGE RankNTypes #-}
910{-# LANGUAGE ScopedTypeVariables #-}
@@ -357,6 +358,7 @@ import Cardano.Api.Internal.Plutus
357358import Cardano.Api.Internal.Pretty
358359import Cardano.Api.Internal.ProtocolParameters
359360import Cardano.Api.Internal.Query
361+ import Cardano.Api.Internal.ReexposeLedger qualified as L
360362import Cardano.Api.Internal.Script
361363import Cardano.Api.Internal.Tx.Body
362364import Cardano.Api.Internal.Tx.Sign
@@ -370,8 +372,8 @@ import Cardano.Ledger.Alonzo.Scripts qualified as Alonzo
370372import Cardano.Ledger.Api qualified as L
371373import Cardano.Ledger.Coin qualified as L
372374import Cardano.Ledger.Conway.Governance qualified as L
373- import Cardano.Ledger.Core qualified as L
374375import Cardano.Ledger.Credential as Ledger (Credential )
376+ import Cardano.Ledger.Mary.Value qualified as L
375377import Cardano.Ledger.Plutus.Language qualified as Plutus
376378import Cardano.Ledger.Val qualified as L
377379import Ouroboros.Consensus.HardFork.History qualified as Consensus
@@ -395,6 +397,7 @@ import Data.Text (Text)
395397import GHC.Exts (IsList (.. ))
396398import GHC.Stack
397399import Lens.Micro ((.~) , (^.) )
400+ import Prettyprinter (punctuate )
398401
399402-- | Type synonym for logs returned by the ledger's @evalTxExUnitsWithLogs@ function.
400403-- for scripts in transactions.
@@ -639,9 +642,10 @@ estimateBalancedTxBody
639642 let fakeUTxO = createFakeUTxO sbe txbodycontent1 $ selectLovelace availableUTxOValue
640643 balance =
641644 evaluateTransactionBalance sbe pparams poolids stakeDelegDeposits drepDelegDeposits fakeUTxO txbody2
645+ balanceTxOut = TxOut changeaddr balance TxOutDatumNone ReferenceScriptNone
642646 -- check if the balance is positive or negative
643647 -- in one case we can produce change, in the other the inputs are insufficient
644- first TxFeeEstimationBalanceError $ balanceCheck sbe pparams changeaddr balance
648+ first TxFeeEstimationBalanceError $ balanceCheck sbe pparams balanceTxOut
645649
646650 -- Step 6. Check all txouts have the min required UTxO value
647651 forM_ (txOuts txbodycontent1) $
@@ -659,7 +663,7 @@ estimateBalancedTxBody
659663 { txFee = TxFeeExplicit sbe fee
660664 , txOuts =
661665 accountForNoChange
662- ( TxOut changeaddr balance TxOutDatumNone ReferenceScriptNone )
666+ balanceTxOut
663667 (txOuts txbodycontent)
664668 , txReturnCollateral = retColl
665669 , txTotalCollateral = reqCol
@@ -673,7 +677,7 @@ estimateBalancedTxBody
673677 ( BalancedTxBody
674678 finalTxBodyContent
675679 txbody3
676- ( TxOut changeaddr balance TxOutDatumNone ReferenceScriptNone )
680+ balanceTxOut
677681 fee
678682 )
679683
@@ -990,9 +994,7 @@ evaluateTransactionExecutionUnits
990994 -> LedgerProtocolParameters era
991995 -> UTxO era
992996 -> TxBody era
993- -> Either
994- (TransactionValidityError era )
995- (Map ScriptWitnessIndex (Either ScriptExecutionError (EvalTxExecutionUnitsLog , ExecutionUnits )))
997+ -> Map ScriptWitnessIndex (Either ScriptExecutionError (EvalTxExecutionUnitsLog , ExecutionUnits ))
996998evaluateTransactionExecutionUnits era systemstart epochInfo pp utxo txbody =
997999 case makeSignedTransaction' era [] txbody of
9981000 ShelleyTx sbe tx' -> evaluateTransactionExecutionUnitsShelley sbe systemstart epochInfo pp utxo tx'
@@ -1006,14 +1008,12 @@ evaluateTransactionExecutionUnitsShelley
10061008 -> LedgerProtocolParameters era
10071009 -> UTxO era
10081010 -> L. Tx (ShelleyLedgerEra era )
1009- -> Either
1010- (TransactionValidityError era )
1011- (Map ScriptWitnessIndex (Either ScriptExecutionError (EvalTxExecutionUnitsLog , ExecutionUnits )))
1011+ -> Map ScriptWitnessIndex (Either ScriptExecutionError (EvalTxExecutionUnitsLog , ExecutionUnits ))
10121012evaluateTransactionExecutionUnitsShelley sbe systemstart epochInfo (LedgerProtocolParameters pp) utxo tx =
10131013 caseShelleyToMaryOrAlonzoEraOnwards
1014- (const ( Right Map. empty) )
1014+ (const Map. empty)
10151015 ( \ w ->
1016- pure . fromLedgerScriptExUnitsMap w $
1016+ fromLedgerScriptExUnitsMap w $
10171017 alonzoEraOnwardsConstraints w $
10181018 L. evalTxExUnitsWithLogs pp tx (toLedgerUTxO sbe utxo) ledgerEpochInfo systemstart
10191019 )
@@ -1147,37 +1147,32 @@ data TxBodyErrorAutoBalance era
11471147 TxBodyScriptExecutionError [(ScriptWitnessIndex , ScriptExecutionError )]
11481148 | -- | One or more scripts were expected to fail validation, but none did.
11491149 TxBodyScriptBadScriptValidity
1150- | -- | There is not enough ada to cover both the outputs and the fees.
1151- -- The transaction should be changed to provide more input ada , or
1150+ | -- | There is not enough ada and non-ada to cover both the outputs and the fees.
1151+ -- The transaction should be changed to provide more input assets , or
11521152 -- otherwise adjusted to need less (e.g. outputs, script etc).
1153- TxBodyErrorAdaBalanceNegative L. Coin
1153+ TxBodyErrorBalanceNegative L. Coin L. MultiAsset
11541154 | -- | There is enough ada to cover both the outputs and the fees, but the
11551155 -- resulting change is too small: it is under the minimum value for
11561156 -- new UTXO entries. The transaction should be changed to provide more
11571157 -- input ada.
11581158 TxBodyErrorAdaBalanceTooSmall
1159- -- \^ Offending TxOut
1160-
11611159 TxOutInAnyEra
1160+ -- ^ Offending TxOut
1161+ L. Coin
11621162 -- ^ Minimum UTxO
11631163 L. Coin
11641164 -- ^ Tx balance
1165- L. Coin
11661165 | -- | 'makeTransactionBodyAutoBalance' does not yet support the Byron era.
11671166 TxBodyErrorByronEraNotSupported
11681167 | -- | The 'ProtocolParameters' must provide the value for the min utxo
11691168 -- parameter, for eras that use this parameter.
11701169 TxBodyErrorMissingParamMinUTxO
1171- | -- | The transaction validity interval is too far into the future.
1172- -- See 'TransactionValidityIntervalError' for details.
1173- TxBodyErrorValidityInterval (TransactionValidityError era )
11741170 | -- | The minimum spendable UTxO threshold has not been met.
11751171 TxBodyErrorMinUTxONotMet
1176- -- \^ Offending TxOut
1177-
11781172 TxOutInAnyEra
1179- -- ^ Minimum UTXO
1173+ -- ^ Offending TxOut
11801174 L. Coin
1175+ -- ^ Minimum UTXO
11811176 | TxBodyErrorNonAdaAssetsUnbalanced Value
11821177 | TxBodyErrorScriptWitnessIndexMissingFromExecUnitsMap
11831178 ScriptWitnessIndex
@@ -1201,12 +1196,14 @@ instance Error (TxBodyErrorAutoBalance era) where
12011196 ]
12021197 TxBodyScriptBadScriptValidity ->
12031198 " One or more of the scripts were expected to fail validation, but none did."
1204- TxBodyErrorAdaBalanceNegative lovelace ->
1205- mconcat
1206- [ " The transaction does not balance in its use of ada. The net balance "
1207- , " of the transaction is negative: " <> pretty lovelace <> " . "
1208- , " The usual solution is to provide more inputs, or inputs with more ada."
1199+ TxBodyErrorBalanceNegative lovelace assets ->
1200+ mconcat $
1201+ [ " The transaction does not balance in its use of assets. The net balance "
1202+ , " of the transaction is negative: "
12091203 ]
1204+ <> punctuate " , " [pretty lovelace, pretty assets]
1205+ <> [ " . The usual solution is to provide more inputs, or inputs with more assets."
1206+ ]
12101207 TxBodyErrorAdaBalanceTooSmall changeOutput minUTxO balance ->
12111208 mconcat
12121209 [ " The transaction does balance in its use of ada, however the net "
@@ -1221,8 +1218,6 @@ instance Error (TxBodyErrorAutoBalance era) where
12211218 " The Byron era is not yet supported by makeTransactionBodyAutoBalance"
12221219 TxBodyErrorMissingParamMinUTxO ->
12231220 " The minUTxOValue protocol parameter is required but missing"
1224- TxBodyErrorValidityInterval err ->
1225- prettyError err
12261221 TxBodyErrorMinUTxONotMet txout minUTxO ->
12271222 mconcat
12281223 [ " Minimum UTxO threshold not met for tx output: " <> pretty (prettyRenderTxOut txout) <> " \n "
@@ -1365,8 +1360,16 @@ makeTransactionBodyAutoBalance
13651360 -- 4. balance the transaction and update tx change output
13661361
13671362 txbodyForChange <- first TxBodyError $ createTransactionBody sbe txbodycontent
1368- let initialChangeTxOut =
1363+ let initialChangeTxOutValue =
13691364 evaluateTransactionBalance sbe pp poolids stakeDelegDeposits drepDelegDeposits utxo txbodyForChange
1365+ initialChangeTxOut =
1366+ TxOut
1367+ changeaddr
1368+ initialChangeTxOutValue
1369+ TxOutDatumNone
1370+ ReferenceScriptNone
1371+
1372+ balanceCheck sbe pp initialChangeTxOut
13701373
13711374 -- Tx body used only for evaluating execution units. Because txout exact
13721375 -- values do not matter much here, we are using an initial change value,
@@ -1378,16 +1381,15 @@ makeTransactionBodyAutoBalance
13781381 sbe
13791382 $ txbodycontent
13801383 & modTxOuts
1381- (<> [TxOut changeaddr initialChangeTxOut TxOutDatumNone ReferenceScriptNone ])
1382- exUnitsMapWithLogs <-
1383- first TxBodyErrorValidityInterval $
1384- evaluateTransactionExecutionUnits
1385- era
1386- systemstart
1387- history
1388- lpp
1389- utxo
1390- txbody
1384+ (<> [initialChangeTxOut])
1385+ let exUnitsMapWithLogs =
1386+ evaluateTransactionExecutionUnits
1387+ era
1388+ systemstart
1389+ history
1390+ lpp
1391+ utxo
1392+ txbody
13911393
13921394 let exUnitsMap = Map. map (fmap snd ) exUnitsMapWithLogs
13931395
@@ -1419,7 +1421,7 @@ makeTransactionBodyAutoBalance
14191421 { txFee = TxFeeExplicit sbe maxLovelaceFee
14201422 , txOuts =
14211423 txOuts txbodycontent
1422- <> [TxOut changeaddr initialChangeTxOut TxOutDatumNone ReferenceScriptNone ]
1424+ <> [initialChangeTxOut]
14231425 , txReturnCollateral = dummyCollRet
14241426 , txTotalCollateral = dummyTotColl
14251427 }
@@ -1468,11 +1470,12 @@ makeTransactionBodyAutoBalance
14681470 , txTotalCollateral = reqCol
14691471 }
14701472 let balance = evaluateTransactionBalance sbe pp poolids stakeDelegDeposits drepDelegDeposits utxo txbody2
1473+ balanceTxOut = TxOut changeaddr balance TxOutDatumNone ReferenceScriptNone
14711474 forM_ (txOuts txbodycontent1) $ \ txout -> checkMinUTxOValue sbe txout pp
14721475
14731476 -- check if the balance is positive or negative
14741477 -- in one case we can produce change, in the other the inputs are insufficient
1475- balanceCheck sbe pp changeaddr balance
1478+ balanceCheck sbe pp balanceTxOut
14761479
14771480 -- TODO: we could add the extra fee for the CBOR encoding of the change,
14781481 -- now that we know the magnitude of the change: i.e. 1-8 bytes extra.
@@ -1486,7 +1489,7 @@ makeTransactionBodyAutoBalance
14861489 { txFee = TxFeeExplicit sbe fee
14871490 , txOuts =
14881491 accountForNoChange
1489- ( TxOut changeaddr balance TxOutDatumNone ReferenceScriptNone )
1492+ balanceTxOut
14901493 (txOuts txbodycontent)
14911494 , txReturnCollateral = retColl
14921495 , txTotalCollateral = reqCol
@@ -1500,7 +1503,7 @@ makeTransactionBodyAutoBalance
15001503 ( BalancedTxBody
15011504 finalTxBodyContent
15021505 txbody3
1503- ( TxOut changeaddr balance TxOutDatumNone ReferenceScriptNone )
1506+ balanceTxOut
15041507 fee
15051508 )
15061509 where
@@ -1534,26 +1537,20 @@ checkMinUTxOValue sbe txout@(TxOut _ v _ _) bpp = do
15341537balanceCheck
15351538 :: ShelleyBasedEra era
15361539 -> Ledger. PParams (ShelleyLedgerEra era )
1537- -> AddressInEra era
1538- -> TxOutValue era
1540+ -> TxOut CtxTx era
15391541 -> Either (TxBodyErrorAutoBalance era ) ()
1540- balanceCheck sbe bpparams changeaddr balance
1541- | txOutValueToLovelace balance == 0 && onlyAda (txOutValueToValue balance) = return ()
1542- | txOutValueToLovelace balance < 0 =
1543- Left . TxBodyErrorAdaBalanceNegative $ txOutValueToLovelace balance
1544- | otherwise =
1545- case checkMinUTxOValue sbe (TxOut changeaddr balance TxOutDatumNone ReferenceScriptNone ) bpparams of
1546- Left (TxBodyErrorMinUTxONotMet txOutAny minUTxO) ->
1547- Left $ TxBodyErrorAdaBalanceTooSmall txOutAny minUTxO (txOutValueToLovelace balance)
1548- Left err -> Left err
1549- Right _ -> Right ()
1550-
1551- isNotAda :: AssetId -> Bool
1552- isNotAda AdaAssetId = False
1553- isNotAda _ = True
1554-
1555- onlyAda :: Value -> Bool
1556- onlyAda = null . toList . filterValue isNotAda
1542+ balanceCheck sbe bpparams txout@ (TxOut _ balance _ _) = do
1543+ let outValue@ (L. MaryValue coin multiAsset) = toMaryValue $ txOutValueToValue balance
1544+ isPositiveValue = L. pointwise (>) outValue mempty
1545+ if
1546+ | L. isZero outValue -> pure () -- empty TxOut
1547+ | not isPositiveValue -> Left $ TxBodyErrorBalanceNegative coin multiAsset
1548+ | otherwise ->
1549+ case checkMinUTxOValue sbe txout bpparams of
1550+ Left (TxBodyErrorMinUTxONotMet txOutAny minUTxO) ->
1551+ Left $ TxBodyErrorAdaBalanceTooSmall txOutAny minUTxO coin
1552+ Left err -> Left err
1553+ Right _ -> Right ()
15571554
15581555-- Calculation taken from validateInsufficientCollateral:
15591556-- https://github.com/input-output-hk/cardano-ledger/blob/389b266d6226dedf3d2aec7af640b3ca4984c5ea/eras/alonzo/impl/src/Cardano/Ledger/Alonzo/Rules/Utxo.hs#L335
0 commit comments