Skip to content

Commit

Permalink
Propagate more type changes from cardano-api
Browse files Browse the repository at this point in the history
  • Loading branch information
Jimbo4350 committed Aug 21, 2023
1 parent a92fb89 commit eed575f
Show file tree
Hide file tree
Showing 8 changed files with 30 additions and 87 deletions.
38 changes: 9 additions & 29 deletions cardano-cli/src/Cardano/CLI/Commands/Governance.hs
Original file line number Diff line number Diff line change
Expand Up @@ -19,7 +19,6 @@ import Cardano.Prelude (intercalate, toS)
import Control.Monad.IO.Class
import Control.Monad.Trans.Except (ExceptT)
import Control.Monad.Trans.Except.Extra (firstExceptT, hoistEither, newExceptT)
import Data.Bifunctor
import qualified Data.ByteString as BS
import Data.Text (Text)
import qualified Data.Text.Encoding as Text
Expand Down Expand Up @@ -122,33 +121,12 @@ instance Error GovernanceCmdError where
runGovernanceCreateVoteCmd
:: AnyShelleyBasedEra
-> Vote
-> VType
-> TxIn
-> VerificationKeyOrFile StakePoolKey
-> VoteFile Out
-> ExceptT GovernanceCmdError IO ()
runGovernanceCreateVoteCmd anyEra vChoice vType (TxIn govTxInIdentifier _govTxId) votingStakeCred oFp = do
runGovernanceCreateVoteCmd anyEra vChoice oFp = do
AnyShelleyBasedEra sbe <- pure anyEra
vStakePoolKey <- firstExceptT ReadFileError . newExceptT $ readVerificationKeyOrFile AsStakePoolKey votingStakeCred
let stakePoolKeyHash = verificationKeyHash vStakePoolKey
vStakeCred = StakeCredentialByKey . (verificationKeyHash . castVerificationKey) $ vStakePoolKey
case vType of
VCC -> do
votingCred <- hoistEither $ first VotingCredentialDecodeGovCmdEror $ toVotingCredential sbe vStakeCred
let govActIdentifier = makeGoveranceActionId sbe govTxInIdentifier (error "TODO: Conway era - the TxInId does not determine the govActId")
voteProcedure = createVotingProcedure sbe vChoice (VoterCommittee votingCred) govActIdentifier
firstExceptT WriteFileError . newExceptT $ shelleyBasedEraConstraints sbe $ writeFileTextEnvelope oFp Nothing voteProcedure

VDR -> do
votingCred <- hoistEither $ first VotingCredentialDecodeGovCmdEror $ toVotingCredential sbe vStakeCred
let govActIdentifier = makeGoveranceActionId sbe govTxInIdentifier (error "TODO: Conway era - the TxInId does not determine the govActId")
voteProcedure = createVotingProcedure sbe vChoice (VoterDRep votingCred) govActIdentifier
firstExceptT WriteFileError . newExceptT $ shelleyBasedEraConstraints sbe $ writeFileTextEnvelope oFp Nothing voteProcedure

VSP -> do
let govActIdentifier = makeGoveranceActionId sbe govTxInIdentifier (error "TODO: Conway era - the TxInId does not determine the govActId")
voteProcedure = createVotingProcedure sbe vChoice (VoterSpo stakePoolKeyHash) govActIdentifier
firstExceptT WriteFileError . newExceptT $ shelleyBasedEraConstraints sbe $ writeFileTextEnvelope oFp Nothing voteProcedure
let voteProcedure = createVotingProcedure sbe vChoice Nothing
firstExceptT WriteFileError . newExceptT $ shelleyBasedEraConstraints sbe $ writeFileTextEnvelope oFp Nothing voteProcedure


runGovernanceNewConstitutionCmd
Expand All @@ -157,10 +135,11 @@ runGovernanceNewConstitutionCmd
-> Lovelace
-> VerificationKeyOrFile StakePoolKey
-> Maybe (TxId, Word32)
-> (Ledger.Url, Text)
-> Constitution
-> NewConstitutionFile Out
-> ExceptT GovernanceCmdError IO ()
runGovernanceNewConstitutionCmd network sbe deposit stakeVoteCred mPrevGovAct constitution oFp = do
runGovernanceNewConstitutionCmd network sbe deposit stakeVoteCred mPrevGovAct propAnchor constitution oFp = do
vStakePoolKeyHash
<- fmap (verificationKeyHash . castVerificationKey)
<$> firstExceptT ReadFileError . newExceptT
Expand All @@ -173,25 +152,26 @@ runGovernanceNewConstitutionCmd network sbe deposit stakeVoteCred mPrevGovAct co
govAct = ProposeNewConstitution
prevGovActId
(createAnchor url cBs) -- TODO: Conway era - this is wrong, create `AnchorData` then hash that with hashAnchorData
runGovernanceCreateActionCmd network sbe deposit vStakePoolKeyHash govAct oFp
runGovernanceCreateActionCmd network sbe deposit vStakePoolKeyHash propAnchor govAct oFp

