Skip to content

Commit

Permalink
Added ToCBOR and FromCBOR instances to Vote and GovernanceAction
Browse files Browse the repository at this point in the history
  • Loading branch information
Soupstraw committed Dec 2, 2022
1 parent bed3048 commit ea1fffc
Show file tree
Hide file tree
Showing 2 changed files with 145 additions and 29 deletions.
165 changes: 136 additions & 29 deletions eras/conway/impl/src/Cardano/Ledger/Conway/Core.hs
@@ -1,34 +1,53 @@
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}

module Cardano.Ledger.Conway.Core
( ConwayEraTxBody (..),
GovernanceActionInfo (..),
GovernanceAction (..),
GovernanceActionIx,
Vote (..),
VoteDecision (..),
)
where

import Cardano.Ledger.Babbage.Core (BabbageEraTxBody, Era (..), EraTxBody (..))
import Cardano.Ledger.BaseTypes (ProtVer (..))
import Cardano.Ledger.Binary (FromCBOR (..), ToCBOR (..))
import Cardano.Ledger.Binary.Coders
( Decode (..),
Encode (..),
decode,
encode,
(!>),
(<!),
)
import Cardano.Ledger.Coin (Coin (..))
import Cardano.Ledger.Core (EraPParams (..))
import Cardano.Ledger.Credential (Credential)
import Cardano.Ledger.Crypto (Crypto)
import Cardano.Ledger.Keys (KeyHash (..), KeyRole (..))
import Cardano.Ledger.SafeHash (SafeHash)
import Cardano.Ledger.Shelley.TxBody (Url)
import Cardano.Ledger.TxIn (TxId)
import Control.DeepSeq (NFData)
import Data.ByteString (ByteString)
import Data.Map.Strict (Map)
import Data.Sequence.Strict (StrictSeq)
import Data.Word (Word64)
import GHC.Generics (Generic)
import Lens.Micro (Lens')
import NoThunks.Class (NoThunks)
import Cardano.Ledger.Coin (Coin(..))
import Cardano.Ledger.Keys (KeyHash(..), KeyRole (..))
import Cardano.Ledger.Shelley.TxBody (Url)
import Cardano.Ledger.SafeHash (SafeHash)
import Data.ByteString (ByteString)
import Cardano.Ledger.Core (EraPParams(..))
import Cardano.Ledger.BaseTypes (TxIx(..), ProtVer (..))
import Data.Map.Strict (Map)
import Cardano.Ledger.Credential (Credential)

class BabbageEraTxBody era => ConwayEraTxBody era where
govActionsL :: Lens' (TxBody era) (StrictSeq (GovernanceActionInfo era))
Expand Down Expand Up @@ -73,45 +92,133 @@ instance NoThunks (PParamsUpdate era) => NoThunks (GovernanceAction era)

instance NFData (PParamsUpdate era) => NFData (GovernanceAction era)

newtype GovernanceActionIx = GovernanceActionIx Word64
deriving (Generic, Eq, Show)

instance NoThunks GovernanceActionIx

instance NFData GovernanceActionIx

deriving newtype instance FromCBOR GovernanceActionIx

deriving newtype instance ToCBOR GovernanceActionIx

data GovernanceActionId c = GovernanceActionId
{ gaidTransactionId :: TxId c,
gaidGovActionIx :: GovernanceActionIx
}
deriving (Generic, Eq, Show)

instance Crypto c => FromCBOR (GovernanceActionId c) where
fromCBOR =
decode $
RecD GovernanceActionId
<! From
<! From

instance NoThunks (GovernanceActionId c)

instance Crypto c => NFData (GovernanceActionId c)

data Vote era = Vote
{ voteGovActionID :: TxIx,
{ voteGovActionId :: GovernanceActionId (EraCrypto era),
voteRole :: VoterRole,
voteRoleKeyHash :: KeyHash 'Voting (EraCrypto era),
voteMetadataURL :: Url,
voteMetadataHash :: SafeHash (EraCrypto era) ByteString,
voteDecision :: VoteDecision
}
deriving (Generic, Eq)
deriving (Generic, Eq, Show)

instance NoThunks (Vote era)

instance Crypto (EraCrypto era) => NFData (Vote era)

instance
( Era era,
Crypto (EraCrypto era)
) =>
FromCBOR (Vote era)
where
fromCBOR =
decode $
RecD Vote
<! From
<! From
<! From
<! From
<! From
<! From

instance Crypto c => ToCBOR (GovernanceActionId c) where
toCBOR GovernanceActionId {..} =
encode $
Rec GovernanceActionId
!> To gaidTransactionId
!> To gaidGovActionIx

instance
( Era era,
Crypto (EraCrypto era)
) =>
ToCBOR (Vote era)
where
toCBOR Vote {..} =
encode $
Rec (Vote @era)
!> To voteGovActionId
!> To voteRole
!> To voteRoleKeyHash
!> To voteMetadataURL
!> To voteMetadataHash
!> To voteDecision

data VoterRole
= ConstitutionalCommittee
| DRep
| SPO
deriving (Generic, Eq)
deriving (Generic, Eq, Show, Enum)

instance FromCBOR VoterRole where
fromCBOR =
decode $
Summands "VoterRole" dec
where
dec 0 = SumD ConstitutionalCommittee
dec 1 = SumD DRep
dec 2 = SumD SPO
dec k = Invalid k

instance ToCBOR VoterRole where
toCBOR x =
encode $
Sum x (fromIntegral $ fromEnum x)

instance NoThunks VoterRole

instance NFData VoterRole

data VoteDecision
= Yes
| No
= No
| Yes
| Abstain
deriving (Generic, Eq)
deriving (Generic, Eq, Show, Enum)

instance NoThunks VoteDecision

instance NFData VoteDecision

instance NoThunks (Vote era)

instance NFData (Vote era)

instance Show (Vote era) where
show = undefined

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

instance Era era => ToCBOR (Vote era) where
toCBOR = undefined
instance FromCBOR VoteDecision where
fromCBOR =
decode $
Summands "VoteDecision" dec
where
dec 0 = SumD No
dec 1 = SumD Yes
dec 2 = SumD Abstain
dec k = Invalid k

instance ToCBOR VoteDecision where
toCBOR x =
encode $
Sum x (fromIntegral $ fromEnum x)
9 changes: 9 additions & 0 deletions eras/conway/test-suite/cddl-files/conway.cddl
Expand Up @@ -90,6 +90,15 @@ hard_fork_initiation_action = protocol_version

treasury_withdrawals_action = $addr_keyhash => coin

vote =
[ governance_action_id : governance_action_id
]

governance_action_id =
[ transaction_id : $hash32
, governance_action_index : uint
]

required_signers = set<$addr_keyhash>

transaction_input = [ transaction_id : $hash32
Expand Down

0 comments on commit ea1fffc

Please sign in to comment.