diff --git a/cabal.project b/cabal.project index 7bf08979ef..113b8d5403 100644 --- a/cabal.project +++ b/cabal.project @@ -65,3 +65,10 @@ if impl (ghc >= 9.12) -- https://github.com/kapralVV/Unique/issues/11 , Unique:hashable +source-repository-package + type: git + location: https://github.com/IntersectMBO/cardano-api + tag: 45eae266ee73bc19de30400b53112bae78308625 + --sha256: sha256-wHw1JahZB/nuFZkNEFpnPfA4vk+c1XLJ6CNFPFy6FYE= + subdir: + cardano-api \ No newline at end of file diff --git a/cardano-cli/src/Cardano/CLI/Compatible/Json/Friendly.hs b/cardano-cli/src/Cardano/CLI/Compatible/Json/Friendly.hs index fec926236e..4917dc59ec 100644 --- a/cardano-cli/src/Cardano/CLI/Compatible/Json/Friendly.hs +++ b/cardano-cli/src/Cardano/CLI/Compatible/Json/Friendly.hs @@ -601,172 +601,181 @@ friendlyCertificates sbe = \case TxCertificatesNone -> Null TxCertificates _ cs -> array $ map (friendlyCertificate sbe . fst) $ toList cs -friendlyCertificate :: ShelleyBasedEra era -> Certificate era -> Aeson.Value +friendlyCertificate :: ShelleyBasedEra era -> Exp.Certificate (ShelleyLedgerEra era) -> Aeson.Value friendlyCertificate sbe = shelleyBasedEraConstraints sbe $ object . (: []) . renderCertificate sbe -renderCertificate :: ShelleyBasedEra era -> Certificate era -> (Aeson.Key, Aeson.Value) -renderCertificate sbe = \case - ShelleyRelatedCertificate _ c -> - shelleyBasedEraConstraints sbe $ - case c of - L.ShelleyTxCertDelegCert (L.ShelleyRegCert cred) -> - "stake address registration" .= cred - L.ShelleyTxCertDelegCert (L.ShelleyUnRegCert cred) -> - "stake address deregistration" .= cred - L.ShelleyTxCertDelegCert (L.ShelleyDelegCert cred poolId) -> - "stake address delegation" - .= object - [ "credential" .= cred - , "pool" .= poolId - ] - L.ShelleyTxCertPool (L.RetirePool poolId retirementEpoch) -> - "stake pool retirement" - .= object - [ "pool" .= StakePoolKeyHash poolId - , "epoch" .= retirementEpoch - ] - L.ShelleyTxCertPool (L.RegPool poolParams) -> - "stake pool registration" .= poolParams - L.ShelleyTxCertGenesisDeleg (L.GenesisDelegCert genesisKeyHash delegateKeyHash vrfKeyHash) -> - "genesis key delegation" - .= object - [ "genesis key hash" .= genesisKeyHash - , "delegate key hash" .= delegateKeyHash - , "VRF key hash" .= vrfKeyHash - ] - L.ShelleyTxCertMir (L.MIRCert pot target) -> - "MIR" - .= object - [ "pot" .= friendlyMirPot pot - , friendlyMirTarget sbe target - ] - ConwayCertificate w cert -> - conwayEraOnwardsConstraints w $ - case cert of - L.RegDRepTxCert credential coin mAnchor -> - "Drep registration certificate" - .= object - [ "deposit" .= coin - , "certificate" .= conwayToObject w credential - , "anchor" .= mAnchor - ] - L.UnRegDRepTxCert credential coin -> - "Drep unregistration certificate" - .= object - [ "refund" .= coin - , "certificate" .= conwayToObject w credential - ] - L.AuthCommitteeHotKeyTxCert coldCred hotCred - | L.ScriptHashObj sh <- coldCred -> - "Cold committee authorization" - .= object - ["script hash" .= sh] - | L.ScriptHashObj sh <- hotCred -> - "Hot committee authorization" - .= object - ["script hash" .= sh] - | L.KeyHashObj ck@L.KeyHash{} <- coldCred - , L.KeyHashObj hk@L.KeyHash{} <- hotCred -> - "Constitutional committee member hot key registration" - .= object - [ "cold key hash" .= ck - , "hot key hash" .= hk - ] - L.ResignCommitteeColdTxCert cred anchor -> case cred of - L.ScriptHashObj sh -> - "Cold committee resignation" - .= object - [ "script hash" .= sh - , "anchor" .= anchor - ] - L.KeyHashObj ck@L.KeyHash{} -> - "Constitutional committee cold key resignation" - .= object - [ "cold key hash" .= ck - ] - L.RegTxCert stakeCredential -> - "Stake address registration" - .= object - [ "stake credential" .= stakeCredential - ] - L.UnRegTxCert stakeCredential -> - "Stake address deregistration" - .= object - [ "stake credential" .= stakeCredential - ] - L.RegDepositTxCert stakeCredential deposit -> - "Stake address registration" - .= object - [ "stake credential" .= stakeCredential - , "deposit" .= deposit - ] - L.UnRegDepositTxCert stakeCredential refund -> - "Stake address deregistration" - .= object - [ "stake credential" .= stakeCredential - , "refund" .= refund - ] - L.DelegTxCert stakeCredential delegatee -> - "Stake address delegation" - .= object - [ "stake credential" .= stakeCredential - , "delegatee" .= delegateeJson sbe delegatee - ] - L.RegDepositDelegTxCert stakeCredential delegatee deposit -> - "Stake address registration and delegation" - .= object - [ "stake credential" .= stakeCredential - , "delegatee" .= delegateeJson sbe delegatee - , "deposit" .= deposit - ] - L.RegPoolTxCert poolParams -> - "Pool registration" +renderCertificate + :: ShelleyBasedEra era -> Exp.Certificate (ShelleyLedgerEra era) -> (Aeson.Key, Aeson.Value) +renderCertificate sbe (Exp.Certificate c) = + case sbe of + ShelleyBasedEraShelley -> renderShelleyCertificate sbe c + ShelleyBasedEraAllegra -> renderShelleyCertificate sbe c + ShelleyBasedEraMary -> renderShelleyCertificate sbe c + ShelleyBasedEraAlonzo -> renderShelleyCertificate sbe c + ShelleyBasedEraBabbage -> renderShelleyCertificate sbe c + ShelleyBasedEraConway -> renderConwayCertificate c + +renderDrepCredential + :: () + => L.Credential 'L.DRepRole + -> Aeson.Value +renderDrepCredential = + object . \case + L.ScriptHashObj sHash -> ["scriptHash" .= sHash] + L.KeyHashObj keyHash -> ["keyHash" .= keyHash] + +delegateeJson + :: L.Delegatee + -> Aeson.Value +delegateeJson = + object . \case + L.DelegStake hk@L.KeyHash{} -> + [ "delegatee type" .= String "stake" + , "key hash" .= hk + ] + L.DelegVote drep -> do + ["delegatee type" .= String "vote", "DRep" .= drep] + L.DelegStakeVote kh drep -> + [ "delegatee type" .= String "stake vote" + , "key hash" .= kh + , "DRep" .= drep + ] + +renderShelleyCertificate + :: ShelleyBasedEra era -> Ledger.ShelleyTxCert (ShelleyLedgerEra era) -> (Aeson.Key, Aeson.Value) +renderShelleyCertificate sbe c = + case c of + L.ShelleyTxCertDelegCert (L.ShelleyRegCert cred) -> + "stake address registration" .= cred + L.ShelleyTxCertDelegCert (L.ShelleyUnRegCert cred) -> + "stake address deregistration" .= cred + L.ShelleyTxCertDelegCert (L.ShelleyDelegCert cred poolId) -> + "stake address delegation" + .= object + [ "credential" .= cred + , "pool" .= poolId + ] + L.ShelleyTxCertPool (L.RetirePool poolId retirementEpoch) -> + "stake pool retirement" + .= object + [ "pool" .= StakePoolKeyHash poolId + , "epoch" .= retirementEpoch + ] + L.ShelleyTxCertPool (L.RegPool poolParams) -> + "stake pool registration" .= poolParams + L.ShelleyTxCertGenesisDeleg (L.GenesisDelegCert genesisKeyHash delegateKeyHash vrfKeyHash) -> + "genesis key delegation" + .= object + [ "genesis key hash" .= genesisKeyHash + , "delegate key hash" .= delegateKeyHash + , "VRF key hash" .= vrfKeyHash + ] + L.ShelleyTxCertMir (L.MIRCert pot target) -> + "MIR" + .= object + [ "pot" .= friendlyMirPot pot + , friendlyMirTarget sbe target + ] + +renderConwayCertificate + :: Ledger.ConwayTxCert (ShelleyLedgerEra ConwayEra) -> (Aeson.Key, Aeson.Value) +renderConwayCertificate cert = + case cert of + L.RegDRepTxCert credential coin mAnchor -> + "Drep registration certificate" + .= object + [ "deposit" .= coin + , "certificate" .= renderDrepCredential credential + , "anchor" .= mAnchor + ] + L.UnRegDRepTxCert credential coin -> + "Drep unregistration certificate" + .= object + [ "refund" .= coin + , "certificate" .= renderDrepCredential credential + ] + L.AuthCommitteeHotKeyTxCert coldCred hotCred + | L.ScriptHashObj sh <- coldCred -> + "Cold committee authorization" .= object - [ "pool params" .= poolParams - ] - L.RetirePoolTxCert kh@L.KeyHash{} epoch -> - "Pool retirement" + ["script hash" .= sh] + | L.ScriptHashObj sh <- hotCred -> + "Hot committee authorization" .= object - [ "stake pool key hash" .= kh - , "epoch" .= epoch - ] - L.UpdateDRepTxCert drepCredential mbAnchor -> - "Drep certificate update" + ["script hash" .= sh] + | L.KeyHashObj ck@L.KeyHash{} <- coldCred + , L.KeyHashObj hk@L.KeyHash{} <- hotCred -> + "Constitutional committee member hot key registration" .= object - [ "Drep credential" .= drepCredential - , "anchor " .= mbAnchor + [ "cold key hash" .= ck + , "hot key hash" .= hk ] - where - conwayToObject - :: () - => ConwayEraOnwards era - -> L.Credential 'L.DRepRole - -> Aeson.Value - conwayToObject w' = - conwayEraOnwardsConstraints w' $ - object . \case - L.ScriptHashObj sHash -> ["scriptHash" .= sHash] - L.KeyHashObj keyHash -> ["keyHash" .= keyHash] - - delegateeJson - :: ShelleyBasedEra era - -> L.Delegatee - -> Aeson.Value - delegateeJson _ = - object . \case - L.DelegStake hk@L.KeyHash{} -> - [ "delegatee type" .= String "stake" - , "key hash" .= hk - ] - L.DelegVote drep -> do - ["delegatee type" .= String "vote", "DRep" .= drep] - L.DelegStakeVote kh drep -> - [ "delegatee type" .= String "stake vote" - , "key hash" .= kh - , "DRep" .= drep - ] + L.ResignCommitteeColdTxCert cred anchor -> case cred of + L.ScriptHashObj sh -> + "Cold committee resignation" + .= object + [ "script hash" .= sh + , "anchor" .= anchor + ] + L.KeyHashObj ck@L.KeyHash{} -> + "Constitutional committee cold key resignation" + .= object + [ "cold key hash" .= ck + ] + L.RegTxCert stakeCredential -> + "Stake address registration" + .= object + [ "stake credential" .= stakeCredential + ] + L.UnRegTxCert stakeCredential -> + "Stake address deregistration" + .= object + [ "stake credential" .= stakeCredential + ] + L.RegDepositTxCert stakeCredential deposit -> + "Stake address registration" + .= object + [ "stake credential" .= stakeCredential + , "deposit" .= deposit + ] + L.UnRegDepositTxCert stakeCredential refund -> + "Stake address deregistration" + .= object + [ "stake credential" .= stakeCredential + , "refund" .= refund + ] + L.DelegTxCert stakeCredential delegatee -> + "Stake address delegation" + .= object + [ "stake credential" .= stakeCredential + , "delegatee" .= delegateeJson delegatee + ] + L.RegDepositDelegTxCert stakeCredential delegatee deposit -> + "Stake address registration and delegation" + .= object + [ "stake credential" .= stakeCredential + , "delegatee" .= delegateeJson delegatee + , "deposit" .= deposit + ] + L.RegPoolTxCert poolParams -> + "Pool registration" + .= object + [ "pool params" .= poolParams + ] + L.RetirePoolTxCert kh@L.KeyHash{} epoch -> + "Pool retirement" + .= object + [ "stake pool key hash" .= kh + , "epoch" .= epoch + ] + L.UpdateDRepTxCert drepCredential mbAnchor -> + "Drep certificate update" + .= object + [ "Drep credential" .= drepCredential + , "anchor " .= mbAnchor + ] friendlyMirTarget :: ShelleyBasedEra era -> L.MIRTarget -> Aeson.Pair diff --git a/cardano-cli/src/Cardano/CLI/Compatible/StakeAddress/Run.hs b/cardano-cli/src/Cardano/CLI/Compatible/StakeAddress/Run.hs index 0da6460c23..0aaba7c6cc 100644 --- a/cardano-cli/src/Cardano/CLI/Compatible/StakeAddress/Run.hs +++ b/cardano-cli/src/Cardano/CLI/Compatible/StakeAddress/Run.hs @@ -11,6 +11,7 @@ module Cardano.CLI.Compatible.StakeAddress.Run where import Cardano.Api +import Cardano.Api.Experimental qualified as Exp import Cardano.Api.Ledger qualified as L import Cardano.CLI.Compatible.Exception @@ -106,17 +107,17 @@ createStakeDelegationCertificate :: ShelleyBasedEra era -> StakeCredential -> Hash StakePoolKey - -> Certificate era + -> Exp.Certificate (ShelleyLedgerEra era) createStakeDelegationCertificate sbe stakeCredential stakePoolHash = do caseShelleyToBabbageOrConwayEraOnwards ( \w -> shelleyToBabbageEraConstraints w $ - ShelleyRelatedCertificate w $ + Exp.Certificate $ L.mkDelegStakeTxCert (toShelleyStakeCredential stakeCredential) (toLedgerHash stakePoolHash) ) ( \w -> conwayEraOnwardsConstraints w $ - ConwayCertificate w $ + Exp.Certificate $ L.mkDelegTxCert (toShelleyStakeCredential stakeCredential) (L.DelegStake (toLedgerHash stakePoolHash)) diff --git a/cardano-cli/src/Cardano/CLI/EraBased/StakeAddress/Command.hs b/cardano-cli/src/Cardano/CLI/EraBased/StakeAddress/Command.hs index 62a9eba0ac..c31e049ce6 100644 --- a/cardano-cli/src/Cardano/CLI/EraBased/StakeAddress/Command.hs +++ b/cardano-cli/src/Cardano/CLI/EraBased/StakeAddress/Command.hs @@ -42,13 +42,13 @@ data StakeAddressCmds era StakePoolKeyHashSource (File () Out) | StakeAddressStakeAndVoteDelegationCertificateCmd - (ConwayEraOnwards era) + (Exp.Era era) StakeIdentifier StakePoolKeyHashSource VoteDelegationTarget (File () Out) | StakeAddressVoteDelegationCertificateCmd - (ConwayEraOnwards era) + (Exp.Era era) StakeIdentifier VoteDelegationTarget (File () Out) diff --git a/cardano-cli/src/Cardano/CLI/EraBased/StakeAddress/Run.hs b/cardano-cli/src/Cardano/CLI/EraBased/StakeAddress/Run.hs index 2303215601..a75f123f33 100644 --- a/cardano-cli/src/Cardano/CLI/EraBased/StakeAddress/Run.hs +++ b/cardano-cli/src/Cardano/CLI/EraBased/StakeAddress/Run.hs @@ -260,15 +260,15 @@ runStakeAddressStakeDelegationCertificateCmd era stakeVerifier poolVKeyOrHashOrF stakeCred <- getStakeCredentialFromIdentifier stakeVerifier - let certificate :: Certificate era = createStakeDelegationCertificate stakeCred poolStakeVKeyHash + let certificate :: Exp.Certificate (Exp.LedgerEra era) = createStakeDelegationCertificate stakeCred poolStakeVKeyHash fromEitherIOCli @(FileError ()) $ writeLazyByteStringFile outFp $ textEnvelopeToJSON (Just @TextEnvelopeDescr "Stake Delegation Certificate") certificate runStakeAddressStakeAndVoteDelegationCertificateCmd - :: () - => ConwayEraOnwards era + :: forall era e + . Exp.Era era -> StakeIdentifier -- ^ Delegator stake verification key, verification key file or script file. -> StakePoolKeyHashSource @@ -277,64 +277,67 @@ runStakeAddressStakeAndVoteDelegationCertificateCmd -- verification key hash. -> File () Out -> CIO e () -runStakeAddressStakeAndVoteDelegationCertificateCmd w stakeVerifier poolVKeyOrHashOrFile voteDelegationTarget outFp = - conwayEraOnwardsConstraints w $ do - StakePoolKeyHash poolStakeVKeyHash <- getHashFromStakePoolKeyHashSource poolVKeyOrHashOrFile +runStakeAddressStakeAndVoteDelegationCertificateCmd w stakeVerifier poolVKeyOrHashOrFile voteDelegationTarget outFp = do + StakePoolKeyHash poolStakeVKeyHash <- getHashFromStakePoolKeyHashSource poolVKeyOrHashOrFile - stakeCredential <- - getStakeCredentialFromIdentifier stakeVerifier + stakeCredential <- + getStakeCredentialFromIdentifier stakeVerifier - drep <- - readVoteDelegationTarget voteDelegationTarget + drep <- + readVoteDelegationTarget voteDelegationTarget - let delegatee = L.DelegStakeVote poolStakeVKeyHash drep + let delegatee = L.DelegStakeVote poolStakeVKeyHash drep - let certificate = - ConwayCertificate w $ - L.mkDelegTxCert (toShelleyStakeCredential stakeCredential) delegatee + certificate :: Exp.Certificate (Exp.LedgerEra era) <- + return $ + obtainCommonConstraints w $ + Exp.Certificate $ + L.mkDelegTxCert (toShelleyStakeCredential stakeCredential) delegatee - fromEitherIOCli @(FileError ()) $ - writeLazyByteStringFile outFp $ + fromEitherIOCli @(FileError ()) $ + writeLazyByteStringFile outFp $ + obtainCommonConstraints w $ textEnvelopeToJSON (Just @TextEnvelopeDescr "Stake and Vote Delegation Certificate") certificate runStakeAddressVoteDelegationCertificateCmd - :: () - => ConwayEraOnwards era + :: forall era e + . Exp.Era era -> StakeIdentifier -- ^ Delegatee stake pool verification key or verification key file or -> VoteDelegationTarget -- ^ Delegatee stake pool verification key or verification key file or verification key hash. -> File () Out -> CIO e () -runStakeAddressVoteDelegationCertificateCmd w stakeVerifier voteDelegationTarget outFp = - conwayEraOnwardsConstraints w $ do - stakeCredential <- - getStakeCredentialFromIdentifier stakeVerifier +runStakeAddressVoteDelegationCertificateCmd w stakeVerifier voteDelegationTarget outFp = do + stakeCredential <- + getStakeCredentialFromIdentifier stakeVerifier - drep <- - readVoteDelegationTarget voteDelegationTarget + drep <- + readVoteDelegationTarget voteDelegationTarget - let delegatee = L.DelegVote drep + let delegatee = L.DelegVote drep - let certificate = - ConwayCertificate w $ + let certificate :: Exp.Certificate (Exp.LedgerEra era) = + obtainCommonConstraints w $ + Exp.Certificate $ L.mkDelegTxCert (toShelleyStakeCredential stakeCredential) delegatee - fromEitherIOCli @(FileError ()) - $ writeLazyByteStringFile - outFp - $ textEnvelopeToJSON (Just @TextEnvelopeDescr "Vote Delegation Certificate") certificate + fromEitherIOCli @(FileError ()) + $ writeLazyByteStringFile + outFp + $ obtainCommonConstraints w + $ textEnvelopeToJSON (Just @TextEnvelopeDescr "Vote Delegation Certificate") certificate createStakeDelegationCertificate :: forall era . Exp.IsEra era => StakeCredential -> Hash StakePoolKey - -> Certificate era + -> Exp.Certificate (Exp.LedgerEra era) createStakeDelegationCertificate stakeCredential (StakePoolKeyHash poolStakeVKeyHash) = do let w = convert $ Exp.useEra @era - conwayEraOnwardsConstraints w $ - ConwayCertificate (convert Exp.useEra) $ + obtainCommonConstraints w $ + Exp.Certificate $ L.mkDelegTxCert (toShelleyStakeCredential stakeCredential) (L.DelegStake poolStakeVKeyHash) runStakeAddressDeregistrationCertificateCmd diff --git a/cardano-cli/src/Cardano/CLI/EraBased/Transaction/Internal/HashCheck.hs b/cardano-cli/src/Cardano/CLI/EraBased/Transaction/Internal/HashCheck.hs index 0171703ce2..9f7dfd702f 100644 --- a/cardano-cli/src/Cardano/CLI/EraBased/Transaction/Internal/HashCheck.hs +++ b/cardano-cli/src/Cardano/CLI/EraBased/Transaction/Internal/HashCheck.hs @@ -15,11 +15,11 @@ import Cardano.Api , convert , except , firstExceptT - , getAnchorDataFromCertificate , getAnchorDataFromGovernanceAction , shelleyBasedEraConstraints , withExceptT ) +import Cardano.Api.Experimental (obtainCommonConstraints) import Cardano.Api.Experimental qualified as Exp import Cardano.Api.Ledger qualified as L @@ -43,13 +43,13 @@ checkAnchorMetadataHash anchor = -- | Find references to anchor data and check the hashes are valid -- and they match the linked data. checkCertificateHashes - :: Exp.IsEra era => Exp.Certificate (Exp.LedgerEra era) -> ExceptT TxCmdError IO () + :: forall era. Exp.IsEra era => Exp.Certificate (Exp.LedgerEra era) -> ExceptT TxCmdError IO () checkCertificateHashes cert = do mAnchor <- withExceptT TxCmdPoolMetadataHashError $ except $ - getAnchorDataFromCertificate $ - Exp.convertToOldApiCertificate Exp.useEra cert + obtainCommonConstraints (Exp.useEra @era) $ + Exp.getAnchorDataFromCertificate Exp.useEra cert maybe (return mempty) checkAnchorMetadataHash mAnchor -- | Find references to anchor data in voting procedures and check the hashes are valid diff --git a/cardano-cli/src/Cardano/CLI/EraBased/Transaction/Run.hs b/cardano-cli/src/Cardano/CLI/EraBased/Transaction/Run.hs index c098b779a7..023d1b83c5 100644 --- a/cardano-cli/src/Cardano/CLI/EraBased/Transaction/Run.hs +++ b/cardano-cli/src/Cardano/CLI/EraBased/Transaction/Run.hs @@ -180,10 +180,9 @@ runTransactionBuildCmd certsAndMaybeScriptWits <- sequence [ (,mSwit) - <$> ( fmap (Exp.convertToNewCertificate Exp.useEra) $ - fromEitherIOCli @(FileError TextEnvelopeError) $ - shelleyBasedEraConstraints eon $ - readFileTextEnvelope (File certFile) + <$> ( fromEitherIOCli @(FileError TextEnvelopeError) $ + obtainCommonConstraints currentEra $ + readFileTextEnvelope (File certFile) ) | (CertificateFile certFile, mSwit) <- certFilesAndMaybeScriptWits ] @@ -468,10 +467,9 @@ runTransactionBuildEstimateCmd -- TODO change type certsAndMaybeScriptWits <- sequence $ [ (,mSwit) - <$> ( fmap (Exp.convertToNewCertificate Exp.useEra) $ - shelleyBasedEraConstraints sbe $ - fromEitherIOCli $ - readFileTextEnvelope (File certFile) + <$> ( obtainCommonConstraints currentEra $ + fromEitherIOCli $ + readFileTextEnvelope (File certFile) ) | (CertificateFile certFile, mSwit :: Exp.AnyWitness (Exp.LedgerEra era)) <- certFilesAndMaybeScriptWits @@ -674,11 +672,10 @@ runTransactionBuildRawCmd certsAndMaybeScriptWits <- sequence [ (,mSwit) - <$> fmap - (Exp.convertToNewCertificate Exp.useEra) - ( fromEitherIOCli $ - readFileTextEnvelope (File certFile) - ) + <$> ( obtainCommonConstraints eon $ + fromEitherIOCli $ + readFileTextEnvelope (File certFile) + ) | (CertificateFile certFile, mSwit) <- certFilesAndMaybeScriptWits ] txBody <- @@ -917,7 +914,8 @@ constructTxBodyContent & setTxProtocolParams (BuildTxWith $ LedgerProtocolParameters . toShelleyLedgerPParamsShim Exp.useEra <$> mPparams) & setTxWithdrawals (TxWithdrawals sbe $ map convertWithdrawals withdrawals) - & setTxCertificates (Exp.mkTxCertificates certsAndMaybeScriptWits) + & setTxCertificates + (Exp.mkTxCertificates $ obtainCommonConstraints (Exp.useEra @era) certsAndMaybeScriptWits) & setTxUpdateProposal txUpdateProposal & setTxMintValue validatedMintValue & setTxScriptValidity validatedTxScriptValidity @@ -1034,7 +1032,7 @@ runTxBuild testEquality era nodeEra & hoistMaybe (TxCmdTxNodeEraMismatchError $ NodeEraMismatchError era nodeEra) - let certsToQuery = map (Exp.convertToOldApiCertificate Exp.useEra) $ fst <$> certsAndMaybeScriptWits + let certsToQuery = obtainCommonConstraints (Exp.useEra @era) (fst <$> certsAndMaybeScriptWits) (txEraUtxo, pparams, eraHistory, systemStart, stakePools, stakeDelegDeposits, drepDelegDeposits, _) <- lift ( executeLocalStateQueryExpr localNodeConnInfo Consensus.VolatileTip $ diff --git a/cardano-cli/src/Cardano/CLI/Type/Error/TxCmdError.hs b/cardano-cli/src/Cardano/CLI/Type/Error/TxCmdError.hs index adceb94391..9e42f46d85 100644 --- a/cardano-cli/src/Cardano/CLI/Type/Error/TxCmdError.hs +++ b/cardano-cli/src/Cardano/CLI/Type/Error/TxCmdError.hs @@ -65,7 +65,7 @@ data TxCmdError | -- Validation errors forall era. TxCmdTxGovDuplicateVotes (TxGovDuplicateVotes era) | forall era. TxCmdFeeEstimationError (TxFeeEstimationError era) - | TxCmdPoolMetadataHashError AnchorDataFromCertificateError + | TxCmdPoolMetadataHashError Exp.AnchorDataFromCertificateError | TxCmdHashCheckError L.Url HashCheckError | TxCmdUnregisteredStakeAddress !(Set StakeCredential) | forall era. TxCmdAlonzoEraOnwardsRequired !(CardanoEra era) diff --git a/cardano-cli/test/cardano-cli-golden/files/golden/governance/stakeaddress/alwaysAbstainDeleg.cert b/cardano-cli/test/cardano-cli-golden/files/golden/governance/stakeaddress/alwaysAbstainDeleg.cert index 5a3e763092..350a091e68 100644 --- a/cardano-cli/test/cardano-cli-golden/files/golden/governance/stakeaddress/alwaysAbstainDeleg.cert +++ b/cardano-cli/test/cardano-cli-golden/files/golden/governance/stakeaddress/alwaysAbstainDeleg.cert @@ -1,5 +1,5 @@ { - "type": "CertificateConway", + "type": "Certificate", "description": "Vote Delegation Certificate", "cborHex": "83098200581cef1785cf18928f8353c90e76b7a8fc60855472d31a0ea1c1c774ab018102" } diff --git a/cardano-cli/test/cardano-cli-golden/files/golden/governance/stakeaddress/noConfidenceDeleg.cert b/cardano-cli/test/cardano-cli-golden/files/golden/governance/stakeaddress/noConfidenceDeleg.cert index ec66a28ef3..751e6538f2 100644 --- a/cardano-cli/test/cardano-cli-golden/files/golden/governance/stakeaddress/noConfidenceDeleg.cert +++ b/cardano-cli/test/cardano-cli-golden/files/golden/governance/stakeaddress/noConfidenceDeleg.cert @@ -1,5 +1,5 @@ { - "type": "CertificateConway", + "type": "Certificate", "description": "Vote Delegation Certificate", "cborHex": "83098200581cef1785cf18928f8353c90e76b7a8fc60855472d31a0ea1c1c774ab018103" } diff --git a/cardano-cli/test/cardano-cli-golden/files/golden/governance/stakeaddress/poolAndAlwaysAbstainDeleg.cert b/cardano-cli/test/cardano-cli-golden/files/golden/governance/stakeaddress/poolAndAlwaysAbstainDeleg.cert index 26ebf5c581..eb25c3a88a 100644 --- a/cardano-cli/test/cardano-cli-golden/files/golden/governance/stakeaddress/poolAndAlwaysAbstainDeleg.cert +++ b/cardano-cli/test/cardano-cli-golden/files/golden/governance/stakeaddress/poolAndAlwaysAbstainDeleg.cert @@ -1,5 +1,5 @@ { - "type": "CertificateConway", + "type": "Certificate", "description": "Stake and Vote Delegation Certificate", "cborHex": "840a8200581cef1785cf18928f8353c90e76b7a8fc60855472d31a0ea1c1c774ab01581cc27cf021914a2b3bcb286d3d741979083422378c577fe757702b69888102" } diff --git a/cardano-cli/test/cardano-cli-golden/files/golden/governance/stakeaddress/poolAndDrepVkeyDeleg.cert b/cardano-cli/test/cardano-cli-golden/files/golden/governance/stakeaddress/poolAndDrepVkeyDeleg.cert index 6662aef102..9df5cf2e19 100644 --- a/cardano-cli/test/cardano-cli-golden/files/golden/governance/stakeaddress/poolAndDrepVkeyDeleg.cert +++ b/cardano-cli/test/cardano-cli-golden/files/golden/governance/stakeaddress/poolAndDrepVkeyDeleg.cert @@ -1,5 +1,5 @@ { - "type": "CertificateConway", + "type": "Certificate", "description": "Stake and Vote Delegation Certificate", "cborHex": "840a8200581cef1785cf18928f8353c90e76b7a8fc60855472d31a0ea1c1c774ab01581cc27cf021914a2b3bcb286d3d741979083422378c577fe757702b69888200581ce68f9ee70599cb93d9f60678f9c6463c01938c27d9820c7bf93887a5" } diff --git a/cardano-cli/test/cardano-cli-golden/files/golden/governance/stakeaddress/poolAndNoConfidenceDeleg.cert b/cardano-cli/test/cardano-cli-golden/files/golden/governance/stakeaddress/poolAndNoConfidenceDeleg.cert index 7ee0df9837..1a9f57f09f 100644 --- a/cardano-cli/test/cardano-cli-golden/files/golden/governance/stakeaddress/poolAndNoConfidenceDeleg.cert +++ b/cardano-cli/test/cardano-cli-golden/files/golden/governance/stakeaddress/poolAndNoConfidenceDeleg.cert @@ -1,5 +1,5 @@ { - "type": "CertificateConway", + "type": "Certificate", "description": "Stake and Vote Delegation Certificate", "cborHex": "840a8200581cef1785cf18928f8353c90e76b7a8fc60855472d31a0ea1c1c774ab01581cc27cf021914a2b3bcb286d3d741979083422378c577fe757702b69888103" }