1414{-# LANGUAGE TypeApplications #-}
1515{-# LANGUAGE TypeFamilies #-}
1616{-# LANGUAGE TypeOperators #-}
17- {-# LANGUAGE ViewPatterns #-}
1817
1918-- | Transaction bodies
2019module Cardano.Api.Tx.Body
2120 ( parseTxId
2221
2322 -- * Transaction bodies
24- , TxBody (.. , TxBody )
2523 , createTransactionBody
2624 , createAndValidateTransactionBody
2725 , TxBodyContent (.. )
@@ -2148,12 +2146,8 @@ createAndValidateTransactionBody
21482146 -> Either TxBodyError (TxBody era )
21492147createAndValidateTransactionBody = makeShelleyTransactionBody
21502148
2151- pattern TxBody :: TxBodyContent ViewTx era -> TxBody era
2152- pattern TxBody txbodycontent <- (getTxBodyContent -> txbodycontent)
2153-
2154- {-# COMPLETE TxBody #-}
2155-
2156- getTxBodyContent :: TxBody era -> TxBodyContent ViewTx era
2149+ getTxBodyContent
2150+ :: TxBody era -> Either CostModelNotEnoughParametersError (TxBodyContent ViewTx era )
21572151getTxBodyContent = \ case
21582152 ShelleyTxBody sbe body _scripts scriptdata mAux scriptValidity ->
21592153 fromLedgerTxBody sbe scriptValidity body scriptdata mAux
@@ -2164,34 +2158,36 @@ fromLedgerTxBody
21642158 -> Ledger. TxBody (ShelleyLedgerEra era )
21652159 -> TxBodyScriptData era
21662160 -> Maybe (L. TxAuxData (ShelleyLedgerEra era ))
2167- -> TxBodyContent ViewTx era
2161+ -> Either CostModelNotEnoughParametersError ( TxBodyContent ViewTx era )
21682162fromLedgerTxBody sbe scriptValidity body scriptdata mAux =
2169- TxBodyContent
2170- { txIns = fromLedgerTxIns sbe body
2171- , txInsCollateral = fromLedgerTxInsCollateral sbe body
2172- , txInsReference = fromLedgerTxInsReference sbe body
2173- , txOuts = fromLedgerTxOuts sbe body scriptdata
2174- , txTotalCollateral = fromLedgerTxTotalCollateral sbe body
2175- , txReturnCollateral = fromLedgerTxReturnCollateral sbe body
2176- , txFee = fromLedgerTxFee sbe body
2177- , txValidityLowerBound = fromLedgerTxValidityLowerBound sbe (A. TxBody body)
2178- , txValidityUpperBound = fromLedgerTxValidityUpperBound sbe (A. TxBody body)
2179- , txWithdrawals = fromLedgerTxWithdrawals sbe body
2180- , txCertificates = fromLedgerTxCertificates sbe body
2181- , txUpdateProposal = maybeFromLedgerTxUpdateProposal sbe body
2182- , txMintValue = fromLedgerTxMintValue sbe body
2183- , txExtraKeyWits = fromLedgerTxExtraKeyWitnesses sbe body
2184- , txProtocolParams = ViewTx
2185- , txMetadata
2186- , txAuxScripts
2187- , txScriptValidity = scriptValidity
2188- , txProposalProcedures = fromLedgerProposalProcedures sbe body
2189- , txVotingProcedures = fromLedgerVotingProcedures sbe body
2190- , txCurrentTreasuryValue = fromLedgerCurrentTreasuryValue sbe body
2191- , txTreasuryDonation = fromLedgerTreasuryDonation sbe body
2192- }
2163+ txUpdateProposal <&> \ txup ->
2164+ TxBodyContent
2165+ { txIns = fromLedgerTxIns sbe body
2166+ , txInsCollateral = fromLedgerTxInsCollateral sbe body
2167+ , txInsReference = fromLedgerTxInsReference sbe body
2168+ , txOuts = fromLedgerTxOuts sbe body scriptdata
2169+ , txTotalCollateral = fromLedgerTxTotalCollateral sbe body
2170+ , txReturnCollateral = fromLedgerTxReturnCollateral sbe body
2171+ , txFee = fromLedgerTxFee sbe body
2172+ , txValidityLowerBound = fromLedgerTxValidityLowerBound sbe (A. TxBody body)
2173+ , txValidityUpperBound = fromLedgerTxValidityUpperBound sbe (A. TxBody body)
2174+ , txWithdrawals = fromLedgerTxWithdrawals sbe body
2175+ , txCertificates = fromLedgerTxCertificates sbe body
2176+ , txUpdateProposal = txup
2177+ , txMintValue = fromLedgerTxMintValue sbe body
2178+ , txExtraKeyWits = fromLedgerTxExtraKeyWitnesses sbe body
2179+ , txProtocolParams = ViewTx
2180+ , txMetadata
2181+ , txAuxScripts
2182+ , txScriptValidity = scriptValidity
2183+ , txProposalProcedures = fromLedgerProposalProcedures sbe body
2184+ , txVotingProcedures = fromLedgerVotingProcedures sbe body
2185+ , txCurrentTreasuryValue = fromLedgerCurrentTreasuryValue sbe body
2186+ , txTreasuryDonation = fromLedgerTreasuryDonation sbe body
2187+ }
21932188 where
21942189 (txMetadata, txAuxScripts) = fromLedgerTxAuxiliaryData sbe mAux
2190+ txUpdateProposal = maybeFromLedgerTxUpdateProposal sbe body
21952191
21962192fromLedgerProposalProcedures
21972193 :: ShelleyBasedEra era
@@ -2544,15 +2540,15 @@ maybeFromLedgerTxUpdateProposal
25442540 :: ()
25452541 => ShelleyBasedEra era
25462542 -> Ledger. TxBody (ShelleyLedgerEra era )
2547- -> TxUpdateProposal era
2543+ -> Either CostModelNotEnoughParametersError ( TxUpdateProposal era )
25482544maybeFromLedgerTxUpdateProposal sbe body =
25492545 caseShelleyToBabbageOrConwayEraOnwards
25502546 ( \ w ->
25512547 case body ^. L. updateTxBodyL of
2552- SNothing -> TxUpdateProposalNone
2553- SJust p -> TxUpdateProposal w (fromLedgerUpdate sbe p)
2548+ SNothing -> pure TxUpdateProposalNone
2549+ SJust p -> TxUpdateProposal w <$> (fromLedgerUpdate sbe p)
25542550 )
2555- (const TxUpdateProposalNone )
2551+ (const $ pure TxUpdateProposalNone )
25562552 sbe
25572553
25582554fromLedgerTxMintValue
0 commit comments