ConstitutionFromText url c -> do
let constitBs = Text.encodeUtf8 c
prevGovActId = Ledger.maybeToStrictMaybe $ uncurry createPreviousGovernanceActionId <$> mPrevGovAct
govAct = ProposeNewConstitution
prevGovActId
(createAnchor url constitBs)
runGovernanceCreateActionCmd network sbe deposit vStakePoolKeyHash govAct oFp
runGovernanceCreateActionCmd network sbe deposit vStakePoolKeyHash propAnchor govAct oFp

runGovernanceCreateActionCmd
:: Ledger.Network
-> AnyShelleyBasedEra
-> Lovelace
-> Hash StakeKey
-> (Ledger.Url, Text)
-> GovernanceAction
-> File a Out
-> ExceptT GovernanceCmdError IO ()
runGovernanceCreateActionCmd network anyEra deposit depositReturnAddr govAction oFp = do
runGovernanceCreateActionCmd network anyEra deposit depositReturnAddr propAnchor govAction oFp = do
AnyShelleyBasedEra sbe <- pure anyEra
let proposal = createProposalProcedure
sbe
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -53,6 +53,7 @@ data EraBasedNewCommittee
{ ebNetwork :: Ledger.Network
, ebDeposit :: Lovelace
, ebReturnAddress :: AnyStakeIdentifier
, ebPropAnchor :: (Ledger.Url, Text)
, ebOldCommittee :: [AnyStakeIdentifier]
, ebNewCommittee :: [(AnyStakeIdentifier, EpochNo)]
, ebRequiredQuorum :: Rational
Expand All @@ -66,6 +67,7 @@ data EraBasedNewConstitution
, encDeposit :: Lovelace
, encStakeCredential :: AnyStakeIdentifier
, encPrevGovActId :: Maybe (TxId, Word32)
, encPropAnchor :: (Ledger.Url, Text)
, encConstitution :: Constitution
, encFilePath :: File () Out
} deriving Show
Expand All @@ -86,6 +88,7 @@ data EraBasedTreasuryWithdrawal where
:: Ledger.Network
-> Lovelace -- ^ Deposit
-> AnyStakeIdentifier -- ^ Return address
-> (Ledger.Url, Text) -- ^ Proposal anchor
-> [(AnyStakeIdentifier, Lovelace)]
-> File () Out
-> EraBasedTreasuryWithdrawal
Expand Down
6 changes: 2 additions & 4 deletions cardano-cli/src/Cardano/CLI/EraBased/Options/Governance.hs
Original file line number Diff line number Diff line change
Expand Up @@ -231,11 +231,9 @@ pAnyVote :: ConwayEraOnwards era -> Parser AnyVote
pAnyVote cOnwards =
ConwayOnwardsVote cOnwards
<$> pVoteChoice
<*> pGoveranceActionIdentifier "TxIn of governance action (already on chain)."
<*> pAnyVotingStakeVerificationKeyOrHashOrFile

pAnyVotingStakeVerificationKeyOrHashOrFile :: Parser AnyVotingStakeVerificationKeyOrHashOrFile
pAnyVotingStakeVerificationKeyOrHashOrFile =
_pAnyVotingStakeVerificationKeyOrHashOrFile :: Parser AnyVotingStakeVerificationKeyOrHashOrFile
_pAnyVotingStakeVerificationKeyOrHashOrFile =
asum [ AnyDRepVerificationKeyOrHashOrFile <$> pDRepVerificationKeyOrHashOrFile
, AnyStakePoolVerificationKeyOrHashOrFile <$> pStakePoolVerificationKeyOrHashOrFile
]
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -100,7 +100,7 @@ runGovernanceActionCreateConstitution :: ()
=> ConwayEraOnwards era
-> EraBasedNewConstitution
-> ExceptT GovernanceActionsError IO ()
runGovernanceActionCreateConstitution cOn (EraBasedNewConstitution network deposit anyStake mPrevGovActId constit outFp) = do
runGovernanceActionCreateConstitution cOn (EraBasedNewConstitution network deposit anyStake mPrevGovActId propAnchor constit outFp) = do

stakeKeyHash <- readStakeKeyHash anyStake

