{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuantifiedConstraints #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE RoleAnnotations #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
module Cardano.Ledger.Conway.Governance.Procedures (
VotingProcedures (..),
VotingProcedure (..),
foldlVotingProcedures,
foldrVotingProcedures,
ProposalProcedure (..),
Anchor (..),
AnchorData (..),
Vote (..),
Voter (..),
Committee (..),
GovAction (..),
GovActionId (..),
GovActionIx (..),
GovPurposeId (..),
GovActionPurpose (..),
ToGovActionPurpose,
isGovActionWithPurpose,
GovRelation (..),
grPParamUpdateL,
grHardForkL,
grCommitteeL,
grConstitutionL,
hoistGovRelation,
withGovActionParent,
GovActionState (..),
govActionIdToText,
indexedGovProps,
Constitution (..),
constitutionAnchorL,
constitutionScriptL,
showGovActionType,
pProcDepositL,
pProcGovActionL,
pProcReturnAddrL,
pProcAnchorL,
committeeMembersL,
committeeThresholdL,
gasDRepVotesL,
gasStakePoolVotesL,
gasCommitteeVotesL,
gasExpiresAfterL,
gasProposalProcedureL,
gasActionL,
gasReturnAddrL,
gasProposedInL,
gasIdL,
gasDepositL,
gasDeposit,
gasAction,
gasReturnAddr,
) where
import Cardano.Crypto.Hash (hashToTextAsHex)
import Cardano.Ledger.Address (RewardAccount)
import Cardano.Ledger.Alonzo.TxBody (Indexable (..))
import Cardano.Ledger.Babbage.Core
import Cardano.Ledger.BaseTypes (
Anchor (..),
AnchorData (..),
ProtVer,
UnitInterval,
maybeToStrictMaybe,
)
import Cardano.Ledger.Binary (
DecCBOR (..),
DecShareCBOR (..),
EncCBOR (..),
FromCBOR (fromCBOR),
ToCBOR (toCBOR),
decNoShareCBOR,
decodeEnumBounded,
decodeMapByKey,
decodeNullStrictMaybe,
decodeRecordNamed,
encodeEnum,
encodeListLen,
encodeNullStrictMaybe,
encodeWord8,
invalidKey,
)
import Cardano.Ledger.Binary.Coders (
Decode (..),
Encode (..),
decode,
decodeRecordSum,
encode,
(!>),
(<!),
)
import Cardano.Ledger.Coin (Coin)
import Cardano.Ledger.Credential (Credential (..), credToText)
import Cardano.Ledger.Shelley.RewardProvenance ()
import Cardano.Ledger.TxIn (TxId (..))
import Cardano.Slotting.Slot (EpochNo)
import Control.DeepSeq (NFData (..), deepseq)
import Control.Monad (when)
import Data.Aeson (
FromJSON (..),
KeyValue (..),
ToJSON (..),
ToJSONKey (..),
object,
pairs,
withObject,
(.:),
(.:?),
)
import Data.Aeson.Types (toJSONKeyText)
import Data.Data (Typeable)
import Data.Default
import Data.Kind
import Data.Map.Strict (Map)
import qualified Data.Map.Strict as Map
import Data.Maybe.Strict (StrictMaybe (..))
import qualified Data.OMap.Strict as OMap
import qualified Data.Sequence as Seq
import Data.Set (Set)
import qualified Data.Text as Text
import Data.Unit.Strict (forceElemsToWHNF)
import Data.Word (Word16)
import GHC.Generics (Generic)
import Lens.Micro (Lens', lens, (^.))
import NoThunks.Class (NoThunks)
newtype GovActionIx = GovActionIx {GovActionIx -> Word16
unGovActionIx :: Word16}
deriving
( forall x. Rep GovActionIx x -> GovActionIx
forall x. GovActionIx -> Rep GovActionIx x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GovActionIx x -> GovActionIx
$cfrom :: forall x. GovActionIx -> Rep GovActionIx x
Generic
, GovActionIx -> GovActionIx -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GovActionIx -> GovActionIx -> Bool
$c/= :: GovActionIx -> GovActionIx -> Bool
== :: GovActionIx -> GovActionIx -> Bool
$c== :: GovActionIx -> GovActionIx -> Bool
Eq
, Eq GovActionIx
GovActionIx -> GovActionIx -> Bool
GovActionIx -> GovActionIx -> Ordering
GovActionIx -> GovActionIx -> GovActionIx
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: GovActionIx -> GovActionIx -> GovActionIx
$cmin :: GovActionIx -> GovActionIx -> GovActionIx
max :: GovActionIx -> GovActionIx -> GovActionIx
$cmax :: GovActionIx -> GovActionIx -> GovActionIx
>= :: GovActionIx -> GovActionIx -> Bool
$c>= :: GovActionIx -> GovActionIx -> Bool
> :: GovActionIx -> GovActionIx -> Bool
$c> :: GovActionIx -> GovActionIx -> Bool
<= :: GovActionIx -> GovActionIx -> Bool
$c<= :: GovActionIx -> GovActionIx -> Bool
< :: GovActionIx -> GovActionIx -> Bool
$c< :: GovActionIx -> GovActionIx -> Bool
compare :: GovActionIx -> GovActionIx -> Ordering
$ccompare :: GovActionIx -> GovActionIx -> Ordering
Ord
, Int -> GovActionIx -> ShowS
[GovActionIx] -> ShowS
GovActionIx -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GovActionIx] -> ShowS
$cshowList :: [GovActionIx] -> ShowS
show :: GovActionIx -> String
$cshow :: GovActionIx -> String
showsPrec :: Int -> GovActionIx -> ShowS
$cshowsPrec :: Int -> GovActionIx -> ShowS
Show
, GovActionIx -> ()
forall a. (a -> ()) -> NFData a
rnf :: GovActionIx -> ()
$crnf :: GovActionIx -> ()
NFData
, Context -> GovActionIx -> IO (Maybe ThunkInfo)
Proxy GovActionIx -> String
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy GovActionIx -> String
$cshowTypeOf :: Proxy GovActionIx -> String
wNoThunks :: Context -> GovActionIx -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> GovActionIx -> IO (Maybe ThunkInfo)
noThunks :: Context -> GovActionIx -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> GovActionIx -> IO (Maybe ThunkInfo)
NoThunks
, Typeable GovActionIx
GovActionIx -> Encoding
(forall t. EncCBOR t => Proxy t -> Size)
-> Proxy [GovActionIx] -> Size
(forall t. EncCBOR t => Proxy t -> Size)
-> Proxy GovActionIx -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. EncCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> EncCBOR a
encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy [GovActionIx] -> Size
$cencodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy [GovActionIx] -> Size
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy GovActionIx -> Size
$cencodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy GovActionIx -> Size
encCBOR :: GovActionIx -> Encoding
$cencCBOR :: GovActionIx -> Encoding
EncCBOR
, Typeable GovActionIx
Proxy GovActionIx -> Text
forall s. Decoder s GovActionIx
forall a.
Typeable a
-> (forall s. Decoder s a)
-> (forall s. Proxy a -> Decoder s ())
-> (Proxy a -> Text)
-> DecCBOR a
forall s. Proxy GovActionIx -> Decoder s ()
label :: Proxy GovActionIx -> Text
$clabel :: Proxy GovActionIx -> Text
dropCBOR :: forall s. Proxy GovActionIx -> Decoder s ()
$cdropCBOR :: forall s. Proxy GovActionIx -> Decoder s ()
decCBOR :: forall s. Decoder s GovActionIx
$cdecCBOR :: forall s. Decoder s GovActionIx
DecCBOR
, [GovActionIx] -> Encoding
[GovActionIx] -> Value
GovActionIx -> Bool
GovActionIx -> Encoding
GovActionIx -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
omitField :: GovActionIx -> Bool
$comitField :: GovActionIx -> Bool
toEncodingList :: [GovActionIx] -> Encoding
$ctoEncodingList :: [GovActionIx] -> Encoding
toJSONList :: [GovActionIx] -> Value
$ctoJSONList :: [GovActionIx] -> Value
toEncoding :: GovActionIx -> Encoding
$ctoEncoding :: GovActionIx -> Encoding
toJSON :: GovActionIx -> Value
$ctoJSON :: GovActionIx -> Value
ToJSON
)
data GovActionId = GovActionId
{ GovActionId -> TxId
gaidTxId :: !TxId
, GovActionId -> GovActionIx
gaidGovActionIx :: !GovActionIx
}
deriving (forall x. Rep GovActionId x -> GovActionId
forall x. GovActionId -> Rep GovActionId x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GovActionId x -> GovActionId
$cfrom :: forall x. GovActionId -> Rep GovActionId x
Generic, Int -> GovActionId -> ShowS
[GovActionId] -> ShowS
GovActionId -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GovActionId] -> ShowS
$cshowList :: [GovActionId] -> ShowS
show :: GovActionId -> String
$cshow :: GovActionId -> String
showsPrec :: Int -> GovActionId -> ShowS
$cshowsPrec :: Int -> GovActionId -> ShowS
Show, GovActionId -> GovActionId -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GovActionId -> GovActionId -> Bool
$c/= :: GovActionId -> GovActionId -> Bool
== :: GovActionId -> GovActionId -> Bool
$c== :: GovActionId -> GovActionId -> Bool
Eq, Eq GovActionId
GovActionId -> GovActionId -> Bool
GovActionId -> GovActionId -> Ordering
GovActionId -> GovActionId -> GovActionId
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: GovActionId -> GovActionId -> GovActionId
$cmin :: GovActionId -> GovActionId -> GovActionId
max :: GovActionId -> GovActionId -> GovActionId
$cmax :: GovActionId -> GovActionId -> GovActionId
>= :: GovActionId -> GovActionId -> Bool
$c>= :: GovActionId -> GovActionId -> Bool
> :: GovActionId -> GovActionId -> Bool
$c> :: GovActionId -> GovActionId -> Bool
<= :: GovActionId -> GovActionId -> Bool
$c<= :: GovActionId -> GovActionId -> Bool
< :: GovActionId -> GovActionId -> Bool
$c< :: GovActionId -> GovActionId -> Bool
compare :: GovActionId -> GovActionId -> Ordering
$ccompare :: GovActionId -> GovActionId -> Ordering
Ord)
instance DecCBOR GovActionId where
decCBOR :: forall s. Decoder s GovActionId
decCBOR =
forall (w :: Wrapped) t s. Decode w t -> Decoder s t
decode forall a b. (a -> b) -> a -> b
$
forall t. t -> Decode ('Closed 'Dense) t
RecD TxId -> GovActionIx -> GovActionId
GovActionId
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t (w :: Wrapped). DecCBOR t => Decode w t
From
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t (w :: Wrapped). DecCBOR t => Decode w t
From
instance EncCBOR GovActionId where
encCBOR :: GovActionId -> Encoding
encCBOR GovActionId {TxId
GovActionIx
gaidGovActionIx :: GovActionIx
gaidTxId :: TxId
gaidGovActionIx :: GovActionId -> GovActionIx
gaidTxId :: GovActionId -> TxId
..} =
forall (w :: Wrapped) t. Encode w t -> Encoding
encode forall a b. (a -> b) -> a -> b
$
forall t. t -> Encode ('Closed 'Dense) t
Rec TxId -> GovActionIx -> GovActionId
GovActionId
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To TxId
gaidTxId
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To GovActionIx
gaidGovActionIx
instance NoThunks GovActionId
instance NFData GovActionId
instance ToJSON GovActionId where
toJSON :: GovActionId -> Value
toJSON = [Pair] -> Value
object forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall e a. KeyValue e a => GovActionId -> [a]
toGovActionIdPairs
toEncoding :: GovActionId -> Encoding
toEncoding = Series -> Encoding
pairs forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Monoid a => [a] -> a
mconcat forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall e a. KeyValue e a => GovActionId -> [a]
toGovActionIdPairs
toGovActionIdPairs :: KeyValue e a => GovActionId -> [a]
toGovActionIdPairs :: forall e a. KeyValue e a => GovActionId -> [a]
toGovActionIdPairs gaid :: GovActionId
gaid@(GovActionId TxId
_ GovActionIx
_) =
let GovActionId {TxId
GovActionIx
gaidGovActionIx :: GovActionIx
gaidTxId :: TxId
gaidGovActionIx :: GovActionId -> GovActionIx
gaidTxId :: GovActionId -> TxId
..} = GovActionId
gaid
in [ Key
"txId" forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= TxId
gaidTxId
, Key
"govActionIx" forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= GovActionIx
gaidGovActionIx
]
instance ToJSONKey GovActionId where
toJSONKey :: ToJSONKeyFunction GovActionId
toJSONKey = forall a. (a -> Text) -> ToJSONKeyFunction a
toJSONKeyText GovActionId -> Text
govActionIdToText
govActionIdToText :: GovActionId -> Text.Text
govActionIdToText :: GovActionId -> Text
govActionIdToText (GovActionId (TxId SafeHash EraIndependentTxBody
txidHash) (GovActionIx Word16
ix)) =
forall h a. Hash h a -> Text
hashToTextAsHex (forall i. SafeHash i -> Hash HASH i
extractHash SafeHash EraIndependentTxBody
txidHash)
forall a. Semigroup a => a -> a -> a
<> String -> Text
Text.pack String
"#"
forall a. Semigroup a => a -> a -> a
<> String -> Text
Text.pack (forall a. Show a => a -> String
show Word16
ix)
data GovActionState era = GovActionState
{ forall era. GovActionState era -> GovActionId
gasId :: !GovActionId
, forall era.
GovActionState era -> Map (Credential 'HotCommitteeRole) Vote
gasCommitteeVotes :: !(Map (Credential 'HotCommitteeRole) Vote)
, forall era. GovActionState era -> Map (Credential 'DRepRole) Vote
gasDRepVotes :: !(Map (Credential 'DRepRole) Vote)
, forall era. GovActionState era -> Map (KeyHash 'StakePool) Vote
gasStakePoolVotes :: !(Map (KeyHash 'StakePool) Vote)
, forall era. GovActionState era -> ProposalProcedure era
gasProposalProcedure :: !(ProposalProcedure era)
, forall era. GovActionState era -> EpochNo
gasProposedIn :: !EpochNo
, forall era. GovActionState era -> EpochNo
gasExpiresAfter :: !EpochNo
}
deriving (GovActionState era -> GovActionState era -> Bool
GovActionState era -> GovActionState era -> Ordering
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall {era}. EraPParams era => Eq (GovActionState era)
forall era.
EraPParams era =>
GovActionState era -> GovActionState era -> Bool
forall era.
EraPParams era =>
GovActionState era -> GovActionState era -> Ordering
forall era.
EraPParams era =>
GovActionState era -> GovActionState era -> GovActionState era
min :: GovActionState era -> GovActionState era -> GovActionState era
$cmin :: forall era.
EraPParams era =>
GovActionState era -> GovActionState era -> GovActionState era
max :: GovActionState era -> GovActionState era -> GovActionState era
$cmax :: forall era.
EraPParams era =>
GovActionState era -> GovActionState era -> GovActionState era
>= :: GovActionState era -> GovActionState era -> Bool
$c>= :: forall era.
EraPParams era =>
GovActionState era -> GovActionState era -> Bool
> :: GovActionState era -> GovActionState era -> Bool
$c> :: forall era.
EraPParams era =>
GovActionState era -> GovActionState era -> Bool
<= :: GovActionState era -> GovActionState era -> Bool
$c<= :: forall era.
EraPParams era =>
GovActionState era -> GovActionState era -> Bool
< :: GovActionState era -> GovActionState era -> Bool
$c< :: forall era.
EraPParams era =>
GovActionState era -> GovActionState era -> Bool
compare :: GovActionState era -> GovActionState era -> Ordering
$ccompare :: forall era.
EraPParams era =>
GovActionState era -> GovActionState era -> Ordering
Ord, forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall era x. Rep (GovActionState era) x -> GovActionState era
forall era x. GovActionState era -> Rep (GovActionState era) x
$cto :: forall era x. Rep (GovActionState era) x -> GovActionState era
$cfrom :: forall era x. GovActionState era -> Rep (GovActionState era) x
Generic)
gasIdL :: Lens' (GovActionState era) GovActionId
gasIdL :: forall era. Lens' (GovActionState era) GovActionId
gasIdL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall era. GovActionState era -> GovActionId
gasId forall a b. (a -> b) -> a -> b
$ \GovActionState era
x GovActionId
y -> GovActionState era
x {gasId :: GovActionId
gasId = GovActionId
y}
gasCommitteeVotesL ::
Lens' (GovActionState era) (Map (Credential 'HotCommitteeRole) Vote)
gasCommitteeVotesL :: forall era.
Lens'
(GovActionState era) (Map (Credential 'HotCommitteeRole) Vote)
gasCommitteeVotesL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall era.
GovActionState era -> Map (Credential 'HotCommitteeRole) Vote
gasCommitteeVotes (\GovActionState era
x Map (Credential 'HotCommitteeRole) Vote
y -> GovActionState era
x {gasCommitteeVotes :: Map (Credential 'HotCommitteeRole) Vote
gasCommitteeVotes = Map (Credential 'HotCommitteeRole) Vote
y})
gasDRepVotesL :: Lens' (GovActionState era) (Map (Credential 'DRepRole) Vote)
gasDRepVotesL :: forall era.
Lens' (GovActionState era) (Map (Credential 'DRepRole) Vote)
gasDRepVotesL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall era. GovActionState era -> Map (Credential 'DRepRole) Vote
gasDRepVotes (\GovActionState era
x Map (Credential 'DRepRole) Vote
y -> GovActionState era
x {gasDRepVotes :: Map (Credential 'DRepRole) Vote
gasDRepVotes = Map (Credential 'DRepRole) Vote
y})
gasStakePoolVotesL :: Lens' (GovActionState era) (Map (KeyHash 'StakePool) Vote)
gasStakePoolVotesL :: forall era.
Lens' (GovActionState era) (Map (KeyHash 'StakePool) Vote)
gasStakePoolVotesL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall era. GovActionState era -> Map (KeyHash 'StakePool) Vote
gasStakePoolVotes (\GovActionState era
x Map (KeyHash 'StakePool) Vote
y -> GovActionState era
x {gasStakePoolVotes :: Map (KeyHash 'StakePool) Vote
gasStakePoolVotes = Map (KeyHash 'StakePool) Vote
y})
gasProposalProcedureL :: Lens' (GovActionState era) (ProposalProcedure era)
gasProposalProcedureL :: forall era. Lens' (GovActionState era) (ProposalProcedure era)
gasProposalProcedureL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall era. GovActionState era -> ProposalProcedure era
gasProposalProcedure (\GovActionState era
x ProposalProcedure era
y -> GovActionState era
x {gasProposalProcedure :: ProposalProcedure era
gasProposalProcedure = ProposalProcedure era
y})
gasDepositL :: Lens' (GovActionState era) Coin
gasDepositL :: forall era. Lens' (GovActionState era) Coin
gasDepositL = forall era. Lens' (GovActionState era) (ProposalProcedure era)
gasProposalProcedureL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (ProposalProcedure era) Coin
pProcDepositL
gasDeposit :: GovActionState era -> Coin
gasDeposit :: forall era. GovActionState era -> Coin
gasDeposit = forall era. ProposalProcedure era -> Coin
pProcDeposit forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. GovActionState era -> ProposalProcedure era
gasProposalProcedure
gasReturnAddrL :: Lens' (GovActionState era) RewardAccount
gasReturnAddrL :: forall era. Lens' (GovActionState era) RewardAccount
gasReturnAddrL = forall era. Lens' (GovActionState era) (ProposalProcedure era)
gasProposalProcedureL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (ProposalProcedure era) RewardAccount
pProcReturnAddrL
gasReturnAddr :: GovActionState era -> RewardAccount
gasReturnAddr :: forall era. GovActionState era -> RewardAccount
gasReturnAddr = forall era. ProposalProcedure era -> RewardAccount
pProcReturnAddr forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. GovActionState era -> ProposalProcedure era
gasProposalProcedure
gasActionL :: Lens' (GovActionState era) (GovAction era)
gasActionL :: forall era. Lens' (GovActionState era) (GovAction era)
gasActionL = forall era. Lens' (GovActionState era) (ProposalProcedure era)
gasProposalProcedureL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (ProposalProcedure era) (GovAction era)
pProcGovActionL
gasAction :: GovActionState era -> GovAction era
gasAction :: forall era. GovActionState era -> GovAction era
gasAction = forall era. ProposalProcedure era -> GovAction era
pProcGovAction forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. GovActionState era -> ProposalProcedure era
gasProposalProcedure
gasProposedInL :: Lens' (GovActionState era) EpochNo
gasProposedInL :: forall era. Lens' (GovActionState era) EpochNo
gasProposedInL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall era. GovActionState era -> EpochNo
gasProposedIn forall a b. (a -> b) -> a -> b
$ \GovActionState era
x EpochNo
y -> GovActionState era
x {gasProposedIn :: EpochNo
gasProposedIn = EpochNo
y}
gasExpiresAfterL :: Lens' (GovActionState era) EpochNo
gasExpiresAfterL :: forall era. Lens' (GovActionState era) EpochNo
gasExpiresAfterL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall era. GovActionState era -> EpochNo
gasExpiresAfter forall a b. (a -> b) -> a -> b
$ \GovActionState era
x EpochNo
y -> GovActionState era
x {gasExpiresAfter :: EpochNo
gasExpiresAfter = EpochNo
y}
instance EraPParams era => ToJSON (GovActionState era) where
toJSON :: GovActionState era -> Value
toJSON = [Pair] -> Value
object forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall e a era.
(KeyValue e a, EraPParams era) =>
GovActionState era -> [a]
toGovActionStatePairs
toEncoding :: GovActionState era -> Encoding
toEncoding = Series -> Encoding
pairs forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Monoid a => [a] -> a
mconcat forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall e a era.
(KeyValue e a, EraPParams era) =>
GovActionState era -> [a]
toGovActionStatePairs
toGovActionStatePairs :: (KeyValue e a, EraPParams era) => GovActionState era -> [a]
toGovActionStatePairs :: forall e a era.
(KeyValue e a, EraPParams era) =>
GovActionState era -> [a]
toGovActionStatePairs gas :: GovActionState era
gas@(GovActionState GovActionId
_ Map (Credential 'HotCommitteeRole) Vote
_ Map (Credential 'DRepRole) Vote
_ Map (KeyHash 'StakePool) Vote
_ ProposalProcedure era
_ EpochNo
_ EpochNo
_) =
let GovActionState {Map (KeyHash 'StakePool) Vote
Map (Credential 'DRepRole) Vote
Map (Credential 'HotCommitteeRole) Vote
EpochNo
ProposalProcedure era
GovActionId
gasExpiresAfter :: EpochNo
gasProposedIn :: EpochNo
gasProposalProcedure :: ProposalProcedure era
gasStakePoolVotes :: Map (KeyHash 'StakePool) Vote
gasDRepVotes :: Map (Credential 'DRepRole) Vote
gasCommitteeVotes :: Map (Credential 'HotCommitteeRole) Vote
gasId :: GovActionId
gasExpiresAfter :: forall era. GovActionState era -> EpochNo
gasProposedIn :: forall era. GovActionState era -> EpochNo
gasProposalProcedure :: forall era. GovActionState era -> ProposalProcedure era
gasStakePoolVotes :: forall era. GovActionState era -> Map (KeyHash 'StakePool) Vote
gasDRepVotes :: forall era. GovActionState era -> Map (Credential 'DRepRole) Vote
gasCommitteeVotes :: forall era.
GovActionState era -> Map (Credential 'HotCommitteeRole) Vote
gasId :: forall era. GovActionState era -> GovActionId
..} = GovActionState era
gas
in [ Key
"actionId" forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= GovActionId
gasId
, Key
"committeeVotes" forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Map (Credential 'HotCommitteeRole) Vote
gasCommitteeVotes
, Key
"dRepVotes" forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Map (Credential 'DRepRole) Vote
gasDRepVotes
, Key
"stakePoolVotes" forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Map (KeyHash 'StakePool) Vote
gasStakePoolVotes
, Key
"proposalProcedure" forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= ProposalProcedure era
gasProposalProcedure
, Key
"proposedIn" forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= EpochNo
gasProposedIn
, Key
"expiresAfter" forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= EpochNo
gasExpiresAfter
]
deriving instance EraPParams era => Eq (GovActionState era)
deriving instance EraPParams era => Show (GovActionState era)
instance EraPParams era => NoThunks (GovActionState era)
instance EraPParams era => NFData (GovActionState era)
instance EraPParams era => DecShareCBOR (GovActionState era) where
decShareCBOR :: forall s.
Share (GovActionState era) -> Decoder s (GovActionState era)
decShareCBOR Share (GovActionState era)
_ =
forall (w :: Wrapped) t s. Decode w t -> Decoder s t
decode forall a b. (a -> b) -> a -> b
$
forall t. t -> Decode ('Closed 'Dense) t
RecD forall era.
GovActionId
-> Map (Credential 'HotCommitteeRole) Vote
-> Map (Credential 'DRepRole) Vote
-> Map (KeyHash 'StakePool) Vote
-> ProposalProcedure era
-> EpochNo
-> EpochNo
-> GovActionState era
GovActionState
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t (w :: Wrapped). DecCBOR t => Decode w t
From
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t (w :: Wrapped). DecCBOR t => Decode w t
From
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t (w :: Wrapped). DecCBOR t => Decode w t
From
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t (w :: Wrapped). DecCBOR t => Decode w t
From
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t (w :: Wrapped). DecCBOR t => Decode w t
From
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t (w :: Wrapped). DecCBOR t => Decode w t
From
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t (w :: Wrapped). DecCBOR t => Decode w t
From
instance EraPParams era => DecCBOR (GovActionState era) where
decCBOR :: forall s. Decoder s (GovActionState era)
decCBOR = forall a s. DecShareCBOR a => Decoder s a
decNoShareCBOR
instance EraPParams era => EncCBOR (GovActionState era) where
encCBOR :: GovActionState era -> Encoding
encCBOR GovActionState {Map (KeyHash 'StakePool) Vote
Map (Credential 'DRepRole) Vote
Map (Credential 'HotCommitteeRole) Vote
EpochNo
ProposalProcedure era
GovActionId
gasExpiresAfter :: EpochNo
gasProposedIn :: EpochNo
gasProposalProcedure :: ProposalProcedure era
gasStakePoolVotes :: Map (KeyHash 'StakePool) Vote
gasDRepVotes :: Map (Credential 'DRepRole) Vote
gasCommitteeVotes :: Map (Credential 'HotCommitteeRole) Vote
gasId :: GovActionId
gasExpiresAfter :: forall era. GovActionState era -> EpochNo
gasProposedIn :: forall era. GovActionState era -> EpochNo
gasProposalProcedure :: forall era. GovActionState era -> ProposalProcedure era
gasStakePoolVotes :: forall era. GovActionState era -> Map (KeyHash 'StakePool) Vote
gasDRepVotes :: forall era. GovActionState era -> Map (Credential 'DRepRole) Vote
gasCommitteeVotes :: forall era.
GovActionState era -> Map (Credential 'HotCommitteeRole) Vote
gasId :: forall era. GovActionState era -> GovActionId
..} =
forall (w :: Wrapped) t. Encode w t -> Encoding
encode forall a b. (a -> b) -> a -> b
$
forall t. t -> Encode ('Closed 'Dense) t
Rec forall era.
GovActionId
-> Map (Credential 'HotCommitteeRole) Vote
-> Map (Credential 'DRepRole) Vote
-> Map (KeyHash 'StakePool) Vote
-> ProposalProcedure era
-> EpochNo
-> EpochNo
-> GovActionState era
GovActionState
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To GovActionId
gasId
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To Map (Credential 'HotCommitteeRole) Vote
gasCommitteeVotes
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To Map (Credential 'DRepRole) Vote
gasDRepVotes
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To Map (KeyHash 'StakePool) Vote
gasStakePoolVotes
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To ProposalProcedure era
gasProposalProcedure
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To EpochNo
gasProposedIn
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To EpochNo
gasExpiresAfter
instance OMap.HasOKey GovActionId (GovActionState era) where
okeyL :: Lens' (GovActionState era) GovActionId
okeyL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall era. GovActionState era -> GovActionId
gasId forall a b. (a -> b) -> a -> b
$ \GovActionState era
gas GovActionId
gi -> GovActionState era
gas {gasId :: GovActionId
gasId = GovActionId
gi}
data Voter
= CommitteeVoter !(Credential 'HotCommitteeRole)
| DRepVoter !(Credential 'DRepRole)
| StakePoolVoter !(KeyHash 'StakePool)
deriving (forall x. Rep Voter x -> Voter
forall x. Voter -> Rep Voter x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Voter x -> Voter
$cfrom :: forall x. Voter -> Rep Voter x
Generic, Voter -> Voter -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Voter -> Voter -> Bool
$c/= :: Voter -> Voter -> Bool
== :: Voter -> Voter -> Bool
$c== :: Voter -> Voter -> Bool
Eq, Eq Voter
Voter -> Voter -> Bool
Voter -> Voter -> Ordering
Voter -> Voter -> Voter
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Voter -> Voter -> Voter
$cmin :: Voter -> Voter -> Voter
max :: Voter -> Voter -> Voter
$cmax :: Voter -> Voter -> Voter
>= :: Voter -> Voter -> Bool
$c>= :: Voter -> Voter -> Bool
> :: Voter -> Voter -> Bool
$c> :: Voter -> Voter -> Bool
<= :: Voter -> Voter -> Bool
$c<= :: Voter -> Voter -> Bool
< :: Voter -> Voter -> Bool
$c< :: Voter -> Voter -> Bool
compare :: Voter -> Voter -> Ordering
$ccompare :: Voter -> Voter -> Ordering
Ord, Int -> Voter -> ShowS
[Voter] -> ShowS
Voter -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Voter] -> ShowS
$cshowList :: [Voter] -> ShowS
show :: Voter -> String
$cshow :: Voter -> String
showsPrec :: Int -> Voter -> ShowS
$cshowsPrec :: Int -> Voter -> ShowS
Show)
instance ToJSON Voter
instance ToJSONKey Voter where
toJSONKey :: ToJSONKeyFunction Voter
toJSONKey = forall a. (a -> Text) -> ToJSONKeyFunction a
toJSONKeyText forall a b. (a -> b) -> a -> b
$ \case
CommitteeVoter Credential 'HotCommitteeRole
cred ->
Text
"committee-" forall a. Semigroup a => a -> a -> a
<> forall (kr :: KeyRole). Credential kr -> Text
credToText Credential 'HotCommitteeRole
cred
DRepVoter Credential 'DRepRole
cred ->
Text
"drep-" forall a. Semigroup a => a -> a -> a
<> forall (kr :: KeyRole). Credential kr -> Text
credToText Credential 'DRepRole
cred
StakePoolVoter KeyHash 'StakePool
kh ->
Text
"stakepool-" forall a. Semigroup a => a -> a -> a
<> forall (kr :: KeyRole). Credential kr -> Text
credToText (forall (kr :: KeyRole). KeyHash kr -> Credential kr
KeyHashObj KeyHash 'StakePool
kh)
instance DecCBOR Voter where
decCBOR :: forall s. Decoder s Voter
decCBOR = forall s a. Text -> (Word -> Decoder s (Int, a)) -> Decoder s a
decodeRecordSum Text
"Voter" forall a b. (a -> b) -> a -> b
$ \case
Word
0 -> (Int
2,) forall b c a. (b -> c) -> (a -> b) -> a -> c
. Credential 'HotCommitteeRole -> Voter
CommitteeVoter forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (kr :: KeyRole). KeyHash kr -> Credential kr
KeyHashObj forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a s. DecCBOR a => Decoder s a
decCBOR
Word
1 -> (Int
2,) forall b c a. (b -> c) -> (a -> b) -> a -> c
. Credential 'HotCommitteeRole -> Voter
CommitteeVoter forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (kr :: KeyRole). ScriptHash -> Credential kr
ScriptHashObj forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a s. DecCBOR a => Decoder s a
decCBOR
Word
2 -> (Int
2,) forall b c a. (b -> c) -> (a -> b) -> a -> c
. Credential 'DRepRole -> Voter
DRepVoter forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (kr :: KeyRole). KeyHash kr -> Credential kr
KeyHashObj forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a s. DecCBOR a => Decoder s a
decCBOR
Word
3 -> (Int
2,) forall b c a. (b -> c) -> (a -> b) -> a -> c
. Credential 'DRepRole -> Voter
DRepVoter forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (kr :: KeyRole). ScriptHash -> Credential kr
ScriptHashObj forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a s. DecCBOR a => Decoder s a
decCBOR
Word
4 -> (Int
2,) forall b c a. (b -> c) -> (a -> b) -> a -> c
. KeyHash 'StakePool -> Voter
StakePoolVoter forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a s. DecCBOR a => Decoder s a
decCBOR
Word
5 -> forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Script objects are not allowed for StakePool votes"
Word
t -> forall (m :: * -> *) a. MonadFail m => Word -> m a
invalidKey Word
t
instance EncCBOR Voter where
encCBOR :: Voter -> Encoding
encCBOR = \case
CommitteeVoter (KeyHashObj KeyHash 'HotCommitteeRole
keyHash) ->
Word -> Encoding
encodeListLen Word
2 forall a. Semigroup a => a -> a -> a
<> Word8 -> Encoding
encodeWord8 Word8
0 forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR KeyHash 'HotCommitteeRole
keyHash
CommitteeVoter (ScriptHashObj ScriptHash
scriptHash) ->
Word -> Encoding
encodeListLen Word
2 forall a. Semigroup a => a -> a -> a
<> Word8 -> Encoding
encodeWord8 Word8
1 forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR ScriptHash
scriptHash
DRepVoter (KeyHashObj KeyHash 'DRepRole
keyHash) ->
Word -> Encoding
encodeListLen Word
2 forall a. Semigroup a => a -> a -> a
<> Word8 -> Encoding
encodeWord8 Word8
2 forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR KeyHash 'DRepRole
keyHash
DRepVoter (ScriptHashObj ScriptHash
scriptHash) ->
Word -> Encoding
encodeListLen Word
2 forall a. Semigroup a => a -> a -> a
<> Word8 -> Encoding
encodeWord8 Word8
3 forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR ScriptHash
scriptHash
StakePoolVoter KeyHash 'StakePool
keyHash ->
Word -> Encoding
encodeListLen Word
2 forall a. Semigroup a => a -> a -> a
<> Word8 -> Encoding
encodeWord8 Word8
4 forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR KeyHash 'StakePool
keyHash
instance NoThunks Voter
instance NFData Voter
data Vote
= VoteNo
| VoteYes
| Abstain
deriving (Eq Vote
Vote -> Vote -> Bool
Vote -> Vote -> Ordering
Vote -> Vote -> Vote
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Vote -> Vote -> Vote
$cmin :: Vote -> Vote -> Vote
max :: Vote -> Vote -> Vote
$cmax :: Vote -> Vote -> Vote
>= :: Vote -> Vote -> Bool
$c>= :: Vote -> Vote -> Bool
> :: Vote -> Vote -> Bool
$c> :: Vote -> Vote -> Bool
<= :: Vote -> Vote -> Bool
$c<= :: Vote -> Vote -> Bool
< :: Vote -> Vote -> Bool
$c< :: Vote -> Vote -> Bool
compare :: Vote -> Vote -> Ordering
$ccompare :: Vote -> Vote -> Ordering
Ord, forall x. Rep Vote x -> Vote
forall x. Vote -> Rep Vote x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Vote x -> Vote
$cfrom :: forall x. Vote -> Rep Vote x
Generic, Vote -> Vote -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Vote -> Vote -> Bool
$c/= :: Vote -> Vote -> Bool
== :: Vote -> Vote -> Bool
$c== :: Vote -> Vote -> Bool
Eq, Int -> Vote -> ShowS
[Vote] -> ShowS
Vote -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Vote] -> ShowS
$cshowList :: [Vote] -> ShowS
show :: Vote -> String
$cshow :: Vote -> String
showsPrec :: Int -> Vote -> ShowS
$cshowsPrec :: Int -> Vote -> ShowS
Show, Int -> Vote
Vote -> Int
Vote -> [Vote]
Vote -> Vote
Vote -> Vote -> [Vote]
Vote -> Vote -> Vote -> [Vote]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: Vote -> Vote -> Vote -> [Vote]
$cenumFromThenTo :: Vote -> Vote -> Vote -> [Vote]
enumFromTo :: Vote -> Vote -> [Vote]
$cenumFromTo :: Vote -> Vote -> [Vote]
enumFromThen :: Vote -> Vote -> [Vote]
$cenumFromThen :: Vote -> Vote -> [Vote]
enumFrom :: Vote -> [Vote]
$cenumFrom :: Vote -> [Vote]
fromEnum :: Vote -> Int
$cfromEnum :: Vote -> Int
toEnum :: Int -> Vote
$ctoEnum :: Int -> Vote
pred :: Vote -> Vote
$cpred :: Vote -> Vote
succ :: Vote -> Vote
$csucc :: Vote -> Vote
Enum, Vote
forall a. a -> a -> Bounded a
maxBound :: Vote
$cmaxBound :: Vote
minBound :: Vote
$cminBound :: Vote
Bounded)
instance ToJSON Vote
instance NoThunks Vote
instance NFData Vote
instance DecCBOR Vote where
decCBOR :: forall s. Decoder s Vote
decCBOR = forall a s. (Enum a, Bounded a, Typeable a) => Decoder s a
decodeEnumBounded
instance EncCBOR Vote where
encCBOR :: Vote -> Encoding
encCBOR = forall a. Enum a => a -> Encoding
encodeEnum
newtype VotingProcedures era = VotingProcedures
{ forall era.
VotingProcedures era
-> Map Voter (Map GovActionId (VotingProcedure era))
unVotingProcedures :: Map Voter (Map GovActionId (VotingProcedure era))
}
deriving stock (forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall era x. Rep (VotingProcedures era) x -> VotingProcedures era
forall era x. VotingProcedures era -> Rep (VotingProcedures era) x
$cto :: forall era x. Rep (VotingProcedures era) x -> VotingProcedures era
$cfrom :: forall era x. VotingProcedures era -> Rep (VotingProcedures era) x
Generic, VotingProcedures era -> VotingProcedures era -> Bool
forall era. VotingProcedures era -> VotingProcedures era -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VotingProcedures era -> VotingProcedures era -> Bool
$c/= :: forall era. VotingProcedures era -> VotingProcedures era -> Bool
== :: VotingProcedures era -> VotingProcedures era -> Bool
$c== :: forall era. VotingProcedures era -> VotingProcedures era -> Bool
Eq, Int -> VotingProcedures era -> ShowS
forall era. Int -> VotingProcedures era -> ShowS
forall era. [VotingProcedures era] -> ShowS
forall era. VotingProcedures era -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VotingProcedures era] -> ShowS
$cshowList :: forall era. [VotingProcedures era] -> ShowS
show :: VotingProcedures era -> String
$cshow :: forall era. VotingProcedures era -> String
showsPrec :: Int -> VotingProcedures era -> ShowS
$cshowsPrec :: forall era. Int -> VotingProcedures era -> ShowS
Show)
deriving newtype (Context -> VotingProcedures era -> IO (Maybe ThunkInfo)
Proxy (VotingProcedures era) -> String
forall era. Context -> VotingProcedures era -> IO (Maybe ThunkInfo)
forall era. Proxy (VotingProcedures era) -> String
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy (VotingProcedures era) -> String
$cshowTypeOf :: forall era. Proxy (VotingProcedures era) -> String
wNoThunks :: Context -> VotingProcedures era -> IO (Maybe ThunkInfo)
$cwNoThunks :: forall era. Context -> VotingProcedures era -> IO (Maybe ThunkInfo)
noThunks :: Context -> VotingProcedures era -> IO (Maybe ThunkInfo)
$cnoThunks :: forall era. Context -> VotingProcedures era -> IO (Maybe ThunkInfo)
NoThunks, VotingProcedures era -> Encoding
(forall t. EncCBOR t => Proxy t -> Size)
-> Proxy [VotingProcedures era] -> Size
(forall t. EncCBOR t => Proxy t -> Size)
-> Proxy (VotingProcedures era) -> Size
forall a.
Typeable a
-> (a -> Encoding)
-> ((forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size)
-> ((forall t. EncCBOR t => Proxy t -> Size) -> Proxy [a] -> Size)
-> EncCBOR a
forall {era}. Era era => Typeable (VotingProcedures era)
forall era. Era era => VotingProcedures era -> Encoding
forall era.
Era era =>
(forall t. EncCBOR t => Proxy t -> Size)
-> Proxy [VotingProcedures era] -> Size
forall era.
Era era =>
(forall t. EncCBOR t => Proxy t -> Size)
-> Proxy (VotingProcedures era) -> Size
encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy [VotingProcedures era] -> Size
$cencodedListSizeExpr :: forall era.
Era era =>
(forall t. EncCBOR t => Proxy t -> Size)
-> Proxy [VotingProcedures era] -> Size
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy (VotingProcedures era) -> Size
$cencodedSizeExpr :: forall era.
Era era =>
(forall t. EncCBOR t => Proxy t -> Size)
-> Proxy (VotingProcedures era) -> Size
encCBOR :: VotingProcedures era -> Encoding
$cencCBOR :: forall era. Era era => VotingProcedures era -> Encoding
EncCBOR, [VotingProcedures era] -> Encoding
[VotingProcedures era] -> Value
VotingProcedures era -> Bool
VotingProcedures era -> Encoding
VotingProcedures era -> Value
forall era. EraPParams era => [VotingProcedures era] -> Encoding
forall era. EraPParams era => [VotingProcedures era] -> Value
forall era. EraPParams era => VotingProcedures era -> Bool
forall era. EraPParams era => VotingProcedures era -> Encoding
forall era. EraPParams era => VotingProcedures era -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
omitField :: VotingProcedures era -> Bool
$comitField :: forall era. EraPParams era => VotingProcedures era -> Bool
toEncodingList :: [VotingProcedures era] -> Encoding
$ctoEncodingList :: forall era. EraPParams era => [VotingProcedures era] -> Encoding
toJSONList :: [VotingProcedures era] -> Value
$ctoJSONList :: forall era. EraPParams era => [VotingProcedures era] -> Value
toEncoding :: VotingProcedures era -> Encoding
$ctoEncoding :: forall era. EraPParams era => VotingProcedures era -> Encoding
toJSON :: VotingProcedures era -> Value
$ctoJSON :: forall era. EraPParams era => VotingProcedures era -> Value
ToJSON)
deriving newtype instance Era era => NFData (VotingProcedures era)
instance Era era => DecCBOR (VotingProcedures era) where
decCBOR :: forall s. Decoder s (VotingProcedures era)
decCBOR =
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall era.
Map Voter (Map GovActionId (VotingProcedure era))
-> VotingProcedures era
VotingProcedures forall a b. (a -> b) -> a -> b
$ forall k s v.
Ord k =>
Decoder s k -> (k -> Decoder s v) -> Decoder s (Map k v)
decodeMapByKey forall a s. DecCBOR a => Decoder s a
decCBOR forall a b. (a -> b) -> a -> b
$ \Voter
voter -> do
Map GovActionId (VotingProcedure era)
subMap <- forall a s. DecCBOR a => Decoder s a
decCBOR
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (forall (t :: * -> *) a. Foldable t => t a -> Bool
null Map GovActionId (VotingProcedure era)
subMap) forall a b. (a -> b) -> a -> b
$
forall (m :: * -> *) a. MonadFail m => String -> m a
fail forall a b. (a -> b) -> a -> b
$
String
"VotingProcedures require votes, but Voter: " forall a. Semigroup a => a -> a -> a
<> forall a. Show a => a -> String
show Voter
voter forall a. Semigroup a => a -> a -> a
<> String
" didn't have any"
forall (f :: * -> *) a. Applicative f => a -> f a
pure Map GovActionId (VotingProcedure era)
subMap
{-# INLINE decCBOR #-}
foldlVotingProcedures ::
(c -> Voter -> GovActionId -> VotingProcedure era -> c) ->
c ->
VotingProcedures era ->
c
foldlVotingProcedures :: forall c era.
(c -> Voter -> GovActionId -> VotingProcedure era -> c)
-> c -> VotingProcedures era -> c
foldlVotingProcedures c -> Voter -> GovActionId -> VotingProcedure era -> c
f c
initAcc =
let fVotes :: c -> Voter -> Map GovActionId (VotingProcedure era) -> c
fVotes c
initVotesAcc Voter
voter =
forall a k b. (a -> k -> b -> a) -> a -> Map k b -> a
Map.foldlWithKey' (\c
acc -> c -> Voter -> GovActionId -> VotingProcedure era -> c
f c
acc Voter
voter) c
initVotesAcc
in forall a k b. (a -> k -> b -> a) -> a -> Map k b -> a
Map.foldlWithKey' c -> Voter -> Map GovActionId (VotingProcedure era) -> c
fVotes c
initAcc forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era.
VotingProcedures era
-> Map Voter (Map GovActionId (VotingProcedure era))
unVotingProcedures
foldrVotingProcedures ::
(Voter -> GovActionId -> VotingProcedure era -> c -> c) ->
c ->
VotingProcedures era ->
c
foldrVotingProcedures :: forall era c.
(Voter -> GovActionId -> VotingProcedure era -> c -> c)
-> c -> VotingProcedures era -> c
foldrVotingProcedures Voter -> GovActionId -> VotingProcedure era -> c -> c
f c
initAcc =
let fVotes :: Voter -> Map GovActionId (VotingProcedure era) -> c -> c
fVotes Voter
voter Map GovActionId (VotingProcedure era)
votes c
acc =
forall k a b. (k -> a -> b -> b) -> b -> Map k a -> b
Map.foldrWithKey' (Voter -> GovActionId -> VotingProcedure era -> c -> c
f Voter
voter) c
acc Map GovActionId (VotingProcedure era)
votes
in forall k a b. (k -> a -> b -> b) -> b -> Map k a -> b
Map.foldrWithKey' Voter -> Map GovActionId (VotingProcedure era) -> c -> c
fVotes c
initAcc forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era.
VotingProcedures era
-> Map Voter (Map GovActionId (VotingProcedure era))
unVotingProcedures
deriving instance Indexable Voter (VotingProcedures era)
data VotingProcedure era = VotingProcedure
{ forall era. VotingProcedure era -> Vote
vProcVote :: !Vote
, forall era. VotingProcedure era -> StrictMaybe Anchor
vProcAnchor :: !(StrictMaybe Anchor)
}
deriving (forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall era x. Rep (VotingProcedure era) x -> VotingProcedure era
forall era x. VotingProcedure era -> Rep (VotingProcedure era) x
$cto :: forall era x. Rep (VotingProcedure era) x -> VotingProcedure era
$cfrom :: forall era x. VotingProcedure era -> Rep (VotingProcedure era) x
Generic, VotingProcedure era -> VotingProcedure era -> Bool
forall era. VotingProcedure era -> VotingProcedure era -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VotingProcedure era -> VotingProcedure era -> Bool
$c/= :: forall era. VotingProcedure era -> VotingProcedure era -> Bool
== :: VotingProcedure era -> VotingProcedure era -> Bool
$c== :: forall era. VotingProcedure era -> VotingProcedure era -> Bool
Eq, Int -> VotingProcedure era -> ShowS
forall era. Int -> VotingProcedure era -> ShowS
forall era. [VotingProcedure era] -> ShowS
forall era. VotingProcedure era -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VotingProcedure era] -> ShowS
$cshowList :: forall era. [VotingProcedure era] -> ShowS
show :: VotingProcedure era -> String
$cshow :: forall era. VotingProcedure era -> String
showsPrec :: Int -> VotingProcedure era -> ShowS
$cshowsPrec :: forall era. Int -> VotingProcedure era -> ShowS
Show)
instance NoThunks (VotingProcedure era)
instance NFData (VotingProcedure era)
instance Era era => DecCBOR (VotingProcedure era) where
decCBOR :: forall s. Decoder s (VotingProcedure era)
decCBOR =
forall (w :: Wrapped) t s. Decode w t -> Decoder s t
decode forall a b. (a -> b) -> a -> b
$
forall t. t -> Decode ('Closed 'Dense) t
RecD forall era. Vote -> StrictMaybe Anchor -> VotingProcedure era
VotingProcedure
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t (w :: Wrapped). DecCBOR t => Decode w t
From
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t. (forall s. Decoder s t) -> Decode ('Closed 'Dense) t
D (forall s a. Decoder s a -> Decoder s (StrictMaybe a)
decodeNullStrictMaybe forall a s. DecCBOR a => Decoder s a
decCBOR)
{-# INLINE decCBOR #-}
instance Era era => EncCBOR (VotingProcedure era) where
encCBOR :: VotingProcedure era -> Encoding
encCBOR VotingProcedure {StrictMaybe Anchor
Vote
vProcAnchor :: StrictMaybe Anchor
vProcVote :: Vote
vProcAnchor :: forall era. VotingProcedure era -> StrictMaybe Anchor
vProcVote :: forall era. VotingProcedure era -> Vote
..} =
forall (w :: Wrapped) t. Encode w t -> Encoding
encode forall a b. (a -> b) -> a -> b
$
forall t. t -> Encode ('Closed 'Dense) t
Rec (forall era. Vote -> StrictMaybe Anchor -> VotingProcedure era
VotingProcedure @era)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To Vote
vProcVote
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. (t -> Encoding) -> t -> Encode ('Closed 'Dense) t
E (forall a. (a -> Encoding) -> StrictMaybe a -> Encoding
encodeNullStrictMaybe forall a. EncCBOR a => a -> Encoding
encCBOR) StrictMaybe Anchor
vProcAnchor
instance EraPParams era => ToJSON (VotingProcedure era) where
toJSON :: VotingProcedure era -> Value
toJSON = [Pair] -> Value
object forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall e a era. KeyValue e a => VotingProcedure era -> [a]
toVotingProcedurePairs
toEncoding :: VotingProcedure era -> Encoding
toEncoding = Series -> Encoding
pairs forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Monoid a => [a] -> a
mconcat forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall e a era. KeyValue e a => VotingProcedure era -> [a]
toVotingProcedurePairs
toVotingProcedurePairs :: KeyValue e a => VotingProcedure era -> [a]
toVotingProcedurePairs :: forall e a era. KeyValue e a => VotingProcedure era -> [a]
toVotingProcedurePairs vProc :: VotingProcedure era
vProc@(VotingProcedure Vote
_ StrictMaybe Anchor
_) =
let VotingProcedure {StrictMaybe Anchor
Vote
vProcAnchor :: StrictMaybe Anchor
vProcVote :: Vote
vProcAnchor :: forall era. VotingProcedure era -> StrictMaybe Anchor
vProcVote :: forall era. VotingProcedure era -> Vote
..} = VotingProcedure era
vProc
in [ Key
"anchor" forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= StrictMaybe Anchor
vProcAnchor
, Key
"decision" forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Vote
vProcVote
]
indexedGovProps ::
Seq.Seq (ProposalProcedure era) ->
Seq.Seq (GovActionIx, ProposalProcedure era)
indexedGovProps :: forall era.
Seq (ProposalProcedure era)
-> Seq (GovActionIx, ProposalProcedure era)
indexedGovProps = forall {b}. Word16 -> Seq b -> Seq (GovActionIx, b)
enumerateProps Word16
0
where
enumerateProps :: Word16 -> Seq b -> Seq (GovActionIx, b)
enumerateProps Word16
_ Seq b
Seq.Empty = forall a. Seq a
Seq.Empty
enumerateProps !Word16
n (b
x Seq.:<| Seq b
xs) = (Word16 -> GovActionIx
GovActionIx Word16
n, b
x) forall a. a -> Seq a -> Seq a
Seq.:<| Word16 -> Seq b -> Seq (GovActionIx, b)
enumerateProps (forall a. Enum a => a -> a
succ Word16
n) Seq b
xs
data ProposalProcedure era = ProposalProcedure
{ forall era. ProposalProcedure era -> Coin
pProcDeposit :: !Coin
, forall era. ProposalProcedure era -> RewardAccount
pProcReturnAddr :: !RewardAccount
, forall era. ProposalProcedure era -> GovAction era
pProcGovAction :: !(GovAction era)
, forall era. ProposalProcedure era -> Anchor
pProcAnchor :: !Anchor
}
deriving (forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall era x.
Rep (ProposalProcedure era) x -> ProposalProcedure era
forall era x.
ProposalProcedure era -> Rep (ProposalProcedure era) x
$cto :: forall era x.
Rep (ProposalProcedure era) x -> ProposalProcedure era
$cfrom :: forall era x.
ProposalProcedure era -> Rep (ProposalProcedure era) x
Generic, ProposalProcedure era -> ProposalProcedure era -> Bool
forall era.
EraPParams era =>
ProposalProcedure era -> ProposalProcedure era -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ProposalProcedure era -> ProposalProcedure era -> Bool
$c/= :: forall era.
EraPParams era =>
ProposalProcedure era -> ProposalProcedure era -> Bool
== :: ProposalProcedure era -> ProposalProcedure era -> Bool
$c== :: forall era.
EraPParams era =>
ProposalProcedure era -> ProposalProcedure era -> Bool
Eq, Int -> ProposalProcedure era -> ShowS
forall era. EraPParams era => Int -> ProposalProcedure era -> ShowS
forall era. EraPParams era => [ProposalProcedure era] -> ShowS
forall era. EraPParams era => ProposalProcedure era -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ProposalProcedure era] -> ShowS
$cshowList :: forall era. EraPParams era => [ProposalProcedure era] -> ShowS
show :: ProposalProcedure era -> String
$cshow :: forall era. EraPParams era => ProposalProcedure era -> String
showsPrec :: Int -> ProposalProcedure era -> ShowS
$cshowsPrec :: forall era. EraPParams era => Int -> ProposalProcedure era -> ShowS
Show, ProposalProcedure era -> ProposalProcedure era -> Bool
ProposalProcedure era -> ProposalProcedure era -> Ordering
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall era. EraPParams era => Eq (ProposalProcedure era)
forall era.
EraPParams era =>
ProposalProcedure era -> ProposalProcedure era -> Bool
forall era.
EraPParams era =>
ProposalProcedure era -> ProposalProcedure era -> Ordering
forall era.
EraPParams era =>
ProposalProcedure era
-> ProposalProcedure era -> ProposalProcedure era
min :: ProposalProcedure era
-> ProposalProcedure era -> ProposalProcedure era
$cmin :: forall era.
EraPParams era =>
ProposalProcedure era
-> ProposalProcedure era -> ProposalProcedure era
max :: ProposalProcedure era
-> ProposalProcedure era -> ProposalProcedure era
$cmax :: forall era.
EraPParams era =>
ProposalProcedure era
-> ProposalProcedure era -> ProposalProcedure era
>= :: ProposalProcedure era -> ProposalProcedure era -> Bool
$c>= :: forall era.
EraPParams era =>
ProposalProcedure era -> ProposalProcedure era -> Bool
> :: ProposalProcedure era -> ProposalProcedure era -> Bool
$c> :: forall era.
EraPParams era =>
ProposalProcedure era -> ProposalProcedure era -> Bool
<= :: ProposalProcedure era -> ProposalProcedure era -> Bool
$c<= :: forall era.
EraPParams era =>
ProposalProcedure era -> ProposalProcedure era -> Bool
< :: ProposalProcedure era -> ProposalProcedure era -> Bool
$c< :: forall era.
EraPParams era =>
ProposalProcedure era -> ProposalProcedure era -> Bool
compare :: ProposalProcedure era -> ProposalProcedure era -> Ordering
$ccompare :: forall era.
EraPParams era =>
ProposalProcedure era -> ProposalProcedure era -> Ordering
Ord)
pProcDepositL :: Lens' (ProposalProcedure era) Coin
pProcDepositL :: forall era. Lens' (ProposalProcedure era) Coin
pProcDepositL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall era. ProposalProcedure era -> Coin
pProcDeposit (\ProposalProcedure era
p Coin
x -> ProposalProcedure era
p {pProcDeposit :: Coin
pProcDeposit = Coin
x})
pProcReturnAddrL :: Lens' (ProposalProcedure era) RewardAccount
pProcReturnAddrL :: forall era. Lens' (ProposalProcedure era) RewardAccount
pProcReturnAddrL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall era. ProposalProcedure era -> RewardAccount
pProcReturnAddr (\ProposalProcedure era
p RewardAccount
x -> ProposalProcedure era
p {pProcReturnAddr :: RewardAccount
pProcReturnAddr = RewardAccount
x})
pProcGovActionL :: Lens' (ProposalProcedure era) (GovAction era)
pProcGovActionL :: forall era. Lens' (ProposalProcedure era) (GovAction era)
pProcGovActionL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall era. ProposalProcedure era -> GovAction era
pProcGovAction forall a b. (a -> b) -> a -> b
$ \ProposalProcedure era
x GovAction era
y -> ProposalProcedure era
x {pProcGovAction :: GovAction era
pProcGovAction = GovAction era
y}
pProcAnchorL :: Lens' (ProposalProcedure era) Anchor
pProcAnchorL :: forall era. Lens' (ProposalProcedure era) Anchor
pProcAnchorL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall era. ProposalProcedure era -> Anchor
pProcAnchor forall a b. (a -> b) -> a -> b
$ \ProposalProcedure era
x Anchor
y -> ProposalProcedure era
x {pProcAnchor :: Anchor
pProcAnchor = Anchor
y}
instance EraPParams era => NoThunks (ProposalProcedure era)
instance EraPParams era => NFData (ProposalProcedure era)
instance EraPParams era => DecCBOR (ProposalProcedure era) where
decCBOR :: forall s. Decoder s (ProposalProcedure era)
decCBOR =
forall (w :: Wrapped) t s. Decode w t -> Decoder s t
decode forall a b. (a -> b) -> a -> b
$
forall t. t -> Decode ('Closed 'Dense) t
RecD forall era.
Coin
-> RewardAccount
-> GovAction era
-> Anchor
-> ProposalProcedure era
ProposalProcedure
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t (w :: Wrapped). DecCBOR t => Decode w t
From
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t (w :: Wrapped). DecCBOR t => Decode w t
From
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t (w :: Wrapped). DecCBOR t => Decode w t
From
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t (w :: Wrapped). DecCBOR t => Decode w t
From
{-# INLINE decCBOR #-}
instance EraPParams era => EncCBOR (ProposalProcedure era) where
encCBOR :: ProposalProcedure era -> Encoding
encCBOR ProposalProcedure {RewardAccount
Coin
Anchor
GovAction era
pProcAnchor :: Anchor
pProcGovAction :: GovAction era
pProcReturnAddr :: RewardAccount
pProcDeposit :: Coin
pProcAnchor :: forall era. ProposalProcedure era -> Anchor
pProcGovAction :: forall era. ProposalProcedure era -> GovAction era
pProcReturnAddr :: forall era. ProposalProcedure era -> RewardAccount
pProcDeposit :: forall era. ProposalProcedure era -> Coin
..} =
forall (w :: Wrapped) t. Encode w t -> Encoding
encode forall a b. (a -> b) -> a -> b
$
forall t. t -> Encode ('Closed 'Dense) t
Rec (forall era.
Coin
-> RewardAccount
-> GovAction era
-> Anchor
-> ProposalProcedure era
ProposalProcedure @era)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To Coin
pProcDeposit
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To RewardAccount
pProcReturnAddr
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To GovAction era
pProcGovAction
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To Anchor
pProcAnchor
instance EraPParams era => ToJSON (ProposalProcedure era) where
toJSON :: ProposalProcedure era -> Value
toJSON = [Pair] -> Value
object forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall e a era.
(KeyValue e a, EraPParams era) =>
ProposalProcedure era -> [a]
toProposalProcedurePairs
toEncoding :: ProposalProcedure era -> Encoding
toEncoding = Series -> Encoding
pairs forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Monoid a => [a] -> a
mconcat forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall e a era.
(KeyValue e a, EraPParams era) =>
ProposalProcedure era -> [a]
toProposalProcedurePairs
toProposalProcedurePairs :: (KeyValue e a, EraPParams era) => ProposalProcedure era -> [a]
toProposalProcedurePairs :: forall e a era.
(KeyValue e a, EraPParams era) =>
ProposalProcedure era -> [a]
toProposalProcedurePairs proposalProcedure :: ProposalProcedure era
proposalProcedure@(ProposalProcedure Coin
_ RewardAccount
_ GovAction era
_ Anchor
_) =
let ProposalProcedure {RewardAccount
Coin
Anchor
GovAction era
pProcAnchor :: Anchor
pProcGovAction :: GovAction era
pProcReturnAddr :: RewardAccount
pProcDeposit :: Coin
pProcAnchor :: forall era. ProposalProcedure era -> Anchor
pProcGovAction :: forall era. ProposalProcedure era -> GovAction era
pProcReturnAddr :: forall era. ProposalProcedure era -> RewardAccount
pProcDeposit :: forall era. ProposalProcedure era -> Coin
..} = ProposalProcedure era
proposalProcedure
in [ Key
"deposit" forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Coin
pProcDeposit
, Key
"returnAddr" forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= RewardAccount
pProcReturnAddr
, Key
"govAction" forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= GovAction era
pProcGovAction
, Key
"anchor" forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Anchor
pProcAnchor
]
data Committee era = Committee
{ forall era.
Committee era -> Map (Credential 'ColdCommitteeRole) EpochNo
committeeMembers :: !(Map (Credential 'ColdCommitteeRole) EpochNo)
, forall era. Committee era -> UnitInterval
committeeThreshold :: !UnitInterval
}
deriving (Committee era -> Committee era -> Bool
forall era. Committee era -> Committee era -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Committee era -> Committee era -> Bool
$c/= :: forall era. Committee era -> Committee era -> Bool
== :: Committee era -> Committee era -> Bool
$c== :: forall era. Committee era -> Committee era -> Bool
Eq, Int -> Committee era -> ShowS
forall era. Int -> Committee era -> ShowS
forall era. [Committee era] -> ShowS
forall era. Committee era -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Committee era] -> ShowS
$cshowList :: forall era. [Committee era] -> ShowS
show :: Committee era -> String
$cshow :: forall era. Committee era -> String
showsPrec :: Int -> Committee era -> ShowS
$cshowsPrec :: forall era. Int -> Committee era -> ShowS
Show, forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall era x. Rep (Committee era) x -> Committee era
forall era x. Committee era -> Rep (Committee era) x
$cto :: forall era x. Rep (Committee era) x -> Committee era
$cfrom :: forall era x. Committee era -> Rep (Committee era) x
Generic)
instance Era era => NoThunks (Committee era)
instance Era era => NFData (Committee era)
instance Default (Committee era) where
def :: Committee era
def = forall era.
Map (Credential 'ColdCommitteeRole) EpochNo
-> UnitInterval -> Committee era
Committee forall a. Monoid a => a
mempty forall a. Bounded a => a
minBound
committeeMembersL ::
Lens' (Committee era) (Map (Credential 'ColdCommitteeRole) EpochNo)
committeeMembersL :: forall era.
Lens' (Committee era) (Map (Credential 'ColdCommitteeRole) EpochNo)
committeeMembersL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall era.
Committee era -> Map (Credential 'ColdCommitteeRole) EpochNo
committeeMembers (\Committee era
c Map (Credential 'ColdCommitteeRole) EpochNo
m -> Committee era
c {committeeMembers :: Map (Credential 'ColdCommitteeRole) EpochNo
committeeMembers = Map (Credential 'ColdCommitteeRole) EpochNo
m})
committeeThresholdL :: Lens' (Committee era) UnitInterval
committeeThresholdL :: forall era. Lens' (Committee era) UnitInterval
committeeThresholdL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall era. Committee era -> UnitInterval
committeeThreshold (\Committee era
c UnitInterval
q -> Committee era
c {committeeThreshold :: UnitInterval
committeeThreshold = UnitInterval
q})
instance Era era => DecCBOR (Committee era) where
decCBOR :: forall s. Decoder s (Committee era)
decCBOR =
forall (w :: Wrapped) t s. Decode w t -> Decoder s t
decode forall a b. (a -> b) -> a -> b
$
forall t. t -> Decode ('Closed 'Dense) t
RecD forall era.
Map (Credential 'ColdCommitteeRole) EpochNo
-> UnitInterval -> Committee era
Committee
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t (w :: Wrapped). DecCBOR t => Decode w t
From
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t (w :: Wrapped). DecCBOR t => Decode w t
From
{-# INLINE decCBOR #-}
instance Era era => EncCBOR (Committee era) where
encCBOR :: Committee era -> Encoding
encCBOR Committee {Map (Credential 'ColdCommitteeRole) EpochNo
committeeMembers :: Map (Credential 'ColdCommitteeRole) EpochNo
committeeMembers :: forall era.
Committee era -> Map (Credential 'ColdCommitteeRole) EpochNo
committeeMembers, UnitInterval
committeeThreshold :: UnitInterval
committeeThreshold :: forall era. Committee era -> UnitInterval
committeeThreshold} =
forall (w :: Wrapped) t. Encode w t -> Encoding
encode forall a b. (a -> b) -> a -> b
$
forall t. t -> Encode ('Closed 'Dense) t
Rec (forall era.
Map (Credential 'ColdCommitteeRole) EpochNo
-> UnitInterval -> Committee era
Committee @era)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To Map (Credential 'ColdCommitteeRole) EpochNo
committeeMembers
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To UnitInterval
committeeThreshold
instance EraPParams era => ToJSON (Committee era) where
toJSON :: Committee era -> Value
toJSON = [Pair] -> Value
object forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall e a era. KeyValue e a => Committee era -> [a]
toCommitteePairs
toEncoding :: Committee era -> Encoding
toEncoding = Series -> Encoding
pairs forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Monoid a => [a] -> a
mconcat forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall e a era. KeyValue e a => Committee era -> [a]
toCommitteePairs
instance Era era => FromJSON (Committee era) where
parseJSON :: Value -> Parser (Committee era)
parseJSON = forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Committee" forall {era}. Object -> Parser (Committee era)
parseCommittee
where
parseCommittee :: Object -> Parser (Committee era)
parseCommittee Object
o =
forall era.
Map (Credential 'ColdCommitteeRole) EpochNo
-> UnitInterval -> Committee era
Committee
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (t :: * -> *) a. Foldable t => t a -> t a
forceElemsToWHNF forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"members")
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"threshold"
toCommitteePairs :: KeyValue e a => Committee era -> [a]
toCommitteePairs :: forall e a era. KeyValue e a => Committee era -> [a]
toCommitteePairs committee :: Committee era
committee@(Committee Map (Credential 'ColdCommitteeRole) EpochNo
_ UnitInterval
_) =
let Committee {Map (Credential 'ColdCommitteeRole) EpochNo
UnitInterval
committeeThreshold :: UnitInterval
committeeMembers :: Map (Credential 'ColdCommitteeRole) EpochNo
committeeThreshold :: forall era. Committee era -> UnitInterval
committeeMembers :: forall era.
Committee era -> Map (Credential 'ColdCommitteeRole) EpochNo
..} = Committee era
committee
in [ Key
"members" forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Map (Credential 'ColdCommitteeRole) EpochNo
committeeMembers
, Key
"threshold" forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= UnitInterval
committeeThreshold
]
data GovActionPurpose
= PParamUpdatePurpose
| HardForkPurpose
| CommitteePurpose
| ConstitutionPurpose
deriving (GovActionPurpose -> GovActionPurpose -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GovActionPurpose -> GovActionPurpose -> Bool
$c/= :: GovActionPurpose -> GovActionPurpose -> Bool
== :: GovActionPurpose -> GovActionPurpose -> Bool
$c== :: GovActionPurpose -> GovActionPurpose -> Bool
Eq, Int -> GovActionPurpose -> ShowS
[GovActionPurpose] -> ShowS
GovActionPurpose -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GovActionPurpose] -> ShowS
$cshowList :: [GovActionPurpose] -> ShowS
show :: GovActionPurpose -> String
$cshow :: GovActionPurpose -> String
showsPrec :: Int -> GovActionPurpose -> ShowS
$cshowsPrec :: Int -> GovActionPurpose -> ShowS
Show, forall x. Rep GovActionPurpose x -> GovActionPurpose
forall x. GovActionPurpose -> Rep GovActionPurpose x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GovActionPurpose x -> GovActionPurpose
$cfrom :: forall x. GovActionPurpose -> Rep GovActionPurpose x
Generic)
class ToGovActionPurpose (p :: GovActionPurpose) where
toGovActionPurpose :: GovActionPurpose
instance ToGovActionPurpose 'PParamUpdatePurpose where
toGovActionPurpose :: GovActionPurpose
toGovActionPurpose = GovActionPurpose
PParamUpdatePurpose
instance ToGovActionPurpose 'HardForkPurpose where
toGovActionPurpose :: GovActionPurpose
toGovActionPurpose = GovActionPurpose
HardForkPurpose
instance ToGovActionPurpose 'CommitteePurpose where
toGovActionPurpose :: GovActionPurpose
toGovActionPurpose = GovActionPurpose
CommitteePurpose
instance ToGovActionPurpose 'ConstitutionPurpose where
toGovActionPurpose :: GovActionPurpose
toGovActionPurpose = GovActionPurpose
ConstitutionPurpose
isGovActionWithPurpose :: forall p era. ToGovActionPurpose p => GovAction era -> Bool
isGovActionWithPurpose :: forall (p :: GovActionPurpose) era.
ToGovActionPurpose p =>
GovAction era -> Bool
isGovActionWithPurpose GovAction era
govAction =
case GovAction era
govAction of
ParameterChange {} -> forall (p :: GovActionPurpose).
ToGovActionPurpose p =>
GovActionPurpose
toGovActionPurpose @p forall a. Eq a => a -> a -> Bool
== GovActionPurpose
PParamUpdatePurpose
HardForkInitiation {} -> forall (p :: GovActionPurpose).
ToGovActionPurpose p =>
GovActionPurpose
toGovActionPurpose @p forall a. Eq a => a -> a -> Bool
== GovActionPurpose
HardForkPurpose
TreasuryWithdrawals {} -> Bool
False
NoConfidence {} -> forall (p :: GovActionPurpose).
ToGovActionPurpose p =>
GovActionPurpose
toGovActionPurpose @p forall a. Eq a => a -> a -> Bool
== GovActionPurpose
CommitteePurpose
UpdateCommittee {} -> forall (p :: GovActionPurpose).
ToGovActionPurpose p =>
GovActionPurpose
toGovActionPurpose @p forall a. Eq a => a -> a -> Bool
== GovActionPurpose
CommitteePurpose
NewConstitution {} -> forall (p :: GovActionPurpose).
ToGovActionPurpose p =>
GovActionPurpose
toGovActionPurpose @p forall a. Eq a => a -> a -> Bool
== GovActionPurpose
ConstitutionPurpose
GovAction era
InfoAction -> Bool
False
newtype GovPurposeId (p :: GovActionPurpose) era = GovPurposeId
{ forall (p :: GovActionPurpose) era.
GovPurposeId p era -> GovActionId
unGovPurposeId :: GovActionId
}
deriving (GovPurposeId p era -> GovPurposeId p era -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall (p :: GovActionPurpose) era.
GovPurposeId p era -> GovPurposeId p era -> Bool
/= :: GovPurposeId p era -> GovPurposeId p era -> Bool
$c/= :: forall (p :: GovActionPurpose) era.
GovPurposeId p era -> GovPurposeId p era -> Bool
== :: GovPurposeId p era -> GovPurposeId p era -> Bool
$c== :: forall (p :: GovActionPurpose) era.
GovPurposeId p era -> GovPurposeId p era -> Bool
Eq, GovPurposeId p era -> GovPurposeId p era -> Bool
GovPurposeId p era -> GovPurposeId p era -> Ordering
GovPurposeId p era -> GovPurposeId p era -> GovPurposeId p era
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall (p :: GovActionPurpose) era. Eq (GovPurposeId p era)
forall (p :: GovActionPurpose) era.
GovPurposeId p era -> GovPurposeId p era -> Bool
forall (p :: GovActionPurpose) era.
GovPurposeId p era -> GovPurposeId p era -> Ordering
forall (p :: GovActionPurpose) era.
GovPurposeId p era -> GovPurposeId p era -> GovPurposeId p era
min :: GovPurposeId p era -> GovPurposeId p era -> GovPurposeId p era
$cmin :: forall (p :: GovActionPurpose) era.
GovPurposeId p era -> GovPurposeId p era -> GovPurposeId p era
max :: GovPurposeId p era -> GovPurposeId p era -> GovPurposeId p era
$cmax :: forall (p :: GovActionPurpose) era.
GovPurposeId p era -> GovPurposeId p era -> GovPurposeId p era
>= :: GovPurposeId p era -> GovPurposeId p era -> Bool
$c>= :: forall (p :: GovActionPurpose) era.
GovPurposeId p era -> GovPurposeId p era -> Bool
> :: GovPurposeId p era -> GovPurposeId p era -> Bool
$c> :: forall (p :: GovActionPurpose) era.
GovPurposeId p era -> GovPurposeId p era -> Bool
<= :: GovPurposeId p era -> GovPurposeId p era -> Bool
$c<= :: forall (p :: GovActionPurpose) era.
GovPurposeId p era -> GovPurposeId p era -> Bool
< :: GovPurposeId p era -> GovPurposeId p era -> Bool
$c< :: forall (p :: GovActionPurpose) era.
GovPurposeId p era -> GovPurposeId p era -> Bool
compare :: GovPurposeId p era -> GovPurposeId p era -> Ordering
$ccompare :: forall (p :: GovActionPurpose) era.
GovPurposeId p era -> GovPurposeId p era -> Ordering
Ord, forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (p :: GovActionPurpose) era x.
Rep (GovPurposeId p era) x -> GovPurposeId p era
forall (p :: GovActionPurpose) era x.
GovPurposeId p era -> Rep (GovPurposeId p era) x
$cto :: forall (p :: GovActionPurpose) era x.
Rep (GovPurposeId p era) x -> GovPurposeId p era
$cfrom :: forall (p :: GovActionPurpose) era x.
GovPurposeId p era -> Rep (GovPurposeId p era) x
Generic)
type role GovPurposeId nominal nominal
deriving newtype instance
(Era era, Typeable p) => EncCBOR (GovPurposeId (p :: GovActionPurpose) era)
deriving newtype instance
(Era era, Typeable p) => DecCBOR (GovPurposeId (p :: GovActionPurpose) era)
deriving newtype instance Era era => NoThunks (GovPurposeId (p :: GovActionPurpose) era)
deriving newtype instance Era era => NFData (GovPurposeId (p :: GovActionPurpose) era)
deriving newtype instance Era era => ToJSONKey (GovPurposeId (p :: GovActionPurpose) era)
deriving newtype instance Era era => ToJSON (GovPurposeId (p :: GovActionPurpose) era)
deriving newtype instance Era era => Show (GovPurposeId (p :: GovActionPurpose) era)
data GovRelation (f :: Type -> Type) era = GovRelation
{ forall (f :: * -> *) era.
GovRelation f era -> f (GovPurposeId 'PParamUpdatePurpose era)
grPParamUpdate :: !(f (GovPurposeId 'PParamUpdatePurpose era))
, forall (f :: * -> *) era.
GovRelation f era -> f (GovPurposeId 'HardForkPurpose era)
grHardFork :: !(f (GovPurposeId 'HardForkPurpose era))
, forall (f :: * -> *) era.
GovRelation f era -> f (GovPurposeId 'CommitteePurpose era)
grCommittee :: !(f (GovPurposeId 'CommitteePurpose era))
, forall (f :: * -> *) era.
GovRelation f era -> f (GovPurposeId 'ConstitutionPurpose era)
grConstitution :: !(f (GovPurposeId 'ConstitutionPurpose era))
}
deriving (forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (f :: * -> *) era x.
Rep (GovRelation f era) x -> GovRelation f era
forall (f :: * -> *) era x.
GovRelation f era -> Rep (GovRelation f era) x
$cto :: forall (f :: * -> *) era x.
Rep (GovRelation f era) x -> GovRelation f era
$cfrom :: forall (f :: * -> *) era x.
GovRelation f era -> Rep (GovRelation f era) x
Generic)
deriving instance
(forall p. Eq (f (GovPurposeId (p :: GovActionPurpose) era))) =>
Eq (GovRelation f era)
deriving instance
(forall p. Show (f (GovPurposeId (p :: GovActionPurpose) era))) =>
Show (GovRelation f era)
instance
(forall p. NoThunks (f (GovPurposeId (p :: GovActionPurpose) era))) =>
NoThunks (GovRelation f era)
instance
(forall p. Default (f (GovPurposeId (p :: GovActionPurpose) era))) =>
Default (GovRelation f era)
instance
(forall p. NFData (f (GovPurposeId (p :: GovActionPurpose) era))) =>
NFData (GovRelation f era)
where
rnf :: GovRelation f era -> ()
rnf (GovRelation f (GovPurposeId 'PParamUpdatePurpose era)
a f (GovPurposeId 'HardForkPurpose era)
b f (GovPurposeId 'CommitteePurpose era)
c f (GovPurposeId 'ConstitutionPurpose era)
d) = f (GovPurposeId 'PParamUpdatePurpose era)
a forall a b. NFData a => a -> b -> b
`deepseq` f (GovPurposeId 'HardForkPurpose era)
b forall a b. NFData a => a -> b -> b
`deepseq` f (GovPurposeId 'CommitteePurpose era)
c forall a b. NFData a => a -> b -> b
`deepseq` forall a. NFData a => a -> ()
rnf f (GovPurposeId 'ConstitutionPurpose era)
d
instance
(forall p. Semigroup (f (GovPurposeId (p :: GovActionPurpose) era))) =>
Semigroup (GovRelation f era)
where
<> :: GovRelation f era -> GovRelation f era -> GovRelation f era
(<>) GovRelation f era
p1 GovRelation f era
p2 =
GovRelation
{ grPParamUpdate :: f (GovPurposeId 'PParamUpdatePurpose era)
grPParamUpdate = forall (f :: * -> *) era.
GovRelation f era -> f (GovPurposeId 'PParamUpdatePurpose era)
grPParamUpdate GovRelation f era
p1 forall a. Semigroup a => a -> a -> a
<> forall (f :: * -> *) era.
GovRelation f era -> f (GovPurposeId 'PParamUpdatePurpose era)
grPParamUpdate GovRelation f era
p2
, grHardFork :: f (GovPurposeId 'HardForkPurpose era)
grHardFork = forall (f :: * -> *) era.
GovRelation f era -> f (GovPurposeId 'HardForkPurpose era)
grHardFork GovRelation f era
p1 forall a. Semigroup a => a -> a -> a
<> forall (f :: * -> *) era.
GovRelation f era -> f (GovPurposeId 'HardForkPurpose era)
grHardFork GovRelation f era
p2
, grCommittee :: f (GovPurposeId 'CommitteePurpose era)
grCommittee = forall (f :: * -> *) era.
GovRelation f era -> f (GovPurposeId 'CommitteePurpose era)
grCommittee GovRelation f era
p1 forall a. Semigroup a => a -> a -> a
<> forall (f :: * -> *) era.
GovRelation f era -> f (GovPurposeId 'CommitteePurpose era)
grCommittee GovRelation f era
p2
, grConstitution :: f (GovPurposeId 'ConstitutionPurpose era)
grConstitution = forall (f :: * -> *) era.
GovRelation f era -> f (GovPurposeId 'ConstitutionPurpose era)
grConstitution GovRelation f era
p1 forall a. Semigroup a => a -> a -> a
<> forall (f :: * -> *) era.
GovRelation f era -> f (GovPurposeId 'ConstitutionPurpose era)
grConstitution GovRelation f era
p2
}
instance
(forall p. Monoid (f (GovPurposeId (p :: GovActionPurpose) era))) =>
Monoid (GovRelation f era)
where
mempty :: GovRelation f era
mempty =
GovRelation
{ grPParamUpdate :: f (GovPurposeId 'PParamUpdatePurpose era)
grPParamUpdate = forall a. Monoid a => a
mempty
, grHardFork :: f (GovPurposeId 'HardForkPurpose era)
grHardFork = forall a. Monoid a => a
mempty
, grCommittee :: f (GovPurposeId 'CommitteePurpose era)
grCommittee = forall a. Monoid a => a
mempty
, grConstitution :: f (GovPurposeId 'ConstitutionPurpose era)
grConstitution = forall a. Monoid a => a
mempty
}
instance
( Era era
, Typeable f
, (forall p. Typeable p => DecCBOR (f (GovPurposeId (p :: GovActionPurpose) era)))
) =>
DecCBOR (GovRelation f era)
where
decCBOR :: forall s. Decoder s (GovRelation f era)
decCBOR =
forall a s. Text -> (a -> Int) -> Decoder s a -> Decoder s a
decodeRecordNamed
Text
"GovRelation"
(forall a b. a -> b -> a
const Int
4)
(forall (f :: * -> *) era.
f (GovPurposeId 'PParamUpdatePurpose era)
-> f (GovPurposeId 'HardForkPurpose era)
-> f (GovPurposeId 'CommitteePurpose era)
-> f (GovPurposeId 'ConstitutionPurpose era)
-> GovRelation f era
GovRelation forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a s. DecCBOR a => Decoder s a
decCBOR forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a s. DecCBOR a => Decoder s a
decCBOR forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a s. DecCBOR a => Decoder s a
decCBOR forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a s. DecCBOR a => Decoder s a
decCBOR)
instance
( Era era
, Typeable f
, (forall p. Typeable p => EncCBOR (f (GovPurposeId (p :: GovActionPurpose) era)))
) =>
EncCBOR (GovRelation f era)
where
encCBOR :: GovRelation f era -> Encoding
encCBOR govPurpose :: GovRelation f era
govPurpose@(GovRelation f (GovPurposeId 'PParamUpdatePurpose era)
_ f (GovPurposeId 'HardForkPurpose era)
_ f (GovPurposeId 'CommitteePurpose era)
_ f (GovPurposeId 'ConstitutionPurpose era)
_) =
let GovRelation {f (GovPurposeId 'PParamUpdatePurpose era)
f (GovPurposeId 'HardForkPurpose era)
f (GovPurposeId 'CommitteePurpose era)
f (GovPurposeId 'ConstitutionPurpose era)
grConstitution :: f (GovPurposeId 'ConstitutionPurpose era)
grCommittee :: f (GovPurposeId 'CommitteePurpose era)
grHardFork :: f (GovPurposeId 'HardForkPurpose era)
grPParamUpdate :: f (GovPurposeId 'PParamUpdatePurpose era)
grConstitution :: forall (f :: * -> *) era.
GovRelation f era -> f (GovPurposeId 'ConstitutionPurpose era)
grCommittee :: forall (f :: * -> *) era.
GovRelation f era -> f (GovPurposeId 'CommitteePurpose era)
grHardFork :: forall (f :: * -> *) era.
GovRelation f era -> f (GovPurposeId 'HardForkPurpose era)
grPParamUpdate :: forall (f :: * -> *) era.
GovRelation f era -> f (GovPurposeId 'PParamUpdatePurpose era)
..} = GovRelation f era
govPurpose
in Word -> Encoding
encodeListLen Word
4
forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR f (GovPurposeId 'PParamUpdatePurpose era)
grPParamUpdate
forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR f (GovPurposeId 'HardForkPurpose era)
grHardFork
forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR f (GovPurposeId 'CommitteePurpose era)
grCommittee
forall a. Semigroup a => a -> a -> a
<> forall a. EncCBOR a => a -> Encoding
encCBOR f (GovPurposeId 'ConstitutionPurpose era)
grConstitution
toPrevGovActionIdsPairs ::
( KeyValue e a
, (forall p. ToJSON (f (GovPurposeId (p :: GovActionPurpose) era)))
) =>
GovRelation f era ->
[a]
toPrevGovActionIdsPairs :: forall e a (f :: * -> *) era.
(KeyValue e a,
forall (p :: GovActionPurpose). ToJSON (f (GovPurposeId p era))) =>
GovRelation f era -> [a]
toPrevGovActionIdsPairs govPurpose :: GovRelation f era
govPurpose@(GovRelation f (GovPurposeId 'PParamUpdatePurpose era)
_ f (GovPurposeId 'HardForkPurpose era)
_ f (GovPurposeId 'CommitteePurpose era)
_ f (GovPurposeId 'ConstitutionPurpose era)
_) =
let GovRelation {f (GovPurposeId 'PParamUpdatePurpose era)
f (GovPurposeId 'HardForkPurpose era)
f (GovPurposeId 'CommitteePurpose era)
f (GovPurposeId 'ConstitutionPurpose era)
grConstitution :: f (GovPurposeId 'ConstitutionPurpose era)
grCommittee :: f (GovPurposeId 'CommitteePurpose era)
grHardFork :: f (GovPurposeId 'HardForkPurpose era)
grPParamUpdate :: f (GovPurposeId 'PParamUpdatePurpose era)
grConstitution :: forall (f :: * -> *) era.
GovRelation f era -> f (GovPurposeId 'ConstitutionPurpose era)
grCommittee :: forall (f :: * -> *) era.
GovRelation f era -> f (GovPurposeId 'CommitteePurpose era)
grHardFork :: forall (f :: * -> *) era.
GovRelation f era -> f (GovPurposeId 'HardForkPurpose era)
grPParamUpdate :: forall (f :: * -> *) era.
GovRelation f era -> f (GovPurposeId 'PParamUpdatePurpose era)
..} = GovRelation f era
govPurpose
in [ Key
"PParamUpdate" forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= f (GovPurposeId 'PParamUpdatePurpose era)
grPParamUpdate
, Key
"HardFork" forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= f (GovPurposeId 'HardForkPurpose era)
grHardFork
, Key
"Committee" forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= f (GovPurposeId 'CommitteePurpose era)
grCommittee
, Key
"Constitution" forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= f (GovPurposeId 'ConstitutionPurpose era)
grConstitution
]
instance
(Era era, (forall p. ToJSON (f (GovPurposeId (p :: GovActionPurpose) era)))) =>
ToJSON (GovRelation f era)
where
toJSON :: GovRelation f era -> Value
toJSON = [Pair] -> Value
object forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall e a (f :: * -> *) era.
(KeyValue e a,
forall (p :: GovActionPurpose). ToJSON (f (GovPurposeId p era))) =>
GovRelation f era -> [a]
toPrevGovActionIdsPairs
toEncoding :: GovRelation f era -> Encoding
toEncoding = Series -> Encoding
pairs forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Monoid a => [a] -> a
mconcat forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall e a (f :: * -> *) era.
(KeyValue e a,
forall (p :: GovActionPurpose). ToJSON (f (GovPurposeId p era))) =>
GovRelation f era -> [a]
toPrevGovActionIdsPairs
grPParamUpdateL :: Lens' (GovRelation f era) (f (GovPurposeId 'PParamUpdatePurpose era))
grPParamUpdateL :: forall (f :: * -> *) era.
Lens'
(GovRelation f era) (f (GovPurposeId 'PParamUpdatePurpose era))
grPParamUpdateL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall (f :: * -> *) era.
GovRelation f era -> f (GovPurposeId 'PParamUpdatePurpose era)
grPParamUpdate forall a b. (a -> b) -> a -> b
$ \GovRelation f era
x f (GovPurposeId 'PParamUpdatePurpose era)
y -> GovRelation f era
x {grPParamUpdate :: f (GovPurposeId 'PParamUpdatePurpose era)
grPParamUpdate = f (GovPurposeId 'PParamUpdatePurpose era)
y}
grHardForkL :: Lens' (GovRelation f era) (f (GovPurposeId 'HardForkPurpose era))
grHardForkL :: forall (f :: * -> *) era.
Lens' (GovRelation f era) (f (GovPurposeId 'HardForkPurpose era))
grHardForkL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall (f :: * -> *) era.
GovRelation f era -> f (GovPurposeId 'HardForkPurpose era)
grHardFork forall a b. (a -> b) -> a -> b
$ \GovRelation f era
x f (GovPurposeId 'HardForkPurpose era)
y -> GovRelation f era
x {grHardFork :: f (GovPurposeId 'HardForkPurpose era)
grHardFork = f (GovPurposeId 'HardForkPurpose era)
y}
grCommitteeL :: Lens' (GovRelation f era) (f (GovPurposeId 'CommitteePurpose era))
grCommitteeL :: forall (f :: * -> *) era.
Lens' (GovRelation f era) (f (GovPurposeId 'CommitteePurpose era))
grCommitteeL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall (f :: * -> *) era.
GovRelation f era -> f (GovPurposeId 'CommitteePurpose era)
grCommittee forall a b. (a -> b) -> a -> b
$ \GovRelation f era
x f (GovPurposeId 'CommitteePurpose era)
y -> GovRelation f era
x {grCommittee :: f (GovPurposeId 'CommitteePurpose era)
grCommittee = f (GovPurposeId 'CommitteePurpose era)
y}
grConstitutionL :: Lens' (GovRelation f era) (f (GovPurposeId 'ConstitutionPurpose era))
grConstitutionL :: forall (f :: * -> *) era.
Lens'
(GovRelation f era) (f (GovPurposeId 'ConstitutionPurpose era))
grConstitutionL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall (f :: * -> *) era.
GovRelation f era -> f (GovPurposeId 'ConstitutionPurpose era)
grConstitution forall a b. (a -> b) -> a -> b
$ \GovRelation f era
x f (GovPurposeId 'ConstitutionPurpose era)
y -> GovRelation f era
x {grConstitution :: f (GovPurposeId 'ConstitutionPurpose era)
grConstitution = f (GovPurposeId 'ConstitutionPurpose era)
y}
hoistGovRelation :: (forall a. f a -> g a) -> GovRelation f era -> GovRelation g era
hoistGovRelation :: forall (f :: * -> *) (g :: * -> *) era.
(forall a. f a -> g a) -> GovRelation f era -> GovRelation g era
hoistGovRelation forall a. f a -> g a
f GovRelation f era
gr =
GovRelation
{ grPParamUpdate :: g (GovPurposeId 'PParamUpdatePurpose era)
grPParamUpdate = forall a. f a -> g a
f (forall (f :: * -> *) era.
GovRelation f era -> f (GovPurposeId 'PParamUpdatePurpose era)
grPParamUpdate GovRelation f era
gr)
, grHardFork :: g (GovPurposeId 'HardForkPurpose era)
grHardFork = forall a. f a -> g a
f (forall (f :: * -> *) era.
GovRelation f era -> f (GovPurposeId 'HardForkPurpose era)
grHardFork GovRelation f era
gr)
, grCommittee :: g (GovPurposeId 'CommitteePurpose era)
grCommittee = forall a. f a -> g a
f (forall (f :: * -> *) era.
GovRelation f era -> f (GovPurposeId 'CommitteePurpose era)
grCommittee GovRelation f era
gr)
, grConstitution :: g (GovPurposeId 'ConstitutionPurpose era)
grConstitution = forall a. f a -> g a
f (forall (f :: * -> *) era.
GovRelation f era -> f (GovPurposeId 'ConstitutionPurpose era)
grConstitution GovRelation f era
gr)
}
withGovActionParent ::
GovActionState era ->
a ->
( forall p.
(forall f. Lens' (GovRelation f era) (f (GovPurposeId p era))) ->
StrictMaybe (GovPurposeId p era) ->
GovPurposeId p era ->
a
) ->
a
withGovActionParent :: forall era a.
GovActionState era
-> a
-> (forall (p :: GovActionPurpose).
(forall (f :: * -> *).
Lens' (GovRelation f era) (f (GovPurposeId p era)))
-> StrictMaybe (GovPurposeId p era) -> GovPurposeId p era -> a)
-> a
withGovActionParent GovActionState era
gas a
noParent forall (p :: GovActionPurpose).
(forall (f :: * -> *).
Lens' (GovRelation f era) (f (GovPurposeId p era)))
-> StrictMaybe (GovPurposeId p era) -> GovPurposeId p era -> a
f =
case GovActionState era
gas forall s a. s -> Getting a s a -> a
^. forall era. Lens' (GovActionState era) (GovAction era)
gasActionL of
ParameterChange StrictMaybe (GovPurposeId 'PParamUpdatePurpose era)
parent PParamsUpdate era
_ StrictMaybe ScriptHash
_ -> forall (p :: GovActionPurpose).
(forall (f :: * -> *).
Lens' (GovRelation f era) (f (GovPurposeId p era)))
-> StrictMaybe (GovPurposeId p era) -> GovPurposeId p era -> a
f forall (f :: * -> *) era.
Lens'
(GovRelation f era) (f (GovPurposeId 'PParamUpdatePurpose era))
grPParamUpdateL StrictMaybe (GovPurposeId 'PParamUpdatePurpose era)
parent (forall (p :: GovActionPurpose) era.
GovActionId -> GovPurposeId p era
GovPurposeId (GovActionState era
gas forall s a. s -> Getting a s a -> a
^. forall era. Lens' (GovActionState era) GovActionId
gasIdL))
HardForkInitiation StrictMaybe (GovPurposeId 'HardForkPurpose era)
parent ProtVer
_ -> forall (p :: GovActionPurpose).
(forall (f :: * -> *).
Lens' (GovRelation f era) (f (GovPurposeId p era)))
-> StrictMaybe (GovPurposeId p era) -> GovPurposeId p era -> a
f forall (f :: * -> *) era.
Lens' (GovRelation f era) (f (GovPurposeId 'HardForkPurpose era))
grHardForkL StrictMaybe (GovPurposeId 'HardForkPurpose era)
parent (forall (p :: GovActionPurpose) era.
GovActionId -> GovPurposeId p era
GovPurposeId (GovActionState era
gas forall s a. s -> Getting a s a -> a
^. forall era. Lens' (GovActionState era) GovActionId
gasIdL))
TreasuryWithdrawals Map RewardAccount Coin
_ StrictMaybe ScriptHash
_ -> a
noParent
NoConfidence StrictMaybe (GovPurposeId 'CommitteePurpose era)
parent -> forall (p :: GovActionPurpose).
(forall (f :: * -> *).
Lens' (GovRelation f era) (f (GovPurposeId p era)))
-> StrictMaybe (GovPurposeId p era) -> GovPurposeId p era -> a
f forall (f :: * -> *) era.
Lens' (GovRelation f era) (f (GovPurposeId 'CommitteePurpose era))
grCommitteeL StrictMaybe (GovPurposeId 'CommitteePurpose era)
parent (forall (p :: GovActionPurpose) era.
GovActionId -> GovPurposeId p era
GovPurposeId (GovActionState era
gas forall s a. s -> Getting a s a -> a
^. forall era. Lens' (GovActionState era) GovActionId
gasIdL))
UpdateCommittee StrictMaybe (GovPurposeId 'CommitteePurpose era)
parent Set (Credential 'ColdCommitteeRole)
_ Map (Credential 'ColdCommitteeRole) EpochNo
_ UnitInterval
_ -> forall (p :: GovActionPurpose).
(forall (f :: * -> *).
Lens' (GovRelation f era) (f (GovPurposeId p era)))
-> StrictMaybe (GovPurposeId p era) -> GovPurposeId p era -> a
f forall (f :: * -> *) era.
Lens' (GovRelation f era) (f (GovPurposeId 'CommitteePurpose era))
grCommitteeL StrictMaybe (GovPurposeId 'CommitteePurpose era)
parent (forall (p :: GovActionPurpose) era.
GovActionId -> GovPurposeId p era
GovPurposeId (GovActionState era
gas forall s a. s -> Getting a s a -> a
^. forall era. Lens' (GovActionState era) GovActionId
gasIdL))
NewConstitution StrictMaybe (GovPurposeId 'ConstitutionPurpose era)
parent Constitution era
_ -> forall (p :: GovActionPurpose).
(forall (f :: * -> *).
Lens' (GovRelation f era) (f (GovPurposeId p era)))
-> StrictMaybe (GovPurposeId p era) -> GovPurposeId p era -> a
f forall (f :: * -> *) era.
Lens'
(GovRelation f era) (f (GovPurposeId 'ConstitutionPurpose era))
grConstitutionL StrictMaybe (GovPurposeId 'ConstitutionPurpose era)
parent (forall (p :: GovActionPurpose) era.
GovActionId -> GovPurposeId p era
GovPurposeId (GovActionState era
gas forall s a. s -> Getting a s a -> a
^. forall era. Lens' (GovActionState era) GovActionId
gasIdL))
GovAction era
InfoAction -> a
noParent
data GovAction era
= ParameterChange
!(StrictMaybe (GovPurposeId 'PParamUpdatePurpose era))
!(PParamsUpdate era)
!(StrictMaybe ScriptHash)
| HardForkInitiation
!(StrictMaybe (GovPurposeId 'HardForkPurpose era))
!ProtVer
| TreasuryWithdrawals
!(Map RewardAccount Coin)
!(StrictMaybe ScriptHash)
| NoConfidence
!(StrictMaybe (GovPurposeId 'CommitteePurpose era))
| UpdateCommittee
!(StrictMaybe (GovPurposeId 'CommitteePurpose era))
!(Set (Credential 'ColdCommitteeRole))
!(Map (Credential 'ColdCommitteeRole) EpochNo)
!UnitInterval
| NewConstitution
!(StrictMaybe (GovPurposeId 'ConstitutionPurpose era))
!(Constitution era)
| InfoAction
deriving (forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall era x. Rep (GovAction era) x -> GovAction era
forall era x. GovAction era -> Rep (GovAction era) x
$cto :: forall era x. Rep (GovAction era) x -> GovAction era
$cfrom :: forall era x. GovAction era -> Rep (GovAction era) x
Generic, GovAction era -> GovAction era -> Ordering
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall era. EraPParams era => Eq (GovAction era)
forall era.
EraPParams era =>
GovAction era -> GovAction era -> Bool
forall era.
EraPParams era =>
GovAction era -> GovAction era -> Ordering
forall era.
EraPParams era =>
GovAction era -> GovAction era -> GovAction era
min :: GovAction era -> GovAction era -> GovAction era
$cmin :: forall era.
EraPParams era =>
GovAction era -> GovAction era -> GovAction era
max :: GovAction era -> GovAction era -> GovAction era
$cmax :: forall era.
EraPParams era =>
GovAction era -> GovAction era -> GovAction era
>= :: GovAction era -> GovAction era -> Bool
$c>= :: forall era.
EraPParams era =>
GovAction era -> GovAction era -> Bool
> :: GovAction era -> GovAction era -> Bool
$c> :: forall era.
EraPParams era =>
GovAction era -> GovAction era -> Bool
<= :: GovAction era -> GovAction era -> Bool
$c<= :: forall era.
EraPParams era =>
GovAction era -> GovAction era -> Bool
< :: GovAction era -> GovAction era -> Bool
$c< :: forall era.
EraPParams era =>
GovAction era -> GovAction era -> Bool
compare :: GovAction era -> GovAction era -> Ordering
$ccompare :: forall era.
EraPParams era =>
GovAction era -> GovAction era -> Ordering
Ord)
showGovActionType :: GovAction era -> String
showGovActionType :: forall era. GovAction era -> String
showGovActionType NewConstitution {} = String
"NewConstitution"
showGovActionType ParameterChange {} = String
"ParameterChange"
showGovActionType HardForkInitiation {} = String
"HardForkInitiation"
showGovActionType TreasuryWithdrawals {} = String
"TreasuryWithdrawals"
showGovActionType NoConfidence {} = String
"NoConfidence"
showGovActionType UpdateCommittee {} = String
"UpdateCommittee"
showGovActionType InfoAction {} = String
"InfoAction"
deriving instance EraPParams era => Show (GovAction era)
deriving instance EraPParams era => Eq (GovAction era)
instance EraPParams era => NoThunks (GovAction era)
instance EraPParams era => NFData (GovAction era)
instance EraPParams era => ToJSON (GovAction era)
instance EraPParams era => DecCBOR (GovAction era) where
decCBOR :: forall s. Decoder s (GovAction era)
decCBOR =
forall (w :: Wrapped) t s. Decode w t -> Decoder s t
decode forall a b. (a -> b) -> a -> b
$ forall t.
Text -> (Word -> Decode 'Open t) -> Decode ('Closed 'Dense) t
Summands Text
"GovAction" forall a b. (a -> b) -> a -> b
$ \case
Word
0 ->
forall t. t -> Decode 'Open t
SumD forall era.
StrictMaybe (GovPurposeId 'PParamUpdatePurpose era)
-> PParamsUpdate era -> StrictMaybe ScriptHash -> GovAction era
ParameterChange
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t. (forall s. Decoder s t) -> Decode ('Closed 'Dense) t
D (forall s a. Decoder s a -> Decoder s (StrictMaybe a)
decodeNullStrictMaybe forall a s. DecCBOR a => Decoder s a
decCBOR)
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t (w :: Wrapped). DecCBOR t => Decode w t
From
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t. (forall s. Decoder s t) -> Decode ('Closed 'Dense) t
D (forall s a. Decoder s a -> Decoder s (StrictMaybe a)
decodeNullStrictMaybe forall a s. DecCBOR a => Decoder s a
decCBOR)
Word
1 -> forall t. t -> Decode 'Open t
SumD forall era.
StrictMaybe (GovPurposeId 'HardForkPurpose era)
-> ProtVer -> GovAction era
HardForkInitiation forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t. (forall s. Decoder s t) -> Decode ('Closed 'Dense) t
D (forall s a. Decoder s a -> Decoder s (StrictMaybe a)
decodeNullStrictMaybe forall a s. DecCBOR a => Decoder s a
decCBOR) forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t (w :: Wrapped). DecCBOR t => Decode w t
From
Word
2 -> forall t. t -> Decode 'Open t
SumD forall era.
Map RewardAccount Coin -> StrictMaybe ScriptHash -> GovAction era
TreasuryWithdrawals forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t (w :: Wrapped). DecCBOR t => Decode w t
From forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t. (forall s. Decoder s t) -> Decode ('Closed 'Dense) t
D (forall s a. Decoder s a -> Decoder s (StrictMaybe a)
decodeNullStrictMaybe forall a s. DecCBOR a => Decoder s a
decCBOR)
Word
3 -> forall t. t -> Decode 'Open t
SumD forall era.
StrictMaybe (GovPurposeId 'CommitteePurpose era) -> GovAction era
NoConfidence forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t. (forall s. Decoder s t) -> Decode ('Closed 'Dense) t
D (forall s a. Decoder s a -> Decoder s (StrictMaybe a)
decodeNullStrictMaybe forall a s. DecCBOR a => Decoder s a
decCBOR)
Word
4 -> forall t. t -> Decode 'Open t
SumD forall era.
StrictMaybe (GovPurposeId 'CommitteePurpose era)
-> Set (Credential 'ColdCommitteeRole)
-> Map (Credential 'ColdCommitteeRole) EpochNo
-> UnitInterval
-> GovAction era
UpdateCommittee forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t. (forall s. Decoder s t) -> Decode ('Closed 'Dense) t
D (forall s a. Decoder s a -> Decoder s (StrictMaybe a)
decodeNullStrictMaybe forall a s. DecCBOR a => Decoder s a
decCBOR) forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t (w :: Wrapped). DecCBOR t => Decode w t
From forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t (w :: Wrapped). DecCBOR t => Decode w t
From forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t (w :: Wrapped). DecCBOR t => Decode w t
From
Word
5 -> forall t. t -> Decode 'Open t
SumD forall era.
StrictMaybe (GovPurposeId 'ConstitutionPurpose era)
-> Constitution era -> GovAction era
NewConstitution forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t. (forall s. Decoder s t) -> Decode ('Closed 'Dense) t
D (forall s a. Decoder s a -> Decoder s (StrictMaybe a)
decodeNullStrictMaybe forall a s. DecCBOR a => Decoder s a
decCBOR) forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t (w :: Wrapped). DecCBOR t => Decode w t
From
Word
6 -> forall t. t -> Decode 'Open t
SumD forall era. GovAction era
InfoAction
Word
k -> forall (w :: Wrapped) t. Word -> Decode w t
Invalid Word
k
{-# INLINE decCBOR #-}
instance EraPParams era => EncCBOR (GovAction era) where
encCBOR :: GovAction era -> Encoding
encCBOR =
forall (w :: Wrapped) t. Encode w t -> Encoding
encode forall b c a. (b -> c) -> (a -> b) -> a -> c
. \case
ParameterChange StrictMaybe (GovPurposeId 'PParamUpdatePurpose era)
gid PParamsUpdate era
ppup StrictMaybe ScriptHash
pol ->
forall t. t -> Word -> Encode 'Open t
Sum forall era.
StrictMaybe (GovPurposeId 'PParamUpdatePurpose era)
-> PParamsUpdate era -> StrictMaybe ScriptHash -> GovAction era
ParameterChange Word
0
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. (t -> Encoding) -> t -> Encode ('Closed 'Dense) t
E (forall a. (a -> Encoding) -> StrictMaybe a -> Encoding
encodeNullStrictMaybe forall a. EncCBOR a => a -> Encoding
encCBOR) StrictMaybe (GovPurposeId 'PParamUpdatePurpose era)
gid
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To PParamsUpdate era
ppup
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. (t -> Encoding) -> t -> Encode ('Closed 'Dense) t
E (forall a. (a -> Encoding) -> StrictMaybe a -> Encoding
encodeNullStrictMaybe forall a. EncCBOR a => a -> Encoding
encCBOR) StrictMaybe ScriptHash
pol
HardForkInitiation StrictMaybe (GovPurposeId 'HardForkPurpose era)
gid ProtVer
pv ->
forall t. t -> Word -> Encode 'Open t
Sum forall era.
StrictMaybe (GovPurposeId 'HardForkPurpose era)
-> ProtVer -> GovAction era
HardForkInitiation Word
1 forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. (t -> Encoding) -> t -> Encode ('Closed 'Dense) t
E (forall a. (a -> Encoding) -> StrictMaybe a -> Encoding
encodeNullStrictMaybe forall a. EncCBOR a => a -> Encoding
encCBOR) StrictMaybe (GovPurposeId 'HardForkPurpose era)
gid forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To ProtVer
pv
TreasuryWithdrawals Map RewardAccount Coin
ws StrictMaybe ScriptHash
pol ->
forall t. t -> Word -> Encode 'Open t
Sum forall era.
Map RewardAccount Coin -> StrictMaybe ScriptHash -> GovAction era
TreasuryWithdrawals Word
2 forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To Map RewardAccount Coin
ws forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. (t -> Encoding) -> t -> Encode ('Closed 'Dense) t
E (forall a. (a -> Encoding) -> StrictMaybe a -> Encoding
encodeNullStrictMaybe forall a. EncCBOR a => a -> Encoding
encCBOR) StrictMaybe ScriptHash
pol
NoConfidence StrictMaybe (GovPurposeId 'CommitteePurpose era)
gid ->
forall t. t -> Word -> Encode 'Open t
Sum forall era.
StrictMaybe (GovPurposeId 'CommitteePurpose era) -> GovAction era
NoConfidence Word
3 forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. (t -> Encoding) -> t -> Encode ('Closed 'Dense) t
E (forall a. (a -> Encoding) -> StrictMaybe a -> Encoding
encodeNullStrictMaybe forall a. EncCBOR a => a -> Encoding
encCBOR) StrictMaybe (GovPurposeId 'CommitteePurpose era)
gid
UpdateCommittee StrictMaybe (GovPurposeId 'CommitteePurpose era)
gid Set (Credential 'ColdCommitteeRole)
old Map (Credential 'ColdCommitteeRole) EpochNo
new UnitInterval
q ->
forall t. t -> Word -> Encode 'Open t
Sum forall era.
StrictMaybe (GovPurposeId 'CommitteePurpose era)
-> Set (Credential 'ColdCommitteeRole)
-> Map (Credential 'ColdCommitteeRole) EpochNo
-> UnitInterval
-> GovAction era
UpdateCommittee Word
4 forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. (t -> Encoding) -> t -> Encode ('Closed 'Dense) t
E (forall a. (a -> Encoding) -> StrictMaybe a -> Encoding
encodeNullStrictMaybe forall a. EncCBOR a => a -> Encoding
encCBOR) StrictMaybe (GovPurposeId 'CommitteePurpose era)
gid forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To Set (Credential 'ColdCommitteeRole)
old forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To Map (Credential 'ColdCommitteeRole) EpochNo
new forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To UnitInterval
q
NewConstitution StrictMaybe (GovPurposeId 'ConstitutionPurpose era)
gid Constitution era
c ->
forall t. t -> Word -> Encode 'Open t
Sum forall era.
StrictMaybe (GovPurposeId 'ConstitutionPurpose era)
-> Constitution era -> GovAction era
NewConstitution Word
5 forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. (t -> Encoding) -> t -> Encode ('Closed 'Dense) t
E (forall a. (a -> Encoding) -> StrictMaybe a -> Encoding
encodeNullStrictMaybe forall a. EncCBOR a => a -> Encoding
encCBOR) StrictMaybe (GovPurposeId 'ConstitutionPurpose era)
gid forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To Constitution era
c
GovAction era
InfoAction ->
forall t. t -> Word -> Encode 'Open t
Sum forall era. GovAction era
InfoAction Word
6
data Constitution era = Constitution
{ forall era. Constitution era -> Anchor
constitutionAnchor :: !Anchor
, forall era. Constitution era -> StrictMaybe ScriptHash
constitutionScript :: !(StrictMaybe ScriptHash)
}
deriving (forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall era x. Rep (Constitution era) x -> Constitution era
forall era x. Constitution era -> Rep (Constitution era) x
$cto :: forall era x. Rep (Constitution era) x -> Constitution era
$cfrom :: forall era x. Constitution era -> Rep (Constitution era) x
Generic, Constitution era -> Constitution era -> Bool
Constitution era -> Constitution era -> Ordering
forall era. Eq (Constitution era)
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall era. Constitution era -> Constitution era -> Bool
forall era. Constitution era -> Constitution era -> Ordering
forall era.
Constitution era -> Constitution era -> Constitution era
min :: Constitution era -> Constitution era -> Constitution era
$cmin :: forall era.
Constitution era -> Constitution era -> Constitution era
max :: Constitution era -> Constitution era -> Constitution era
$cmax :: forall era.
Constitution era -> Constitution era -> Constitution era
>= :: Constitution era -> Constitution era -> Bool
$c>= :: forall era. Constitution era -> Constitution era -> Bool
> :: Constitution era -> Constitution era -> Bool
$c> :: forall era. Constitution era -> Constitution era -> Bool
<= :: Constitution era -> Constitution era -> Bool
$c<= :: forall era. Constitution era -> Constitution era -> Bool
< :: Constitution era -> Constitution era -> Bool
$c< :: forall era. Constitution era -> Constitution era -> Bool
compare :: Constitution era -> Constitution era -> Ordering
$ccompare :: forall era. Constitution era -> Constitution era -> Ordering
Ord)
constitutionAnchorL :: Lens' (Constitution era) Anchor
constitutionAnchorL :: forall era. Lens' (Constitution era) Anchor
constitutionAnchorL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall era. Constitution era -> Anchor
constitutionAnchor (\Constitution era
x Anchor
y -> Constitution era
x {constitutionAnchor :: Anchor
constitutionAnchor = Anchor
y})
constitutionScriptL :: Lens' (Constitution era) (StrictMaybe ScriptHash)
constitutionScriptL :: forall era. Lens' (Constitution era) (StrictMaybe ScriptHash)
constitutionScriptL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall era. Constitution era -> StrictMaybe ScriptHash
constitutionScript (\Constitution era
x StrictMaybe ScriptHash
y -> Constitution era
x {constitutionScript :: StrictMaybe ScriptHash
constitutionScript = StrictMaybe ScriptHash
y})
instance Era era => ToJSON (Constitution era) where
toJSON :: Constitution era -> Value
toJSON = [Pair] -> Value
object forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall e a era. KeyValue e a => Constitution era -> [a]
toConstitutionPairs
toEncoding :: Constitution era -> Encoding
toEncoding = Series -> Encoding
pairs forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Monoid a => [a] -> a
mconcat forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall e a era. KeyValue e a => Constitution era -> [a]
toConstitutionPairs
instance Era era => FromJSON (Constitution era) where
parseJSON :: Value -> Parser (Constitution era)
parseJSON = forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Constitution" forall a b. (a -> b) -> a -> b
$ \Object
o ->
forall era. Anchor -> StrictMaybe ScriptHash -> Constitution era
Constitution
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"anchor"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall a. Maybe a -> StrictMaybe a
maybeToStrictMaybe forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Object
o forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"script"))
toConstitutionPairs :: KeyValue e a => Constitution era -> [a]
toConstitutionPairs :: forall e a era. KeyValue e a => Constitution era -> [a]
toConstitutionPairs c :: Constitution era
c@(Constitution Anchor
_ StrictMaybe ScriptHash
_) =
let Constitution {StrictMaybe ScriptHash
Anchor
constitutionScript :: StrictMaybe ScriptHash
constitutionAnchor :: Anchor
constitutionScript :: forall era. Constitution era -> StrictMaybe ScriptHash
constitutionAnchor :: forall era. Constitution era -> Anchor
..} = Constitution era
c
in [Key
"anchor" forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Anchor
constitutionAnchor]
forall a. Semigroup a => a -> a -> a
<> [Key
"script" forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= ScriptHash
cScript | SJust ScriptHash
cScript <- [StrictMaybe ScriptHash
constitutionScript]]
deriving instance Eq (Constitution era)
deriving instance Show (Constitution era)
instance Era era => Default (Constitution era) where
def :: Constitution era
def = forall era. Anchor -> StrictMaybe ScriptHash -> Constitution era
Constitution forall a. Default a => a
def forall a. Default a => a
def
instance Era era => DecCBOR (Constitution era) where
decCBOR :: forall s. Decoder s (Constitution era)
decCBOR =
forall (w :: Wrapped) t s. Decode w t -> Decoder s t
decode forall a b. (a -> b) -> a -> b
$
forall t. t -> Decode ('Closed 'Dense) t
RecD forall era. Anchor -> StrictMaybe ScriptHash -> Constitution era
Constitution
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t (w :: Wrapped). DecCBOR t => Decode w t
From
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! forall t. (forall s. Decoder s t) -> Decode ('Closed 'Dense) t
D (forall s a. Decoder s a -> Decoder s (StrictMaybe a)
decodeNullStrictMaybe forall a s. DecCBOR a => Decoder s a
decCBOR)
instance Era era => EncCBOR (Constitution era) where
encCBOR :: Constitution era -> Encoding
encCBOR Constitution {StrictMaybe ScriptHash
Anchor
constitutionScript :: StrictMaybe ScriptHash
constitutionAnchor :: Anchor
constitutionScript :: forall era. Constitution era -> StrictMaybe ScriptHash
constitutionAnchor :: forall era. Constitution era -> Anchor
..} =
forall (w :: Wrapped) t. Encode w t -> Encoding
encode forall a b. (a -> b) -> a -> b
$
forall t. t -> Encode ('Closed 'Dense) t
Rec (forall era. Anchor -> StrictMaybe ScriptHash -> Constitution era
Constitution @era)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To Anchor
constitutionAnchor
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> forall t. (t -> Encoding) -> t -> Encode ('Closed 'Dense) t
E (forall a. (a -> Encoding) -> StrictMaybe a -> Encoding
encodeNullStrictMaybe forall a. EncCBOR a => a -> Encoding
encCBOR) StrictMaybe ScriptHash
constitutionScript
instance Era era => ToCBOR (Constitution era) where
toCBOR :: Constitution era -> Encoding
toCBOR = forall era t. (Era era, EncCBOR t) => t -> Encoding
toEraCBOR @era
instance Era era => FromCBOR (Constitution era) where
fromCBOR :: forall s. Decoder s (Constitution era)
fromCBOR = forall era t s. (Era era, DecCBOR t) => Decoder s t
fromEraCBOR @era
instance Era era => NFData (Constitution era)
instance Era era => NoThunks (Constitution era)