Skip to content

Commit 2a1154b

Browse files
committed
Adapt callers outside ProtocolParameters
1 parent cd62068 commit 2a1154b

File tree

2 files changed

+46
-42
lines changed

2 files changed

+46
-42
lines changed

cardano-api/internal/Cardano/Api/Governance/Poll.hs

+13-5
Original file line numberDiff line numberDiff line change
@@ -7,7 +7,6 @@
77
{-# LANGUAGE ScopedTypeVariables #-}
88
{-# LANGUAGE TypeApplications #-}
99
{-# LANGUAGE TypeFamilies #-}
10-
{-# LANGUAGE ViewPatterns #-}
1110

1211
-- | An API for driving on-chain poll for SPOs.
1312
--
@@ -37,8 +36,10 @@ module Cardano.Api.Governance.Poll
3736
)
3837
where
3938

39+
import Cardano.Api.Pretty
40+
import Cardano.Api.Error
41+
import Cardano.Api.ProtocolParameters
4042
import Cardano.Api.Eon.ShelleyBasedEra
41-
import Cardano.Api.Eras
4243
import Cardano.Api.Hash
4344
import Cardano.Api.HasTypeProxy
4445
import Cardano.Api.Keys.Shelley
@@ -58,6 +59,7 @@ import Cardano.Ledger.Crypto (HASH, StandardCrypto)
5859

5960
import Control.Arrow (left)
6061
import Control.Monad (foldM, when)
62+
import Data.Bifunctor (first)
6163
import Data.Either.Combinators (maybeToRight)
6264
import Data.Function ((&))
6365
import qualified Data.Map.Strict as Map
@@ -279,6 +281,7 @@ data GovernancePollError
279281
| ErrGovernancePollUnauthenticated
280282
| ErrGovernancePollMalformedAnswer DecoderError
281283
| ErrGovernancePollInvalidAnswer GovernancePollInvalidAnswerError
284+
| ErrGovernancePollCostModelNotEnoughParameters CostModelNotEnoughParametersError
282285
deriving Show
283286

284287
data GovernancePollInvalidAnswerError = GovernancePollInvalidAnswerError
@@ -331,6 +334,9 @@ renderGovernancePollError err =
331334
| (ix, answer) <- invalidAnswerAcceptableAnswers invalidAnswer
332335
]
333336
]
337+
ErrGovernancePollCostModelNotEnoughParameters err' ->
338+
-- TODO can be simplified?
339+
Text.pack $ docToString $ prettyError err'
334340

335341
-- | Verify a poll against a given transaction and returns the signatories
336342
-- (verification key only) when valid.
@@ -341,12 +347,14 @@ verifyPollAnswer
341347
:: GovernancePoll
342348
-> InAnyShelleyBasedEra Tx
343349
-> Either GovernancePollError [Hash PaymentKey]
344-
verifyPollAnswer poll (InAnyShelleyBasedEra _era (getTxBody -> TxBody body)) = do
345-
answer <- extractPollAnswer (txMetadata body)
350+
verifyPollAnswer poll (InAnyShelleyBasedEra _era tx) = do
351+
content <- first ErrGovernancePollCostModelNotEnoughParameters $ getTxBodyContent body
352+
answer <- extractPollAnswer (txMetadata content)
346353
answer `hasMatchingHash` hashGovernancePoll poll
347354
answer `isAmongAcceptableChoices` govPollAnswers poll
348-
extraKeyWitnesses (txExtraKeyWits body)
355+
extraKeyWitnesses (txExtraKeyWits content)
349356
where
357+
body = getTxBody tx
350358
extractPollAnswer = \case
351359
TxMetadataNone ->
352360
Left ErrGovernancePollNoAnswer

cardano-api/internal/Cardano/Api/Tx/Body.hs

+33-37
Original file line numberDiff line numberDiff line change
@@ -14,14 +14,12 @@
1414
{-# LANGUAGE TypeApplications #-}
1515
{-# LANGUAGE TypeFamilies #-}
1616
{-# LANGUAGE TypeOperators #-}
17-
{-# LANGUAGE ViewPatterns #-}
1817

1918
-- | Transaction bodies
2019
module 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)
21492147
createAndValidateTransactionBody = 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)
21572151
getTxBodyContent = \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)
21682162
fromLedgerTxBody 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

21962192
fromLedgerProposalProcedures
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)
25482544
maybeFromLedgerTxUpdateProposal 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

25582554
fromLedgerTxMintValue

0 commit comments

Comments
 (0)