Skip to content

Commit

Permalink
Expose createProposalProcedure, GovernanceAction, Proposal
Browse files Browse the repository at this point in the history
Implement Proposal
  • Loading branch information
Jimbo4350 committed Jun 29, 2023
1 parent 82f57df commit abc4226
Show file tree
Hide file tree
Showing 4 changed files with 35 additions and 5 deletions.
Original file line number Diff line number Diff line change
@@ -1,11 +1,15 @@
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeFamilies #-}

module Cardano.Api.Governance.Actions.ProposalProcedure where

import Cardano.Api.Eras
import Cardano.Api.HasTypeProxy
import Cardano.Api.Keys.Shelley
import Cardano.Api.SerialiseCBOR
import Cardano.Api.SerialiseTextEnvelope
import Cardano.Api.Utils
import Cardano.Api.Value

Expand All @@ -16,7 +20,6 @@ import Cardano.Ledger.SafeHash

import Data.ByteString (ByteString)
import Data.Maybe.Strict
import Data.Proxy

-- | A representation of whether the era supports tx governance actions.
--
Expand Down Expand Up @@ -67,14 +70,35 @@ toGovernanceAction MotionOfNoConfidence = Gov.NoConfidence
toGovernanceAction (ProposeNewConstitution bs) =
Gov.NewConstitution $ toSafeHash bs

newtype Proposal era = Proposal { unProposal :: Gov.ProposalProcedure (ShelleyLedgerEra era) }
instance IsShelleyBasedEra era => ToCBOR (Proposal era) where
toCBOR (Proposal _vp) = undefined

instance IsShelleyBasedEra era => FromCBOR (Proposal era) where
fromCBOR = undefined

instance IsShelleyBasedEra era => SerialiseAsCBOR (Proposal era) where

serialiseToCBOR = undefined
deserialiseFromCBOR = undefined


instance IsShelleyBasedEra era => HasTextEnvelope (Proposal era) where
textEnvelopeType _ = "Governance proposal"

instance HasTypeProxy era => HasTypeProxy (Proposal era) where
data AsType (Proposal era) = AsProposal
proxyToAsType _ = AsProposal


createProposalProcedure
:: ShelleyBasedEra era
-> Lovelace -- ^ Deposit
-> Hash StakeKey -- ^ Return address
-> GovernanceAction
-> Gov.ProposalProcedure (ShelleyLedgerEra era)
-> Proposal era
createProposalProcedure sbe dep (StakeKeyHash retAddrh) govAct =
obtainEraCryptoConstraints sbe $
Proposal $ obtainEraCryptoConstraints sbe $
Gov.ProposalProcedure
{ Gov.pProcDeposit = toShelleyLovelace dep
, Gov.pProcReturnAddr = retAddrh
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -13,7 +13,8 @@ import Cardano.Api.Address
import Cardano.Api.Eras
import Cardano.Api.HasTypeProxy
import Cardano.Api.Script
import Cardano.Api.SerialiseCBOR
import Cardano.Api.SerialiseCBOR (FromCBOR (fromCBOR), SerialiseAsCBOR (..),
ToCBOR (toCBOR))
import Cardano.Api.SerialiseTextEnvelope
import Cardano.Api.TxIn
import Cardano.Api.Utils
Expand Down Expand Up @@ -171,6 +172,7 @@ instance IsShelleyBasedEra era => ToCBOR (Vote era) where

instance IsShelleyBasedEra era => FromCBOR (Vote era) where
fromCBOR = undefined

instance IsShelleyBasedEra era => SerialiseAsCBOR (Vote era) where

serialiseToCBOR = undefined
Expand Down
2 changes: 1 addition & 1 deletion cardano-api/internal/Cardano/Api/TxBody.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3623,7 +3623,7 @@ convGovActions :: ShelleyBasedEra era -> TxGovernanceActions era -> Seq.StrictSe
convGovActions _ TxGovernanceActionsNone = Seq.empty
convGovActions sbe (TxGovernanceActions _ govActions) =
Seq.fromList
[ createProposalProcedure sbe deposit stakeCred action
[ unProposal $ createProposalProcedure sbe deposit stakeCred action
| (deposit, stakeCred, action) <- govActions
]

Expand Down
4 changes: 4 additions & 0 deletions cardano-api/src/Cardano/Api/Shelley.hs
Original file line number Diff line number Diff line change
Expand Up @@ -237,7 +237,9 @@ module Cardano.Api.Shelley
SystemStart(..),

-- ** Governance
GovernanceAction(..),
GovernanceActionIdentifier(..),
Proposal(..),
TxGovernanceActions(..),
TxVotes(..),
GovernancePoll (..),
Expand All @@ -246,6 +248,7 @@ module Cardano.Api.Shelley
VoteChoice(..),
VotingCredential(..),
VoterType(..),
createProposalProcedure,
createVotingProcedure,
makeGoveranceActionIdentifier,
renderGovernancePollError,
Expand Down Expand Up @@ -274,6 +277,7 @@ import Cardano.Api.Certificate
import Cardano.Api.DRepMetadata
import Cardano.Api.Eras
import Cardano.Api.Genesis
import Cardano.Api.Governance.Actions.ProposalProcedure
import Cardano.Api.Governance.Actions.VotingProcedure
import Cardano.Api.Governance.Poll
import Cardano.Api.InMode
Expand Down

0 comments on commit abc4226

Please sign in to comment.