Expand Down Expand Up @@ -150,7 +150,7 @@ runGovernanceActionCreateNewCommittee
:: ConwayEraOnwards era
-> EraBasedNewCommittee
-> ExceptT GovernanceActionsError IO ()
runGovernanceActionCreateNewCommittee cOn (EraBasedNewCommittee network deposit retAddr old new q prevActId oFp) = do
runGovernanceActionCreateNewCommittee cOn (EraBasedNewCommittee network deposit retAddr propAnchor old new q prevActId oFp) = do
let sbe = conwayEraOnwardsToShelleyBasedEra cOn -- TODO: Conway era - update vote creation related function to take ConwayEraOnwards
govActIdentifier = Ledger.maybeToStrictMaybe $ uncurry createPreviousGovernanceActionId <$> prevActId
quorumRational = toRational q
Expand Down Expand Up @@ -218,7 +218,7 @@ runGovernanceActionTreasuryWithdrawal
:: ConwayEraOnwards era
-> EraBasedTreasuryWithdrawal
-> ExceptT GovernanceActionsError IO ()
runGovernanceActionTreasuryWithdrawal cOn (EraBasedTreasuryWithdrawal network deposit returnAddr treasuryWithdrawal outFp) = do
runGovernanceActionTreasuryWithdrawal cOn (EraBasedTreasuryWithdrawal network deposit returnAddr propAnchor treasuryWithdrawal outFp) = do
returnKeyHash <- readStakeKeyHash returnAddr
_withdrawals <- sequence [ (,ll) <$> stakeIdentifiertoCredential stakeIdentifier
| (stakeIdentifier,ll) <- treasuryWithdrawal
Expand Down
47 changes: 8 additions & 39 deletions cardano-cli/src/Cardano/CLI/EraBased/Vote.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,17 +4,16 @@

module Cardano.CLI.EraBased.Vote where

import Cardano.Api.Ledger (HasKeyRole (coerceKeyRole))
import Cardano.Api.Shelley
import Cardano.Api.Shelley (Error (..), File, FileDirection (Out), FileError,
InputDecodeError, conwayEraOnwardsToShelleyBasedEra, createVotingProcedure,
shelleyBasedEraConstraints, writeFileTextEnvelope)

import Cardano.Binary (DecoderError)
import Cardano.CLI.Types.Governance
import Cardano.CLI.Types.Key
import Cardano.Prelude (toS)

import Control.Monad.Trans.Except
import Control.Monad.Trans.Except.Extra
import Data.Bifunctor
import qualified Data.Text.Lazy.Builder as TL
import qualified Formatting.Buildable as B

Expand All @@ -39,38 +38,8 @@ runGovernanceVote
:: AnyVote
-> File () Out
-> ExceptT EraBasedVoteError IO ()
runGovernanceVote (ConwayOnwardsVote cOnwards v (TxIn govTxInIdentifier _govTxId) anyStake) outFp =
case anyStake of
AnyDRepVerificationKeyOrHashOrFile stake -> do
let sbe = conwayEraOnwardsToShelleyBasedEra cOnwards -- TODO: Conway era - update vote creation related function to take ConwayEraOnwards
DRepKeyHash h <- firstExceptT EraBasedVoteReadError
. newExceptT $ readVerificationKeyOrHashOrTextEnvFile AsDRepKey stake
let vStakeCred = StakeCredentialByKey . StakeKeyHash $ coerceKeyRole h

votingCred <- hoistEither $ first EraBasedVotingCredentialDecodeError $ toVotingCredential sbe vStakeCred
let govActIdentifier = makeGoveranceActionId sbe govTxInIdentifier (error "TODO: Conway era - the TxInId does not determine the govActId")
voteProcedure = createVotingProcedure sbe v (VoterDRep votingCred) govActIdentifier
firstExceptT EraBasedVoteWriteError . newExceptT
$ shelleyBasedEraConstraints sbe $ writeFileTextEnvelope outFp Nothing voteProcedure

AnyStakePoolVerificationKeyOrHashOrFile stake -> do
let sbe = conwayEraOnwardsToShelleyBasedEra cOnwards -- TODO: Conway era - update vote creation related function to take ConwayEraOnwards
h <- firstExceptT EraBasedVoteReadError
. newExceptT $ readVerificationKeyOrHashOrTextEnvFile AsStakePoolKey stake

let govActIdentifier = makeGoveranceActionId sbe govTxInIdentifier (error "TODO: Conway era - the TxInId does not determine the govActId")
voteProcedure = createVotingProcedure sbe v (VoterSpo h) govActIdentifier
firstExceptT EraBasedVoteWriteError . newExceptT
$ shelleyBasedEraConstraints sbe $ writeFileTextEnvelope outFp Nothing voteProcedure

AnyCommitteeHotVerificationKeyOrHashOrFile stake -> do
let sbe = conwayEraOnwardsToShelleyBasedEra cOnwards -- TODO: Conway era - update vote creation related function to take ConwayEraOnwards
CommitteeHotKeyHash h <- firstExceptT EraBasedVoteReadError
. newExceptT $ readVerificationKeyOrHashOrTextEnvFile AsCommitteeHotKey stake
let vStakeCred = StakeCredentialByKey . StakeKeyHash $ coerceKeyRole h
votingCred <- hoistEither $ first EraBasedVotingCredentialDecodeError $ toVotingCredential sbe vStakeCred

let govActIdentifier = makeGoveranceActionId sbe govTxInIdentifier (error "TODO: Conway era - the TxInId does not determine the govActId")
voteProcedure = createVotingProcedure sbe v (VoterCommittee votingCred) govActIdentifier
firstExceptT EraBasedVoteWriteError . newExceptT
$ shelleyBasedEraConstraints sbe $ writeFileTextEnvelope outFp Nothing voteProcedure
runGovernanceVote (ConwayOnwardsVote cOnwards v) outFp = do
let sbe = conwayEraOnwardsToShelleyBasedEra cOnwards -- TODO: Conway era - update vote creation related function to take ConwayEraOnwards
voteProcedure = createVotingProcedure sbe v Nothing
firstExceptT EraBasedVoteWriteError . newExceptT
$ shelleyBasedEraConstraints sbe $ writeFileTextEnvelope outFp Nothing voteProcedure
4 changes: 1 addition & 3 deletions cardano-cli/src/Cardano/CLI/Legacy/Commands/Governance.hs
Original file line number Diff line number Diff line change
Expand Up @@ -93,9 +93,6 @@ pCreateVote envCli =
fmap CreateVoteCmd $
ConwayVote
<$> pVoteChoice
<*> pVoterType
<*> pGoveranceActionIdentifier "TxIn of governance action (already on chain)."
<*> pVotingCredential
<*> (pShelleyBasedConway envCli <|> pure (AnyShelleyBasedEra ShelleyBasedEraConway))
<*> pFileOutDirection "out-file" "Output filepath of the vote."

Expand Down Expand Up @@ -131,6 +128,7 @@ pCreateConstitution envCli =
<*> pGovActionDeposit
<*> pVotingCredential
<*> pPreviousGovernanceAction
<*> pProposalAnchor
<*> pConstitution
<*> pFileOutDirection "out-file" "Output filepath of the governance action."

Expand Down
8 changes: 4 additions & 4 deletions cardano-cli/src/Cardano/CLI/Legacy/Run/Governance.hs
Original file line number Diff line number Diff line change
Expand Up @@ -42,10 +42,10 @@ import System.IO (stderr, stdin, stdout)

runGovernanceCmds :: LegacyGovernanceCmds -> ExceptT GovernanceCmdError IO ()
runGovernanceCmds = \case
GovernanceVoteCmd (CreateVoteCmd (ConwayVote voteChoice voteType govActTcIn voteStakeCred sbe fp)) ->
runGovernanceCreateVoteCmd sbe voteChoice voteType govActTcIn voteStakeCred fp
GovernanceActionCmd (CreateConstitution (Cli.NewConstitution network sbe deposit voteStakeCred mPrevGovActId newconstitution fp)) ->
runGovernanceNewConstitutionCmd network sbe deposit voteStakeCred mPrevGovActId newconstitution fp
GovernanceVoteCmd (CreateVoteCmd (ConwayVote voteChoice sbe fp)) ->
runGovernanceCreateVoteCmd sbe voteChoice fp
GovernanceActionCmd (CreateConstitution (Cli.NewConstitution network sbe deposit voteStakeCred mPrevGovActId propAnchor newconstitution fp)) ->
runGovernanceNewConstitutionCmd network sbe deposit voteStakeCred mPrevGovActId propAnchor newconstitution fp
GovernanceMIRPayStakeAddressesCertificate (AnyShelleyToBabbageEra w) mirpot vKeys rewards out ->
runGovernanceMIRCertificatePayStakeAddrs w mirpot vKeys rewards out
GovernanceMIRTransfer (AnyShelleyToBabbageEra w) amt out direction -> do
Expand Down
5 changes: 0 additions & 5 deletions cardano-cli/src/Cardano/CLI/Types/Governance.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,9 +18,6 @@ type VoteFile = File ConwayVote
data ConwayVote
= ConwayVote
{ cvVoteChoice :: Vote
, cvVoterType :: VType
, cvGovActionTxIn :: TxIn
, cvVotingStakeCredential :: VerificationKeyOrFile StakePoolKey
, cvEra :: AnyShelleyBasedEra
, cvFilepath :: VoteFile Out
} deriving Show
Expand Down Expand Up @@ -49,8 +46,6 @@ data AnyVote where
ConwayOnwardsVote
:: ConwayEraOnwards era
-> Vote
-> TxIn
-> AnyVotingStakeVerificationKeyOrHashOrFile
-> AnyVote

data AnyVotingStakeVerificationKeyOrHashOrFile where
Expand Down

0 comments on commit eed575f

Please sign in to comment.