{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MonoLocalBinds #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -Wno-orphans #-}

module Cardano.Ledger.Conway.Governance.Internal (
  EnactState (..),
  RatifyState (..),
  RatifyEnv (..),
  RatifySignal (..),
  votingStakePoolThreshold,
  votingDRepThreshold,
  votingCommitteeThreshold,
  isStakePoolVotingAllowed,
  isDRepVotingAllowed,
  isCommitteeVotingAllowed,
  reorderActions,
  actionPriority,
  hoistGovRelation,
  withGovActionParent,
  ensCommitteeL,
  ensConstitutionL,
  ensCurPParamsL,
  ensPrevPParamsL,
  ensWithdrawalsL,
  ensTreasuryL,
  ensPrevGovActionIdsL,
  ensPrevPParamUpdateL,
  ensPrevHardForkL,
  ensPrevCommitteeL,
  ensPrevConstitutionL,
  ensProtVerL,
  rsEnactStateL,
  rsExpiredL,
  rsEnactedL,
  rsDelayedL,
  epochStateStakeDistrL,
  epochStateIncrStakeDistrL,
  epochStateRegDrepL,
  epochStateUMapL,
  ratifySignalL,
  reStakeDistrL,
  reStakePoolDistrL,
  reDRepDistrL,
  reDRepStateL,
  reCurrentEpochL,
  reCommitteeStateL,

  -- * Exported for testing
  pparamsUpdateThreshold,
) where

import Cardano.Ledger.BaseTypes (
  EpochNo (..),
  ProtVer (..),
  StrictMaybe (..),
  UnitInterval,
  isSJust,
 )
import Cardano.Ledger.Binary (
  DecCBOR (..),
  DecShareCBOR (..),
  EncCBOR (..),
  FromCBOR (..),
  ToCBOR (..),
  decNoShareCBOR,
 )
import Cardano.Ledger.Binary.Coders (
  Decode (..),
  Encode (..),
  decode,
  encode,
  (!>),
  (<!),
 )
import Cardano.Ledger.CertState (CommitteeAuthorization (..), CommitteeState (..))
import Cardano.Ledger.Coin (Coin (..))
import Cardano.Ledger.Conway.Governance.Procedures
import Cardano.Ledger.Conway.PParams (
  ConwayEraPParams (..),
  DRepGroup (..),
  DRepVotingThresholds (..),
  PPGroups (..),
  PoolVotingThresholds (..),
  StakePoolGroup (..),
  dvtPPEconomicGroupL,
  dvtPPGovGroupL,
  dvtPPNetworkGroupL,
  dvtPPTechnicalGroupL,
  ppCommitteeMinSizeL,
  ppDRepVotingThresholdsL,
  ppPoolVotingThresholdsL,
 )
import Cardano.Ledger.Core (
  Era (EraCrypto),
  EraPParams (..),
  PParams (..),
  PParamsUpdate,
  emptyPParams,
  fromEraCBOR,
  ppProtocolVersionL,
  toEraCBOR,
 )
import Cardano.Ledger.Credential (Credential (..))
import Cardano.Ledger.DRep (DRep (..), DRepState (..))
import Cardano.Ledger.Keys (KeyHash, KeyRole (..))
import Cardano.Ledger.PoolDistr (PoolDistr (..))
import Cardano.Ledger.PoolParams (PoolParams)
import qualified Cardano.Ledger.Shelley.HardForks as HF (bootstrapPhase)
import Cardano.Ledger.Shelley.LedgerState (
  epochStateIncrStakeDistrL,
  epochStateRegDrepL,
  epochStateStakeDistrL,
  epochStateUMapL,
 )
import Cardano.Ledger.UMap
import Control.DeepSeq (NFData (rnf), deepseq)
import Data.Aeson (KeyValue, ToJSON (..), object, pairs, (.=))
import Data.Default.Class (Default (..))
import Data.Foldable (Foldable (..))
import Data.List (sortOn)
import Data.Map.Strict (Map)
import qualified Data.Map.Strict as Map
import Data.Sequence (Seq)
import Data.Sequence.Strict (StrictSeq (..))
import qualified Data.Sequence.Strict as SS
import Data.Set (Set)
import qualified Data.Set as Set
import Data.Typeable
import GHC.Generics (Generic)
import Lens.Micro
import NoThunks.Class (NoThunks (..), allNoThunks)

data EnactState era = EnactState
  { forall era. EnactState era -> StrictMaybe (Committee era)
ensCommittee :: !(StrictMaybe (Committee era))
  -- ^ Constitutional Committee
  , forall era. EnactState era -> Constitution era
ensConstitution :: !(Constitution era)
  -- ^ Constitution
  , forall era. EnactState era -> PParams era
ensCurPParams :: !(PParams era)
  , forall era. EnactState era -> PParams era
ensPrevPParams :: !(PParams era)
  , forall era. EnactState era -> Coin
ensTreasury :: !Coin
  , forall era.
EnactState era -> Map (Credential 'Staking (EraCrypto era)) Coin
ensWithdrawals :: !(Map (Credential 'Staking (EraCrypto era)) Coin)
  , forall era. EnactState era -> GovRelation StrictMaybe era
ensPrevGovActionIds :: !(GovRelation StrictMaybe era)
  -- ^ Last enacted GovAction Ids
  }
  deriving (forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall era x. Rep (EnactState era) x -> EnactState era
forall era x. EnactState era -> Rep (EnactState era) x
$cto :: forall era x. Rep (EnactState era) x -> EnactState era
$cfrom :: forall era x. EnactState era -> Rep (EnactState era) x
Generic)

ensCommitteeL :: Lens' (EnactState era) (StrictMaybe (Committee era))
ensCommitteeL :: forall era. Lens' (EnactState era) (StrictMaybe (Committee era))
ensCommitteeL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall era. EnactState era -> StrictMaybe (Committee era)
ensCommittee (\EnactState era
x StrictMaybe (Committee era)
y -> EnactState era
x {ensCommittee :: StrictMaybe (Committee era)
ensCommittee = StrictMaybe (Committee era)
y})

ensConstitutionL :: Lens' (EnactState era) (Constitution era)
ensConstitutionL :: forall era. Lens' (EnactState era) (Constitution era)
ensConstitutionL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall era. EnactState era -> Constitution era
ensConstitution (\EnactState era
x Constitution era
y -> EnactState era
x {ensConstitution :: Constitution era
ensConstitution = Constitution era
y})

ensProtVerL :: EraPParams era => Lens' (EnactState era) ProtVer
ensProtVerL :: forall era. EraPParams era => Lens' (EnactState era) ProtVer
ensProtVerL = forall era. Lens' (EnactState era) (PParams era)
ensCurPParamsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. EraPParams era => Lens' (PParams era) ProtVer
ppProtocolVersionL

ensCurPParamsL :: Lens' (EnactState era) (PParams era)
ensCurPParamsL :: forall era. Lens' (EnactState era) (PParams era)
ensCurPParamsL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall era. EnactState era -> PParams era
ensCurPParams (\EnactState era
es PParams era
x -> EnactState era
es {ensCurPParams :: PParams era
ensCurPParams = PParams era
x})

ensPrevPParamsL :: Lens' (EnactState era) (PParams era)
ensPrevPParamsL :: forall era. Lens' (EnactState era) (PParams era)
ensPrevPParamsL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall era. EnactState era -> PParams era
ensPrevPParams (\EnactState era
es PParams era
x -> EnactState era
es {ensPrevPParams :: PParams era
ensPrevPParams = PParams era
x})

ensTreasuryL :: Lens' (EnactState era) Coin
ensTreasuryL :: forall era. Lens' (EnactState era) Coin
ensTreasuryL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall era. EnactState era -> Coin
ensTreasury forall a b. (a -> b) -> a -> b
$ \EnactState era
es Coin
x -> EnactState era
es {ensTreasury :: Coin
ensTreasury = Coin
x}

ensWithdrawalsL :: Lens' (EnactState era) (Map (Credential 'Staking (EraCrypto era)) Coin)
ensWithdrawalsL :: forall era.
Lens'
  (EnactState era) (Map (Credential 'Staking (EraCrypto era)) Coin)
ensWithdrawalsL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall era.
EnactState era -> Map (Credential 'Staking (EraCrypto era)) Coin
ensWithdrawals forall a b. (a -> b) -> a -> b
$ \EnactState era
es Map (Credential 'Staking (EraCrypto era)) Coin
x -> EnactState era
es {ensWithdrawals :: Map (Credential 'Staking (EraCrypto era)) Coin
ensWithdrawals = Map (Credential 'Staking (EraCrypto era)) Coin
x}

ensPrevGovActionIdsL :: Lens' (EnactState era) (GovRelation StrictMaybe era)
ensPrevGovActionIdsL :: forall era. Lens' (EnactState era) (GovRelation StrictMaybe era)
ensPrevGovActionIdsL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall era. EnactState era -> GovRelation StrictMaybe era
ensPrevGovActionIds (\EnactState era
es GovRelation StrictMaybe era
x -> EnactState era
es {ensPrevGovActionIds :: GovRelation StrictMaybe era
ensPrevGovActionIds = GovRelation StrictMaybe era
x})

ensPrevPParamUpdateL ::
  Lens' (EnactState era) (StrictMaybe (GovPurposeId 'PParamUpdatePurpose era))
ensPrevPParamUpdateL :: forall era.
Lens'
  (EnactState era)
  (StrictMaybe (GovPurposeId 'PParamUpdatePurpose era))
ensPrevPParamUpdateL = forall era. Lens' (EnactState era) (GovRelation StrictMaybe era)
ensPrevGovActionIdsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) era.
Lens'
  (GovRelation f era) (f (GovPurposeId 'PParamUpdatePurpose era))
grPParamUpdateL

ensPrevHardForkL ::
  Lens' (EnactState era) (StrictMaybe (GovPurposeId 'HardForkPurpose era))
ensPrevHardForkL :: forall era.
Lens'
  (EnactState era) (StrictMaybe (GovPurposeId 'HardForkPurpose era))
ensPrevHardForkL = forall era. Lens' (EnactState era) (GovRelation StrictMaybe era)
ensPrevGovActionIdsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) era.
Lens' (GovRelation f era) (f (GovPurposeId 'HardForkPurpose era))
grHardForkL

ensPrevCommitteeL ::
  Lens' (EnactState era) (StrictMaybe (GovPurposeId 'CommitteePurpose era))
ensPrevCommitteeL :: forall era.
Lens'
  (EnactState era) (StrictMaybe (GovPurposeId 'CommitteePurpose era))
ensPrevCommitteeL = forall era. Lens' (EnactState era) (GovRelation StrictMaybe era)
ensPrevGovActionIdsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) era.
Lens' (GovRelation f era) (f (GovPurposeId 'CommitteePurpose era))
grCommitteeL

ensPrevConstitutionL ::
  Lens' (EnactState era) (StrictMaybe (GovPurposeId 'ConstitutionPurpose era))
ensPrevConstitutionL :: forall era.
Lens'
  (EnactState era)
  (StrictMaybe (GovPurposeId 'ConstitutionPurpose era))
ensPrevConstitutionL = forall era. Lens' (EnactState era) (GovRelation StrictMaybe era)
ensPrevGovActionIdsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) era.
Lens'
  (GovRelation f era) (f (GovPurposeId 'ConstitutionPurpose era))
grConstitutionL

instance EraPParams era => ToJSON (EnactState era) where
  toJSON :: EnactState 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) =>
EnactState era -> [a]
toEnactStatePairs
  toEncoding :: EnactState 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) =>
EnactState era -> [a]
toEnactStatePairs

toEnactStatePairs :: (KeyValue e a, EraPParams era) => EnactState era -> [a]
toEnactStatePairs :: forall e a era.
(KeyValue e a, EraPParams era) =>
EnactState era -> [a]
toEnactStatePairs cg :: EnactState era
cg@(EnactState StrictMaybe (Committee era)
_ Constitution era
_ PParams era
_ PParams era
_ Coin
_ Map (Credential 'Staking (EraCrypto era)) Coin
_ GovRelation StrictMaybe era
_) =
  let EnactState {Map (Credential 'Staking (EraCrypto era)) Coin
PParams era
StrictMaybe (Committee era)
Coin
Constitution era
GovRelation StrictMaybe era
ensPrevGovActionIds :: GovRelation StrictMaybe era
ensWithdrawals :: Map (Credential 'Staking (EraCrypto era)) Coin
ensTreasury :: Coin
ensPrevPParams :: PParams era
ensCurPParams :: PParams era
ensConstitution :: Constitution era
ensCommittee :: StrictMaybe (Committee era)
ensPrevGovActionIds :: forall era. EnactState era -> GovRelation StrictMaybe era
ensWithdrawals :: forall era.
EnactState era -> Map (Credential 'Staking (EraCrypto era)) Coin
ensTreasury :: forall era. EnactState era -> Coin
ensPrevPParams :: forall era. EnactState era -> PParams era
ensCurPParams :: forall era. EnactState era -> PParams era
ensConstitution :: forall era. EnactState era -> Constitution era
ensCommittee :: forall era. EnactState era -> StrictMaybe (Committee era)
..} = EnactState era
cg
   in [ Key
"committee" forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= StrictMaybe (Committee era)
ensCommittee
      , Key
"constitution" forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Constitution era
ensConstitution
      , Key
"curPParams" forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= PParams era
ensCurPParams
      , Key
"prevPParams" forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= PParams era
ensPrevPParams
      , Key
"prevGovActionIds" forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= GovRelation StrictMaybe era
ensPrevGovActionIds
      ]

deriving instance (Era era, Eq (PParams era)) => Eq (EnactState era)

deriving instance (Era era, Show (PParams era)) => Show (EnactState era)

instance EraPParams era => Default (EnactState era) where
  def :: EnactState era
def =
    forall era.
StrictMaybe (Committee era)
-> Constitution era
-> PParams era
-> PParams era
-> Coin
-> Map (Credential 'Staking (EraCrypto era)) Coin
-> GovRelation StrictMaybe era
-> EnactState era
EnactState
      forall a. Default a => a
def
      forall a. Default a => a
def
      forall a. Default a => a
def
      forall a. Default a => a
def
      (Integer -> Coin
Coin Integer
0)
      forall a. Default a => a
def
      forall a. Default a => a
def

instance EraPParams era => DecCBOR (EnactState era) where
  decCBOR :: forall s. Decoder s (EnactState era)
decCBOR = forall a s. DecShareCBOR a => Decoder s a
decNoShareCBOR

-- TODO: Implement Sharing: https://github.com/intersectmbo/cardano-ledger/issues/3486
instance EraPParams era => DecShareCBOR (EnactState era) where
  decShareCBOR :: forall s. Share (EnactState era) -> Decoder s (EnactState era)
decShareCBOR Share (EnactState 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.
StrictMaybe (Committee era)
-> Constitution era
-> PParams era
-> PParams era
-> Coin
-> Map (Credential 'Staking (EraCrypto era)) Coin
-> GovRelation StrictMaybe era
-> EnactState era
EnactState
        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 => EncCBOR (EnactState era) where
  encCBOR :: EnactState era -> Encoding
encCBOR EnactState {Map (Credential 'Staking (EraCrypto era)) Coin
PParams era
StrictMaybe (Committee era)
Coin
Constitution era
GovRelation StrictMaybe era
ensPrevGovActionIds :: GovRelation StrictMaybe era
ensWithdrawals :: Map (Credential 'Staking (EraCrypto era)) Coin
ensTreasury :: Coin
ensPrevPParams :: PParams era
ensCurPParams :: PParams era
ensConstitution :: Constitution era
ensCommittee :: StrictMaybe (Committee era)
ensPrevGovActionIds :: forall era. EnactState era -> GovRelation StrictMaybe era
ensWithdrawals :: forall era.
EnactState era -> Map (Credential 'Staking (EraCrypto era)) Coin
ensTreasury :: forall era. EnactState era -> Coin
ensPrevPParams :: forall era. EnactState era -> PParams era
ensCurPParams :: forall era. EnactState era -> PParams era
ensConstitution :: forall era. EnactState era -> Constitution era
ensCommittee :: forall era. EnactState era -> StrictMaybe (Committee era)
..} =
    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.
StrictMaybe (Committee era)
-> Constitution era
-> PParams era
-> PParams era
-> Coin
-> Map (Credential 'Staking (EraCrypto era)) Coin
-> GovRelation StrictMaybe era
-> EnactState era
EnactState
        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 StrictMaybe (Committee era)
ensCommittee
        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
ensConstitution
        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 PParams era
ensCurPParams
        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 PParams era
ensPrevPParams
        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
ensTreasury
        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 'Staking (EraCrypto era)) Coin
ensWithdrawals
        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 GovRelation StrictMaybe era
ensPrevGovActionIds

instance EraPParams era => ToCBOR (EnactState era) where
  toCBOR :: EnactState era -> Encoding
toCBOR = forall era t. (Era era, EncCBOR t) => t -> Encoding
toEraCBOR @era

instance EraPParams era => FromCBOR (EnactState era) where
  fromCBOR :: forall s. Decoder s (EnactState era)
fromCBOR = forall era t s. (Era era, DecCBOR t) => Decoder s t
fromEraCBOR @era

instance EraPParams era => NFData (EnactState era)

instance EraPParams era => NoThunks (EnactState era)

-- ========================================

data RatifyState era = RatifyState
  { forall era. RatifyState era -> EnactState era
rsEnactState :: !(EnactState era)
  , forall era. RatifyState era -> Seq (GovActionState era)
rsEnacted :: !(Seq (GovActionState era))
  , forall era. RatifyState era -> Set (GovActionId (EraCrypto era))
rsExpired :: !(Set (GovActionId (EraCrypto era)))
  , forall era. RatifyState era -> Bool
rsDelayed :: !Bool
  }
  deriving (forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall era x. Rep (RatifyState era) x -> RatifyState era
forall era x. RatifyState era -> Rep (RatifyState era) x
$cto :: forall era x. Rep (RatifyState era) x -> RatifyState era
$cfrom :: forall era x. RatifyState era -> Rep (RatifyState era) x
Generic)

deriving instance EraPParams era => Eq (RatifyState era)

deriving instance EraPParams era => Show (RatifyState era)

rsEnactStateL :: Lens' (RatifyState era) (EnactState era)
rsEnactStateL :: forall era. Lens' (RatifyState era) (EnactState era)
rsEnactStateL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall era. RatifyState era -> EnactState era
rsEnactState (\RatifyState era
x EnactState era
y -> RatifyState era
x {rsEnactState :: EnactState era
rsEnactState = EnactState era
y})

rsEnactedL :: Lens' (RatifyState era) (Seq (GovActionState era))
rsEnactedL :: forall era. Lens' (RatifyState era) (Seq (GovActionState era))
rsEnactedL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall era. RatifyState era -> Seq (GovActionState era)
rsEnacted (\RatifyState era
x Seq (GovActionState era)
y -> RatifyState era
x {rsEnacted :: Seq (GovActionState era)
rsEnacted = Seq (GovActionState era)
y})

rsExpiredL :: Lens' (RatifyState era) (Set (GovActionId (EraCrypto era)))
rsExpiredL :: forall era.
Lens' (RatifyState era) (Set (GovActionId (EraCrypto era)))
rsExpiredL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall era. RatifyState era -> Set (GovActionId (EraCrypto era))
rsExpired (\RatifyState era
x Set (GovActionId (EraCrypto era))
y -> RatifyState era
x {rsExpired :: Set (GovActionId (EraCrypto era))
rsExpired = Set (GovActionId (EraCrypto era))
y})

rsDelayedL :: Lens' (RatifyState era) Bool
rsDelayedL :: forall era. Lens' (RatifyState era) Bool
rsDelayedL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall era. RatifyState era -> Bool
rsDelayed (\RatifyState era
x Bool
y -> RatifyState era
x {rsDelayed :: Bool
rsDelayed = Bool
y})

instance EraPParams era => Default (RatifyState era)

instance EraPParams era => NFData (RatifyState era)

instance EraPParams era => NoThunks (RatifyState era)

instance EraPParams era => ToJSON (RatifyState era) where
  toJSON :: RatifyState 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) =>
RatifyState era -> [a]
toRatifyStatePairs
  toEncoding :: RatifyState 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) =>
RatifyState era -> [a]
toRatifyStatePairs

toRatifyStatePairs :: (KeyValue e a, EraPParams era) => RatifyState era -> [a]
toRatifyStatePairs :: forall e a era.
(KeyValue e a, EraPParams era) =>
RatifyState era -> [a]
toRatifyStatePairs cg :: RatifyState era
cg@(RatifyState EnactState era
_ Seq (GovActionState era)
_ Set (GovActionId (EraCrypto era))
_ Bool
_) =
  let RatifyState {Bool
Set (GovActionId (EraCrypto era))
Seq (GovActionState era)
EnactState era
rsDelayed :: Bool
rsExpired :: Set (GovActionId (EraCrypto era))
rsEnacted :: Seq (GovActionState era)
rsEnactState :: EnactState era
rsDelayed :: forall era. RatifyState era -> Bool
rsExpired :: forall era. RatifyState era -> Set (GovActionId (EraCrypto era))
rsEnacted :: forall era. RatifyState era -> Seq (GovActionState era)
rsEnactState :: forall era. RatifyState era -> EnactState era
..} = RatifyState era
cg
   in [ Key
"nextEnactState" forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= EnactState era
rsEnactState
      , Key
"enactedGovActions" forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Seq (GovActionState era)
rsEnacted
      , Key
"expiredGovActions" forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Set (GovActionId (EraCrypto era))
rsExpired
      , Key
"ratificationDelayed" forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= Bool
rsDelayed
      ]

pparamsUpdateThreshold ::
  forall era.
  ConwayEraPParams era =>
  DRepVotingThresholds ->
  PParamsUpdate era ->
  UnitInterval
pparamsUpdateThreshold :: forall era.
ConwayEraPParams era =>
DRepVotingThresholds -> PParamsUpdate era -> UnitInterval
pparamsUpdateThreshold DRepVotingThresholds
thresholds PParamsUpdate era
ppu =
  let thresholdLens :: DRepGroup
-> (UnitInterval -> Const UnitInterval UnitInterval)
-> DRepVotingThresholds
-> Const UnitInterval DRepVotingThresholds
thresholdLens = \case
        DRepGroup
NetworkGroup -> Lens' DRepVotingThresholds UnitInterval
dvtPPNetworkGroupL
        DRepGroup
GovGroup -> Lens' DRepVotingThresholds UnitInterval
dvtPPGovGroupL
        DRepGroup
TechnicalGroup -> Lens' DRepVotingThresholds UnitInterval
dvtPPTechnicalGroupL
        DRepGroup
EconomicGroup -> Lens' DRepVotingThresholds UnitInterval
dvtPPEconomicGroupL
      lookupGroupThreshold :: PPGroups -> UnitInterval
lookupGroupThreshold (PPGroups DRepGroup
grp StakePoolGroup
_) =
        DRepVotingThresholds
thresholds forall s a. s -> Getting a s a -> a
^. DRepGroup
-> (UnitInterval -> Const UnitInterval UnitInterval)
-> DRepVotingThresholds
-> Const UnitInterval DRepVotingThresholds
thresholdLens DRepGroup
grp
   in forall a b. (a -> b -> b) -> b -> Set a -> b
Set.foldr' forall a. Ord a => a -> a -> a
max forall a. Bounded a => a
minBound forall a b. (a -> b) -> a -> b
$
        forall b a. Ord b => (a -> b) -> Set a -> Set b
Set.map PPGroups -> UnitInterval
lookupGroupThreshold forall a b. (a -> b) -> a -> b
$
          forall era.
ConwayEraPParams era =>
PParamsUpdate era -> Set PPGroups
modifiedPPGroups @era PParamsUpdate era
ppu

data VotingThreshold
  = -- | This is the actual threshold. It is lazy, because upon proposal we only care if
    -- the voting is allowed or not, instead of getting the actual threshold value.
    VotingThreshold UnitInterval -- <- lazy on purpose
  | -- | Does not have a threshold, therefore an action can not be ratified
    NoVotingThreshold
  | -- | Some GovActions are not allowed to be voted by some entities
    NoVotingAllowed

toRatifyVotingThreshold :: VotingThreshold -> StrictMaybe UnitInterval
toRatifyVotingThreshold :: VotingThreshold -> StrictMaybe UnitInterval
toRatifyVotingThreshold = \case
  VotingThreshold UnitInterval
t -> forall a. a -> StrictMaybe a
SJust UnitInterval
t -- concrete threshold
  VotingThreshold
NoVotingThreshold -> forall a. StrictMaybe a
SNothing -- no voting threshold prevents ratification
  VotingThreshold
NoVotingAllowed -> forall a. a -> StrictMaybe a
SJust forall a. Bounded a => a
minBound -- votes should not count, set threshold to zero

isVotingAllowed :: VotingThreshold -> Bool
isVotingAllowed :: VotingThreshold -> Bool
isVotingAllowed = \case
  VotingThreshold {} -> Bool
True
  VotingThreshold
NoVotingThreshold -> Bool
True
  VotingThreshold
NoVotingAllowed -> Bool
False

isStakePoolVotingAllowed ::
  ConwayEraPParams era =>
  GovAction era ->
  Bool
isStakePoolVotingAllowed :: forall era. ConwayEraPParams era => GovAction era -> Bool
isStakePoolVotingAllowed =
  VotingThreshold -> Bool
isVotingAllowed forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era.
ConwayEraPParams era =>
PParams era -> Bool -> GovAction era -> VotingThreshold
votingStakePoolThresholdInternal PParams era
pp Bool
isElectedCommittee
  where
    -- Information about presence of committe or values in PParams are irrelevant for
    -- knowing if voting is allowed or not:
    pp :: PParams era
pp = forall era. EraPParams era => PParams era
emptyPParams
    isElectedCommittee :: Bool
isElectedCommittee = Bool
False

votingStakePoolThreshold ::
  ConwayEraPParams era =>
  RatifyState era ->
  GovAction era ->
  StrictMaybe UnitInterval
votingStakePoolThreshold :: forall era.
ConwayEraPParams era =>
RatifyState era -> GovAction era -> StrictMaybe UnitInterval
votingStakePoolThreshold RatifyState era
ratifyState =
  VotingThreshold -> StrictMaybe UnitInterval
toRatifyVotingThreshold forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era.
ConwayEraPParams era =>
PParams era -> Bool -> GovAction era -> VotingThreshold
votingStakePoolThresholdInternal PParams era
pp Bool
isElectedCommittee
  where
    pp :: PParams era
pp = RatifyState era
ratifyState forall s a. s -> Getting a s a -> a
^. forall era. Lens' (RatifyState era) (EnactState era)
rsEnactStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (EnactState era) (PParams era)
ensCurPParamsL
    isElectedCommittee :: Bool
isElectedCommittee = forall a. StrictMaybe a -> Bool
isSJust forall a b. (a -> b) -> a -> b
$ RatifyState era
ratifyState forall s a. s -> Getting a s a -> a
^. forall era. Lens' (RatifyState era) (EnactState era)
rsEnactStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (EnactState era) (StrictMaybe (Committee era))
ensCommitteeL

votingStakePoolThresholdInternal ::
  ConwayEraPParams era =>
  PParams era ->
  Bool ->
  GovAction era ->
  VotingThreshold
votingStakePoolThresholdInternal :: forall era.
ConwayEraPParams era =>
PParams era -> Bool -> GovAction era -> VotingThreshold
votingStakePoolThresholdInternal PParams era
pp Bool
isElectedCommittee GovAction era
action =
  let PoolVotingThresholds
        { UnitInterval
pvtCommitteeNoConfidence :: PoolVotingThresholds -> UnitInterval
pvtCommitteeNoConfidence :: UnitInterval
pvtCommitteeNoConfidence
        , UnitInterval
pvtCommitteeNormal :: PoolVotingThresholds -> UnitInterval
pvtCommitteeNormal :: UnitInterval
pvtCommitteeNormal
        , UnitInterval
pvtHardForkInitiation :: PoolVotingThresholds -> UnitInterval
pvtHardForkInitiation :: UnitInterval
pvtHardForkInitiation
        , UnitInterval
pvtPPSecurityGroup :: PoolVotingThresholds -> UnitInterval
pvtPPSecurityGroup :: UnitInterval
pvtPPSecurityGroup
        , UnitInterval
pvtMotionNoConfidence :: PoolVotingThresholds -> UnitInterval
pvtMotionNoConfidence :: UnitInterval
pvtMotionNoConfidence
        } = PParams era
pp forall s a. s -> Getting a s a -> a
^. forall era.
ConwayEraPParams era =>
Lens' (PParams era) PoolVotingThresholds
ppPoolVotingThresholdsL
      isSecurityRelevant :: PPGroups -> Bool
isSecurityRelevant (PPGroups DRepGroup
_ StakePoolGroup
s) =
        case StakePoolGroup
s of
          StakePoolGroup
SecurityGroup -> Bool
True
          StakePoolGroup
NoStakePoolGroup -> Bool
False
      paramChangeThreshold :: PParamsUpdate era -> VotingThreshold
paramChangeThreshold PParamsUpdate era
ppu
        | forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any PPGroups -> Bool
isSecurityRelevant (forall era.
ConwayEraPParams era =>
PParamsUpdate era -> Set PPGroups
modifiedPPGroups PParamsUpdate era
ppu) =
            UnitInterval -> VotingThreshold
VotingThreshold UnitInterval
pvtPPSecurityGroup
        | Bool
otherwise = VotingThreshold
NoVotingAllowed
   in case GovAction era
action of
        NoConfidence {} -> UnitInterval -> VotingThreshold
VotingThreshold UnitInterval
pvtMotionNoConfidence
        UpdateCommittee {} ->
          UnitInterval -> VotingThreshold
VotingThreshold forall a b. (a -> b) -> a -> b
$
            if Bool
isElectedCommittee
              then UnitInterval
pvtCommitteeNormal
              else UnitInterval
pvtCommitteeNoConfidence
        NewConstitution {} -> VotingThreshold
NoVotingAllowed
        HardForkInitiation {} -> UnitInterval -> VotingThreshold
VotingThreshold UnitInterval
pvtHardForkInitiation
        ParameterChange StrictMaybe (GovPurposeId 'PParamUpdatePurpose era)
_ PParamsUpdate era
ppu StrictMaybe (ScriptHash (EraCrypto era))
_ -> PParamsUpdate era -> VotingThreshold
paramChangeThreshold PParamsUpdate era
ppu
        TreasuryWithdrawals {} -> VotingThreshold
NoVotingAllowed
        InfoAction {} -> VotingThreshold
NoVotingThreshold

isCommitteeVotingAllowed ::
  ConwayEraPParams era =>
  EpochNo ->
  CommitteeState era ->
  GovAction era ->
  Bool
isCommitteeVotingAllowed :: forall era.
ConwayEraPParams era =>
EpochNo -> CommitteeState era -> GovAction era -> Bool
isCommitteeVotingAllowed EpochNo
currentEpoch CommitteeState era
committeeState =
  VotingThreshold -> Bool
isVotingAllowed
    forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era.
ConwayEraPParams era =>
EpochNo
-> PParams era
-> StrictMaybe (Committee era)
-> CommitteeState era
-> GovAction era
-> VotingThreshold
votingCommitteeThresholdInternal
      EpochNo
currentEpoch
      forall a. Default a => a
def
      forall a. StrictMaybe a
committee
      CommitteeState era
committeeState
  where
    -- Information about presence of committee is irrelevant for knowing if voting is
    -- allowed or not
    committee :: StrictMaybe a
committee = forall a. StrictMaybe a
SNothing

votingCommitteeThreshold ::
  ConwayEraPParams era =>
  EpochNo ->
  RatifyState era ->
  CommitteeState era ->
  GovAction era ->
  StrictMaybe UnitInterval
votingCommitteeThreshold :: forall era.
ConwayEraPParams era =>
EpochNo
-> RatifyState era
-> CommitteeState era
-> GovAction era
-> StrictMaybe UnitInterval
votingCommitteeThreshold EpochNo
currentEpoch RatifyState era
ratifyState CommitteeState era
committeeState =
  VotingThreshold -> StrictMaybe UnitInterval
toRatifyVotingThreshold
    forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era.
ConwayEraPParams era =>
EpochNo
-> PParams era
-> StrictMaybe (Committee era)
-> CommitteeState era
-> GovAction era
-> VotingThreshold
votingCommitteeThresholdInternal
      EpochNo
currentEpoch
      PParams era
pp
      StrictMaybe (Committee era)
committee
      CommitteeState era
committeeState
  where
    committee :: StrictMaybe (Committee era)
committee = RatifyState era
ratifyState forall s a. s -> Getting a s a -> a
^. forall era. Lens' (RatifyState era) (EnactState era)
rsEnactStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (EnactState era) (StrictMaybe (Committee era))
ensCommitteeL
    pp :: PParams era
pp = RatifyState era
ratifyState forall s a. s -> Getting a s a -> a
^. forall era. Lens' (RatifyState era) (EnactState era)
rsEnactStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (EnactState era) (PParams era)
ensCurPParamsL

votingCommitteeThresholdInternal ::
  ConwayEraPParams era =>
  EpochNo ->
  PParams era ->
  StrictMaybe (Committee era) ->
  CommitteeState era ->
  GovAction era ->
  VotingThreshold
votingCommitteeThresholdInternal :: forall era.
ConwayEraPParams era =>
EpochNo
-> PParams era
-> StrictMaybe (Committee era)
-> CommitteeState era
-> GovAction era
-> VotingThreshold
votingCommitteeThresholdInternal EpochNo
currentEpoch PParams era
pp StrictMaybe (Committee era)
committee (CommitteeState Map
  (Credential 'ColdCommitteeRole (EraCrypto era))
  (CommitteeAuthorization (EraCrypto era))
hotKeys) = \case
  NoConfidence {} -> VotingThreshold
NoVotingAllowed
  UpdateCommittee {} -> VotingThreshold
NoVotingAllowed
  NewConstitution {} -> VotingThreshold
threshold
  HardForkInitiation {} -> VotingThreshold
threshold
  ParameterChange {} -> VotingThreshold
threshold
  TreasuryWithdrawals {} -> VotingThreshold
threshold
  InfoAction {} -> VotingThreshold
NoVotingThreshold
  where
    threshold :: VotingThreshold
threshold =
      case forall era. Committee era -> UnitInterval
committeeThreshold forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> StrictMaybe (Committee era)
committee of
        -- when we are not in a bootstrap phase,
        -- if the committee size is smaller than the minimum given in PParams,
        -- we treat it as if we had no committee
        SJust UnitInterval
t
          | ProtVer -> Bool
HF.bootstrapPhase (PParams era
pp forall s a. s -> Getting a s a -> a
^. forall era. EraPParams era => Lens' (PParams era) ProtVer
ppProtocolVersionL)
              Bool -> Bool -> Bool
|| Natural
activeCommitteeSize forall a. Ord a => a -> a -> Bool
>= Natural
minSize ->
              UnitInterval -> VotingThreshold
VotingThreshold UnitInterval
t
        StrictMaybe UnitInterval
_ -> VotingThreshold
NoVotingThreshold
    minSize :: Natural
minSize = PParams era
pp forall s a. s -> Getting a s a -> a
^. forall era. ConwayEraPParams era => Lens' (PParams era) Natural
ppCommitteeMinSizeL
    isActive :: Credential 'ColdCommitteeRole (EraCrypto era) -> EpochNo -> Bool
isActive Credential 'ColdCommitteeRole (EraCrypto era)
coldKey EpochNo
validUntil =
      case forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup Credential 'ColdCommitteeRole (EraCrypto era)
coldKey Map
  (Credential 'ColdCommitteeRole (EraCrypto era))
  (CommitteeAuthorization (EraCrypto era))
hotKeys of
        Just (CommitteeMemberResigned StrictMaybe (Anchor (EraCrypto era))
_) -> Bool
False
        Just CommitteeAuthorization (EraCrypto era)
_ -> EpochNo
currentEpoch forall a. Ord a => a -> a -> Bool
<= EpochNo
validUntil
        Maybe (CommitteeAuthorization (EraCrypto era))
Nothing -> Bool
False
    activeCommitteeSize :: Natural
activeCommitteeSize =
      forall a b. (Integral a, Num b) => a -> b
fromIntegral forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k a. Map k a -> Int
Map.size forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k a. (k -> a -> Bool) -> Map k a -> Map k a
Map.filterWithKey Credential 'ColdCommitteeRole (EraCrypto era) -> EpochNo -> Bool
isActive forall a b. (a -> b) -> a -> b
$
        forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap' forall era.
Committee era
-> Map (Credential 'ColdCommitteeRole (EraCrypto era)) EpochNo
committeeMembers StrictMaybe (Committee era)
committee

isDRepVotingAllowed ::
  ConwayEraPParams era =>
  GovAction era ->
  Bool
isDRepVotingAllowed :: forall era. ConwayEraPParams era => GovAction era -> Bool
isDRepVotingAllowed =
  VotingThreshold -> Bool
isVotingAllowed forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era.
ConwayEraPParams era =>
PParams era -> Bool -> GovAction era -> VotingThreshold
votingDRepThresholdInternal PParams era
pp Bool
isElectedCommittee
  where
    -- Information about presence of committee or values in PParams are irrelevant for
    -- knowing if voting is allowed or not:
    pp :: PParams era
pp = forall era. EraPParams era => PParams era
emptyPParams
    isElectedCommittee :: Bool
isElectedCommittee = Bool
False

votingDRepThreshold ::
  ConwayEraPParams era =>
  RatifyState era ->
  GovAction era ->
  StrictMaybe UnitInterval
votingDRepThreshold :: forall era.
ConwayEraPParams era =>
RatifyState era -> GovAction era -> StrictMaybe UnitInterval
votingDRepThreshold RatifyState era
ratifyState =
  VotingThreshold -> StrictMaybe UnitInterval
toRatifyVotingThreshold forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era.
ConwayEraPParams era =>
PParams era -> Bool -> GovAction era -> VotingThreshold
votingDRepThresholdInternal PParams era
pp Bool
isElectedCommittee
  where
    pp :: PParams era
pp = RatifyState era
ratifyState forall s a. s -> Getting a s a -> a
^. forall era. Lens' (RatifyState era) (EnactState era)
rsEnactStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (EnactState era) (PParams era)
ensCurPParamsL
    isElectedCommittee :: Bool
isElectedCommittee = forall a. StrictMaybe a -> Bool
isSJust forall a b. (a -> b) -> a -> b
$ RatifyState era
ratifyState forall s a. s -> Getting a s a -> a
^. forall era. Lens' (RatifyState era) (EnactState era)
rsEnactStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (EnactState era) (StrictMaybe (Committee era))
ensCommitteeL

votingDRepThresholdInternal ::
  ConwayEraPParams era =>
  PParams era ->
  Bool ->
  GovAction era ->
  VotingThreshold
votingDRepThresholdInternal :: forall era.
ConwayEraPParams era =>
PParams era -> Bool -> GovAction era -> VotingThreshold
votingDRepThresholdInternal PParams era
pp Bool
isElectedCommittee GovAction era
action =
  let thresholds :: DRepVotingThresholds
thresholds@DRepVotingThresholds
        { UnitInterval
dvtCommitteeNoConfidence :: DRepVotingThresholds -> UnitInterval
dvtCommitteeNoConfidence :: UnitInterval
dvtCommitteeNoConfidence
        , UnitInterval
dvtCommitteeNormal :: DRepVotingThresholds -> UnitInterval
dvtCommitteeNormal :: UnitInterval
dvtCommitteeNormal
        , UnitInterval
dvtMotionNoConfidence :: DRepVotingThresholds -> UnitInterval
dvtMotionNoConfidence :: UnitInterval
dvtMotionNoConfidence
        , UnitInterval
dvtUpdateToConstitution :: DRepVotingThresholds -> UnitInterval
dvtUpdateToConstitution :: UnitInterval
dvtUpdateToConstitution
        , UnitInterval
dvtHardForkInitiation :: DRepVotingThresholds -> UnitInterval
dvtHardForkInitiation :: UnitInterval
dvtHardForkInitiation
        , UnitInterval
dvtTreasuryWithdrawal :: DRepVotingThresholds -> UnitInterval
dvtTreasuryWithdrawal :: UnitInterval
dvtTreasuryWithdrawal
        } -- We reset all (except InfoAction) DRep thresholds to 0 during bootstrap phase
          | ProtVer -> Bool
HF.bootstrapPhase (PParams era
pp forall s a. s -> Getting a s a -> a
^. forall era. EraPParams era => Lens' (PParams era) ProtVer
ppProtocolVersionL) = forall a. Default a => a
def
          | Bool
otherwise = PParams era
pp forall s a. s -> Getting a s a -> a
^. forall era.
ConwayEraPParams era =>
Lens' (PParams era) DRepVotingThresholds
ppDRepVotingThresholdsL
   in case GovAction era
action of
        NoConfidence {} -> UnitInterval -> VotingThreshold
VotingThreshold UnitInterval
dvtMotionNoConfidence
        UpdateCommittee {} ->
          UnitInterval -> VotingThreshold
VotingThreshold forall a b. (a -> b) -> a -> b
$
            if Bool
isElectedCommittee
              then UnitInterval
dvtCommitteeNormal
              else UnitInterval
dvtCommitteeNoConfidence
        NewConstitution {} -> UnitInterval -> VotingThreshold
VotingThreshold UnitInterval
dvtUpdateToConstitution
        HardForkInitiation {} -> UnitInterval -> VotingThreshold
VotingThreshold UnitInterval
dvtHardForkInitiation
        ParameterChange StrictMaybe (GovPurposeId 'PParamUpdatePurpose era)
_ PParamsUpdate era
ppu StrictMaybe (ScriptHash (EraCrypto era))
_ -> UnitInterval -> VotingThreshold
VotingThreshold forall a b. (a -> b) -> a -> b
$ forall era.
ConwayEraPParams era =>
DRepVotingThresholds -> PParamsUpdate era -> UnitInterval
pparamsUpdateThreshold DRepVotingThresholds
thresholds PParamsUpdate era
ppu
        TreasuryWithdrawals {} -> UnitInterval -> VotingThreshold
VotingThreshold UnitInterval
dvtTreasuryWithdrawal
        InfoAction {} -> VotingThreshold
NoVotingThreshold

actionPriority :: GovAction era -> Int
actionPriority :: forall era. GovAction era -> Int
actionPriority NoConfidence {} = Int
0
actionPriority UpdateCommittee {} = Int
1
actionPriority NewConstitution {} = Int
2
actionPriority HardForkInitiation {} = Int
3
actionPriority ParameterChange {} = Int
4
actionPriority TreasuryWithdrawals {} = Int
5
actionPriority InfoAction {} = Int
6

reorderActions :: SS.StrictSeq (GovActionState era) -> SS.StrictSeq (GovActionState era)
reorderActions :: forall era.
StrictSeq (GovActionState era) -> StrictSeq (GovActionState era)
reorderActions = forall a. [a] -> StrictSeq a
SS.fromList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall b a. Ord b => (a -> b) -> [a] -> [a]
sortOn (forall era. GovAction era -> Int
actionPriority forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. GovActionState era -> GovAction era
gasAction) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t a -> [a]
toList

newtype RatifySignal era = RatifySignal {forall era. RatifySignal era -> StrictSeq (GovActionState era)
unRatifySignal :: StrictSeq (GovActionState era)}
  deriving (RatifySignal era -> RatifySignal era -> Bool
forall era.
EraPParams era =>
RatifySignal era -> RatifySignal era -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RatifySignal era -> RatifySignal era -> Bool
$c/= :: forall era.
EraPParams era =>
RatifySignal era -> RatifySignal era -> Bool
== :: RatifySignal era -> RatifySignal era -> Bool
$c== :: forall era.
EraPParams era =>
RatifySignal era -> RatifySignal era -> Bool
Eq, Int -> RatifySignal era -> ShowS
forall era. EraPParams era => Int -> RatifySignal era -> ShowS
forall era. EraPParams era => [RatifySignal era] -> ShowS
forall era. EraPParams era => RatifySignal era -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RatifySignal era] -> ShowS
$cshowList :: forall era. EraPParams era => [RatifySignal era] -> ShowS
show :: RatifySignal era -> String
$cshow :: forall era. EraPParams era => RatifySignal era -> String
showsPrec :: Int -> RatifySignal era -> ShowS
$cshowsPrec :: forall era. EraPParams era => Int -> RatifySignal era -> ShowS
Show, forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall era x. Rep (RatifySignal era) x -> RatifySignal era
forall era x. RatifySignal era -> Rep (RatifySignal era) x
$cto :: forall era x. Rep (RatifySignal era) x -> RatifySignal era
$cfrom :: forall era x. RatifySignal era -> Rep (RatifySignal era) x
Generic)

ratifySignalL :: Lens' (RatifySignal era) (StrictSeq (GovActionState era))
ratifySignalL :: forall era.
Lens' (RatifySignal era) (StrictSeq (GovActionState era))
ratifySignalL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall era. RatifySignal era -> StrictSeq (GovActionState era)
unRatifySignal (\RatifySignal era
x StrictSeq (GovActionState era)
y -> RatifySignal era
x {unRatifySignal :: StrictSeq (GovActionState era)
unRatifySignal = StrictSeq (GovActionState era)
y})

instance EraPParams era => NFData (RatifySignal era)

data RatifyEnv era = RatifyEnv
  { forall era.
RatifyEnv era
-> Map (Credential 'Staking (EraCrypto era)) (CompactForm Coin)
reStakeDistr :: !(Map (Credential 'Staking (EraCrypto era)) (CompactForm Coin))
  , forall era. RatifyEnv era -> PoolDistr (EraCrypto era)
reStakePoolDistr :: !(PoolDistr (EraCrypto era))
  , forall era.
RatifyEnv era -> Map (DRep (EraCrypto era)) (CompactForm Coin)
reDRepDistr :: !(Map (DRep (EraCrypto era)) (CompactForm Coin))
  , forall era.
RatifyEnv era
-> Map
     (Credential 'DRepRole (EraCrypto era)) (DRepState (EraCrypto era))
reDRepState :: !(Map (Credential 'DRepRole (EraCrypto era)) (DRepState (EraCrypto era)))
  , forall era. RatifyEnv era -> EpochNo
reCurrentEpoch :: !EpochNo
  , forall era. RatifyEnv era -> CommitteeState era
reCommitteeState :: !(CommitteeState era)
  , forall era.
RatifyEnv era
-> Map (Credential 'Staking (EraCrypto era)) (DRep (EraCrypto era))
reDelegatees :: !(Map (Credential 'Staking (EraCrypto era)) (DRep (EraCrypto era)))
  , forall era.
RatifyEnv era
-> Map
     (KeyHash 'StakePool (EraCrypto era)) (PoolParams (EraCrypto era))
rePoolParams :: !(Map (KeyHash 'StakePool (EraCrypto era)) (PoolParams (EraCrypto era)))
  }
  deriving (forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall era x. Rep (RatifyEnv era) x -> RatifyEnv era
forall era x. RatifyEnv era -> Rep (RatifyEnv era) x
$cto :: forall era x. Rep (RatifyEnv era) x -> RatifyEnv era
$cfrom :: forall era x. RatifyEnv era -> Rep (RatifyEnv era) x
Generic)

reStakeDistrL ::
  Lens' (RatifyEnv era) (Map (Credential 'Staking (EraCrypto era)) (CompactForm Coin))
reStakeDistrL :: forall era.
Lens'
  (RatifyEnv era)
  (Map (Credential 'Staking (EraCrypto era)) (CompactForm Coin))
reStakeDistrL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall era.
RatifyEnv era
-> Map (Credential 'Staking (EraCrypto era)) (CompactForm Coin)
reStakeDistr (\RatifyEnv era
x Map (Credential 'Staking (EraCrypto era)) (CompactForm Coin)
y -> RatifyEnv era
x {reStakeDistr :: Map (Credential 'Staking (EraCrypto era)) (CompactForm Coin)
reStakeDistr = Map (Credential 'Staking (EraCrypto era)) (CompactForm Coin)
y})

reStakePoolDistrL :: Lens' (RatifyEnv era) (PoolDistr (EraCrypto era))
reStakePoolDistrL :: forall era. Lens' (RatifyEnv era) (PoolDistr (EraCrypto era))
reStakePoolDistrL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall era. RatifyEnv era -> PoolDistr (EraCrypto era)
reStakePoolDistr (\RatifyEnv era
x PoolDistr (EraCrypto era)
y -> RatifyEnv era
x {reStakePoolDistr :: PoolDistr (EraCrypto era)
reStakePoolDistr = PoolDistr (EraCrypto era)
y})

reDRepDistrL :: Lens' (RatifyEnv era) (Map (DRep (EraCrypto era)) (CompactForm Coin))
reDRepDistrL :: forall era.
Lens'
  (RatifyEnv era) (Map (DRep (EraCrypto era)) (CompactForm Coin))
reDRepDistrL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall era.
RatifyEnv era -> Map (DRep (EraCrypto era)) (CompactForm Coin)
reDRepDistr (\RatifyEnv era
x Map (DRep (EraCrypto era)) (CompactForm Coin)
y -> RatifyEnv era
x {reDRepDistr :: Map (DRep (EraCrypto era)) (CompactForm Coin)
reDRepDistr = Map (DRep (EraCrypto era)) (CompactForm Coin)
y})

reDRepStateL ::
  Lens' (RatifyEnv era) (Map (Credential 'DRepRole (EraCrypto era)) (DRepState (EraCrypto era)))
reDRepStateL :: forall era.
Lens'
  (RatifyEnv era)
  (Map
     (Credential 'DRepRole (EraCrypto era)) (DRepState (EraCrypto era)))
reDRepStateL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall era.
RatifyEnv era
-> Map
     (Credential 'DRepRole (EraCrypto era)) (DRepState (EraCrypto era))
reDRepState (\RatifyEnv era
x Map
  (Credential 'DRepRole (EraCrypto era)) (DRepState (EraCrypto era))
y -> RatifyEnv era
x {reDRepState :: Map
  (Credential 'DRepRole (EraCrypto era)) (DRepState (EraCrypto era))
reDRepState = Map
  (Credential 'DRepRole (EraCrypto era)) (DRepState (EraCrypto era))
y})

reCurrentEpochL :: Lens' (RatifyEnv era) EpochNo
reCurrentEpochL :: forall era. Lens' (RatifyEnv era) EpochNo
reCurrentEpochL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall era. RatifyEnv era -> EpochNo
reCurrentEpoch (\RatifyEnv era
x EpochNo
y -> RatifyEnv era
x {reCurrentEpoch :: EpochNo
reCurrentEpoch = EpochNo
y})

reCommitteeStateL :: Lens' (RatifyEnv era) (CommitteeState era)
reCommitteeStateL :: forall era. Lens' (RatifyEnv era) (CommitteeState era)
reCommitteeStateL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall era. RatifyEnv era -> CommitteeState era
reCommitteeState (\RatifyEnv era
x CommitteeState era
y -> RatifyEnv era
x {reCommitteeState :: CommitteeState era
reCommitteeState = CommitteeState era
y})

deriving instance Show (RatifyEnv era)
deriving instance Eq (RatifyEnv era)

instance Default (RatifyEnv era) where
  def :: RatifyEnv era
def =
    forall era.
Map (Credential 'Staking (EraCrypto era)) (CompactForm Coin)
-> PoolDistr (EraCrypto era)
-> Map (DRep (EraCrypto era)) (CompactForm Coin)
-> Map
     (Credential 'DRepRole (EraCrypto era)) (DRepState (EraCrypto era))
-> EpochNo
-> CommitteeState era
-> Map (Credential 'Staking (EraCrypto era)) (DRep (EraCrypto era))
-> Map
     (KeyHash 'StakePool (EraCrypto era)) (PoolParams (EraCrypto era))
-> RatifyEnv era
RatifyEnv
      forall k a. Map k a
Map.empty
      (forall c.
Map (KeyHash 'StakePool c) (IndividualPoolStake c)
-> CompactForm Coin -> PoolDistr c
PoolDistr forall k a. Map k a
Map.empty forall a. Monoid a => a
mempty)
      forall k a. Map k a
Map.empty
      forall k a. Map k a
Map.empty
      (Word64 -> EpochNo
EpochNo Word64
0)
      forall a. Default a => a
def
      forall k a. Map k a
Map.empty
      forall k a. Map k a
Map.empty

instance Typeable era => NoThunks (RatifyEnv era) where
  showTypeOf :: Proxy (RatifyEnv era) -> String
showTypeOf Proxy (RatifyEnv era)
_ = String
"RatifyEnv"
  wNoThunks :: Context -> RatifyEnv era -> IO (Maybe ThunkInfo)
wNoThunks Context
ctxt (RatifyEnv Map (Credential 'Staking (EraCrypto era)) (CompactForm Coin)
stake PoolDistr (EraCrypto era)
pool Map (DRep (EraCrypto era)) (CompactForm Coin)
drep Map
  (Credential 'DRepRole (EraCrypto era)) (DRepState (EraCrypto era))
dstate EpochNo
ep CommitteeState era
cs Map (Credential 'Staking (EraCrypto era)) (DRep (EraCrypto era))
delegatees Map
  (KeyHash 'StakePool (EraCrypto era)) (PoolParams (EraCrypto era))
poolps) =
    [IO (Maybe ThunkInfo)] -> IO (Maybe ThunkInfo)
allNoThunks
      [ forall a. NoThunks a => Context -> a -> IO (Maybe ThunkInfo)
noThunks Context
ctxt Map (Credential 'Staking (EraCrypto era)) (CompactForm Coin)
stake
      , forall a. NoThunks a => Context -> a -> IO (Maybe ThunkInfo)
noThunks Context
ctxt PoolDistr (EraCrypto era)
pool
      , forall a. NoThunks a => Context -> a -> IO (Maybe ThunkInfo)
noThunks Context
ctxt Map (DRep (EraCrypto era)) (CompactForm Coin)
drep
      , forall a. NoThunks a => Context -> a -> IO (Maybe ThunkInfo)
noThunks Context
ctxt Map
  (Credential 'DRepRole (EraCrypto era)) (DRepState (EraCrypto era))
dstate
      , forall a. NoThunks a => Context -> a -> IO (Maybe ThunkInfo)
noThunks Context
ctxt EpochNo
ep
      , forall a. NoThunks a => Context -> a -> IO (Maybe ThunkInfo)
noThunks Context
ctxt CommitteeState era
cs
      , forall a. NoThunks a => Context -> a -> IO (Maybe ThunkInfo)
noThunks Context
ctxt Map (Credential 'Staking (EraCrypto era)) (DRep (EraCrypto era))
delegatees
      , forall a. NoThunks a => Context -> a -> IO (Maybe ThunkInfo)
noThunks Context
ctxt Map
  (KeyHash 'StakePool (EraCrypto era)) (PoolParams (EraCrypto era))
poolps
      ]

instance Era era => NFData (RatifyEnv era) where
  rnf :: RatifyEnv era -> ()
rnf (RatifyEnv Map (Credential 'Staking (EraCrypto era)) (CompactForm Coin)
stake PoolDistr (EraCrypto era)
pool Map (DRep (EraCrypto era)) (CompactForm Coin)
drep Map
  (Credential 'DRepRole (EraCrypto era)) (DRepState (EraCrypto era))
dstate EpochNo
ep CommitteeState era
cs Map (Credential 'Staking (EraCrypto era)) (DRep (EraCrypto era))
delegatees Map
  (KeyHash 'StakePool (EraCrypto era)) (PoolParams (EraCrypto era))
poolps) =
    Map (Credential 'Staking (EraCrypto era)) (CompactForm Coin)
stake forall a b. NFData a => a -> b -> b
`deepseq`
      PoolDistr (EraCrypto era)
pool forall a b. NFData a => a -> b -> b
`deepseq`
        Map (DRep (EraCrypto era)) (CompactForm Coin)
drep forall a b. NFData a => a -> b -> b
`deepseq`
          Map
  (Credential 'DRepRole (EraCrypto era)) (DRepState (EraCrypto era))
dstate forall a b. NFData a => a -> b -> b
`deepseq`
            EpochNo
ep forall a b. NFData a => a -> b -> b
`deepseq`
              CommitteeState era
cs forall a b. NFData a => a -> b -> b
`deepseq`
                Map (Credential 'Staking (EraCrypto era)) (DRep (EraCrypto era))
delegatees forall a b. NFData a => a -> b -> b
`deepseq`
                  forall a. NFData a => a -> ()
rnf Map
  (KeyHash 'StakePool (EraCrypto era)) (PoolParams (EraCrypto era))
poolps

instance Era era => EncCBOR (RatifyEnv era) where
  encCBOR :: RatifyEnv era -> Encoding
encCBOR env :: RatifyEnv era
env@(RatifyEnv Map (Credential 'Staking (EraCrypto era)) (CompactForm Coin)
_ PoolDistr (EraCrypto era)
_ Map (DRep (EraCrypto era)) (CompactForm Coin)
_ Map
  (Credential 'DRepRole (EraCrypto era)) (DRepState (EraCrypto era))
_ EpochNo
_ CommitteeState era
_ Map (Credential 'Staking (EraCrypto era)) (DRep (EraCrypto era))
_ Map
  (KeyHash 'StakePool (EraCrypto era)) (PoolParams (EraCrypto era))
_) =
    let RatifyEnv {Map (DRep (EraCrypto era)) (CompactForm Coin)
Map
  (Credential 'DRepRole (EraCrypto era)) (DRepState (EraCrypto era))
Map (Credential 'Staking (EraCrypto era)) (DRep (EraCrypto era))
Map (Credential 'Staking (EraCrypto era)) (CompactForm Coin)
Map
  (KeyHash 'StakePool (EraCrypto era)) (PoolParams (EraCrypto era))
CommitteeState era
PoolDistr (EraCrypto era)
EpochNo
rePoolParams :: Map
  (KeyHash 'StakePool (EraCrypto era)) (PoolParams (EraCrypto era))
reDelegatees :: Map (Credential 'Staking (EraCrypto era)) (DRep (EraCrypto era))
reCommitteeState :: CommitteeState era
reCurrentEpoch :: EpochNo
reDRepState :: Map
  (Credential 'DRepRole (EraCrypto era)) (DRepState (EraCrypto era))
reDRepDistr :: Map (DRep (EraCrypto era)) (CompactForm Coin)
reStakePoolDistr :: PoolDistr (EraCrypto era)
reStakeDistr :: Map (Credential 'Staking (EraCrypto era)) (CompactForm Coin)
rePoolParams :: forall era.
RatifyEnv era
-> Map
     (KeyHash 'StakePool (EraCrypto era)) (PoolParams (EraCrypto era))
reDelegatees :: forall era.
RatifyEnv era
-> Map (Credential 'Staking (EraCrypto era)) (DRep (EraCrypto era))
reCommitteeState :: forall era. RatifyEnv era -> CommitteeState era
reCurrentEpoch :: forall era. RatifyEnv era -> EpochNo
reDRepState :: forall era.
RatifyEnv era
-> Map
     (Credential 'DRepRole (EraCrypto era)) (DRepState (EraCrypto era))
reDRepDistr :: forall era.
RatifyEnv era -> Map (DRep (EraCrypto era)) (CompactForm Coin)
reStakePoolDistr :: forall era. RatifyEnv era -> PoolDistr (EraCrypto era)
reStakeDistr :: forall era.
RatifyEnv era
-> Map (Credential 'Staking (EraCrypto era)) (CompactForm Coin)
..} = RatifyEnv era
env
     in 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 'Staking (EraCrypto era)) (CompactForm Coin)
-> PoolDistr (EraCrypto era)
-> Map (DRep (EraCrypto era)) (CompactForm Coin)
-> Map
     (Credential 'DRepRole (EraCrypto era)) (DRepState (EraCrypto era))
-> EpochNo
-> CommitteeState era
-> Map (Credential 'Staking (EraCrypto era)) (DRep (EraCrypto era))
-> Map
     (KeyHash 'StakePool (EraCrypto era)) (PoolParams (EraCrypto era))
-> RatifyEnv era
RatifyEnv @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 'Staking (EraCrypto era)) (CompactForm Coin)
reStakeDistr
            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 PoolDistr (EraCrypto era)
reStakePoolDistr
            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 (DRep (EraCrypto era)) (CompactForm Coin)
reDRepDistr
            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 (EraCrypto era)) (DRepState (EraCrypto era))
reDRepState
            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
reCurrentEpoch
            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 CommitteeState era
reCommitteeState
            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 'Staking (EraCrypto era)) (DRep (EraCrypto era))
reDelegatees
            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 (EraCrypto era)) (PoolParams (EraCrypto era))
rePoolParams

instance Era era => DecCBOR (RatifyEnv era) where
  decCBOR :: forall s. Decoder s (RatifyEnv 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 'Staking (EraCrypto era)) (CompactForm Coin)
-> PoolDistr (EraCrypto era)
-> Map (DRep (EraCrypto era)) (CompactForm Coin)
-> Map
     (Credential 'DRepRole (EraCrypto era)) (DRepState (EraCrypto era))
-> EpochNo
-> CommitteeState era
-> Map (Credential 'Staking (EraCrypto era)) (DRep (EraCrypto era))
-> Map
     (KeyHash 'StakePool (EraCrypto era)) (PoolParams (EraCrypto era))
-> RatifyEnv era
RatifyEnv
        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
        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 => EncCBOR (RatifyState era) where
  encCBOR :: RatifyState era -> Encoding
encCBOR (RatifyState EnactState era
es Seq (GovActionState era)
enacted Set (GovActionId (EraCrypto era))
expired Bool
delayed) =
    forall (w :: Wrapped) t. Encode w t -> Encoding
encode
      ( forall t. t -> Encode ('Closed 'Dense) t
Rec (forall era.
EnactState era
-> Seq (GovActionState era)
-> Set (GovActionId (EraCrypto era))
-> Bool
-> RatifyState era
RatifyState @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 EnactState era
es
          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 Seq (GovActionState era)
enacted
          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 (GovActionId (EraCrypto era))
expired
          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 Bool
delayed
      )

instance EraPParams era => EncCBOR (RatifySignal era) where
  encCBOR :: RatifySignal era -> Encoding
encCBOR (RatifySignal StrictSeq (GovActionState era)
govActions) = forall a. EncCBOR a => a -> Encoding
encCBOR StrictSeq (GovActionState era)
govActions

instance EraPParams era => DecCBOR (RatifySignal era) where
  decCBOR :: forall s. Decoder s (RatifySignal era)
decCBOR = forall era. StrictSeq (GovActionState era) -> RatifySignal era
RatifySignal forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a s. DecCBOR a => Decoder s a
decCBOR

instance EraPParams era => DecCBOR (RatifyState era) where
  decCBOR :: forall s. Decoder s (RatifyState era)
decCBOR = forall (w :: Wrapped) t s. Decode w t -> Decoder s t
decode (forall t. t -> Decode ('Closed 'Dense) t
RecD forall era.
EnactState era
-> Seq (GovActionState era)
-> Set (GovActionId (EraCrypto era))
-> Bool
-> RatifyState era
RatifyState 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)

-- TODO: Implement Sharing: https://github.com/intersectmbo/cardano-ledger/issues/3486
instance EraPParams era => DecShareCBOR (RatifyState era) where
  decShareCBOR :: forall s. Share (RatifyState era) -> Decoder s (RatifyState era)
decShareCBOR Share (RatifyState 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.
EnactState era
-> Seq (GovActionState era)
-> Set (GovActionId (EraCrypto era))
-> Bool
-> RatifyState era
RatifyState
        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