{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}
module Test.Cardano.Ledger.Constrained.Vars where
import Cardano.Crypto.Signing (SigningKey)
import Cardano.Ledger.Address (Addr (..), Withdrawals (..))
import Cardano.Ledger.Allegra.Scripts (ValidityInterval (..))
import Cardano.Ledger.Alonzo.PParams (AlonzoEraPParams, ppCollateralPercentageL, ppMaxTxExUnitsL)
import Cardano.Ledger.Alonzo.Tx (IsValid (..), ScriptIntegrityHash)
import Cardano.Ledger.Alonzo.TxWits (TxDats (..))
import Cardano.Ledger.Alonzo.UTxO (AlonzoScriptsNeeded (..))
import Cardano.Ledger.BaseTypes (
BlocksMade (..),
EpochNo,
Globals (..),
Network (..),
ProtVer (..),
SlotNo (..),
StrictMaybe (..),
UnitInterval,
)
import qualified Cardano.Ledger.BaseTypes as Base (EpochInterval (..), Globals (..))
import Cardano.Ledger.CertState (
CommitteeAuthorization (..),
CommitteeState (..),
csCommitteeCredsL,
vsNumDormantEpochsL,
)
import Cardano.Ledger.Coin (Coin (..), CompactForm (CompactCoin), DeltaCoin)
import Cardano.Ledger.Conway.Governance hiding (GovState)
import Cardano.Ledger.Conway.PParams (
ConwayEraPParams,
ppDRepActivityL,
ppDRepDepositL,
ppGovActionDepositL,
)
import Cardano.Ledger.Core (
Era,
PParams,
TxOut,
TxWits,
Value,
addrTxOutL,
coinTxOutL,
ppEMaxL,
ppKeyDepositL,
ppMaxBBSizeL,
ppMaxBHSizeL,
ppMaxTxSizeL,
ppMinFeeAL,
ppMinFeeBL,
ppPoolDepositL,
ppProtocolVersionL,
valueTxOutL,
)
import Cardano.Ledger.Credential (Credential, Ptr)
import Cardano.Ledger.DRep (DRep (..), DRepState (..))
import Cardano.Ledger.EpochBoundary (SnapShot (..), SnapShots (..), Stake (..))
import Cardano.Ledger.Hashes (
DataHash,
EraIndependentScriptIntegrity,
SafeHash,
ScriptHash (..),
TxAuxDataHash (..),
)
import Cardano.Ledger.Keys (GenDelegPair, GenDelegs (..), KeyHash, KeyRole (..))
import Cardano.Ledger.Keys.Bootstrap (BootstrapWitness)
import Cardano.Ledger.Keys.WitVKey (WitVKey (..))
import Cardano.Ledger.Mary.Value (AssetName (..), MaryValue (..), MultiAsset (..), PolicyID (..))
import Cardano.Ledger.Plutus (ExUnits (..))
import Cardano.Ledger.Plutus.Data (Data (..), Datum (..))
import Cardano.Ledger.PoolDistr (IndividualPoolStake (..), PoolDistr (..), poolDistrDistrL)
import Cardano.Ledger.PoolParams (PoolParams)
import Cardano.Ledger.Shelley.Governance (FuturePParams (..), futureProposalsL, proposalsL)
import qualified Cardano.Ledger.Shelley.Governance as Gov
import Cardano.Ledger.Shelley.HardForks as HardForks (allowMIRTransfer)
import Cardano.Ledger.Shelley.LedgerState hiding (
credMapL,
delegations,
deltaReserves,
deltaTreasury,
ptrMap,
ptrMapL,
rewards,
)
import Cardano.Ledger.Shelley.PParams (ProposedPPUpdates (..))
import Cardano.Ledger.Shelley.PoolRank (NonMyopic (..))
import qualified Cardano.Ledger.Shelley.RewardUpdate as RU
import Cardano.Ledger.Shelley.Rewards (Reward (..))
import Cardano.Ledger.Shelley.TxBody (RewardAccount (..))
import Cardano.Ledger.Shelley.UTxO (EraUTxO (..), ShelleyScriptsNeeded (..))
import Cardano.Ledger.TxIn (TxIn (..))
import Cardano.Ledger.UMap (compactCoinOrError, fromCompact, ptrMap, rdPairMap, sPoolMap, unify)
import Cardano.Ledger.UTxO (UTxO (..))
import Cardano.Ledger.Val (Val (..))
import Control.Arrow (first)
import Data.Default (Default (def))
import Data.Foldable (toList)
import qualified Data.Foldable as F
import Data.Functor.Identity (Identity)
import Data.Map.Strict (Map)
import qualified Data.Map.Strict as Map
import Data.Maybe.Strict (maybeToStrictMaybe, strictMaybeToMaybe)
import qualified Data.OMap.Strict as OMap
import Data.Ratio ((%))
import qualified Data.Sequence.Strict as SS
import Data.Set (Set)
import qualified Data.VMap as VMap
import Data.Word (Word16, Word32, Word64)
import GHC.Stack (HasCallStack)
import Lens.Micro
import Numeric.Natural (Natural)
import Test.Cardano.Ledger.Babbage.Serialisation.Generators ()
import Test.Cardano.Ledger.Constrained.Ast
import Test.Cardano.Ledger.Constrained.Classes (
GovState (..),
PParamsF (..),
PParamsUpdateF (..),
PlutusPointerF (..),
PlutusPurposeF (..),
ScriptF (..),
ScriptsNeededF (..),
TxAuxDataF (..),
TxBodyF (..),
TxCertF (..),
TxF (..),
TxOutF (..),
TxWitsF (..),
ValueF (..),
liftUTxO,
pparamsWrapperL,
unPParamsUpdate,
unPlutusPointerF,
unPlutusPurposeF,
unScriptF,
unTxCertF,
unTxOut,
unValue,
)
import Test.Cardano.Ledger.Constrained.Env (
Access (..),
AnyF (..),
Field (..),
Name (..),
V (..),
pV,
)
import Test.Cardano.Ledger.Constrained.Lenses
import Test.Cardano.Ledger.Constrained.TypeRep (Rep (..), testEql, (:~:) (Refl))
import Test.Cardano.Ledger.Core.KeyPair (KeyPair (..))
import Test.Cardano.Ledger.Generic.Fields (TxBodyField (..), TxField (..), WitnessesField (..))
import qualified Test.Cardano.Ledger.Generic.Fields as Fields
import Test.Cardano.Ledger.Generic.Functions (protocolVersion)
import Test.Cardano.Ledger.Generic.GenState (mkRedeemers)
import Test.Cardano.Ledger.Generic.PrettyCore (ppString, withEraPParams)
import Test.Cardano.Ledger.Generic.Proof
import Test.Cardano.Ledger.Generic.Updaters (merge, newPParams, newTx, newTxBody, newWitnesses)
import Test.Cardano.Ledger.Shelley.Utils (testGlobals)
import qualified Test.Cardano.Ledger.Shelley.Utils as Utils (testGlobals)
import Type.Reflection (Typeable, typeRep)
field :: Era era => Rep era s -> Term era t -> AnyF era s
field :: forall era s t. Era era => Rep era s -> Term era t -> AnyF era s
field Rep era s
repS1 (Var (V String
name Rep era t
rept (Yes Rep era s
repS2 Lens' s t
l))) = case forall {k} (t :: k -> *) (i :: k) (j :: k).
Singleton t =>
t i -> t j -> Maybe (i :~: j)
testEql Rep era s
repS1 Rep era s
repS2 of
Just s :~: s
Refl -> forall era s t. Field era s t -> AnyF era s
AnyF (forall era t s.
Era era =>
String -> Rep era t -> Rep era s -> Lens' s t -> Field era s t
Field String
name Rep era t
rept Rep era s
repS2 Lens' s t
l)
Maybe (s :~: s)
Nothing ->
forall a. HasCallStack => String -> a
error
( [String] -> String
unlines
[ String
"Given rep and lens target do not match: "
, String
"rep: " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Rep era s
repS1
, String
"lens target: " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Rep era s
repS2
]
)
field Rep era s
_ Term era t
term = forall a. HasCallStack => String -> a
error (String
"field can only be applied to variable terms: " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Term era t
term)
getName :: Term era t -> Name era
getName :: forall era t. Term era t -> Name era
getName (Var V era t
v) = forall era t. V era t -> Name era
Name V era t
v
getName Term era t
x = forall a. HasCallStack => String -> a
error (String
"nameOf can't find the name in: " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Term era t
x)
type NELens era t = Lens' (NewEpochState era) t
currentEpoch :: Era era => Term era EpochNo
currentEpoch :: forall era. Era era => Term era EpochNo
currentEpoch = forall era t. V era t -> Term era t
Var (forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"currentEpoch" forall era. Rep era EpochNo
EpochR (forall era s t. Rep era s -> Lens' s t -> Access era s t
Yes forall era. Era era => Rep era (NewEpochState era)
NewEpochStateR forall era. Lens' (NewEpochState era) EpochNo
nesELL))
prevBlocksMade :: Era era => Term era (Map (KeyHash 'StakePool) Natural)
prevBlocksMade :: forall era. Era era => Term era (Map (KeyHash 'StakePool) Natural)
prevBlocksMade = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"prevBlocksMade" (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Era era => Rep era (KeyHash 'StakePool)
PoolHashR forall era. Rep era Natural
NaturalR) (forall era s t. Rep era s -> Lens' s t -> Access era s t
Yes forall era. Era era => Rep era (NewEpochState era)
NewEpochStateR forall era.
Lens' (NewEpochState era) (Map (KeyHash 'StakePool) Natural)
nesBprevL)
currBlocksMade :: Era era => Term era (Map (KeyHash 'StakePool) Natural)
currBlocksMade :: forall era. Era era => Term era (Map (KeyHash 'StakePool) Natural)
currBlocksMade = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"currBlocksMade" (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Era era => Rep era (KeyHash 'StakePool)
PoolHashR forall era. Rep era Natural
NaturalR) (forall era s t. Rep era s -> Lens' s t -> Access era s t
Yes forall era. Era era => Rep era (NewEpochState era)
NewEpochStateR forall era.
Lens' (NewEpochState era) (Map (KeyHash 'StakePool) Natural)
nesBcurL)
poolDistr ::
Era era => Term era (Map (KeyHash 'StakePool) IndividualPoolStake)
poolDistr :: forall era.
Era era =>
Term era (Map (KeyHash 'StakePool) IndividualPoolStake)
poolDistr = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"poolDistr" (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Era era => Rep era (KeyHash 'StakePool)
PoolHashR forall era. Era era => Rep era IndividualPoolStake
IPoolStakeR) (forall era s t. Rep era s -> Lens' s t -> Access era s t
Yes forall era. Era era => Rep era (NewEpochState era)
NewEpochStateR forall era.
NELens era (Map (KeyHash 'StakePool) IndividualPoolStake)
poolDistrL)
mockPoolDistr :: Era era => Term era (Map (KeyHash 'StakePool) Rational)
mockPoolDistr :: forall era. Era era => Term era (Map (KeyHash 'StakePool) Rational)
mockPoolDistr = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"mockPoolDistr" (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Era era => Rep era (KeyHash 'StakePool)
PoolHashR forall era. Rep era Rational
RationalR) forall era s t. Access era s t
No
poolDistrL ::
NELens era (Map (KeyHash 'StakePool) IndividualPoolStake)
poolDistrL :: forall era.
NELens era (Map (KeyHash 'StakePool) IndividualPoolStake)
poolDistrL = forall era. Lens' (NewEpochState era) PoolDistr
nesPdL forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' PoolDistr (Map (KeyHash 'StakePool) IndividualPoolStake)
poolDistrDistrL
rewards :: Era era => Term era (Map (Credential 'Staking) Coin)
rewards :: forall era. Era era => Term era (Map (Credential 'Staking) Coin)
rewards = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"rewards" (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Era era => Rep era (Credential 'Staking)
CredR forall era. Rep era Coin
CoinR) (forall era s t. Rep era s -> Lens' s t -> Access era s t
Yes forall era. Era era => Rep era (NewEpochState era)
NewEpochStateR forall era. NELens era (Map (Credential 'Staking) Coin)
rewardsL)
rewardsL :: NELens era (Map (Credential 'Staking) Coin)
rewardsL :: forall era. NELens era (Map (Credential 'Staking) Coin)
rewardsL = forall era. Lens' (NewEpochState era) (EpochState era)
nesEsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (EpochState era) (LedgerState era)
esLStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (LedgerState era) (CertState era)
lsCertStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (CertState era) (DState era)
certDStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (DState era) UMap
dsUnifiedL forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' UMap (Map (Credential 'Staking) Coin)
rewardsUMapL
delegations ::
Era era => Term era (Map (Credential 'Staking) (KeyHash 'StakePool))
delegations :: forall era.
Era era =>
Term era (Map (Credential 'Staking) (KeyHash 'StakePool))
delegations = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"delegations" (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Era era => Rep era (Credential 'Staking)
CredR forall era. Era era => Rep era (KeyHash 'StakePool)
PoolHashR) (forall era s t. Rep era s -> Lens' s t -> Access era s t
Yes forall era. Era era => Rep era (NewEpochState era)
NewEpochStateR forall era.
NELens era (Map (Credential 'Staking) (KeyHash 'StakePool))
delegationsL)
delegationsL ::
NELens era (Map (Credential 'Staking) (KeyHash 'StakePool))
delegationsL :: forall era.
NELens era (Map (Credential 'Staking) (KeyHash 'StakePool))
delegationsL = forall era. Lens' (NewEpochState era) (EpochState era)
nesEsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (EpochState era) (LedgerState era)
esLStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (LedgerState era) (CertState era)
lsCertStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (CertState era) (DState era)
certDStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (DState era) UMap
dsUnifiedL forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' UMap (Map (Credential 'Staking) (KeyHash 'StakePool))
delegationsUMapL
stakeDeposits :: Era era => Term era (Map (Credential 'Staking) Coin)
stakeDeposits :: forall era. Era era => Term era (Map (Credential 'Staking) Coin)
stakeDeposits = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"stakeDeposits" (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Era era => Rep era (Credential 'Staking)
CredR forall era. Rep era Coin
CoinR) (forall era s t. Rep era s -> Lens' s t -> Access era s t
Yes forall era. Era era => Rep era (NewEpochState era)
NewEpochStateR forall era. NELens era (Map (Credential 'Staking) Coin)
stakeDepositsL)
stakeDepositsL :: NELens era (Map (Credential 'Staking) Coin)
stakeDepositsL :: forall era. NELens era (Map (Credential 'Staking) Coin)
stakeDepositsL = forall era. Lens' (NewEpochState era) (EpochState era)
nesEsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (EpochState era) (LedgerState era)
esLStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (LedgerState era) (CertState era)
lsCertStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (CertState era) (DState era)
certDStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (DState era) UMap
dsUnifiedL forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' UMap (Map (Credential 'Staking) Coin)
stakeDepositsUMapL
ptrs :: Era era => Term era (Map Ptr (Credential 'Staking))
ptrs :: forall era. Era era => Term era (Map Ptr (Credential 'Staking))
ptrs = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"ptrs" (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Rep era Ptr
PtrR forall era. Era era => Rep era (Credential 'Staking)
CredR) (forall era s t. Rep era s -> Lens' s t -> Access era s t
Yes forall era. Era era => Rep era (NewEpochState era)
NewEpochStateR forall era. NELens era (Map Ptr (Credential 'Staking))
ptrsL)
ptrsL :: NELens era (Map Ptr (Credential 'Staking))
ptrsL :: forall era. NELens era (Map Ptr (Credential 'Staking))
ptrsL = forall era. Lens' (NewEpochState era) (EpochState era)
nesEsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (EpochState era) (LedgerState era)
esLStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (LedgerState era) (CertState era)
lsCertStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (CertState era) (DState era)
certDStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (DState era) UMap
dsUnifiedL forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' UMap (Map Ptr (Credential 'Staking))
ptrsUMapL
currentDRepState ::
Era era => Term era (Map (Credential 'DRepRole) DRepState)
currentDRepState :: forall era.
Era era =>
Term era (Map (Credential 'DRepRole) DRepState)
currentDRepState = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"currentDRepState" (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Era era => Rep era (Credential 'DRepRole)
VCredR forall era. Era era => Rep era DRepState
DRepStateR) (forall era s t. Rep era s -> Lens' s t -> Access era s t
Yes forall era. Era era => Rep era (NewEpochState era)
NewEpochStateR forall era. NELens era (Map (Credential 'DRepRole) DRepState)
drepsL)
drepsL :: NELens era (Map (Credential 'DRepRole) DRepState)
drepsL :: forall era. NELens era (Map (Credential 'DRepRole) DRepState)
drepsL = forall era. Lens' (NewEpochState era) (EpochState era)
nesEsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (EpochState era) (LedgerState era)
esLStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (LedgerState era) (CertState era)
lsCertStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (CertState era) (VState era)
certVStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era.
Lens' (VState era) (Map (Credential 'DRepRole) DRepState)
vsDRepsL
drepDelegation ::
Era era => Term era (Map (Credential 'Staking) DRep)
drepDelegation :: forall era. Era era => Term era (Map (Credential 'Staking) DRep)
drepDelegation = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"drepDelegation" (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Era era => Rep era (Credential 'Staking)
CredR forall era. Era era => Rep era DRep
DRepR) (forall era s t. Rep era s -> Lens' s t -> Access era s t
Yes forall era. Era era => Rep era (NewEpochState era)
NewEpochStateR forall era. NELens era (Map (Credential 'Staking) DRep)
drepDelegationL)
drepDelegationL :: NELens era (Map (Credential 'Staking) DRep)
drepDelegationL :: forall era. NELens era (Map (Credential 'Staking) DRep)
drepDelegationL = forall era. Lens' (NewEpochState era) (EpochState era)
nesEsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (EpochState era) (LedgerState era)
esLStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (LedgerState era) (CertState era)
lsCertStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (CertState era) (DState era)
certDStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (DState era) UMap
dsUnifiedL forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' UMap (Map (Credential 'Staking) DRep)
drepUMapL
futureGenDelegs ::
Era era => Term era (Map FutureGenDeleg GenDelegPair)
futureGenDelegs :: forall era. Era era => Term era (Map FutureGenDeleg GenDelegPair)
futureGenDelegs =
forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$
forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V
String
"futureGenDelegs"
(forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Era era => Rep era FutureGenDeleg
FutureGenDelegR forall era. Era era => Rep era GenDelegPair
GenDelegPairR)
(forall era s t. Rep era s -> Lens' s t -> Access era s t
Yes forall era. Era era => Rep era (NewEpochState era)
NewEpochStateR forall era. NELens era (Map FutureGenDeleg GenDelegPair)
futureGenDelegsL)
futureGenDelegsL :: NELens era (Map FutureGenDeleg GenDelegPair)
futureGenDelegsL :: forall era. NELens era (Map FutureGenDeleg GenDelegPair)
futureGenDelegsL = forall era. Lens' (NewEpochState era) (EpochState era)
nesEsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (EpochState era) (LedgerState era)
esLStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (LedgerState era) (CertState era)
lsCertStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (CertState era) (DState era)
certDStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (DState era) (Map FutureGenDeleg GenDelegPair)
dsFutureGenDelegsL
genDelegs ::
Era era => Term era (Map (KeyHash 'Genesis) GenDelegPair)
genDelegs :: forall era.
Era era =>
Term era (Map (KeyHash 'Genesis) GenDelegPair)
genDelegs = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"genDelegs" (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Era era => Rep era (KeyHash 'Genesis)
GenHashR forall era. Era era => Rep era GenDelegPair
GenDelegPairR) (forall era s t. Rep era s -> Lens' s t -> Access era s t
Yes forall era. Era era => Rep era (NewEpochState era)
NewEpochStateR forall era. NELens era (Map (KeyHash 'Genesis) GenDelegPair)
genDelegsL)
genDelegsL :: NELens era (Map (KeyHash 'Genesis) GenDelegPair)
genDelegsL :: forall era. NELens era (Map (KeyHash 'Genesis) GenDelegPair)
genDelegsL = forall era. Lens' (NewEpochState era) (EpochState era)
nesEsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (EpochState era) (LedgerState era)
esLStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (LedgerState era) (CertState era)
lsCertStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (CertState era) (DState era)
certDStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (DState era) GenDelegs
dsGenDelegsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' GenDelegs (Map (KeyHash 'Genesis) GenDelegPair)
unGenDelegsL
instanReserves :: Era era => Term era (Map (Credential 'Staking) Coin)
instanReserves :: forall era. Era era => Term era (Map (Credential 'Staking) Coin)
instanReserves = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"instanReserves" (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Era era => Rep era (Credential 'Staking)
CredR forall era. Rep era Coin
CoinR) (forall era s t. Rep era s -> Lens' s t -> Access era s t
Yes forall era. Era era => Rep era (NewEpochState era)
NewEpochStateR forall era. NELens era (Map (Credential 'Staking) Coin)
instanReservesL)
instanReservesL :: NELens era (Map (Credential 'Staking) Coin)
instanReservesL :: forall era. NELens era (Map (Credential 'Staking) Coin)
instanReservesL = forall era. Lens' (NewEpochState era) (EpochState era)
nesEsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (EpochState era) (LedgerState era)
esLStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (LedgerState era) (CertState era)
lsCertStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (CertState era) (DState era)
certDStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (DState era) InstantaneousRewards
dsIRewardsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' InstantaneousRewards (Map (Credential 'Staking) Coin)
iRReservesL
instanReservesSum :: Era era => Term era Coin
instanReservesSum :: forall era. Era era => Term era Coin
instanReservesSum = forall era t. V era t -> Term era t
Var (forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"instanReservesSum" forall era. Rep era Coin
CoinR forall era s t. Access era s t
No)
instanTreasury :: Era era => Term era (Map (Credential 'Staking) Coin)
instanTreasury :: forall era. Era era => Term era (Map (Credential 'Staking) Coin)
instanTreasury = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"instanTreasury" (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Era era => Rep era (Credential 'Staking)
CredR forall era. Rep era Coin
CoinR) (forall era s t. Rep era s -> Lens' s t -> Access era s t
Yes forall era. Era era => Rep era (NewEpochState era)
NewEpochStateR forall era. NELens era (Map (Credential 'Staking) Coin)
instanTreasuryL)
instanTreasuryL :: NELens era (Map (Credential 'Staking) Coin)
instanTreasuryL :: forall era. NELens era (Map (Credential 'Staking) Coin)
instanTreasuryL = forall era. Lens' (NewEpochState era) (EpochState era)
nesEsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (EpochState era) (LedgerState era)
esLStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (LedgerState era) (CertState era)
lsCertStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (CertState era) (DState era)
certDStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (DState era) InstantaneousRewards
dsIRewardsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' InstantaneousRewards (Map (Credential 'Staking) Coin)
iRTreasuryL
instanTreasurySum :: Era era => Term era Coin
instanTreasurySum :: forall era. Era era => Term era Coin
instanTreasurySum = forall era t. V era t -> Term era t
Var (forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"instanTreasurySum" forall era. Rep era Coin
CoinR forall era s t. Access era s t
No)
deltaReserves :: Era era => Term era DeltaCoin
deltaReserves :: forall era. Era era => Term era DeltaCoin
deltaReserves = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"deltaReserves" forall era. Rep era DeltaCoin
DeltaCoinR (forall era s t. Rep era s -> Lens' s t -> Access era s t
Yes forall era. Era era => Rep era (NewEpochState era)
NewEpochStateR forall era. NELens era DeltaCoin
deltaReservesNEL)
deltaReservesNEL :: NELens era DeltaCoin
deltaReservesNEL :: forall era. NELens era DeltaCoin
deltaReservesNEL = forall era. Lens' (NewEpochState era) (EpochState era)
nesEsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (EpochState era) (LedgerState era)
esLStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (LedgerState era) (CertState era)
lsCertStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (CertState era) (DState era)
certDStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (DState era) InstantaneousRewards
dsIRewardsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' InstantaneousRewards DeltaCoin
deltaReservesL
deltaTreasury :: Era era => Term era DeltaCoin
deltaTreasury :: forall era. Era era => Term era DeltaCoin
deltaTreasury = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"deltaTreasury" forall era. Rep era DeltaCoin
DeltaCoinR (forall era s t. Rep era s -> Lens' s t -> Access era s t
Yes forall era. Era era => Rep era (NewEpochState era)
NewEpochStateR forall era. NELens era DeltaCoin
deltaTreasuryNEL)
deltaTreasuryNEL :: NELens era DeltaCoin
deltaTreasuryNEL :: forall era. NELens era DeltaCoin
deltaTreasuryNEL = forall era. Lens' (NewEpochState era) (EpochState era)
nesEsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (EpochState era) (LedgerState era)
esLStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (LedgerState era) (CertState era)
lsCertStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (CertState era) (DState era)
certDStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (DState era) InstantaneousRewards
dsIRewardsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' InstantaneousRewards DeltaCoin
deltaTreasuryL
regPools :: Era era => Term era (Map (KeyHash 'StakePool) PoolParams)
regPools :: forall era.
Era era =>
Term era (Map (KeyHash 'StakePool) PoolParams)
regPools = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"regPools" (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Era era => Rep era (KeyHash 'StakePool)
PoolHashR forall era. Era era => Rep era PoolParams
PoolParamsR) (forall era s t. Rep era s -> Lens' s t -> Access era s t
Yes forall era. Era era => Rep era (NewEpochState era)
NewEpochStateR forall era. NELens era (Map (KeyHash 'StakePool) PoolParams)
regPoolsL)
regPoolsL :: NELens era (Map (KeyHash 'StakePool) PoolParams)
regPoolsL :: forall era. NELens era (Map (KeyHash 'StakePool) PoolParams)
regPoolsL = forall era. Lens' (NewEpochState era) (EpochState era)
nesEsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (EpochState era) (LedgerState era)
esLStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (LedgerState era) (CertState era)
lsCertStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (CertState era) (PState era)
certPStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era.
Lens' (PState era) (Map (KeyHash 'StakePool) PoolParams)
psStakePoolParamsL
futureRegPools :: Era era => Term era (Map (KeyHash 'StakePool) PoolParams)
futureRegPools :: forall era.
Era era =>
Term era (Map (KeyHash 'StakePool) PoolParams)
futureRegPools = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"futureRegPools" (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Era era => Rep era (KeyHash 'StakePool)
PoolHashR forall era. Era era => Rep era PoolParams
PoolParamsR) (forall era s t. Rep era s -> Lens' s t -> Access era s t
Yes forall era. Era era => Rep era (NewEpochState era)
NewEpochStateR forall era. NELens era (Map (KeyHash 'StakePool) PoolParams)
futureRegPoolsL)
futureRegPoolsL :: NELens era (Map (KeyHash 'StakePool) PoolParams)
futureRegPoolsL :: forall era. NELens era (Map (KeyHash 'StakePool) PoolParams)
futureRegPoolsL = forall era. Lens' (NewEpochState era) (EpochState era)
nesEsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (EpochState era) (LedgerState era)
esLStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (LedgerState era) (CertState era)
lsCertStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (CertState era) (PState era)
certPStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era.
Lens' (PState era) (Map (KeyHash 'StakePool) PoolParams)
psFutureStakePoolParamsL
retiring :: Era era => Term era (Map (KeyHash 'StakePool) EpochNo)
retiring :: forall era. Era era => Term era (Map (KeyHash 'StakePool) EpochNo)
retiring = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"retiring" (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Era era => Rep era (KeyHash 'StakePool)
PoolHashR forall era. Rep era EpochNo
EpochR) (forall era s t. Rep era s -> Lens' s t -> Access era s t
Yes forall era. Era era => Rep era (NewEpochState era)
NewEpochStateR forall era. NELens era (Map (KeyHash 'StakePool) EpochNo)
retiringL)
retiringL :: NELens era (Map (KeyHash 'StakePool) EpochNo)
retiringL :: forall era. NELens era (Map (KeyHash 'StakePool) EpochNo)
retiringL = forall era. Lens' (NewEpochState era) (EpochState era)
nesEsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (EpochState era) (LedgerState era)
esLStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (LedgerState era) (CertState era)
lsCertStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (CertState era) (PState era)
certPStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (PState era) (Map (KeyHash 'StakePool) EpochNo)
psRetiringL
poolDeposits :: Era era => Term era (Map (KeyHash 'StakePool) Coin)
poolDeposits :: forall era. Era era => Term era (Map (KeyHash 'StakePool) Coin)
poolDeposits = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"poolDeposits" (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Era era => Rep era (KeyHash 'StakePool)
PoolHashR forall era. Rep era Coin
CoinR) (forall era s t. Rep era s -> Lens' s t -> Access era s t
Yes forall era. Era era => Rep era (NewEpochState era)
NewEpochStateR forall era. NELens era (Map (KeyHash 'StakePool) Coin)
poolDepositsL)
poolDepositsL :: NELens era (Map (KeyHash 'StakePool) Coin)
poolDepositsL :: forall era. NELens era (Map (KeyHash 'StakePool) Coin)
poolDepositsL = forall era. Lens' (NewEpochState era) (EpochState era)
nesEsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (EpochState era) (LedgerState era)
esLStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (LedgerState era) (CertState era)
lsCertStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (CertState era) (PState era)
certPStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (PState era) (Map (KeyHash 'StakePool) Coin)
psDepositsL
committeeState ::
Era era =>
Term era (Map (Credential 'ColdCommitteeRole) CommitteeAuthorization)
committeeState :: forall era.
Era era =>
Term
era (Map (Credential 'ColdCommitteeRole) CommitteeAuthorization)
committeeState =
forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$
forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"committeeState" (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Era era => Rep era (Credential 'ColdCommitteeRole)
CommColdCredR forall era. Era era => Rep era CommitteeAuthorization
CommitteeAuthorizationR) (forall era s t. Rep era s -> Lens' s t -> Access era s t
Yes forall era. Era era => Rep era (NewEpochState era)
NewEpochStateR forall era.
NELens
era (Map (Credential 'ColdCommitteeRole) CommitteeAuthorization)
committeeStateL)
committeeStateL ::
NELens era (Map (Credential 'ColdCommitteeRole) CommitteeAuthorization)
committeeStateL :: forall era.
NELens
era (Map (Credential 'ColdCommitteeRole) CommitteeAuthorization)
committeeStateL = forall era. Lens' (NewEpochState era) (EpochState era)
nesEsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (EpochState era) (LedgerState era)
esLStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (LedgerState era) (CertState era)
lsCertStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (CertState era) (VState era)
certVStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (VState era) (CommitteeState era)
vsCommitteeStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era.
Lens'
(CommitteeState era)
(Map (Credential 'ColdCommitteeRole) CommitteeAuthorization)
csCommitteeCredsL
numDormantEpochs :: Era era => Term era EpochNo
numDormantEpochs :: forall era. Era era => Term era EpochNo
numDormantEpochs = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"numDormantEpochs" forall era. Rep era EpochNo
EpochR (forall era s t. Rep era s -> Lens' s t -> Access era s t
Yes forall era. Era era => Rep era (NewEpochState era)
NewEpochStateR forall era. Lens' (NewEpochState era) EpochNo
numDormantEpochsL)
numDormantEpochsL :: NELens era EpochNo
numDormantEpochsL :: forall era. Lens' (NewEpochState era) EpochNo
numDormantEpochsL = forall era. Lens' (NewEpochState era) (EpochState era)
nesEsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (EpochState era) (LedgerState era)
esLStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (LedgerState era) (CertState era)
lsCertStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (CertState era) (VState era)
certVStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (VState era) EpochNo
vsNumDormantEpochsL
utxo :: Era era => Proof era -> Term era (Map TxIn (TxOutF era))
utxo :: forall era.
Era era =>
Proof era -> Term era (Map TxIn (TxOutF era))
utxo Proof era
p = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Proof era -> String -> Rep era t -> Access era s t -> V era t
pV Proof era
p String
"utxo" (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Era era => Rep era TxIn
TxInR (forall era. Era era => Proof era -> Rep era (TxOutF era)
TxOutR Proof era
p)) (forall era s t. Rep era s -> Lens' s t -> Access era s t
Yes forall era. Era era => Rep era (NewEpochState era)
NewEpochStateR (forall era. Proof era -> NELens era (Map TxIn (TxOutF era))
utxoL Proof era
p))
utxoL :: Proof era -> NELens era (Map TxIn (TxOutF era))
utxoL :: forall era. Proof era -> NELens era (Map TxIn (TxOutF era))
utxoL Proof era
proof = forall era. Lens' (NewEpochState era) (EpochState era)
nesEsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (EpochState era) (LedgerState era)
esLStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (LedgerState era) (UTxOState era)
lsUTxOStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (UTxOState era) (UTxO era)
utxosUtxoL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Proof era -> Lens' (UTxO era) (Map TxIn (TxOutF era))
unUtxoL Proof era
proof
unUtxoL :: Proof era -> Lens' (UTxO era) (Map TxIn (TxOutF era))
unUtxoL :: forall era. Proof era -> Lens' (UTxO era) (Map TxIn (TxOutF era))
unUtxoL Proof era
p = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens (forall a b k. (a -> b) -> Map k a -> Map k b
Map.map (forall era. Proof era -> TxOut era -> TxOutF era
TxOutF Proof era
p) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. UTxO era -> Map TxIn (TxOut era)
unUTxO) (\(UTxO Map TxIn (TxOut era)
_) Map TxIn (TxOutF era)
new -> forall era. Map TxIn (TxOutF era) -> UTxO era
liftUTxO Map TxIn (TxOutF era)
new)
deposits :: Era era => Term era Coin
deposits :: forall era. Era era => Term era Coin
deposits = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"deposits" forall era. Rep era Coin
CoinR (forall era s t. Rep era s -> Lens' s t -> Access era s t
Yes forall era. Era era => Rep era (NewEpochState era)
NewEpochStateR forall era. NELens era Coin
depositsL)
depositsL :: NELens era Coin
depositsL :: forall era. NELens era Coin
depositsL = forall era. Lens' (NewEpochState era) (EpochState era)
nesEsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (EpochState era) (LedgerState era)
esLStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (LedgerState era) (UTxOState era)
lsUTxOStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (UTxOState era) Coin
utxosDepositedL
fees :: Era era => Term era Coin
fees :: forall era. Era era => Term era Coin
fees = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"fees" forall era. Rep era Coin
CoinR (forall era s t. Rep era s -> Lens' s t -> Access era s t
Yes forall era. Era era => Rep era (NewEpochState era)
NewEpochStateR forall era. NELens era Coin
feesL)
feesL :: NELens era Coin
feesL :: forall era. NELens era Coin
feesL = forall era. Lens' (NewEpochState era) (EpochState era)
nesEsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (EpochState era) (LedgerState era)
esLStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (LedgerState era) (UTxOState era)
lsUTxOStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (UTxOState era) Coin
utxosFeesL
donation :: Era era => Term era Coin
donation :: forall era. Era era => Term era Coin
donation = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"donation" forall era. Rep era Coin
CoinR (forall era s t. Rep era s -> Lens' s t -> Access era s t
Yes forall era. Era era => Rep era (NewEpochState era)
NewEpochStateR forall era. NELens era Coin
donationL)
donationL :: NELens era Coin
donationL :: forall era. NELens era Coin
donationL = forall era. Lens' (NewEpochState era) (EpochState era)
nesEsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (EpochState era) (LedgerState era)
esLStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (LedgerState era) (UTxOState era)
lsUTxOStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (UTxOState era) Coin
utxosDonationL
ppup :: Era era => Proof era -> Term era (ShelleyGovState era)
ppup :: forall era. Era era => Proof era -> Term era (ShelleyGovState era)
ppup Proof era
p = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Proof era -> String -> Rep era t -> Access era s t -> V era t
pV Proof era
p String
"ppup" (forall era. Era era => Proof era -> Rep era (ShelleyGovState era)
PPUPStateR Proof era
p) (forall era s t. Rep era s -> Lens' s t -> Access era s t
Yes forall era. Era era => Rep era (NewEpochState era)
NewEpochStateR (forall era. Proof era -> NELens era (ShelleyGovState era)
ppupsL Proof era
p))
ppupsL :: Proof era -> NELens era (ShelleyGovState era)
ppupsL :: forall era. Proof era -> NELens era (ShelleyGovState era)
ppupsL Proof era
Shelley = forall era. Lens' (NewEpochState era) (EpochState era)
nesEsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (EpochState era) (LedgerState era)
esLStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (LedgerState era) (UTxOState era)
lsUTxOStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (UTxOState era) (GovState era)
utxosGovStateL
ppupsL Proof era
Allegra = forall era. Lens' (NewEpochState era) (EpochState era)
nesEsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (EpochState era) (LedgerState era)
esLStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (LedgerState era) (UTxOState era)
lsUTxOStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (UTxOState era) (GovState era)
utxosGovStateL
ppupsL Proof era
Mary = forall era. Lens' (NewEpochState era) (EpochState era)
nesEsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (EpochState era) (LedgerState era)
esLStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (LedgerState era) (UTxOState era)
lsUTxOStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (UTxOState era) (GovState era)
utxosGovStateL
ppupsL Proof era
Alonzo = forall era. Lens' (NewEpochState era) (EpochState era)
nesEsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (EpochState era) (LedgerState era)
esLStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (LedgerState era) (UTxOState era)
lsUTxOStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (UTxOState era) (GovState era)
utxosGovStateL
ppupsL Proof era
Babbage = forall era. Lens' (NewEpochState era) (EpochState era)
nesEsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (EpochState era) (LedgerState era)
esLStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (LedgerState era) (UTxOState era)
lsUTxOStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (UTxOState era) (GovState era)
utxosGovStateL
ppupsL Proof era
Conway = forall a. HasCallStack => String -> a
error String
"Conway era does not have a PPUPState, in ppupsL"
pparamProposals ::
Era era => Proof era -> Term era (Map (KeyHash 'Genesis) (PParamsUpdateF era))
pparamProposals :: forall era.
Era era =>
Proof era -> Term era (Map (KeyHash 'Genesis) (PParamsUpdateF era))
pparamProposals Proof era
p = forall era t. V era t -> Term era t
Var (forall era t s.
Proof era -> String -> Rep era t -> Access era s t -> V era t
pV Proof era
p String
"pparamProposals" (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Era era => Rep era (KeyHash 'Genesis)
GenHashR (forall era. Era era => Proof era -> Rep era (PParamsUpdateF era)
PParamsUpdateR Proof era
p)) forall era s t. Access era s t
No)
futurePParamProposals ::
Era era => Proof era -> Term era (Map (KeyHash 'Genesis) (PParamsUpdateF era))
futurePParamProposals :: forall era.
Era era =>
Proof era -> Term era (Map (KeyHash 'Genesis) (PParamsUpdateF era))
futurePParamProposals Proof era
p = forall era t. V era t -> Term era t
Var (forall era t s.
Proof era -> String -> Rep era t -> Access era s t -> V era t
pV Proof era
p String
"futurePParamProposals" (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Era era => Rep era (KeyHash 'Genesis)
GenHashR (forall era. Era era => Proof era -> Rep era (PParamsUpdateF era)
PParamsUpdateR Proof era
p)) forall era s t. Access era s t
No)
currPParams :: Era era => Proof era -> Term era (PParamsF era)
currPParams :: forall era. Era era => Proof era -> Term era (PParamsF era)
currPParams Proof era
p = forall era t. V era t -> Term era t
Var (forall era t s.
Proof era -> String -> Rep era t -> Access era s t -> V era t
pV Proof era
p String
"currPParams" (forall era. Era era => Proof era -> Rep era (PParamsF era)
PParamsR Proof era
p) forall era s t. Access era s t
No)
futurePParams :: Era era => Proof era -> Term era (FuturePParams era)
futurePParams :: forall era. Era era => Proof era -> Term era (FuturePParams era)
futurePParams Proof era
p = forall era t. V era t -> Term era t
Var (forall era t s.
Proof era -> String -> Rep era t -> Access era s t -> V era t
pV Proof era
p String
"futurePParams" (forall era. Era era => Proof era -> Rep era (FuturePParams era)
FuturePParamsR Proof era
p) forall era s t. Access era s t
No)
prevPParams :: Gov.EraGov era => Proof era -> Term era (PParamsF era)
prevPParams :: forall era. EraGov era => Proof era -> Term era (PParamsF era)
prevPParams Proof era
p =
forall era t. V era t -> Term era t
Var (forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"prevPParams" (forall era. Era era => Proof era -> Rep era (PParamsF era)
PParamsR Proof era
p) (forall era s t. Rep era s -> Lens' s t -> Access era s t
Yes forall era. Era era => Rep era (NewEpochState era)
NewEpochStateR (forall era. Lens' (NewEpochState era) (EpochState era)
nesEsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. EraGov era => Lens' (EpochState era) (PParams era)
prevPParamsEpochStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Proof era -> Lens' (PParams era) (PParamsF era)
ppFL Proof era
p)))
ppupStateT ::
forall era.
( Gov.GovState era ~ ShelleyGovState era
, Gov.EraGov era
) =>
Proof era ->
RootTarget era (ShelleyGovState era) (ShelleyGovState era)
ppupStateT :: forall era.
(GovState era ~ ShelleyGovState era, EraGov era) =>
Proof era
-> RootTarget era (ShelleyGovState era) (ShelleyGovState era)
ppupStateT Proof era
p =
forall root a b era.
String -> TypeRep root -> (a -> b) -> RootTarget era root (a -> b)
Invert String
"PPUPState" (forall {k} (a :: k). Typeable a => TypeRep a
typeRep @(ShelleyGovState era)) forall {era}.
Map (KeyHash 'Genesis) (PParamsUpdateF era)
-> Map (KeyHash 'Genesis) (PParamsUpdateF era)
-> PParamsF era
-> PParamsF era
-> FuturePParams era
-> ShelleyGovState era
ppupfun
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed (forall era.
Era era =>
Proof era -> Term era (Map (KeyHash 'Genesis) (PParamsUpdateF era))
pparamProposals Proof era
p) (forall era. Lens' (ShelleyGovState era) (ProposedPPUpdates era)
proposalsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era.
Proof era
-> Lens'
(ProposedPPUpdates era)
(Map (KeyHash 'Genesis) (PParamsUpdateF era))
proposedMapL Proof era
p)
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed (forall era.
Era era =>
Proof era -> Term era (Map (KeyHash 'Genesis) (PParamsUpdateF era))
futurePParamProposals Proof era
p) (forall era. Lens' (ShelleyGovState era) (ProposedPPUpdates era)
futureProposalsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era.
Proof era
-> Lens'
(ProposedPPUpdates era)
(Map (KeyHash 'Genesis) (PParamsUpdateF era))
proposedMapL Proof era
p)
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed (forall era. Era era => Proof era -> Term era (PParamsF era)
currPParams Proof era
p) (forall era. EraGov era => Lens' (GovState era) (PParams era)
Gov.curPParamsGovStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Proof era -> Lens' (PParams era) (PParamsF era)
pparamsFL Proof era
p)
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed (forall era. EraGov era => Proof era -> Term era (PParamsF era)
prevPParams Proof era
p) (forall era. EraGov era => Lens' (GovState era) (PParams era)
Gov.prevPParamsGovStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Proof era -> Lens' (PParams era) (PParamsF era)
pparamsFL Proof era
p)
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed (forall era. Era era => Proof era -> Term era (FuturePParams era)
futurePParams Proof era
p) (forall era. EraGov era => Lens' (GovState era) (FuturePParams era)
Gov.futurePParamsGovStateL)
where
ppupfun :: Map (KeyHash 'Genesis) (PParamsUpdateF era)
-> Map (KeyHash 'Genesis) (PParamsUpdateF era)
-> PParamsF era
-> PParamsF era
-> FuturePParams era
-> ShelleyGovState era
ppupfun Map (KeyHash 'Genesis) (PParamsUpdateF era)
x Map (KeyHash 'Genesis) (PParamsUpdateF era)
y (PParamsF Proof era
_ PParams era
pp) (PParamsF Proof era
_ PParams era
prev) FuturePParams era
z =
forall era.
ProposedPPUpdates era
-> ProposedPPUpdates era
-> PParams era
-> PParams era
-> FuturePParams era
-> ShelleyGovState era
ShelleyGovState
(forall era.
Map (KeyHash 'Genesis) (PParamsUpdate era) -> ProposedPPUpdates era
ProposedPPUpdates (forall a b k. (a -> b) -> Map k a -> Map k b
Map.map forall era. PParamsUpdateF era -> PParamsUpdate era
unPParamsUpdate Map (KeyHash 'Genesis) (PParamsUpdateF era)
x))
(forall era.
Map (KeyHash 'Genesis) (PParamsUpdate era) -> ProposedPPUpdates era
ProposedPPUpdates (forall a b k. (a -> b) -> Map k a -> Map k b
Map.map forall era. PParamsUpdateF era -> PParamsUpdate era
unPParamsUpdate Map (KeyHash 'Genesis) (PParamsUpdateF era)
y))
PParams era
pp
PParams era
prev
FuturePParams era
z
govL :: Lens' (GovState era) (Gov.GovState era)
govL :: forall era. Lens' (GovState era) (GovState era)
govL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall era. GovState era -> GovState era
f forall era. GovState era -> GovState era -> GovState era
g
where
f :: GovState era -> Gov.GovState era
f :: forall era. GovState era -> GovState era
f (GovState Proof era
Shelley GovState era
x) = GovState era
x
f (GovState Proof era
Allegra GovState era
x) = GovState era
x
f (GovState Proof era
Mary GovState era
x) = GovState era
x
f (GovState Proof era
Alonzo GovState era
x) = GovState era
x
f (GovState Proof era
Babbage GovState era
x) = GovState era
x
f (GovState Proof era
Conway GovState era
x) = GovState era
x
g :: GovState era -> Gov.GovState era -> GovState era
g :: forall era. GovState era -> GovState era -> GovState era
g (GovState p :: Proof era
p@Proof era
Shelley GovState era
_) GovState era
y = forall era. Proof era -> GovState era -> GovState era
GovState Proof era
p GovState era
y
g (GovState p :: Proof era
p@Proof era
Allegra GovState era
_) GovState era
y = forall era. Proof era -> GovState era -> GovState era
GovState Proof era
p GovState era
y
g (GovState p :: Proof era
p@Proof era
Mary GovState era
_) GovState era
y = forall era. Proof era -> GovState era -> GovState era
GovState Proof era
p GovState era
y
g (GovState p :: Proof era
p@Proof era
Alonzo GovState era
_) GovState era
y = forall era. Proof era -> GovState era -> GovState era
GovState Proof era
p GovState era
y
g (GovState p :: Proof era
p@Proof era
Babbage GovState era
_) GovState era
y = forall era. Proof era -> GovState era -> GovState era
GovState Proof era
p GovState era
y
g (GovState p :: Proof era
p@Proof era
Conway GovState era
_) GovState era
y = forall era. Proof era -> GovState era -> GovState era
GovState Proof era
p GovState era
y
govStateT :: forall era. Era era => Proof era -> RootTarget era (GovState era) (GovState era)
govStateT :: forall era.
Era era =>
Proof era -> RootTarget era (GovState era) (GovState era)
govStateT p :: Proof era
p@Proof era
Shelley = forall root a b era.
String -> TypeRep root -> (a -> b) -> RootTarget era root (a -> b)
Invert String
"GovState" (forall {k} (a :: k). Typeable a => TypeRep a
typeRep @(GovState era)) (forall era. Proof era -> GovState era -> GovState era
GovState Proof era
p) forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era root2 t root.
RootTarget era root2 t -> Lens' root root2 -> RootTarget era root t
Shift (forall era.
(GovState era ~ ShelleyGovState era, EraGov era) =>
Proof era
-> RootTarget era (ShelleyGovState era) (ShelleyGovState era)
ppupStateT Proof era
p) forall era. Lens' (GovState era) (GovState era)
govL
govStateT p :: Proof era
p@Proof era
Allegra = forall root a b era.
String -> TypeRep root -> (a -> b) -> RootTarget era root (a -> b)
Invert String
"GovState" (forall {k} (a :: k). Typeable a => TypeRep a
typeRep @(GovState era)) (forall era. Proof era -> GovState era -> GovState era
GovState Proof era
p) forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era root2 t root.
RootTarget era root2 t -> Lens' root root2 -> RootTarget era root t
Shift (forall era.
(GovState era ~ ShelleyGovState era, EraGov era) =>
Proof era
-> RootTarget era (ShelleyGovState era) (ShelleyGovState era)
ppupStateT Proof era
p) forall era. Lens' (GovState era) (GovState era)
govL
govStateT p :: Proof era
p@Proof era
Mary = forall root a b era.
String -> TypeRep root -> (a -> b) -> RootTarget era root (a -> b)
Invert String
"GovState" (forall {k} (a :: k). Typeable a => TypeRep a
typeRep @(GovState era)) (forall era. Proof era -> GovState era -> GovState era
GovState Proof era
p) forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era root2 t root.
RootTarget era root2 t -> Lens' root root2 -> RootTarget era root t
Shift (forall era.
(GovState era ~ ShelleyGovState era, EraGov era) =>
Proof era
-> RootTarget era (ShelleyGovState era) (ShelleyGovState era)
ppupStateT Proof era
p) forall era. Lens' (GovState era) (GovState era)
govL
govStateT p :: Proof era
p@Proof era
Alonzo = forall root a b era.
String -> TypeRep root -> (a -> b) -> RootTarget era root (a -> b)
Invert String
"GovState" (forall {k} (a :: k). Typeable a => TypeRep a
typeRep @(GovState era)) (forall era. Proof era -> GovState era -> GovState era
GovState Proof era
p) forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era root2 t root.
RootTarget era root2 t -> Lens' root root2 -> RootTarget era root t
Shift (forall era.
(GovState era ~ ShelleyGovState era, EraGov era) =>
Proof era
-> RootTarget era (ShelleyGovState era) (ShelleyGovState era)
ppupStateT Proof era
p) forall era. Lens' (GovState era) (GovState era)
govL
govStateT p :: Proof era
p@Proof era
Babbage = forall root a b era.
String -> TypeRep root -> (a -> b) -> RootTarget era root (a -> b)
Invert String
"GovState" (forall {k} (a :: k). Typeable a => TypeRep a
typeRep @(GovState era)) (forall era. Proof era -> GovState era -> GovState era
GovState Proof era
p) forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era root2 t root.
RootTarget era root2 t -> Lens' root root2 -> RootTarget era root t
Shift (forall era.
(GovState era ~ ShelleyGovState era, EraGov era) =>
Proof era
-> RootTarget era (ShelleyGovState era) (ShelleyGovState era)
ppupStateT Proof era
p) forall era. Lens' (GovState era) (GovState era)
govL
govStateT p :: Proof era
p@Proof era
Conway =
forall root a b era.
String -> TypeRep root -> (a -> b) -> RootTarget era root (a -> b)
Invert String
"GovState" (forall {k} (a :: k). Typeable a => TypeRep a
typeRep @(GovState era)) (forall era. Proof era -> GovState era -> GovState era
GovState Proof era
p) forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era root2 t root.
RootTarget era root2 t -> Lens' root root2 -> RootTarget era root t
Shift (forall era a. (Reflect era => Proof era -> a) -> Proof era -> a
unReflect forall era.
(RunConwayRatify era, Reflect era) =>
Proof era
-> RootTarget era (ConwayGovState era) (ConwayGovState era)
conwayGovStateT Proof era
p) forall era. Lens' (GovState era) (GovState era)
govL
individualPoolStakeL :: Lens' IndividualPoolStake Rational
individualPoolStakeL :: Lens' IndividualPoolStake Rational
individualPoolStakeL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens IndividualPoolStake -> Rational
individualPoolStake (\IndividualPoolStake
ds Rational
u -> IndividualPoolStake
ds {individualPoolStake :: Rational
individualPoolStake = Rational
u})
isPtrMapT :: Era era => Term era (Map Ptr Coin)
isPtrMapT :: forall era. Era era => Term era (Map Ptr Coin)
isPtrMapT = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"ptrMap" (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Rep era Ptr
PtrR forall era. Rep era Coin
CoinR) (forall era s t. Rep era s -> Lens' s t -> Access era s t
Yes forall era. Era era => Rep era (NewEpochState era)
NewEpochStateR forall era. Lens' (NewEpochState era) (Map Ptr Coin)
ptrMapL)
ptrMapL :: Lens' (NewEpochState era) (Map Ptr Coin)
ptrMapL :: forall era. Lens' (NewEpochState era) (Map Ptr Coin)
ptrMapL = forall era. Lens' (NewEpochState era) (EpochState era)
nesEsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (EpochState era) (LedgerState era)
esLStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (LedgerState era) (UTxOState era)
lsUTxOStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (UTxOState era) IncrementalStake
utxosStakeDistrL forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' IncrementalStake (Map Ptr Coin)
isPtrMapL
isCredMapT :: Era era => Term era (Map (Credential 'Staking) Coin)
isCredMapT :: forall era. Era era => Term era (Map (Credential 'Staking) Coin)
isCredMapT = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"credMap" (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Era era => Rep era (Credential 'Staking)
CredR forall era. Rep era Coin
CoinR) (forall era s t. Rep era s -> Lens' s t -> Access era s t
Yes forall era. Era era => Rep era (NewEpochState era)
NewEpochStateR forall era. NELens era (Map (Credential 'Staking) Coin)
credMapL)
credMapL :: Lens' (NewEpochState era) (Map (Credential 'Staking) Coin)
credMapL :: forall era. NELens era (Map (Credential 'Staking) Coin)
credMapL = forall era. Lens' (NewEpochState era) (EpochState era)
nesEsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (EpochState era) (LedgerState era)
esLStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (LedgerState era) (UTxOState era)
lsUTxOStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (UTxOState era) IncrementalStake
utxosStakeDistrL forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' IncrementalStake (Map (Credential 'Staking) Coin)
isCredMapL
incrementalStake :: Era era => Term era (Map (Credential 'Staking) Coin)
incrementalStake :: forall era. Era era => Term era (Map (Credential 'Staking) Coin)
incrementalStake = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"incrementalStake" (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Era era => Rep era (Credential 'Staking)
CredR forall era. Rep era Coin
CoinR) forall era s t. Access era s t
No
incrementalStakeT ::
Reflect era => Proof era -> Target era (Map (Credential 'Staking) Coin)
incrementalStakeT :: forall era.
Reflect era =>
Proof era -> Target era (Map (Credential 'Staking) Coin)
incrementalStakeT Proof era
proof = forall a b era. String -> (a -> b) -> RootTarget era Void (a -> b)
Constr String
"computeIncrementalStake" Map TxIn (TxOutF era) -> Map (Credential 'Staking) Coin
get forall era a t. Target era (a -> t) -> Term era a -> Target era t
^$ (forall era.
Era era =>
Proof era -> Term era (Map TxIn (TxOutF era))
utxo Proof era
proof)
where
get :: Map TxIn (TxOutF era) -> Map (Credential 'Staking) Coin
get Map TxIn (TxOutF era)
utxom =
let IStake Map (Credential 'Staking) (CompactForm Coin)
stakeDistr Map Ptr (CompactForm Coin)
_ = forall era.
EraTxOut era =>
PParams era
-> IncrementalStake -> UTxO era -> UTxO era -> IncrementalStake
updateStakeDistribution (forall era. Reflect era => Proof era -> PParams era
justProtocolVersion Proof era
proof) forall a. Monoid a => a
mempty forall a. Monoid a => a
mempty (forall era. Map TxIn (TxOutF era) -> UTxO era
liftUTxO Map TxIn (TxOutF era)
utxom)
in forall a b k. (a -> b) -> Map k a -> Map k b
Map.map forall a. Compactible a => CompactForm a -> a
fromCompact Map (Credential 'Staking) (CompactForm Coin)
stakeDistr
treasury :: Era era => Term era Coin
treasury :: forall era. Era era => Term era Coin
treasury = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"treasury" forall era. Rep era Coin
CoinR (forall era s t. Rep era s -> Lens' s t -> Access era s t
Yes forall era. Era era => Rep era (NewEpochState era)
NewEpochStateR forall era. NELens era Coin
treasuryL)
treasuryL :: NELens era Coin
treasuryL :: forall era. NELens era Coin
treasuryL = forall era. Lens' (NewEpochState era) (EpochState era)
nesEsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (EpochState era) AccountState
esAccountStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' AccountState Coin
asTreasuryL
reserves :: Era era => Term era Coin
reserves :: forall era. Era era => Term era Coin
reserves = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"reserves" forall era. Rep era Coin
CoinR (forall era s t. Rep era s -> Lens' s t -> Access era s t
Yes forall era. Era era => Rep era (NewEpochState era)
NewEpochStateR forall era. NELens era Coin
reservesL)
reservesL :: NELens era Coin
reservesL :: forall era. NELens era Coin
reservesL = forall era. Lens' (NewEpochState era) (EpochState era)
nesEsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (EpochState era) AccountState
esAccountStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' AccountState Coin
asReservesL
mirAvailTreasury :: Era era => Term era Coin
mirAvailTreasury :: forall era. Era era => Term era Coin
mirAvailTreasury = forall era t. V era t -> Term era t
Var (forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"mirAvailTreasury" forall era. Rep era Coin
CoinR forall era s t. Access era s t
No)
mirAvailReserves :: Era era => Term era Coin
mirAvailReserves :: forall era. Era era => Term era Coin
mirAvailReserves = forall era t. V era t -> Term era t
Var (forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"mirAvailReserves" forall era. Rep era Coin
CoinR forall era s t. Access era s t
No)
snapshots :: Era era => Term era SnapShots
snapshots :: forall era. Era era => Term era SnapShots
snapshots = forall era t. V era t -> Term era t
Var (forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"snapshots" forall era. Era era => Rep era SnapShots
SnapShotsR (forall era s t. Rep era s -> Lens' s t -> Access era s t
Yes forall era. Era era => Rep era (NewEpochState era)
NewEpochStateR forall era. NELens era SnapShots
snapshotsL))
snapshotsL :: NELens era SnapShots
snapshotsL :: forall era. NELens era SnapShots
snapshotsL = forall era. Lens' (NewEpochState era) (EpochState era)
nesEsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (EpochState era) SnapShots
esSnapshotsL
ppFL :: Proof era -> Lens' (PParams era) (PParamsF era)
ppFL :: forall era. Proof era -> Lens' (PParams era) (PParamsF era)
ppFL Proof era
p = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens (\PParams era
pp -> forall era. Proof era -> PParams era -> PParamsF era
PParamsF Proof era
p PParams era
pp) (\PParams era
_ (PParamsF Proof era
_ PParams era
qq) -> PParams era
qq)
pparamsVar :: Gov.EraGov era => Proof era -> V era (PParamsF era)
pparamsVar :: forall era. EraGov era => Proof era -> V era (PParamsF era)
pparamsVar Proof era
p = (forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"pparams" (forall era. Era era => Proof era -> Rep era (PParamsF era)
PParamsR Proof era
p) (forall era s t. Rep era s -> Lens' s t -> Access era s t
Yes forall era. Era era => Rep era (NewEpochState era)
NewEpochStateR (forall era. Lens' (NewEpochState era) (EpochState era)
nesEsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. EraGov era => Lens' (EpochState era) (PParams era)
curPParamsEpochStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Proof era -> Lens' (PParams era) (PParamsF era)
ppFL Proof era
p)))
pparams :: Gov.EraGov era => Proof era -> Term era (PParamsF era)
pparams :: forall era. EraGov era => Proof era -> Term era (PParamsF era)
pparams Proof era
p = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era. EraGov era => Proof era -> V era (PParamsF era)
pparamsVar Proof era
p
nmLikelihoodsT :: Era era => Term era (Map (KeyHash 'StakePool) [Float])
nmLikelihoodsT :: forall era. Era era => Term era (Map (KeyHash 'StakePool) [Float])
nmLikelihoodsT =
forall era t. V era t -> Term era t
Var
( forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V
String
"likelihoodsNM"
(forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Era era => Rep era (KeyHash 'StakePool)
PoolHashR (forall era a. Rep era a -> Rep era [a]
ListR forall era. Rep era Float
FloatR))
(forall era s t. Rep era s -> Lens' s t -> Access era s t
Yes forall era. Era era => Rep era (NewEpochState era)
NewEpochStateR (forall era. Lens' (NewEpochState era) (EpochState era)
nesEsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (EpochState era) NonMyopic
esNonMyopicL forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' NonMyopic (Map (KeyHash 'StakePool) [Float])
nmLikelihoodsL))
)
nmRewardPotT :: Era era => Term era Coin
nmRewardPotT :: forall era. Era era => Term era Coin
nmRewardPotT = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"rewardPotNM" forall era. Rep era Coin
CoinR (forall era s t. Rep era s -> Lens' s t -> Access era s t
Yes forall era. Era era => Rep era (NewEpochState era)
NewEpochStateR (forall era. Lens' (NewEpochState era) (EpochState era)
nesEsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (EpochState era) NonMyopic
esNonMyopicL forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' NonMyopic Coin
nmRewardPotL))
stakeL :: Lens' Stake (Map (Credential 'Staking) Coin)
stakeL :: Lens' Stake (Map (Credential 'Staking) Coin)
stakeL =
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens
(forall a b k. (a -> b) -> Map k a -> Map k b
Map.map forall a. Compactible a => CompactForm a -> a
fromCompact forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (kv :: * -> *) k (vv :: * -> *) v.
(Vector kv k, Vector vv v) =>
VMap kv vv k v -> Map k v
VMap.toMap forall b c a. (b -> c) -> (a -> b) -> a -> c
. Stake -> VMap VB VP (Credential 'Staking) (CompactForm Coin)
unStake)
(\Stake
_ Map (Credential 'Staking) Coin
u -> VMap VB VP (Credential 'Staking) (CompactForm Coin) -> Stake
Stake forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (kv :: * -> *) k (vv :: * -> *) v.
(Vector kv k, Vector vv v) =>
Map k v -> VMap kv vv k v
VMap.fromMap forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b k. (a -> b) -> Map k a -> Map k b
Map.map HasCallStack => Coin -> CompactForm Coin
compactCoinOrError forall a b. (a -> b) -> a -> b
$ Map (Credential 'Staking) Coin
u)
vmapL :: Lens' (VMap.VMap VMap.VB VMap.VB k v) (Map k v)
vmapL :: forall k v. Lens' (VMap VB VB k v) (Map k v)
vmapL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall (kv :: * -> *) k (vv :: * -> *) v.
(Vector kv k, Vector vv v) =>
VMap kv vv k v -> Map k v
VMap.toMap (\VMap VB VB k v
_ Map k v
u -> forall (kv :: * -> *) k (vv :: * -> *) v.
(Vector kv k, Vector vv v) =>
Map k v -> VMap kv vv k v
VMap.fromMap Map k v
u)
markStakeL :: NELens era (Map (Credential 'Staking) Coin)
markStakeL :: forall era. NELens era (Map (Credential 'Staking) Coin)
markStakeL = forall era. Lens' (NewEpochState era) (EpochState era)
nesEsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (EpochState era) SnapShots
esSnapshotsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' SnapShots SnapShot
ssStakeMarkL forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' SnapShot Stake
ssStakeL forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' Stake (Map (Credential 'Staking) Coin)
stakeL
markStake :: Era era => Term era (Map (Credential 'Staking) Coin)
markStake :: forall era. Era era => Term era (Map (Credential 'Staking) Coin)
markStake = forall era t. V era t -> Term era t
Var (forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"markStake" (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Era era => Rep era (Credential 'Staking)
CredR forall era. Rep era Coin
CoinR) (forall era s t. Rep era s -> Lens' s t -> Access era s t
Yes forall era. Era era => Rep era (NewEpochState era)
NewEpochStateR forall era. NELens era (Map (Credential 'Staking) Coin)
markStakeL))
markDelegs ::
Era era => Term era (Map (Credential 'Staking) (KeyHash 'StakePool))
markDelegs :: forall era.
Era era =>
Term era (Map (Credential 'Staking) (KeyHash 'StakePool))
markDelegs = forall era t. V era t -> Term era t
Var (forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"markDelegs" (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Era era => Rep era (Credential 'Staking)
CredR forall era. Era era => Rep era (KeyHash 'StakePool)
PoolHashR) (forall era s t. Rep era s -> Lens' s t -> Access era s t
Yes forall era. Era era => Rep era (NewEpochState era)
NewEpochStateR forall era.
NELens era (Map (Credential 'Staking) (KeyHash 'StakePool))
markDelegsL))
markDelegsL ::
NELens era (Map (Credential 'Staking) (KeyHash 'StakePool))
markDelegsL :: forall era.
NELens era (Map (Credential 'Staking) (KeyHash 'StakePool))
markDelegsL = forall era. Lens' (NewEpochState era) (EpochState era)
nesEsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (EpochState era) SnapShots
esSnapshotsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' SnapShots SnapShot
ssStakeMarkL forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens'
SnapShot (VMap VB VB (Credential 'Staking) (KeyHash 'StakePool))
ssDelegationsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k v. Lens' (VMap VB VB k v) (Map k v)
vmapL
markPools ::
Era era => Term era (Map (KeyHash 'StakePool) PoolParams)
markPools :: forall era.
Era era =>
Term era (Map (KeyHash 'StakePool) PoolParams)
markPools = forall era t. V era t -> Term era t
Var (forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"markPools" (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Era era => Rep era (KeyHash 'StakePool)
PoolHashR forall era. Era era => Rep era PoolParams
PoolParamsR) (forall era s t. Rep era s -> Lens' s t -> Access era s t
Yes forall era. Era era => Rep era (NewEpochState era)
NewEpochStateR forall era. NELens era (Map (KeyHash 'StakePool) PoolParams)
markPoolsL))
markPoolsL :: NELens era (Map (KeyHash 'StakePool) PoolParams)
markPoolsL :: forall era. NELens era (Map (KeyHash 'StakePool) PoolParams)
markPoolsL = forall era. Lens' (NewEpochState era) (EpochState era)
nesEsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (EpochState era) SnapShots
esSnapshotsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' SnapShots SnapShot
ssStakeMarkL forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' SnapShot (VMap VB VB (KeyHash 'StakePool) PoolParams)
ssPoolParamsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k v. Lens' (VMap VB VB k v) (Map k v)
vmapL
markSnapShotT ::
forall era. Era era => RootTarget era SnapShot SnapShot
markSnapShotT :: forall era. Era era => RootTarget era SnapShot SnapShot
markSnapShotT =
forall root a b era.
String -> TypeRep root -> (a -> b) -> RootTarget era root (a -> b)
Invert String
"SnapShot" (forall {k} (a :: k). Typeable a => TypeRep a
typeRep @SnapShot) Map (Credential 'Staking) Coin
-> Map (Credential 'Staking) (KeyHash 'StakePool)
-> Map (KeyHash 'StakePool) PoolParams
-> SnapShot
snapfun
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed forall era. Era era => Term era (Map (Credential 'Staking) Coin)
markStake (Lens' SnapShot Stake
ssStakeL forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' Stake (Map (Credential 'Staking) Coin)
stakeL)
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed forall era.
Era era =>
Term era (Map (Credential 'Staking) (KeyHash 'StakePool))
markDelegs (Lens'
SnapShot (VMap VB VB (Credential 'Staking) (KeyHash 'StakePool))
ssDelegationsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k v. Lens' (VMap VB VB k v) (Map k v)
vmapL)
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed forall era.
Era era =>
Term era (Map (KeyHash 'StakePool) PoolParams)
markPools (Lens' SnapShot (VMap VB VB (KeyHash 'StakePool) PoolParams)
ssPoolParamsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k v. Lens' (VMap VB VB k v) (Map k v)
vmapL)
where
snapfun :: Map (Credential 'Staking) Coin
-> Map (Credential 'Staking) (KeyHash 'StakePool)
-> Map (KeyHash 'StakePool) PoolParams
-> SnapShot
snapfun Map (Credential 'Staking) Coin
x Map (Credential 'Staking) (KeyHash 'StakePool)
y Map (KeyHash 'StakePool) PoolParams
z =
Stake
-> VMap VB VB (Credential 'Staking) (KeyHash 'StakePool)
-> VMap VB VB (KeyHash 'StakePool) PoolParams
-> SnapShot
SnapShot
(VMap VB VP (Credential 'Staking) (CompactForm Coin) -> Stake
Stake (forall (kv :: * -> *) k (vv :: * -> *) v.
(Vector kv k, Vector vv v) =>
Map k v -> VMap kv vv k v
VMap.fromMap (forall a b k. (a -> b) -> Map k a -> Map k b
Map.map HasCallStack => Coin -> CompactForm Coin
compactCoinOrError Map (Credential 'Staking) Coin
x)))
(forall (kv :: * -> *) k (vv :: * -> *) v.
(Vector kv k, Vector vv v) =>
Map k v -> VMap kv vv k v
VMap.fromMap Map (Credential 'Staking) (KeyHash 'StakePool)
y)
(forall (kv :: * -> *) k (vv :: * -> *) v.
(Vector kv k, Vector vv v) =>
Map k v -> VMap kv vv k v
VMap.fromMap Map (KeyHash 'StakePool) PoolParams
z)
setStake :: Era era => Term era (Map (Credential 'Staking) Coin)
setStake :: forall era. Era era => Term era (Map (Credential 'Staking) Coin)
setStake = forall era t. V era t -> Term era t
Var (forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"setStake" (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Era era => Rep era (Credential 'Staking)
CredR forall era. Rep era Coin
CoinR) (forall era s t. Rep era s -> Lens' s t -> Access era s t
Yes forall era. Era era => Rep era (NewEpochState era)
NewEpochStateR forall era. NELens era (Map (Credential 'Staking) Coin)
setStakeL))
setStakeL :: NELens era (Map (Credential 'Staking) Coin)
setStakeL :: forall era. NELens era (Map (Credential 'Staking) Coin)
setStakeL = forall era. Lens' (NewEpochState era) (EpochState era)
nesEsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (EpochState era) SnapShots
esSnapshotsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' SnapShots SnapShot
ssStakeSetL forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' SnapShot Stake
ssStakeL forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' Stake (Map (Credential 'Staking) Coin)
stakeL
setDelegs ::
Era era => Term era (Map (Credential 'Staking) (KeyHash 'StakePool))
setDelegs :: forall era.
Era era =>
Term era (Map (Credential 'Staking) (KeyHash 'StakePool))
setDelegs = forall era t. V era t -> Term era t
Var (forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"setDelegs" (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Era era => Rep era (Credential 'Staking)
CredR forall era. Era era => Rep era (KeyHash 'StakePool)
PoolHashR) (forall era s t. Rep era s -> Lens' s t -> Access era s t
Yes forall era. Era era => Rep era (NewEpochState era)
NewEpochStateR forall era.
NELens era (Map (Credential 'Staking) (KeyHash 'StakePool))
setDelegsL))
setDelegsL ::
NELens era (Map (Credential 'Staking) (KeyHash 'StakePool))
setDelegsL :: forall era.
NELens era (Map (Credential 'Staking) (KeyHash 'StakePool))
setDelegsL = forall era. Lens' (NewEpochState era) (EpochState era)
nesEsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (EpochState era) SnapShots
esSnapshotsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' SnapShots SnapShot
ssStakeSetL forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens'
SnapShot (VMap VB VB (Credential 'Staking) (KeyHash 'StakePool))
ssDelegationsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k v. Lens' (VMap VB VB k v) (Map k v)
vmapL
setPools ::
Era era => Term era (Map (KeyHash 'StakePool) PoolParams)
setPools :: forall era.
Era era =>
Term era (Map (KeyHash 'StakePool) PoolParams)
setPools = forall era t. V era t -> Term era t
Var (forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"setPools" (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Era era => Rep era (KeyHash 'StakePool)
PoolHashR forall era. Era era => Rep era PoolParams
PoolParamsR) (forall era s t. Rep era s -> Lens' s t -> Access era s t
Yes forall era. Era era => Rep era (NewEpochState era)
NewEpochStateR forall era. NELens era (Map (KeyHash 'StakePool) PoolParams)
setPoolsL))
setPoolsL :: NELens era (Map (KeyHash 'StakePool) PoolParams)
setPoolsL :: forall era. NELens era (Map (KeyHash 'StakePool) PoolParams)
setPoolsL = forall era. Lens' (NewEpochState era) (EpochState era)
nesEsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (EpochState era) SnapShots
esSnapshotsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' SnapShots SnapShot
ssStakeSetL forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' SnapShot (VMap VB VB (KeyHash 'StakePool) PoolParams)
ssPoolParamsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k v. Lens' (VMap VB VB k v) (Map k v)
vmapL
setSnapShotT ::
forall era. Era era => RootTarget era SnapShot SnapShot
setSnapShotT :: forall era. Era era => RootTarget era SnapShot SnapShot
setSnapShotT =
forall root a b era.
String -> TypeRep root -> (a -> b) -> RootTarget era root (a -> b)
Invert String
"SnapShot" (forall {k} (a :: k). Typeable a => TypeRep a
typeRep @SnapShot) Map (Credential 'Staking) Coin
-> Map (Credential 'Staking) (KeyHash 'StakePool)
-> Map (KeyHash 'StakePool) PoolParams
-> SnapShot
snapfun
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed forall era. Era era => Term era (Map (Credential 'Staking) Coin)
setStake (Lens' SnapShot Stake
ssStakeL forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' Stake (Map (Credential 'Staking) Coin)
stakeL)
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed forall era.
Era era =>
Term era (Map (Credential 'Staking) (KeyHash 'StakePool))
setDelegs (Lens'
SnapShot (VMap VB VB (Credential 'Staking) (KeyHash 'StakePool))
ssDelegationsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k v. Lens' (VMap VB VB k v) (Map k v)
vmapL)
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed forall era.
Era era =>
Term era (Map (KeyHash 'StakePool) PoolParams)
setPools (Lens' SnapShot (VMap VB VB (KeyHash 'StakePool) PoolParams)
ssPoolParamsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k v. Lens' (VMap VB VB k v) (Map k v)
vmapL)
where
snapfun :: Map (Credential 'Staking) Coin
-> Map (Credential 'Staking) (KeyHash 'StakePool)
-> Map (KeyHash 'StakePool) PoolParams
-> SnapShot
snapfun Map (Credential 'Staking) Coin
x Map (Credential 'Staking) (KeyHash 'StakePool)
y Map (KeyHash 'StakePool) PoolParams
z =
Stake
-> VMap VB VB (Credential 'Staking) (KeyHash 'StakePool)
-> VMap VB VB (KeyHash 'StakePool) PoolParams
-> SnapShot
SnapShot
(VMap VB VP (Credential 'Staking) (CompactForm Coin) -> Stake
Stake (forall (kv :: * -> *) k (vv :: * -> *) v.
(Vector kv k, Vector vv v) =>
Map k v -> VMap kv vv k v
VMap.fromMap (forall a b k. (a -> b) -> Map k a -> Map k b
Map.map HasCallStack => Coin -> CompactForm Coin
compactCoinOrError Map (Credential 'Staking) Coin
x)))
(forall (kv :: * -> *) k (vv :: * -> *) v.
(Vector kv k, Vector vv v) =>
Map k v -> VMap kv vv k v
VMap.fromMap Map (Credential 'Staking) (KeyHash 'StakePool)
y)
(forall (kv :: * -> *) k (vv :: * -> *) v.
(Vector kv k, Vector vv v) =>
Map k v -> VMap kv vv k v
VMap.fromMap Map (KeyHash 'StakePool) PoolParams
z)
goStake :: Era era => Term era (Map (Credential 'Staking) Coin)
goStake :: forall era. Era era => Term era (Map (Credential 'Staking) Coin)
goStake = forall era t. V era t -> Term era t
Var (forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"goStake" (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Era era => Rep era (Credential 'Staking)
CredR forall era. Rep era Coin
CoinR) (forall era s t. Rep era s -> Lens' s t -> Access era s t
Yes forall era. Era era => Rep era (NewEpochState era)
NewEpochStateR forall era. NELens era (Map (Credential 'Staking) Coin)
goStakeL))
goStakeL :: NELens era (Map (Credential 'Staking) Coin)
goStakeL :: forall era. NELens era (Map (Credential 'Staking) Coin)
goStakeL = forall era. Lens' (NewEpochState era) (EpochState era)
nesEsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (EpochState era) SnapShots
esSnapshotsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' SnapShots SnapShot
ssStakeGoL forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' SnapShot Stake
ssStakeL forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' Stake (Map (Credential 'Staking) Coin)
stakeL
goDelegs ::
Era era => Term era (Map (Credential 'Staking) (KeyHash 'StakePool))
goDelegs :: forall era.
Era era =>
Term era (Map (Credential 'Staking) (KeyHash 'StakePool))
goDelegs = forall era t. V era t -> Term era t
Var (forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"goDelegs" (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Era era => Rep era (Credential 'Staking)
CredR forall era. Era era => Rep era (KeyHash 'StakePool)
PoolHashR) (forall era s t. Rep era s -> Lens' s t -> Access era s t
Yes forall era. Era era => Rep era (NewEpochState era)
NewEpochStateR forall era.
NELens era (Map (Credential 'Staking) (KeyHash 'StakePool))
goDelegsL))
goDelegsL ::
NELens era (Map (Credential 'Staking) (KeyHash 'StakePool))
goDelegsL :: forall era.
NELens era (Map (Credential 'Staking) (KeyHash 'StakePool))
goDelegsL = forall era. Lens' (NewEpochState era) (EpochState era)
nesEsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (EpochState era) SnapShots
esSnapshotsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' SnapShots SnapShot
ssStakeGoL forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens'
SnapShot (VMap VB VB (Credential 'Staking) (KeyHash 'StakePool))
ssDelegationsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k v. Lens' (VMap VB VB k v) (Map k v)
vmapL
goPools ::
Era era => Term era (Map (KeyHash 'StakePool) PoolParams)
goPools :: forall era.
Era era =>
Term era (Map (KeyHash 'StakePool) PoolParams)
goPools = forall era t. V era t -> Term era t
Var (forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"goPools" (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Era era => Rep era (KeyHash 'StakePool)
PoolHashR forall era. Era era => Rep era PoolParams
PoolParamsR) (forall era s t. Rep era s -> Lens' s t -> Access era s t
Yes forall era. Era era => Rep era (NewEpochState era)
NewEpochStateR forall era. NELens era (Map (KeyHash 'StakePool) PoolParams)
goPoolsL))
goPoolsL :: NELens era (Map (KeyHash 'StakePool) PoolParams)
goPoolsL :: forall era. NELens era (Map (KeyHash 'StakePool) PoolParams)
goPoolsL = forall era. Lens' (NewEpochState era) (EpochState era)
nesEsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (EpochState era) SnapShots
esSnapshotsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' SnapShots SnapShot
ssStakeGoL forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' SnapShot (VMap VB VB (KeyHash 'StakePool) PoolParams)
ssPoolParamsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k v. Lens' (VMap VB VB k v) (Map k v)
vmapL
goSnapShotT ::
forall era. Era era => RootTarget era SnapShot SnapShot
goSnapShotT :: forall era. Era era => RootTarget era SnapShot SnapShot
goSnapShotT =
forall root a b era.
String -> TypeRep root -> (a -> b) -> RootTarget era root (a -> b)
Invert String
"SnapShot" (forall {k} (a :: k). Typeable a => TypeRep a
typeRep @SnapShot) Map (Credential 'Staking) Coin
-> Map (Credential 'Staking) (KeyHash 'StakePool)
-> Map (KeyHash 'StakePool) PoolParams
-> SnapShot
snapfun
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed forall era. Era era => Term era (Map (Credential 'Staking) Coin)
goStake (Lens' SnapShot Stake
ssStakeL forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' Stake (Map (Credential 'Staking) Coin)
stakeL)
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed forall era.
Era era =>
Term era (Map (Credential 'Staking) (KeyHash 'StakePool))
goDelegs (Lens'
SnapShot (VMap VB VB (Credential 'Staking) (KeyHash 'StakePool))
ssDelegationsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k v. Lens' (VMap VB VB k v) (Map k v)
vmapL)
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed forall era.
Era era =>
Term era (Map (KeyHash 'StakePool) PoolParams)
goPools (Lens' SnapShot (VMap VB VB (KeyHash 'StakePool) PoolParams)
ssPoolParamsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k v. Lens' (VMap VB VB k v) (Map k v)
vmapL)
where
snapfun :: Map (Credential 'Staking) Coin
-> Map (Credential 'Staking) (KeyHash 'StakePool)
-> Map (KeyHash 'StakePool) PoolParams
-> SnapShot
snapfun Map (Credential 'Staking) Coin
x Map (Credential 'Staking) (KeyHash 'StakePool)
y Map (KeyHash 'StakePool) PoolParams
z =
Stake
-> VMap VB VB (Credential 'Staking) (KeyHash 'StakePool)
-> VMap VB VB (KeyHash 'StakePool) PoolParams
-> SnapShot
SnapShot
(VMap VB VP (Credential 'Staking) (CompactForm Coin) -> Stake
Stake (forall (kv :: * -> *) k (vv :: * -> *) v.
(Vector kv k, Vector vv v) =>
Map k v -> VMap kv vv k v
VMap.fromMap (forall a b k. (a -> b) -> Map k a -> Map k b
Map.map HasCallStack => Coin -> CompactForm Coin
compactCoinOrError Map (Credential 'Staking) Coin
x)))
(forall (kv :: * -> *) k (vv :: * -> *) v.
(Vector kv k, Vector vv v) =>
Map k v -> VMap kv vv k v
VMap.fromMap Map (Credential 'Staking) (KeyHash 'StakePool)
y)
(forall (kv :: * -> *) k (vv :: * -> *) v.
(Vector kv k, Vector vv v) =>
Map k v -> VMap kv vv k v
VMap.fromMap Map (KeyHash 'StakePool) PoolParams
z)
markPoolDistr ::
Era era => Term era (Map (KeyHash 'StakePool) IndividualPoolStake)
markPoolDistr :: forall era.
Era era =>
Term era (Map (KeyHash 'StakePool) IndividualPoolStake)
markPoolDistr = forall era t. V era t -> Term era t
Var (forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"markPoolDistr" (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Era era => Rep era (KeyHash 'StakePool)
PoolHashR forall era. Era era => Rep era IndividualPoolStake
IPoolStakeR) forall era s t. Access era s t
No)
markPoolDistrL ::
NELens era (Map (KeyHash 'StakePool) IndividualPoolStake)
markPoolDistrL :: forall era.
NELens era (Map (KeyHash 'StakePool) IndividualPoolStake)
markPoolDistrL = forall era. Lens' (NewEpochState era) (EpochState era)
nesEsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Lens' (EpochState era) SnapShots
esSnapshotsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' SnapShots PoolDistr
ssStakeMarkPoolDistrL forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' PoolDistr (Map (KeyHash 'StakePool) IndividualPoolStake)
poolDistrDistrL
snapShotFee :: Era era => Term era Coin
snapShotFee :: forall era. Era era => Term era Coin
snapShotFee = forall era t. V era t -> Term era t
Var (forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"snapShotFee" forall era. Rep era Coin
CoinR forall era s t. Access era s t
No)
snapShotsT ::
forall era. Era era => RootTarget era SnapShots SnapShots
snapShotsT :: forall era. Era era => RootTarget era SnapShots SnapShots
snapShotsT =
forall root a b era.
String -> TypeRep root -> (a -> b) -> RootTarget era root (a -> b)
Invert String
"SnapShots" (forall {k} (a :: k). Typeable a => TypeRep a
typeRep @SnapShots) SnapShot
-> Map (KeyHash 'StakePool) IndividualPoolStake
-> SnapShot
-> SnapShot
-> Coin
-> SnapShots
shotsfun
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era root2 t root.
RootTarget era root2 t -> Lens' root root2 -> RootTarget era root t
Shift forall era. Era era => RootTarget era SnapShot SnapShot
markSnapShotT Lens' SnapShots SnapShot
ssStakeMarkL
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed forall era.
Era era =>
Term era (Map (KeyHash 'StakePool) IndividualPoolStake)
markPoolDistr (Lens' SnapShots PoolDistr
ssStakeMarkPoolDistrL forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' PoolDistr (Map (KeyHash 'StakePool) IndividualPoolStake)
poolDistrDistrL)
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era root2 t root.
RootTarget era root2 t -> Lens' root root2 -> RootTarget era root t
Shift forall era. Era era => RootTarget era SnapShot SnapShot
setSnapShotT Lens' SnapShots SnapShot
ssStakeSetL
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era root2 t root.
RootTarget era root2 t -> Lens' root root2 -> RootTarget era root t
Shift forall era. Era era => RootTarget era SnapShot SnapShot
goSnapShotT Lens' SnapShots SnapShot
ssStakeGoL
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed forall era. Era era => Term era Coin
snapShotFee Lens' SnapShots Coin
ssFeeL
where
shotsfun :: SnapShot
-> Map (KeyHash 'StakePool) IndividualPoolStake
-> SnapShot
-> SnapShot
-> Coin
-> SnapShots
shotsfun SnapShot
w Map (KeyHash 'StakePool) IndividualPoolStake
x = SnapShot -> PoolDistr -> SnapShot -> SnapShot -> Coin -> SnapShots
SnapShots SnapShot
w (Map (KeyHash 'StakePool) IndividualPoolStake
-> CompactForm Coin -> PoolDistr
PoolDistr Map (KeyHash 'StakePool) IndividualPoolStake
x forall a b. (a -> b) -> a -> b
$ Word64 -> CompactForm Coin
CompactCoin Word64
1)
deltaT :: Era era => Term era (Maybe DeltaCoin)
deltaT :: forall era. Era era => Term era (Maybe DeltaCoin)
deltaT = forall era t. V era t -> Term era t
Var (forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"deltaT" (forall era t1. Rep era t1 -> Rep era (Maybe t1)
MaybeR forall era. Rep era DeltaCoin
DeltaCoinR) (forall era s t. Rep era s -> Lens' s t -> Access era s t
Yes forall era. Era era => Rep era (NewEpochState era)
NewEpochStateR forall era. NELens era (Maybe DeltaCoin)
deltaTL))
deltaTL :: NELens era (Maybe DeltaCoin)
deltaTL :: forall era. NELens era (Maybe DeltaCoin)
deltaTL = forall era.
Lens' (NewEpochState era) (StrictMaybe PulsingRewUpdate)
nesRuL forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' (StrictMaybe PulsingRewUpdate) (Maybe DeltaCoin)
help
where
help :: Lens' (StrictMaybe PulsingRewUpdate) (Maybe DeltaCoin)
help :: Lens' (StrictMaybe PulsingRewUpdate) (Maybe DeltaCoin)
help = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens StrictMaybe PulsingRewUpdate -> Maybe DeltaCoin
view StrictMaybe PulsingRewUpdate
-> Maybe DeltaCoin -> StrictMaybe PulsingRewUpdate
update
where
view :: StrictMaybe PulsingRewUpdate -> Maybe DeltaCoin
view StrictMaybe PulsingRewUpdate
SNothing = forall a. Maybe a
Nothing
view (SJust (Complete RewardUpdate
x)) = forall a. a -> Maybe a
Just (RewardUpdate -> DeltaCoin
RU.deltaT RewardUpdate
x)
view (SJust PulsingRewUpdate
_) = forall a. Maybe a
Nothing
update :: StrictMaybe PulsingRewUpdate
-> Maybe DeltaCoin -> StrictMaybe PulsingRewUpdate
update (SJust (Complete RewardUpdate
ru)) (Just DeltaCoin
change) = forall a. a -> StrictMaybe a
SJust (RewardUpdate -> PulsingRewUpdate
Complete (RewardUpdate
ru {deltaT :: DeltaCoin
RU.deltaT = DeltaCoin
change}))
update StrictMaybe PulsingRewUpdate
_ Maybe DeltaCoin
_ = forall a. StrictMaybe a
SNothing
deltaR :: Era era => Term era (Maybe DeltaCoin)
deltaR :: forall era. Era era => Term era (Maybe DeltaCoin)
deltaR = forall era t. V era t -> Term era t
Var (forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"deltaR" (forall era t1. Rep era t1 -> Rep era (Maybe t1)
MaybeR forall era. Rep era DeltaCoin
DeltaCoinR) (forall era s t. Rep era s -> Lens' s t -> Access era s t
Yes forall era. Era era => Rep era (NewEpochState era)
NewEpochStateR forall era. NELens era (Maybe DeltaCoin)
deltaRL))
deltaRL :: NELens era (Maybe DeltaCoin)
deltaRL :: forall era. NELens era (Maybe DeltaCoin)
deltaRL = forall era.
Lens' (NewEpochState era) (StrictMaybe PulsingRewUpdate)
nesRuL forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' (StrictMaybe PulsingRewUpdate) (Maybe DeltaCoin)
help
where
help :: Lens' (StrictMaybe PulsingRewUpdate) (Maybe DeltaCoin)
help :: Lens' (StrictMaybe PulsingRewUpdate) (Maybe DeltaCoin)
help = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens StrictMaybe PulsingRewUpdate -> Maybe DeltaCoin
view StrictMaybe PulsingRewUpdate
-> Maybe DeltaCoin -> StrictMaybe PulsingRewUpdate
update
where
view :: StrictMaybe PulsingRewUpdate -> Maybe DeltaCoin
view StrictMaybe PulsingRewUpdate
SNothing = forall a. Maybe a
Nothing
view (SJust (Complete RewardUpdate
x)) = forall a. a -> Maybe a
Just (RewardUpdate -> DeltaCoin
RU.deltaR RewardUpdate
x)
view (SJust PulsingRewUpdate
_) = forall a. Maybe a
Nothing
update :: StrictMaybe PulsingRewUpdate
-> Maybe DeltaCoin -> StrictMaybe PulsingRewUpdate
update (SJust (Complete RewardUpdate
ru)) (Just DeltaCoin
change) = forall a. a -> StrictMaybe a
SJust (RewardUpdate -> PulsingRewUpdate
Complete (RewardUpdate
ru {deltaR :: DeltaCoin
RU.deltaR = DeltaCoin
change}))
update StrictMaybe PulsingRewUpdate
_ Maybe DeltaCoin
_ = forall a. StrictMaybe a
SNothing
deltaF :: Era era => Term era (Maybe DeltaCoin)
deltaF :: forall era. Era era => Term era (Maybe DeltaCoin)
deltaF = forall era t. V era t -> Term era t
Var (forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"deltaF" (forall era t1. Rep era t1 -> Rep era (Maybe t1)
MaybeR forall era. Rep era DeltaCoin
DeltaCoinR) (forall era s t. Rep era s -> Lens' s t -> Access era s t
Yes forall era. Era era => Rep era (NewEpochState era)
NewEpochStateR forall era. NELens era (Maybe DeltaCoin)
deltaFL))
deltaFL :: NELens era (Maybe DeltaCoin)
deltaFL :: forall era. NELens era (Maybe DeltaCoin)
deltaFL = forall era.
Lens' (NewEpochState era) (StrictMaybe PulsingRewUpdate)
nesRuL forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' (StrictMaybe PulsingRewUpdate) (Maybe DeltaCoin)
help
where
help :: Lens' (StrictMaybe PulsingRewUpdate) (Maybe DeltaCoin)
help :: Lens' (StrictMaybe PulsingRewUpdate) (Maybe DeltaCoin)
help = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens StrictMaybe PulsingRewUpdate -> Maybe DeltaCoin
view StrictMaybe PulsingRewUpdate
-> Maybe DeltaCoin -> StrictMaybe PulsingRewUpdate
update
where
view :: StrictMaybe PulsingRewUpdate -> Maybe DeltaCoin
view StrictMaybe PulsingRewUpdate
SNothing = forall a. Maybe a
Nothing
view (SJust (Complete RewardUpdate
x)) = forall a. a -> Maybe a
Just (RewardUpdate -> DeltaCoin
RU.deltaF RewardUpdate
x)
view (SJust PulsingRewUpdate
_) = forall a. Maybe a
Nothing
update :: StrictMaybe PulsingRewUpdate
-> Maybe DeltaCoin -> StrictMaybe PulsingRewUpdate
update (SJust (Complete RewardUpdate
ru)) (Just DeltaCoin
change) = forall a. a -> StrictMaybe a
SJust (RewardUpdate -> PulsingRewUpdate
Complete (RewardUpdate
ru {deltaF :: DeltaCoin
RU.deltaF = DeltaCoin
change}))
update StrictMaybe PulsingRewUpdate
_ Maybe DeltaCoin
_ = forall a. StrictMaybe a
SNothing
rewardSet ::
Era era => Term era (Map (Credential 'Staking) (Set Reward))
rewardSet :: forall era.
Era era =>
Term era (Map (Credential 'Staking) (Set Reward))
rewardSet = forall era t. V era t -> Term era t
Var (forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"rewardSet" (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Era era => Rep era (Credential 'Staking)
CredR (forall a era. Ord a => Rep era a -> Rep era (Set a)
SetR forall era. Era era => Rep era Reward
RewardR)) forall era s t. Access era s t
No)
rewardSetL ::
NELens era (Maybe (Map (Credential 'Staking) (Set Reward)))
rewardSetL :: forall era.
NELens era (Maybe (Map (Credential 'Staking) (Set Reward)))
rewardSetL = forall era.
Lens' (NewEpochState era) (StrictMaybe PulsingRewUpdate)
nesRuL forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens'
(StrictMaybe PulsingRewUpdate)
(Maybe (Map (Credential 'Staking) (Set Reward)))
help
where
help ::
Lens' (StrictMaybe PulsingRewUpdate) (Maybe (Map (Credential 'Staking) (Set Reward)))
help :: Lens'
(StrictMaybe PulsingRewUpdate)
(Maybe (Map (Credential 'Staking) (Set Reward)))
help = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens StrictMaybe PulsingRewUpdate
-> Maybe (Map (Credential 'Staking) (Set Reward))
view StrictMaybe PulsingRewUpdate
-> Maybe (Map (Credential 'Staking) (Set Reward))
-> StrictMaybe PulsingRewUpdate
update
where
view :: StrictMaybe PulsingRewUpdate
-> Maybe (Map (Credential 'Staking) (Set Reward))
view StrictMaybe PulsingRewUpdate
SNothing = forall a. Maybe a
Nothing
view (SJust (Complete RewardUpdate
x)) = forall a. a -> Maybe a
Just (RewardUpdate -> Map (Credential 'Staking) (Set Reward)
RU.rs RewardUpdate
x)
view (SJust PulsingRewUpdate
_) = forall a. Maybe a
Nothing
update :: StrictMaybe PulsingRewUpdate
-> Maybe (Map (Credential 'Staking) (Set Reward))
-> StrictMaybe PulsingRewUpdate
update (SJust (Complete RewardUpdate
ru)) (Just Map (Credential 'Staking) (Set Reward)
change) = forall a. a -> StrictMaybe a
SJust (RewardUpdate -> PulsingRewUpdate
Complete (RewardUpdate
ru {rs :: Map (Credential 'Staking) (Set Reward)
RU.rs = Map (Credential 'Staking) (Set Reward)
change}))
update StrictMaybe PulsingRewUpdate
_ Maybe (Map (Credential 'Staking) (Set Reward))
_ = forall a. StrictMaybe a
SNothing
totalAda :: Era era => Term era Coin
totalAda :: forall era. Era era => Term era Coin
totalAda = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"totalAda" forall era. Rep era Coin
CoinR forall era s t. Access era s t
No
utxoCoin :: Era era => Term era Coin
utxoCoin :: forall era. Era era => Term era Coin
utxoCoin = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"utxoCoin" forall era. Rep era Coin
CoinR forall era s t. Access era s t
No
credsUniv :: Era era => Term era (Set (Credential 'Staking))
credsUniv :: forall era. Era era => Term era (Set (Credential 'Staking))
credsUniv = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"credsUniv" (forall a era. Ord a => Rep era a -> Rep era (Set a)
SetR forall era. Era era => Rep era (Credential 'Staking)
CredR) forall era s t. Access era s t
No
spendCredsUniv :: Era era => Term era (Set (Credential 'Payment))
spendCredsUniv :: forall era. Era era => Term era (Set (Credential 'Payment))
spendCredsUniv = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"spendCredsUniv" (forall a era. Ord a => Rep era a -> Rep era (Set a)
SetR forall era. Era era => Rep era (Credential 'Payment)
PCredR) forall era s t. Access era s t
No
voteUniv :: Era era => Term era (Set (Credential 'DRepRole))
voteUniv :: forall era. Era era => Term era (Set (Credential 'DRepRole))
voteUniv = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"voteUniv" (forall a era. Ord a => Rep era a -> Rep era (Set a)
SetR forall era. Era era => Rep era (Credential 'DRepRole)
VCredR) forall era s t. Access era s t
No
drepUniv :: Era era => Term era (Set DRep)
drepUniv :: forall era. Era era => Term era (Set DRep)
drepUniv = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"drepUniv" (forall a era. Ord a => Rep era a -> Rep era (Set a)
SetR forall era. Era era => Rep era DRep
DRepR) forall era s t. Access era s t
No
hotCommitteeCredsUniv :: Era era => Term era (Set (Credential 'HotCommitteeRole))
hotCommitteeCredsUniv :: forall era.
Era era =>
Term era (Set (Credential 'HotCommitteeRole))
hotCommitteeCredsUniv = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"hotCommitteeCredsUniv" (forall a era. Ord a => Rep era a -> Rep era (Set a)
SetR forall era. Era era => Rep era (Credential 'HotCommitteeRole)
CommHotCredR) forall era s t. Access era s t
No
coldCommitteeCredsUniv :: Era era => Term era (Set (Credential 'ColdCommitteeRole))
coldCommitteeCredsUniv :: forall era.
Era era =>
Term era (Set (Credential 'ColdCommitteeRole))
coldCommitteeCredsUniv = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"coldCommitteeCredsUniv" (forall a era. Ord a => Rep era a -> Rep era (Set a)
SetR forall era. Era era => Rep era (Credential 'ColdCommitteeRole)
CommColdCredR) forall era s t. Access era s t
No
payUniv :: Era era => Term era (Set (Credential 'Payment))
payUniv :: forall era. Era era => Term era (Set (Credential 'Payment))
payUniv = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"payUniv" (forall a era. Ord a => Rep era a -> Rep era (Set a)
SetR forall era. Era era => Rep era (Credential 'Payment)
PCredR) forall era s t. Access era s t
No
spendscriptUniv :: Era era => Proof era -> Term era (Map ScriptHash (ScriptF era))
spendscriptUniv :: forall era.
Era era =>
Proof era -> Term era (Map ScriptHash (ScriptF era))
spendscriptUniv Proof era
p = forall era t. V era t -> Term era t
Var (forall era t s.
Proof era -> String -> Rep era t -> Access era s t -> V era t
pV Proof era
p String
"spendscriptUniv" (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Era era => Rep era ScriptHash
ScriptHashR (forall era. Era era => Proof era -> Rep era (ScriptF era)
ScriptR Proof era
p)) forall era s t. Access era s t
No)
nonSpendScriptUniv ::
Era era => Proof era -> Term era (Map ScriptHash (ScriptF era))
nonSpendScriptUniv :: forall era.
Era era =>
Proof era -> Term era (Map ScriptHash (ScriptF era))
nonSpendScriptUniv Proof era
p = forall era t. V era t -> Term era t
Var (forall era t s.
Proof era -> String -> Rep era t -> Access era s t -> V era t
pV Proof era
p String
"nonSpendScriptUniv" (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Era era => Rep era ScriptHash
ScriptHashR (forall era. Era era => Proof era -> Rep era (ScriptF era)
ScriptR Proof era
p)) forall era s t. Access era s t
No)
allScriptUniv :: Era era => Proof era -> Term era (Map ScriptHash (ScriptF era))
allScriptUniv :: forall era.
Era era =>
Proof era -> Term era (Map ScriptHash (ScriptF era))
allScriptUniv Proof era
p = forall era t. V era t -> Term era t
Var (forall era t s.
Proof era -> String -> Rep era t -> Access era s t -> V era t
pV Proof era
p String
"allScriptUniv" (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Era era => Rep era ScriptHash
ScriptHashR (forall era. Era era => Proof era -> Rep era (ScriptF era)
ScriptR Proof era
p)) forall era s t. Access era s t
No)
dataUniv :: Era era => Term era (Map DataHash (Data era))
dataUniv :: forall era. Era era => Term era (Map DataHash (Data era))
dataUniv = forall era t. V era t -> Term era t
Var (forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"dataUniv" (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Era era => Rep era DataHash
DataHashR forall era. Era era => Rep era (Data era)
DataR) forall era s t. Access era s t
No)
poolHashUniv :: Era era => Term era (Set (KeyHash 'StakePool))
poolHashUniv :: forall era. Era era => Term era (Set (KeyHash 'StakePool))
poolHashUniv = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"poolHashUniv" (forall a era. Ord a => Rep era a -> Rep era (Set a)
SetR forall era. Era era => Rep era (KeyHash 'StakePool)
PoolHashR) forall era s t. Access era s t
No
stakeHashUniv :: Era era => Term era (Set (KeyHash 'Staking))
stakeHashUniv :: forall era. Era era => Term era (Set (KeyHash 'Staking))
stakeHashUniv = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"stakeHashUniv" (forall a era. Ord a => Rep era a -> Rep era (Set a)
SetR forall era. Era era => Rep era (KeyHash 'Staking)
StakeHashR) forall era s t. Access era s t
No
drepHashUniv :: Era era => Term era (Set (KeyHash 'DRepRole))
drepHashUniv :: forall era. Era era => Term era (Set (KeyHash 'DRepRole))
drepHashUniv = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"drepHashUniv" (forall a era. Ord a => Rep era a -> Rep era (Set a)
SetR forall era. Era era => Rep era (KeyHash 'DRepRole)
DRepHashR) forall era s t. Access era s t
No
genesisHashUniv ::
Era era => Term era (Map (KeyHash 'Genesis) GenDelegPair)
genesisHashUniv :: forall era.
Era era =>
Term era (Map (KeyHash 'Genesis) GenDelegPair)
genesisHashUniv = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"genesisHashUniv" (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Era era => Rep era (KeyHash 'Genesis)
GenHashR forall era. Era era => Rep era GenDelegPair
GenDelegPairR) forall era s t. Access era s t
No
voteCredUniv :: Era era => Term era (Set (Credential 'ColdCommitteeRole))
voteCredUniv :: forall era.
Era era =>
Term era (Set (Credential 'ColdCommitteeRole))
voteCredUniv = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"voteHashUniv" (forall a era. Ord a => Rep era a -> Rep era (Set a)
SetR forall era. Era era => Rep era (Credential 'ColdCommitteeRole)
CommColdCredR) forall era s t. Access era s t
No
txinUniv :: Era era => Term era (Set TxIn)
txinUniv :: forall era. Era era => Term era (Set TxIn)
txinUniv = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"txinUniv" (forall a era. Ord a => Rep era a -> Rep era (Set a)
SetR forall era. Era era => Rep era TxIn
TxInR) forall era s t. Access era s t
No
govActionIdUniv :: Era era => Term era (Set GovActionId)
govActionIdUniv :: forall era. Era era => Term era (Set GovActionId)
govActionIdUniv = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"govActionIdUniv" (forall a era. Ord a => Rep era a -> Rep era (Set a)
SetR forall era. Era era => Rep era GovActionId
GovActionIdR) forall era s t. Access era s t
No
txoutUniv :: Era era => Proof era -> Term era (Set (TxOutF era))
txoutUniv :: forall era. Era era => Proof era -> Term era (Set (TxOutF era))
txoutUniv Proof era
p = forall era t. V era t -> Term era t
Var (forall era t s.
Proof era -> String -> Rep era t -> Access era s t -> V era t
pV Proof era
p String
"txoutUniv" (forall a era. Ord a => Rep era a -> Rep era (Set a)
SetR (forall era. Era era => Proof era -> Rep era (TxOutF era)
TxOutR Proof era
p)) forall era s t. Access era s t
No)
colTxoutUniv :: Era era => Proof era -> Term era (Set (TxOutF era))
colTxoutUniv :: forall era. Era era => Proof era -> Term era (Set (TxOutF era))
colTxoutUniv Proof era
p = forall era t. V era t -> Term era t
Var (forall era t s.
Proof era -> String -> Rep era t -> Access era s t -> V era t
pV Proof era
p String
"colTxoutUniv" (forall a era. Ord a => Rep era a -> Rep era (Set a)
SetR (forall era. Era era => Proof era -> Rep era (TxOutF era)
TxOutR Proof era
p)) forall era s t. Access era s t
No)
feeTxOut :: Reflect era => Term era (TxOutF era)
feeTxOut :: forall era. Reflect era => Term era (TxOutF era)
feeTxOut = forall era t. V era t -> Term era t
Var (forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"feeTxOut" (forall era. Era era => Proof era -> Rep era (TxOutF era)
TxOutR forall era. Reflect era => Proof era
reify) forall era s t. Access era s t
No)
feeTxIn :: Era era => Term era TxIn
feeTxIn :: forall era. Era era => Term era TxIn
feeTxIn = forall era t. V era t -> Term era t
Var (forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"feeTxIn" forall era. Era era => Rep era TxIn
TxInR forall era s t. Access era s t
No)
bigCoin :: Era era => Term era Coin
bigCoin :: forall era. Era era => Term era Coin
bigCoin = forall era t. V era t -> Term era t
Var (forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"bigCoin" forall era. Rep era Coin
CoinR forall era s t. Access era s t
No)
datumsUniv :: Era era => Term era [Datum era]
datumsUniv :: forall era. Era era => Term era [Datum era]
datumsUniv = forall era t. V era t -> Term era t
Var (forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"datumsUniv" (forall era a. Rep era a -> Rep era [a]
ListR forall era. Era era => Rep era (Datum era)
DatumR) forall era s t. Access era s t
No)
multiAssetUniv :: Era era => Term era [MultiAsset]
multiAssetUniv :: forall era. Era era => Term era [MultiAsset]
multiAssetUniv = forall era t. V era t -> Term era t
Var (forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"multiAssetUniv" (forall era a. Rep era a -> Rep era [a]
ListR forall era. Era era => Rep era MultiAsset
MultiAssetR) forall era s t. Access era s t
No)
keymapUniv ::
Era era => Term era (Map (KeyHash 'Witness) (KeyPair 'Witness))
keymapUniv :: forall era.
Era era =>
Term era (Map (KeyHash 'Witness) (KeyPair 'Witness))
keymapUniv = forall era t. V era t -> Term era t
Var (forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"keymapUniv" (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Era era => Rep era (KeyHash 'Witness)
WitHashR forall era. Era era => Rep era (KeyPair 'Witness)
KeyPairR) forall era s t. Access era s t
No)
currentSlot :: Era era => Term era SlotNo
currentSlot :: forall era. Era era => Term era SlotNo
currentSlot = forall era t. V era t -> Term era t
Var (forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"currentSlot" forall era. Rep era SlotNo
SlotNoR forall era s t. Access era s t
No)
endSlotDelta :: Era era => Term era SlotNo
endSlotDelta :: forall era. Era era => Term era SlotNo
endSlotDelta = forall era t. V era t -> Term era t
Var (forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"endSlotDelta" forall era. Rep era SlotNo
SlotNoR forall era s t. Access era s t
No)
beginSlotDelta :: Era era => Term era SlotNo
beginSlotDelta :: forall era. Era era => Term era SlotNo
beginSlotDelta = forall era t. V era t -> Term era t
Var (forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"beginSlotDelta" forall era. Rep era SlotNo
SlotNoR forall era s t. Access era s t
No)
network :: Era era => Term era Network
network :: forall era. Era era => Term era Network
network = forall era t. V era t -> Term era t
Var (forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"network" forall era. Rep era Network
NetworkR forall era s t. Access era s t
No)
quorumConstant :: Word64
quorumConstant :: Word64
quorumConstant = Globals -> Word64
Base.quorum Globals
Utils.testGlobals
quorum :: Era era => Term era Int
quorum :: forall era. Era era => Term era Int
quorum = forall era t. V era t -> Term era t
Var (forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"quorum" forall era. Rep era Int
IntR forall era s t. Access era s t
No)
addrUniv :: Era era => Term era (Set Addr)
addrUniv :: forall era. Era era => Term era (Set Addr)
addrUniv = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"addrUniv" (forall a era. Ord a => Rep era a -> Rep era (Set a)
SetR forall era. Era era => Rep era Addr
AddrR) forall era s t. Access era s t
No
ptrUniv :: Era era => Term era (Set Ptr)
ptrUniv :: forall era. Era era => Term era (Set Ptr)
ptrUniv = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"ptrUniv" (forall a era. Ord a => Rep era a -> Rep era (Set a)
SetR forall era. Rep era Ptr
PtrR) forall era s t. Access era s t
No
plutusUniv :: Reflect era => Term era (Map ScriptHash (IsValid, ScriptF era))
plutusUniv :: forall era.
Reflect era =>
Term era (Map ScriptHash (IsValid, ScriptF era))
plutusUniv = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"plutusUniv" (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Era era => Rep era ScriptHash
ScriptHashR (forall era a b. Rep era a -> Rep era b -> Rep era (a, b)
PairR forall era. Rep era IsValid
IsValidR (forall era. Era era => Proof era -> Rep era (ScriptF era)
ScriptR forall era. Reflect era => Proof era
reify))) forall era s t. Access era s t
No
spendPlutusUniv :: Reflect era => Term era (Map ScriptHash (IsValid, ScriptF era))
spendPlutusUniv :: forall era.
Reflect era =>
Term era (Map ScriptHash (IsValid, ScriptF era))
spendPlutusUniv = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"spendPlutusUniv" (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Era era => Rep era ScriptHash
ScriptHashR (forall era a b. Rep era a -> Rep era b -> Rep era (a, b)
PairR forall era. Rep era IsValid
IsValidR (forall era. Era era => Proof era -> Rep era (ScriptF era)
ScriptR forall era. Reflect era => Proof era
reify))) forall era s t. Access era s t
No
byronAddrUniv ::
Era era => Term era (Map (KeyHash 'Payment) (Addr, SigningKey))
byronAddrUniv :: forall era.
Era era =>
Term era (Map (KeyHash 'Payment) (Addr, SigningKey))
byronAddrUniv = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"byronAddrUniv" (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Era era => Rep era (KeyHash 'Payment)
PayHashR (forall era a b. Rep era a -> Rep era b -> Rep era (a, b)
PairR forall era. Era era => Rep era Addr
AddrR forall era. Rep era SigningKey
SigningKeyR)) forall era s t. Access era s t
No
newEpochStateConstr ::
Proof era ->
EpochNo ->
Map (KeyHash 'StakePool) Natural ->
Map (KeyHash 'StakePool) Natural ->
EpochState era ->
Map (KeyHash 'StakePool) IndividualPoolStake ->
NewEpochState era
newEpochStateConstr :: forall era.
Proof era
-> EpochNo
-> Map (KeyHash 'StakePool) Natural
-> Map (KeyHash 'StakePool) Natural
-> EpochState era
-> Map (KeyHash 'StakePool) IndividualPoolStake
-> NewEpochState era
newEpochStateConstr
Proof era
proof
EpochNo
nesEL'
Map (KeyHash 'StakePool) Natural
nesBprev'
Map (KeyHash 'StakePool) Natural
nesBcur'
EpochState era
nesEs'
Map (KeyHash 'StakePool) IndividualPoolStake
nesPd' =
forall era.
EpochNo
-> BlocksMade
-> BlocksMade
-> EpochState era
-> StrictMaybe PulsingRewUpdate
-> PoolDistr
-> StashedAVVMAddresses era
-> NewEpochState era
NewEpochState
EpochNo
nesEL'
(Map (KeyHash 'StakePool) Natural -> BlocksMade
BlocksMade Map (KeyHash 'StakePool) Natural
nesBprev')
(Map (KeyHash 'StakePool) Natural -> BlocksMade
BlocksMade Map (KeyHash 'StakePool) Natural
nesBcur')
EpochState era
nesEs'
forall a. StrictMaybe a
SNothing
(Map (KeyHash 'StakePool) IndividualPoolStake
-> CompactForm Coin -> PoolDistr
PoolDistr Map (KeyHash 'StakePool) IndividualPoolStake
nesPd' forall a b. (a -> b) -> a -> b
$ Word64 -> CompactForm Coin
CompactCoin Word64
1)
( case Proof era
proof of
Proof era
Shelley -> forall era. Map TxIn (TxOut era) -> UTxO era
UTxO forall k a. Map k a
Map.empty
Proof era
Allegra -> ()
Proof era
Mary -> ()
Proof era
Alonzo -> ()
Proof era
Babbage -> ()
Proof era
Conway -> ()
)
newEpochStateT ::
forall era. Gov.EraGov era => Proof era -> RootTarget era (NewEpochState era) (NewEpochState era)
newEpochStateT :: forall era.
EraGov era =>
Proof era -> RootTarget era (NewEpochState era) (NewEpochState era)
newEpochStateT Proof era
proof =
forall root a b era.
String -> TypeRep root -> (a -> b) -> RootTarget era root (a -> b)
Invert String
"NewEpochState" (forall {k} (a :: k). Typeable a => TypeRep a
typeRep @(NewEpochState era)) (forall era.
Proof era
-> EpochNo
-> Map (KeyHash 'StakePool) Natural
-> Map (KeyHash 'StakePool) Natural
-> EpochState era
-> Map (KeyHash 'StakePool) IndividualPoolStake
-> NewEpochState era
newEpochStateConstr Proof era
proof)
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed forall era. Era era => Term era EpochNo
currentEpoch forall era. Lens' (NewEpochState era) EpochNo
nesELL
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed forall era. Era era => Term era (Map (KeyHash 'StakePool) Natural)
prevBlocksMade forall era.
Lens' (NewEpochState era) (Map (KeyHash 'StakePool) Natural)
nesBprevL
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed forall era. Era era => Term era (Map (KeyHash 'StakePool) Natural)
currBlocksMade forall era.
Lens' (NewEpochState era) (Map (KeyHash 'StakePool) Natural)
nesBcurL
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era root2 t root.
RootTarget era root2 t -> Lens' root root2 -> RootTarget era root t
Shift (forall era.
EraGov era =>
Proof era -> RootTarget era (EpochState era) (EpochState era)
epochStateT Proof era
proof) forall era. Lens' (NewEpochState era) (EpochState era)
nesEsL
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed forall era.
Era era =>
Term era (Map (KeyHash 'StakePool) IndividualPoolStake)
poolDistr (forall era. Lens' (NewEpochState era) PoolDistr
nesPdL forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' PoolDistr (Map (KeyHash 'StakePool) IndividualPoolStake)
poolDistrDistrL)
epochStateT ::
forall era. Gov.EraGov era => Proof era -> RootTarget era (EpochState era) (EpochState era)
epochStateT :: forall era.
EraGov era =>
Proof era -> RootTarget era (EpochState era) (EpochState era)
epochStateT Proof era
proof =
forall root a b era.
String -> TypeRep root -> (a -> b) -> RootTarget era root (a -> b)
Invert String
"EpochState" (forall {k} (a :: k). Typeable a => TypeRep a
typeRep @(EpochState era)) forall {era}.
AccountState -> LedgerState era -> SnapShots -> EpochState era
epochStateFun
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era root2 t root.
RootTarget era root2 t -> Lens' root root2 -> RootTarget era root t
Shift forall era. Era era => RootTarget era AccountState AccountState
accountStateT forall era. Lens' (EpochState era) AccountState
esAccountStateL
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era root2 t root.
RootTarget era root2 t -> Lens' root root2 -> RootTarget era root t
Shift (forall era.
EraGov era =>
Proof era -> RootTarget era (LedgerState era) (LedgerState era)
ledgerStateT Proof era
proof) forall era. Lens' (EpochState era) (LedgerState era)
esLStateL
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era root2 t root.
RootTarget era root2 t -> Lens' root root2 -> RootTarget era root t
Shift forall era. Era era => RootTarget era SnapShots SnapShots
snapShotsT forall era. Lens' (EpochState era) SnapShots
esSnapshotsL
where
epochStateFun :: AccountState -> LedgerState era -> SnapShots -> EpochState era
epochStateFun AccountState
a LedgerState era
s SnapShots
l = forall era.
AccountState
-> LedgerState era -> SnapShots -> NonMyopic -> EpochState era
EpochState AccountState
a LedgerState era
s SnapShots
l (Map (KeyHash 'StakePool) Likelihood -> Coin -> NonMyopic
NonMyopic forall k a. Map k a
Map.empty (Integer -> Coin
Coin Integer
0))
accountStateT :: Era era => RootTarget era AccountState AccountState
accountStateT :: forall era. Era era => RootTarget era AccountState AccountState
accountStateT =
forall root a b era.
String -> TypeRep root -> (a -> b) -> RootTarget era root (a -> b)
Invert String
"AccountState" (forall {k} (a :: k). Typeable a => TypeRep a
typeRep @AccountState) Coin -> Coin -> AccountState
AccountState
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed forall era. Era era => Term era Coin
treasury Lens' AccountState Coin
asTreasuryL
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed forall era. Era era => Term era Coin
reserves Lens' AccountState Coin
asReservesL
ledgerStateT ::
forall era. Gov.EraGov era => Proof era -> RootTarget era (LedgerState era) (LedgerState era)
ledgerStateT :: forall era.
EraGov era =>
Proof era -> RootTarget era (LedgerState era) (LedgerState era)
ledgerStateT Proof era
proof =
forall root a b era.
String -> TypeRep root -> (a -> b) -> RootTarget era root (a -> b)
Invert String
"LedgerState" (forall {k} (a :: k). Typeable a => TypeRep a
typeRep @(LedgerState era)) forall era. UTxOState era -> CertState era -> LedgerState era
LedgerState
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era root2 t root.
RootTarget era root2 t -> Lens' root root2 -> RootTarget era root t
Shift (forall era.
EraGov era =>
Proof era -> RootTarget era (UTxOState era) (UTxOState era)
utxoStateT Proof era
proof) forall era. Lens' (LedgerState era) (UTxOState era)
lsUTxOStateL
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era root2 t root.
RootTarget era root2 t -> Lens' root root2 -> RootTarget era root t
Shift forall era.
Era era =>
RootTarget era (CertState era) (CertState era)
certstateT forall era. Lens' (LedgerState era) (CertState era)
lsCertStateL
ledgerState :: Reflect era => Term era (LedgerState era)
ledgerState :: forall era. Reflect era => Term era (LedgerState era)
ledgerState = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"ledgerState" (forall era. Era era => Proof era -> Rep era (LedgerState era)
LedgerStateR forall era. Reflect era => Proof era
reify) forall era s t. Access era s t
No
utxoStateT ::
forall era. Gov.EraGov era => Proof era -> RootTarget era (UTxOState era) (UTxOState era)
utxoStateT :: forall era.
EraGov era =>
Proof era -> RootTarget era (UTxOState era) (UTxOState era)
utxoStateT Proof era
p =
forall root a b era.
String -> TypeRep root -> (a -> b) -> RootTarget era root (a -> b)
Invert String
"UTxOState" (forall {k} (a :: k). Typeable a => TypeRep a
typeRep @(UTxOState era)) (forall era a. (Reflect era => Proof era -> a) -> Proof era -> a
unReflect Reflect era =>
Proof era
-> Map TxIn (TxOutF era)
-> Coin
-> Coin
-> GovState era
-> Coin
-> UTxOState era
utxofun Proof era
p)
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed (forall era.
Era era =>
Proof era -> Term era (Map TxIn (TxOutF era))
utxo Proof era
p) (forall era. Lens' (UTxOState era) (UTxO era)
utxosUtxoL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Proof era -> Lens' (UTxO era) (Map TxIn (TxOutF era))
unUtxoL Proof era
p)
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed forall era. Era era => Term era Coin
deposits forall era. Lens' (UTxOState era) Coin
utxosDepositedL
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed forall era. Era era => Term era Coin
fees forall era. Lens' (UTxOState era) Coin
utxosFeesL
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era root2 t root.
RootTarget era root2 t -> Lens' root root2 -> RootTarget era root t
Shift (forall era.
Era era =>
Proof era -> RootTarget era (GovState era) (GovState era)
govStateT Proof era
p) (forall era. Lens' (UTxOState era) (GovState era)
utxosGovStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Proof era -> Lens' (GovState era) (GovState era)
unGovL Proof era
p)
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed forall era. Era era => Term era Coin
donation forall era. Lens' (UTxOState era) Coin
utxosDonationL
where
utxofun ::
Reflect era =>
Proof era ->
Map TxIn (TxOutF era) ->
Coin ->
Coin ->
GovState era ->
Coin ->
UTxOState era
utxofun :: Reflect era =>
Proof era
-> Map TxIn (TxOutF era)
-> Coin
-> Coin
-> GovState era
-> Coin
-> UTxOState era
utxofun Proof era
proof Map TxIn (TxOutF era)
u Coin
c1 Coin
c2 (GovState Proof era
_ GovState era
x) = forall era.
EraTxOut era =>
PParams era
-> UTxO era
-> Coin
-> Coin
-> GovState era
-> Coin
-> UTxOState era
smartUTxOState (forall era. Reflect era => Proof era -> PParams era
justProtocolVersion Proof era
proof) (forall era. Map TxIn (TxOutF era) -> UTxO era
liftUTxO Map TxIn (TxOutF era)
u) Coin
c1 Coin
c2 GovState era
x
unGovL :: Proof era -> Lens' (Gov.GovState era) (GovState era)
unGovL :: forall era. Proof era -> Lens' (GovState era) (GovState era)
unGovL Proof era
p = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens (\GovState era
x -> forall era. Proof era -> GovState era -> GovState era
GovState Proof era
p GovState era
x) (\GovState era
_ (GovState Proof era
_ GovState era
y) -> GovState era
y)
justProtocolVersion :: forall era. Reflect era => Proof era -> PParams era
justProtocolVersion :: forall era. Reflect era => Proof era -> PParams era
justProtocolVersion Proof era
proof = forall era.
EraPParams era =>
Proof era -> [PParamsField era] -> PParams era
newPParams Proof era
proof [forall era. ProtVer -> PParamsField era
Fields.ProtocolVersion forall a b. (a -> b) -> a -> b
$ forall era. Proof era -> ProtVer
protocolVersion Proof era
proof]
certstateT :: forall era. Era era => RootTarget era (CertState era) (CertState era)
certstateT :: forall era.
Era era =>
RootTarget era (CertState era) (CertState era)
certstateT =
forall root a b era.
String -> TypeRep root -> (a -> b) -> RootTarget era root (a -> b)
Invert String
"CertState" (forall {k} (a :: k). Typeable a => TypeRep a
typeRep @(CertState era)) forall era. VState era -> PState era -> DState era -> CertState era
CertState
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ (forall era root2 t root.
RootTarget era root2 t -> Lens' root root2 -> RootTarget era root t
Shift forall era. Era era => RootTarget era (VState era) (VState era)
vstateT forall era. Lens' (CertState era) (VState era)
certVStateL)
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ (forall era root2 t root.
RootTarget era root2 t -> Lens' root root2 -> RootTarget era root t
Shift forall era. Era era => RootTarget era (PState era) (PState era)
pstateT forall era. Lens' (CertState era) (PState era)
certPStateL)
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ (forall era root2 t root.
RootTarget era root2 t -> Lens' root root2 -> RootTarget era root t
Shift forall era. Era era => RootTarget era (DState era) (DState era)
dstateT forall era. Lens' (CertState era) (DState era)
certDStateL)
vstateT :: forall era. Era era => RootTarget era (VState era) (VState era)
vstateT :: forall era. Era era => RootTarget era (VState era) (VState era)
vstateT =
forall root a b era.
String -> TypeRep root -> (a -> b) -> RootTarget era root (a -> b)
Invert String
"VState" (forall {k} (a :: k). Typeable a => TypeRep a
typeRep @(VState era)) (\Map (Credential 'DRepRole) DRepState
x Map (Credential 'ColdCommitteeRole) CommitteeAuthorization
y EpochNo
z -> forall era.
Map (Credential 'DRepRole) DRepState
-> CommitteeState era -> EpochNo -> VState era
VState Map (Credential 'DRepRole) DRepState
x (forall era.
Map (Credential 'ColdCommitteeRole) CommitteeAuthorization
-> CommitteeState era
CommitteeState Map (Credential 'ColdCommitteeRole) CommitteeAuthorization
y) EpochNo
z)
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed forall era.
Era era =>
Term era (Map (Credential 'DRepRole) DRepState)
currentDRepState forall era.
Lens' (VState era) (Map (Credential 'DRepRole) DRepState)
vsDRepsL
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed forall era.
Era era =>
Term
era (Map (Credential 'ColdCommitteeRole) CommitteeAuthorization)
committeeState (forall era. Lens' (VState era) (CommitteeState era)
vsCommitteeStateL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era.
Lens'
(CommitteeState era)
(Map (Credential 'ColdCommitteeRole) CommitteeAuthorization)
csCommitteeCredsL)
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed forall era. Era era => Term era EpochNo
numDormantEpochs forall era. Lens' (VState era) EpochNo
vsNumDormantEpochsL
committeeL ::
Lens' (Map (Credential 'ColdCommitteeRole) CommitteeAuthorization) (CommitteeState era)
committeeL :: forall era.
Lens'
(Map (Credential 'ColdCommitteeRole) CommitteeAuthorization)
(CommitteeState era)
committeeL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall era.
Map (Credential 'ColdCommitteeRole) CommitteeAuthorization
-> CommitteeState era
CommitteeState (\Map (Credential 'ColdCommitteeRole) CommitteeAuthorization
_ (CommitteeState Map (Credential 'ColdCommitteeRole) CommitteeAuthorization
x) -> Map (Credential 'ColdCommitteeRole) CommitteeAuthorization
x)
pstateT :: forall era. Era era => RootTarget era (PState era) (PState era)
pstateT :: forall era. Era era => RootTarget era (PState era) (PState era)
pstateT =
forall root a b era.
String -> TypeRep root -> (a -> b) -> RootTarget era root (a -> b)
Invert String
"PState" (forall {k} (a :: k). Typeable a => TypeRep a
typeRep @(PState era)) forall era.
Map (KeyHash 'StakePool) PoolParams
-> Map (KeyHash 'StakePool) PoolParams
-> Map (KeyHash 'StakePool) EpochNo
-> Map (KeyHash 'StakePool) Coin
-> PState era
PState
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed forall era.
Era era =>
Term era (Map (KeyHash 'StakePool) PoolParams)
regPools forall era.
Lens' (PState era) (Map (KeyHash 'StakePool) PoolParams)
psStakePoolParamsL
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed forall era.
Era era =>
Term era (Map (KeyHash 'StakePool) PoolParams)
futureRegPools forall era.
Lens' (PState era) (Map (KeyHash 'StakePool) PoolParams)
psFutureStakePoolParamsL
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed forall era. Era era => Term era (Map (KeyHash 'StakePool) EpochNo)
retiring forall era. Lens' (PState era) (Map (KeyHash 'StakePool) EpochNo)
psRetiringL
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed forall era. Era era => Term era (Map (KeyHash 'StakePool) Coin)
poolDeposits forall era. Lens' (PState era) (Map (KeyHash 'StakePool) Coin)
psDepositsL
dstateT :: forall era. Era era => RootTarget era (DState era) (DState era)
dstateT :: forall era. Era era => RootTarget era (DState era) (DState era)
dstateT =
forall root a b era.
String -> TypeRep root -> (a -> b) -> RootTarget era root (a -> b)
Invert String
"DState" (forall {k} (a :: k). Typeable a => TypeRep a
typeRep @(DState era)) forall era.
Map (Credential 'Staking) Coin
-> Map (Credential 'Staking) Coin
-> Map (Credential 'Staking) (KeyHash 'StakePool)
-> Map (Credential 'Staking) DRep
-> Map Ptr (Credential 'Staking)
-> Map FutureGenDeleg GenDelegPair
-> Map (KeyHash 'Genesis) GenDelegPair
-> InstantaneousRewards
-> DState era
dstate
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed forall era. Era era => Term era (Map (Credential 'Staking) Coin)
rewards (forall era. Lens' (DState era) UMap
dsUnifiedL forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' UMap (Map (Credential 'Staking) Coin)
rewardsUMapL)
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed forall era. Era era => Term era (Map (Credential 'Staking) Coin)
stakeDeposits (forall era. Lens' (DState era) UMap
dsUnifiedL forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' UMap (Map (Credential 'Staking) Coin)
stakeDepositsUMapL)
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed forall era.
Era era =>
Term era (Map (Credential 'Staking) (KeyHash 'StakePool))
delegations (forall era. Lens' (DState era) UMap
dsUnifiedL forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' UMap (Map (Credential 'Staking) (KeyHash 'StakePool))
delegationsUMapL)
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed forall era. Era era => Term era (Map (Credential 'Staking) DRep)
drepDelegation (forall era. Lens' (DState era) UMap
dsUnifiedL forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' UMap (Map (Credential 'Staking) DRep)
drepUMapL)
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed forall era. Era era => Term era (Map Ptr (Credential 'Staking))
ptrs (forall era. Lens' (DState era) UMap
dsUnifiedL forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' UMap (Map Ptr (Credential 'Staking))
ptrsUMapL)
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed forall era. Era era => Term era (Map FutureGenDeleg GenDelegPair)
futureGenDelegs forall era. Lens' (DState era) (Map FutureGenDeleg GenDelegPair)
dsFutureGenDelegsL
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed forall era.
Era era =>
Term era (Map (KeyHash 'Genesis) GenDelegPair)
genDelegs (forall era. Lens' (DState era) GenDelegs
dsGenDelegsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' GenDelegs (Map (KeyHash 'Genesis) GenDelegPair)
unGenDelegsL)
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era root2 t root.
RootTarget era root2 t -> Lens' root root2 -> RootTarget era root t
Shift forall era.
Era era =>
RootTarget era InstantaneousRewards InstantaneousRewards
instantaneousRewardsT forall era. Lens' (DState era) InstantaneousRewards
dsIRewardsL
dstate ::
Map (Credential 'Staking) Coin ->
Map (Credential 'Staking) Coin ->
Map (Credential 'Staking) (KeyHash 'StakePool) ->
Map (Credential 'Staking) DRep ->
Map Ptr (Credential 'Staking) ->
Map FutureGenDeleg GenDelegPair ->
Map (KeyHash 'Genesis) GenDelegPair ->
InstantaneousRewards ->
DState era
dstate :: forall era.
Map (Credential 'Staking) Coin
-> Map (Credential 'Staking) Coin
-> Map (Credential 'Staking) (KeyHash 'StakePool)
-> Map (Credential 'Staking) DRep
-> Map Ptr (Credential 'Staking)
-> Map FutureGenDeleg GenDelegPair
-> Map (KeyHash 'Genesis) GenDelegPair
-> InstantaneousRewards
-> DState era
dstate Map (Credential 'Staking) Coin
rew Map (Credential 'Staking) Coin
dep Map (Credential 'Staking) (KeyHash 'StakePool)
deleg Map (Credential 'Staking) DRep
drepdeleg Map Ptr (Credential 'Staking)
ptr Map FutureGenDeleg GenDelegPair
fgen Map (KeyHash 'Genesis) GenDelegPair
gen =
forall era.
UMap
-> Map FutureGenDeleg GenDelegPair
-> GenDelegs
-> InstantaneousRewards
-> DState era
DState
(Split -> UMap
unSplitUMap (Map (Credential 'Staking) Coin
-> Map (Credential 'Staking) Coin
-> Map (Credential 'Staking) (KeyHash 'StakePool)
-> Map (Credential 'Staking) DRep
-> Map (Credential 'Staking) (Set Ptr)
-> Map Ptr (Credential 'Staking)
-> Split
Split Map (Credential 'Staking) Coin
rew Map (Credential 'Staking) Coin
dep Map (Credential 'Staking) (KeyHash 'StakePool)
deleg Map (Credential 'Staking) DRep
drepdeleg (forall a. HasCallStack => String -> a
error String
"Not implemented") Map Ptr (Credential 'Staking)
ptr))
Map FutureGenDeleg GenDelegPair
fgen
(Map (KeyHash 'Genesis) GenDelegPair -> GenDelegs
GenDelegs Map (KeyHash 'Genesis) GenDelegPair
gen)
instantaneousRewardsT ::
forall era.
Era era =>
RootTarget era InstantaneousRewards InstantaneousRewards
instantaneousRewardsT :: forall era.
Era era =>
RootTarget era InstantaneousRewards InstantaneousRewards
instantaneousRewardsT =
forall root a b era.
String -> TypeRep root -> (a -> b) -> RootTarget era root (a -> b)
Invert String
"InstanRew" (forall {k} (a :: k). Typeable a => TypeRep a
typeRep @InstantaneousRewards) Map (Credential 'Staking) Coin
-> Map (Credential 'Staking) Coin
-> DeltaCoin
-> DeltaCoin
-> InstantaneousRewards
InstantaneousRewards
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed forall era. Era era => Term era (Map (Credential 'Staking) Coin)
instanReserves Lens' InstantaneousRewards (Map (Credential 'Staking) Coin)
iRReservesL
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed forall era. Era era => Term era (Map (Credential 'Staking) Coin)
instanTreasury Lens' InstantaneousRewards (Map (Credential 'Staking) Coin)
iRTreasuryL
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed forall era. Era era => Term era DeltaCoin
deltaReserves Lens' InstantaneousRewards DeltaCoin
deltaReservesL
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed forall era. Era era => Term era DeltaCoin
deltaTreasury Lens' InstantaneousRewards DeltaCoin
deltaTreasuryL
allvars :: String
allvars :: String
allvars = forall a. Show a => a -> String
show (forall era r t. RootTarget era r t -> PDoc
ppTarget (forall era.
EraGov era =>
Proof era -> RootTarget era (NewEpochState era) (NewEpochState era)
newEpochStateT Proof ConwayEra
Conway))
printTarget :: RootTarget era root t -> IO ()
printTarget :: forall era root t. RootTarget era root t -> IO ()
printTarget RootTarget era root t
t = String -> IO ()
putStrLn (forall a. Show a => a -> String
show (forall era r t. RootTarget era r t -> PDoc
ppTarget RootTarget era root t
t))
protVer :: Era era => Proof era -> Term era ProtVer
protVer :: forall era. Era era => Proof era -> Term era ProtVer
protVer Proof era
proof =
forall era t. V era t -> Term era t
Var
( forall era t s.
Proof era -> String -> Rep era t -> Access era s t -> V era t
pV
Proof era
proof
String
"protVer"
(forall era. Era era => Proof era -> Rep era ProtVer
ProtVerR Proof era
proof)
(forall era s t. Rep era s -> Lens' s t -> Access era s t
Yes (forall era. Era era => Proof era -> Rep era (PParamsF era)
PParamsR Proof era
proof) forall a b. (a -> b) -> a -> b
$ forall era a. Proof era -> (EraPParams era => a) -> a
withEraPParams Proof era
proof (forall era. Lens' (PParamsF era) (PParams era)
pparamsWrapperL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. EraPParams era => Lens' (PParams era) ProtVer
ppProtocolVersionL))
)
prevProtVer :: Era era => Proof era -> Term era ProtVer
prevProtVer :: forall era. Era era => Proof era -> Term era ProtVer
prevProtVer Proof era
proof =
forall era t. V era t -> Term era t
Var
( forall era t s.
Proof era -> String -> Rep era t -> Access era s t -> V era t
pV
Proof era
proof
String
"prevProtVer"
(forall era. Era era => Proof era -> Rep era ProtVer
ProtVerR Proof era
proof)
(forall era s t. Rep era s -> Lens' s t -> Access era s t
Yes (forall era. Era era => Proof era -> Rep era (PParamsF era)
PParamsR Proof era
proof) forall a b. (a -> b) -> a -> b
$ forall era a. Proof era -> (EraPParams era => a) -> a
withEraPParams Proof era
proof (forall era. Lens' (PParamsF era) (PParams era)
pparamsWrapperL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. EraPParams era => Lens' (PParams era) ProtVer
ppProtocolVersionL))
)
minFeeA :: Era era => Proof era -> Term era Coin
minFeeA :: forall era. Era era => Proof era -> Term era Coin
minFeeA Proof era
proof =
forall era t. V era t -> Term era t
Var
( forall era t s.
Proof era -> String -> Rep era t -> Access era s t -> V era t
pV
Proof era
proof
String
"minFeeA"
forall era. Rep era Coin
CoinR
(forall era s t. Rep era s -> Lens' s t -> Access era s t
Yes (forall era. Era era => Proof era -> Rep era (PParamsF era)
PParamsR Proof era
proof) forall a b. (a -> b) -> a -> b
$ forall era a. Proof era -> (EraPParams era => a) -> a
withEraPParams Proof era
proof (forall era. Lens' (PParamsF era) (PParams era)
pparamsWrapperL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. EraPParams era => Lens' (PParams era) Coin
ppMinFeeAL))
)
minFeeB :: Era era => Proof era -> Term era Coin
minFeeB :: forall era. Era era => Proof era -> Term era Coin
minFeeB Proof era
proof =
forall era t. V era t -> Term era t
Var
( forall era t s.
Proof era -> String -> Rep era t -> Access era s t -> V era t
pV
Proof era
proof
String
"minFeeB"
forall era. Rep era Coin
CoinR
(forall era s t. Rep era s -> Lens' s t -> Access era s t
Yes (forall era. Era era => Proof era -> Rep era (PParamsF era)
PParamsR Proof era
proof) forall a b. (a -> b) -> a -> b
$ forall era a. Proof era -> (EraPParams era => a) -> a
withEraPParams Proof era
proof (forall era. Lens' (PParamsF era) (PParams era)
pparamsWrapperL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. EraPParams era => Lens' (PParams era) Coin
ppMinFeeBL))
)
maxBBSize :: Era era => Proof era -> Term era Natural
maxBBSize :: forall era. Era era => Proof era -> Term era Natural
maxBBSize Proof era
p =
forall era t. V era t -> Term era t
Var
( forall era t s.
Proof era -> String -> Rep era t -> Access era s t -> V era t
pV
Proof era
p
String
"maxBBSize"
forall era. Rep era Natural
NaturalR
(forall era s t. Rep era s -> Lens' s t -> Access era s t
Yes (forall era. Era era => Proof era -> Rep era (PParamsF era)
PParamsR Proof era
p) (forall era a. Proof era -> (EraPParams era => a) -> a
withEraPParams Proof era
p (forall era. Lens' (PParamsF era) (PParams era)
pparamsWrapperL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. EraPParams era => Lens' (PParams era) Word32
ppMaxBBSizeL forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' Word32 Natural
word32NaturalL)))
)
maxTxSize :: Era era => Proof era -> Term era Natural
maxTxSize :: forall era. Era era => Proof era -> Term era Natural
maxTxSize Proof era
p =
forall era t. V era t -> Term era t
Var
( forall era t s.
Proof era -> String -> Rep era t -> Access era s t -> V era t
pV
Proof era
p
String
"maxTxSize"
forall era. Rep era Natural
NaturalR
(forall era s t. Rep era s -> Lens' s t -> Access era s t
Yes (forall era. Era era => Proof era -> Rep era (PParamsF era)
PParamsR Proof era
p) (forall era a. Proof era -> (EraPParams era => a) -> a
withEraPParams Proof era
p (forall era. Lens' (PParamsF era) (PParams era)
pparamsWrapperL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. EraPParams era => Lens' (PParams era) Word32
ppMaxTxSizeL forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' Word32 Natural
word32NaturalL)))
)
fromIntegralBounded ::
forall a b.
(HasCallStack, Integral a, Show a, Integral b, Bounded b, Show b) =>
String ->
a ->
b
fromIntegralBounded :: forall a b.
(HasCallStack, Integral a, Show a, Integral b, Bounded b,
Show b) =>
String -> a -> b
fromIntegralBounded String
name a
x
| forall a. Integral a => a -> Integer
toInteger (forall a. Bounded a => a
minBound :: b) forall a. Ord a => a -> a -> Bool
<= Integer
xi Bool -> Bool -> Bool
&& Integer
xi forall a. Ord a => a -> a -> Bool
<= forall a. Integral a => a -> Integer
toInteger (forall a. Bounded a => a
maxBound :: b) = forall a b. (Integral a, Num b) => a -> b
fromIntegral a
x
| Bool
otherwise =
forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$
String
"While converting "
forall a. [a] -> [a] -> [a]
++ String
name
forall a. [a] -> [a] -> [a]
++ String
", "
forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show a
x forall a. Semigroup a => a -> a -> a
<> String
" is out of bounds: " forall a. Semigroup a => a -> a -> a
<> forall a. Show a => a -> String
show (forall a. Bounded a => a
minBound :: b, forall a. Bounded a => a
maxBound :: b)
where
xi :: Integer
xi = forall a. Integral a => a -> Integer
toInteger a
x
word32NaturalL :: Lens' Word32 Natural
word32NaturalL :: Lens' Word32 Natural
word32NaturalL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall a b. (Integral a, Num b) => a -> b
fromIntegral (\Word32
_ Natural
y -> forall a b.
(HasCallStack, Integral a, Show a, Integral b, Bounded b,
Show b) =>
String -> a -> b
fromIntegralBounded String
"word32NaturaL" (forall a. Integral a => a -> Integer
toInteger Natural
y))
word16NaturalL :: Lens' Word16 Natural
word16NaturalL :: Lens' Word16 Natural
word16NaturalL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall a b. (Integral a, Num b) => a -> b
fromIntegral (\Word16
_ Natural
y -> forall a b.
(HasCallStack, Integral a, Show a, Integral b, Bounded b,
Show b) =>
String -> a -> b
fromIntegralBounded String
"word16NaturalL" (forall a. Integral a => a -> Integer
toInteger Natural
y))
maxBHSize :: Era era => Proof era -> Term era Natural
maxBHSize :: forall era. Era era => Proof era -> Term era Natural
maxBHSize Proof era
p =
forall era t. V era t -> Term era t
Var
( forall era t s.
Proof era -> String -> Rep era t -> Access era s t -> V era t
pV
Proof era
p
String
"maxBHSize"
forall era. Rep era Natural
NaturalR
(forall era s t. Rep era s -> Lens' s t -> Access era s t
Yes (forall era. Era era => Proof era -> Rep era (PParamsF era)
PParamsR Proof era
p) (forall era a. Proof era -> (EraPParams era => a) -> a
withEraPParams Proof era
p (forall era. Lens' (PParamsF era) (PParams era)
pparamsWrapperL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. EraPParams era => Lens' (PParams era) Word16
ppMaxBHSizeL forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lens' Word16 Natural
word16NaturalL)))
)
poolDepAmt :: Era era => Proof era -> Term era Coin
poolDepAmt :: forall era. Era era => Proof era -> Term era Coin
poolDepAmt Proof era
p =
forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$
forall era t s.
Proof era -> String -> Rep era t -> Access era s t -> V era t
pV
Proof era
p
String
"poolDepAmt"
forall era. Rep era Coin
CoinR
(forall era s t. Rep era s -> Lens' s t -> Access era s t
Yes (forall era. Era era => Proof era -> Rep era (PParamsF era)
PParamsR Proof era
p) (forall era a. Proof era -> (EraPParams era => a) -> a
withEraPParams Proof era
p (forall era. Lens' (PParamsF era) (PParams era)
pparamsWrapperL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. EraPParams era => Lens' (PParams era) Coin
ppPoolDepositL)))
keyDepAmt :: Era era => Proof era -> Term era Coin
keyDepAmt :: forall era. Era era => Proof era -> Term era Coin
keyDepAmt Proof era
p =
forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$
forall era t s.
Proof era -> String -> Rep era t -> Access era s t -> V era t
pV
Proof era
p
String
"keyDepAmt"
forall era. Rep era Coin
CoinR
(forall era s t. Rep era s -> Lens' s t -> Access era s t
Yes (forall era. Era era => Proof era -> Rep era (PParamsF era)
PParamsR Proof era
p) (forall era a. Proof era -> (EraPParams era => a) -> a
withEraPParams Proof era
p (forall era. Lens' (PParamsF era) (PParams era)
pparamsWrapperL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. EraPParams era => Lens' (PParams era) Coin
ppKeyDepositL)))
proposalDeposit :: ConwayEraPParams era => Proof era -> Term era Coin
proposalDeposit :: forall era. ConwayEraPParams era => Proof era -> Term era Coin
proposalDeposit Proof era
p =
forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$
forall era t s.
Proof era -> String -> Rep era t -> Access era s t -> V era t
pV
Proof era
p
String
"proposalDeposit"
forall era. Rep era Coin
CoinR
(forall era s t. Rep era s -> Lens' s t -> Access era s t
Yes (forall era. Era era => Proof era -> Rep era (PParamsF era)
PParamsR Proof era
p) (forall era a. Proof era -> (EraPParams era => a) -> a
withEraPParams Proof era
p (forall era. Lens' (PParamsF era) (PParams era)
pparamsWrapperL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. ConwayEraPParams era => Lens' (PParams era) Coin
ppGovActionDepositL)))
maxTxExUnits :: AlonzoEraPParams era => Proof era -> Term era ExUnits
maxTxExUnits :: forall era. AlonzoEraPParams era => Proof era -> Term era ExUnits
maxTxExUnits Proof era
p =
forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$
forall era t s.
Proof era -> String -> Rep era t -> Access era s t -> V era t
pV
Proof era
p
String
"maxTxExUnits"
forall era. Rep era ExUnits
ExUnitsR
(forall era s t. Rep era s -> Lens' s t -> Access era s t
Yes (forall era. Era era => Proof era -> Rep era (PParamsF era)
PParamsR Proof era
p) (forall era a. Proof era -> (EraPParams era => a) -> a
withEraPParams Proof era
p (forall era. Lens' (PParamsF era) (PParams era)
pparamsWrapperL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. AlonzoEraPParams era => Lens' (PParams era) ExUnits
ppMaxTxExUnitsL)))
collateralPercentage :: AlonzoEraPParams era => Proof era -> Term era Natural
collateralPercentage :: forall era. AlonzoEraPParams era => Proof era -> Term era Natural
collateralPercentage Proof era
p =
forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$
forall era t s.
Proof era -> String -> Rep era t -> Access era s t -> V era t
pV
Proof era
p
String
"collateralPercentage"
forall era. Rep era Natural
NaturalR
(forall era s t. Rep era s -> Lens' s t -> Access era s t
Yes (forall era. Era era => Proof era -> Rep era (PParamsF era)
PParamsR Proof era
p) (forall era a. Proof era -> (EraPParams era => a) -> a
withEraPParams Proof era
p (forall era. Lens' (PParamsF era) (PParams era)
pparamsWrapperL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. AlonzoEraPParams era => Lens' (PParams era) Natural
ppCollateralPercentageL)))
drepDeposit :: ConwayEraPParams era => Proof era -> Term era Coin
drepDeposit :: forall era. ConwayEraPParams era => Proof era -> Term era Coin
drepDeposit Proof era
p =
forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$
forall era t s.
Proof era -> String -> Rep era t -> Access era s t -> V era t
pV Proof era
p String
"drepDeposit" forall era. Rep era Coin
CoinR (forall era s t. Rep era s -> Lens' s t -> Access era s t
Yes (forall era. Era era => Proof era -> Rep era (PParamsF era)
PParamsR Proof era
p) (forall era a. Proof era -> (EraPParams era => a) -> a
withEraPParams Proof era
p (forall era. Lens' (PParamsF era) (PParams era)
pparamsWrapperL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. ConwayEraPParams era => Lens' (PParams era) Coin
ppDRepDepositL)))
drepActivity :: ConwayEraPParams era => Proof era -> Term era Base.EpochInterval
drepActivity :: forall era.
ConwayEraPParams era =>
Proof era -> Term era EpochInterval
drepActivity Proof era
p =
forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$
forall era t s.
Proof era -> String -> Rep era t -> Access era s t -> V era t
pV
Proof era
p
String
"drepActivty"
forall era. Rep era EpochInterval
EpochIntervalR
(forall era s t. Rep era s -> Lens' s t -> Access era s t
Yes (forall era. Era era => Proof era -> Rep era (PParamsF era)
PParamsR Proof era
p) (forall era a. Proof era -> (EraPParams era => a) -> a
withEraPParams Proof era
p (forall era. Lens' (PParamsF era) (PParams era)
pparamsWrapperL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era.
ConwayEraPParams era =>
Lens' (PParams era) EpochInterval
ppDRepActivityL)))
maxEpoch :: Era era => Proof era -> Term era Base.EpochInterval
maxEpoch :: forall era. Era era => Proof era -> Term era EpochInterval
maxEpoch Proof era
p =
forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$
forall era t s.
Proof era -> String -> Rep era t -> Access era s t -> V era t
pV
Proof era
p
String
"maxEpoch"
forall era. Rep era EpochInterval
EpochIntervalR
(forall era s t. Rep era s -> Lens' s t -> Access era s t
Yes (forall era. Era era => Proof era -> Rep era (PParamsF era)
PParamsR Proof era
p) (forall era a. Proof era -> (EraPParams era => a) -> a
withEraPParams Proof era
p (forall era. Lens' (PParamsF era) (PParams era)
pparamsWrapperL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. EraPParams era => Lens' (PParams era) EpochInterval
ppEMaxL)))
txbodyterm :: Reflect era => Term era (TxBodyF era)
txbodyterm :: forall era. Reflect era => Term era (TxBodyF era)
txbodyterm = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"txbodyterm" (forall era. Era era => Proof era -> Rep era (TxBodyF era)
TxBodyR forall era. Reflect era => Proof era
reify) forall era s t. Access era s t
No
inputs :: Era era => Term era (Set TxIn)
inputs :: forall era. Era era => Term era (Set TxIn)
inputs = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"inputs" (forall a era. Ord a => Rep era a -> Rep era (Set a)
SetR forall era. Era era => Rep era TxIn
TxInR) forall era s t. Access era s t
No
collateral :: Era era => Term era (Set TxIn)
collateral :: forall era. Era era => Term era (Set TxIn)
collateral = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"collateral" (forall a era. Ord a => Rep era a -> Rep era (Set a)
SetR forall era. Era era => Rep era TxIn
TxInR) forall era s t. Access era s t
No
refInputs :: Era era => Term era (Set TxIn)
refInputs :: forall era. Era era => Term era (Set TxIn)
refInputs = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"refInputs" (forall a era. Ord a => Rep era a -> Rep era (Set a)
SetR forall era. Era era => Rep era TxIn
TxInR) forall era s t. Access era s t
No
outputs :: Era era => Proof era -> Term era [TxOutF era]
outputs :: forall era. Era era => Proof era -> Term era [TxOutF era]
outputs Proof era
p = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Proof era -> String -> Rep era t -> Access era s t -> V era t
pV Proof era
p String
"outputs" (forall era a. Rep era a -> Rep era [a]
ListR (forall era. Era era => Proof era -> Rep era (TxOutF era)
TxOutR Proof era
p)) forall era s t. Access era s t
No
collateralReturn :: Era era => Proof era -> Term era (TxOutF era)
collateralReturn :: forall era. Era era => Proof era -> Term era (TxOutF era)
collateralReturn Proof era
p = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Proof era -> String -> Rep era t -> Access era s t -> V era t
pV Proof era
p String
"collateralReturn" (forall era. Era era => Proof era -> Rep era (TxOutF era)
TxOutR Proof era
p) forall era s t. Access era s t
No
totalCol :: Era era => Term era Coin
totalCol :: forall era. Era era => Term era Coin
totalCol = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"totalCol" forall era. Rep era Coin
CoinR forall era s t. Access era s t
No
certs :: Reflect era => Term era [TxCertF era]
certs :: forall era. Reflect era => Term era [TxCertF era]
certs = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"certs" (forall era a. Rep era a -> Rep era [a]
ListR (forall era. Era era => Proof era -> Rep era (TxCertF era)
TxCertR forall era. Reflect era => Proof era
reify)) forall era s t. Access era s t
No
withdrawals :: forall era. Era era => Term era (Map RewardAccount Coin)
withdrawals :: forall era. Era era => Term era (Map RewardAccount Coin)
withdrawals = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"withdrawals" (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR (forall era. Era era => Rep era RewardAccount
RewardAccountR @era) forall era. Rep era Coin
CoinR) forall era s t. Access era s t
No
txfee :: Era era => Term era Coin
txfee :: forall era. Era era => Term era Coin
txfee = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"txfee" forall era. Rep era Coin
CoinR forall era s t. Access era s t
No
ttl :: Era era => Term era SlotNo
ttl :: forall era. Era era => Term era SlotNo
ttl = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"ttl" forall era. Rep era SlotNo
SlotNoR forall era s t. Access era s t
No
validityInterval :: Era era => Term era ValidityInterval
validityInterval :: forall era. Era era => Term era ValidityInterval
validityInterval = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"validityInterval" forall era. Era era => Rep era ValidityInterval
ValidityIntervalR forall era s t. Access era s t
No
mint :: Era era => Term era (Map ScriptHash (Map AssetName Integer))
mint :: forall era.
Era era =>
Term era (Map ScriptHash (Map AssetName Integer))
mint = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"mint" (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Era era => Rep era ScriptHash
ScriptHashR (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Rep era AssetName
AssetNameR forall era. Rep era Integer
IntegerR)) forall era s t. Access era s t
No
reqSignerHashes :: Era era => Term era (Set (KeyHash 'Witness))
reqSignerHashes :: forall era. Era era => Term era (Set (KeyHash 'Witness))
reqSignerHashes = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"reqSignerHashes" (forall a era. Ord a => Rep era a -> Rep era (Set a)
SetR forall era. Era era => Rep era (KeyHash 'Witness)
WitHashR) forall era s t. Access era s t
No
networkID :: Era era => Term era (Maybe Network)
networkID :: forall era. Era era => Term era (Maybe Network)
networkID = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"networkID" (forall era t1. Rep era t1 -> Rep era (Maybe t1)
MaybeR forall era. Rep era Network
NetworkR) forall era s t. Access era s t
No
adHash :: Era era => Term era (Maybe TxAuxDataHash)
adHash :: forall era. Era era => Term era (Maybe TxAuxDataHash)
adHash = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"adHash" (forall era t1. Rep era t1 -> Rep era (Maybe t1)
MaybeR forall era. Era era => Rep era TxAuxDataHash
TxAuxDataHashR) forall era s t. Access era s t
No
wppHash :: Era era => Term era (Maybe (SafeHash EraIndependentScriptIntegrity))
wppHash :: forall era.
Era era =>
Term era (Maybe (SafeHash EraIndependentScriptIntegrity))
wppHash = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"wppHash" (forall era t1. Rep era t1 -> Rep era (Maybe t1)
MaybeR forall era.
Era era =>
Rep era (SafeHash EraIndependentScriptIntegrity)
ScriptIntegrityHashR) forall era s t. Access era s t
No
txDonation :: Era era => Term era Coin
txDonation :: forall era. Era era => Term era Coin
txDonation = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"txDonation" forall era. Rep era Coin
CoinR forall era s t. Access era s t
No
liftMultiAsset :: Map ScriptHash (Map AssetName Integer) -> MultiAsset
liftMultiAsset :: Map ScriptHash (Map AssetName Integer) -> MultiAsset
liftMultiAsset Map ScriptHash (Map AssetName Integer)
m = Map PolicyID (Map AssetName Integer) -> MultiAsset
MultiAsset (forall k2 k1 a. Ord k2 => (k1 -> k2) -> Map k1 a -> Map k2 a
Map.mapKeys ScriptHash -> PolicyID
PolicyID Map ScriptHash (Map AssetName Integer)
m)
scriptsNeeded :: Reflect era => Term era (ScriptsNeededF era)
scriptsNeeded :: forall era. Reflect era => Term era (ScriptsNeededF era)
scriptsNeeded = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"scriptsNeeded" (forall era. Era era => Proof era -> Rep era (ScriptsNeededF era)
ScriptsNeededR forall era. Reflect era => Proof era
reify) forall era s t. Access era s t
No
smNeededL ::
ScriptsNeeded era ~ ShelleyScriptsNeeded era =>
Lens' (ScriptsNeededF era) (Set ScriptHash)
smNeededL :: forall era.
(ScriptsNeeded era ~ ShelleyScriptsNeeded era) =>
Lens' (ScriptsNeededF era) (Set ScriptHash)
smNeededL =
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens
(\(ScriptsNeededF Proof era
_ (ShelleyScriptsNeeded Set ScriptHash
s)) -> Set ScriptHash
s)
(\(ScriptsNeededF Proof era
p ScriptsNeeded era
_) Set ScriptHash
s -> forall era. Proof era -> ScriptsNeeded era -> ScriptsNeededF era
ScriptsNeededF Proof era
p (forall era. Set ScriptHash -> ShelleyScriptsNeeded era
ShelleyScriptsNeeded Set ScriptHash
s))
acNeededL ::
ScriptsNeeded era ~ AlonzoScriptsNeeded era =>
Lens' (ScriptsNeededF era) [(PlutusPurposeF era, ScriptHash)]
acNeededL :: forall era.
(ScriptsNeeded era ~ AlonzoScriptsNeeded era) =>
Lens' (ScriptsNeededF era) [(PlutusPurposeF era, ScriptHash)]
acNeededL =
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens
(\(ScriptsNeededF Proof era
p (AlonzoScriptsNeeded [(PlutusPurpose AsIxItem era, ScriptHash)]
s)) -> forall a b. (a -> b) -> [a] -> [b]
map (forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (b, d) (c, d)
first (forall era.
Proof era -> PlutusPurpose AsIxItem era -> PlutusPurposeF era
PlutusPurposeF Proof era
p)) [(PlutusPurpose AsIxItem era, ScriptHash)]
s)
( \(ScriptsNeededF Proof era
p ScriptsNeeded era
_) [(PlutusPurposeF era, ScriptHash)]
s ->
forall era. Proof era -> ScriptsNeeded era -> ScriptsNeededF era
ScriptsNeededF Proof era
p (forall era.
[(PlutusPurpose AsIxItem era, ScriptHash)]
-> AlonzoScriptsNeeded era
AlonzoScriptsNeeded (forall a b. (a -> b) -> [a] -> [b]
map (forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (b, d) (c, d)
first forall era. PlutusPurposeF era -> PlutusPurpose AsIxItem era
unPlutusPurposeF) [(PlutusPurposeF era, ScriptHash)]
s))
)
extraCol :: Era era => Term era Coin
= forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"extraCol" forall era. Rep era Coin
CoinR forall era s t. Access era s t
No
sumCol :: Era era => Term era Coin
sumCol :: forall era. Era era => Term era Coin
sumCol = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"sumCol" forall era. Rep era Coin
CoinR forall era s t. Access era s t
No
colRetAddr :: Era era => Term era Addr
colRetAddr :: forall era. Era era => Term era Addr
colRetAddr = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"colRetAddr" forall era. Era era => Rep era Addr
AddrR forall era s t. Access era s t
No
colRetCoin :: Era era => Term era Coin
colRetCoin :: forall era. Era era => Term era Coin
colRetCoin = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"colRetCoin" forall era. Rep era Coin
CoinR forall era s t. Access era s t
No
owed :: Era era => Term era Coin
owed :: forall era. Era era => Term era Coin
owed = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"owed" forall era. Rep era Coin
CoinR forall era s t. Access era s t
No
txbody :: Reflect era => Term era (TxBodyF era)
txbody :: forall era. Reflect era => Term era (TxBodyF era)
txbody = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"txbody" (forall era. Era era => Proof era -> Rep era (TxBodyF era)
TxBodyR forall era. Reflect era => Proof era
reify) forall era s t. Access era s t
No
txwits :: Reflect era => Term era (TxWitsF era)
txwits :: forall era. Reflect era => Term era (TxWitsF era)
txwits = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"txwits" (forall era. Era era => Proof era -> Rep era (TxWitsF era)
TxWitsR forall era. Reflect era => Proof era
reify) forall era s t. Access era s t
No
txauxdata :: Reflect era => Term era (Maybe (TxAuxDataF era))
txauxdata :: forall era. Reflect era => Term era (Maybe (TxAuxDataF era))
txauxdata = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"txauxdata" (forall era t1. Rep era t1 -> Rep era (Maybe t1)
MaybeR (forall era. Era era => Proof era -> Rep era (TxAuxDataF era)
TxAuxDataR forall era. Reflect era => Proof era
reify)) forall era s t. Access era s t
No
txisvalid :: Era era => Term era IsValid
txisvalid :: forall era. Era era => Term era IsValid
txisvalid = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"txisvalid" forall era. Rep era IsValid
IsValidR forall era s t. Access era s t
No
valids :: Era era => Term era [IsValid]
valids :: forall era. Era era => Term era [IsValid]
valids = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"valids" (forall era a. Rep era a -> Rep era [a]
ListR forall era. Rep era IsValid
IsValidR) forall era s t. Access era s t
No
txterm :: Reflect era => Term era (TxF era)
txterm :: forall era. Reflect era => Term era (TxF era)
txterm = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"txterm" (forall era. Era era => Proof era -> Rep era (TxF era)
TxR forall era. Reflect era => Proof era
reify) forall era s t. Access era s t
No
getRwdCredL :: Lens' RewardAccount (Credential 'Staking)
getRwdCredL :: Lens' RewardAccount (Credential 'Staking)
getRwdCredL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens RewardAccount -> Credential 'Staking
raCredential (\RewardAccount
r Credential 'Staking
c -> RewardAccount
r {raCredential :: Credential 'Staking
raCredential = Credential 'Staking
c})
txOutFL :: Lens' (TxOutF era) (TxOut era)
txOutFL :: forall era. Lens' (TxOutF era) (TxOut era)
txOutFL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall era. TxOutF era -> TxOut era
unTxOut (\(TxOutF Proof era
p TxOut era
_) TxOut era
y -> forall era. Proof era -> TxOut era -> TxOutF era
TxOutF Proof era
p TxOut era
y)
valueFL :: Reflect era => Lens' (Value era) (ValueF era)
valueFL :: forall era. Reflect era => Lens' (Value era) (ValueF era)
valueFL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens (forall era. Proof era -> Value era -> ValueF era
ValueF forall era. Reflect era => Proof era
reify) (\Value era
_ (ValueF Proof era
_ Value era
u) -> Value era
u)
lensVC :: Val t => Lens' t Coin
lensVC :: forall t. Val t => Lens' t Coin
lensVC = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall t. Val t => t -> Coin
coin forall a b. (a -> b) -> a -> b
$ \t
t Coin
c -> forall t. Val t => (Coin -> Coin) -> t -> t
modifyCoin (forall a b. a -> b -> a
const Coin
c) t
t
valueFCoinL :: (HasCallStack, Reflect era) => Lens' (ValueF era) Coin
valueFCoinL :: forall era. (HasCallStack, Reflect era) => Lens' (ValueF era) Coin
valueFCoinL =
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens
(forall t. Val t => t -> Coin
coin forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. ValueF era -> Value era
unValue)
( \(ValueF Proof era
p Value era
v) c :: Coin
c@(Coin Integer
i) ->
if Integer
i forall a. Ord a => a -> a -> Bool
< Integer
0
then forall a. HasCallStack => String -> a
error (String
"Coin is less than 0 " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Integer
i forall a. [a] -> [a] -> [a]
++ String
" in valueFCoinL")
else (forall era. Proof era -> Value era -> ValueF era
ValueF Proof era
p (forall t. Val t => (Coin -> Coin) -> t -> t
modifyCoin (forall a b. a -> b -> a
const Coin
c) Value era
v))
)
outputCoinL :: (HasCallStack, Reflect era) => Lens' (TxOutF era) Coin
outputCoinL :: forall era. (HasCallStack, Reflect era) => Lens' (TxOutF era) Coin
outputCoinL =
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens
(\(TxOutF Proof era
_ TxOut era
out) -> TxOut era
out forall s a. s -> Getting a s a -> a
^. forall era. (HasCallStack, EraTxOut era) => Lens' (TxOut era) Coin
coinTxOutL)
(\(TxOutF Proof era
p TxOut era
out) Coin
c -> forall era. Proof era -> TxOut era -> TxOutF era
TxOutF Proof era
p (TxOut era
out forall a b. a -> (a -> b) -> b
& forall era. (HasCallStack, EraTxOut era) => Lens' (TxOut era) Coin
coinTxOutL forall s t a b. ASetter s t a b -> b -> s -> t
.~ Coin
c))
valCoinF :: (HasCallStack, Reflect era) => Field era (ValueF era) Coin
valCoinF :: forall era.
(HasCallStack, Reflect era) =>
Field era (ValueF era) Coin
valCoinF = forall era t s.
Era era =>
String -> Rep era t -> Rep era s -> Lens' s t -> Field era s t
Field String
"valCoin" forall era. Rep era Coin
CoinR (forall era. Era era => Proof era -> Rep era (ValueF era)
ValueR forall era. Reflect era => Proof era
reify) forall era. (HasCallStack, Reflect era) => Lens' (ValueF era) Coin
valueFCoinL
valCoin :: (HasCallStack, Reflect era) => Term era Coin
valCoin :: forall era. (HasCallStack, Reflect era) => Term era Coin
valCoin = forall era rec field. Field era rec field -> Term era field
fieldToTerm forall era.
(HasCallStack, Reflect era) =>
Field era (ValueF era) Coin
valCoinF
maryValueMultiAssetL :: Lens' MaryValue MultiAsset
maryValueMultiAssetL :: Lens' MaryValue MultiAsset
maryValueMultiAssetL =
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens
(\(MaryValue Coin
_ MultiAsset
ma) -> MultiAsset
ma)
(\(MaryValue Coin
c MultiAsset
_) MultiAsset
ma -> Coin -> MultiAsset -> MaryValue
MaryValue Coin
c MultiAsset
ma)
valueFMultiAssetL :: Lens' (ValueF era) MultiAsset
valueFMultiAssetL :: forall era. Lens' (ValueF era) MultiAsset
valueFMultiAssetL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall era. ValueF era -> MultiAsset
get forall era. ValueF era -> MultiAsset -> ValueF era
put
where
get :: ValueF era -> MultiAsset
get :: forall era. ValueF era -> MultiAsset
get (ValueF Proof era
p Value era
x) = case forall era. Proof era -> ValueWit era
whichValue Proof era
p of
ValueWit era
ValueShelleyToAllegra -> Map PolicyID (Map AssetName Integer) -> MultiAsset
MultiAsset forall k a. Map k a
Map.empty
ValueWit era
ValueMaryToConway -> Value era
x forall s a. s -> Getting a s a -> a
^. Lens' MaryValue MultiAsset
maryValueMultiAssetL
put :: ValueF era -> MultiAsset -> ValueF era
put :: forall era. ValueF era -> MultiAsset -> ValueF era
put (ValueF Proof era
p Value era
x) MultiAsset
new = case forall era. Proof era -> ValueWit era
whichValue Proof era
p of
ValueWit era
ValueShelleyToAllegra -> forall era. Proof era -> Value era -> ValueF era
ValueF Proof era
p Value era
x
ValueWit era
ValueMaryToConway -> forall era. Proof era -> Value era -> ValueF era
ValueF Proof era
p (Value era
x forall a b. a -> (a -> b) -> b
& Lens' MaryValue MultiAsset
maryValueMultiAssetL forall s t a b. ASetter s t a b -> b -> s -> t
.~ MultiAsset
new)
valueFMultiAssetF :: Reflect era => Field era (ValueF era) MultiAsset
valueFMultiAssetF :: forall era. Reflect era => Field era (ValueF era) MultiAsset
valueFMultiAssetF = forall era t s.
Era era =>
String -> Rep era t -> Rep era s -> Lens' s t -> Field era s t
Field String
"valueFMultiAsset" forall era. Era era => Rep era MultiAsset
MultiAssetR (forall era. Era era => Proof era -> Rep era (ValueF era)
ValueR forall era. Reflect era => Proof era
reify) forall era. Lens' (ValueF era) MultiAsset
valueFMultiAssetL
valueFMultiAsset :: Reflect era => Term era MultiAsset
valueFMultiAsset :: forall era. Reflect era => Term era MultiAsset
valueFMultiAsset = forall era rec field. Field era rec field -> Term era field
fieldToTerm forall era. Reflect era => Field era (ValueF era) MultiAsset
valueFMultiAssetF
txoutAddressF :: Reflect era => Field era (TxOutF era) Addr
txoutAddressF :: forall era. Reflect era => Field era (TxOutF era) Addr
txoutAddressF = forall era t s.
Era era =>
String -> Rep era t -> Rep era s -> Lens' s t -> Field era s t
Field String
"txoutAddress" forall era. Era era => Rep era Addr
AddrR (forall era. Era era => Proof era -> Rep era (TxOutF era)
TxOutR forall era. Reflect era => Proof era
reify) (forall era. Lens' (TxOutF era) (TxOut era)
txOutFL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. EraTxOut era => Lens' (TxOut era) Addr
addrTxOutL)
txoutAddress :: Reflect era => Term era Addr
txoutAddress :: forall era. Reflect era => Term era Addr
txoutAddress = forall era rec field. Field era rec field -> Term era field
fieldToTerm forall era. Reflect era => Field era (TxOutF era) Addr
txoutAddressF
txoutCoinF :: (HasCallStack, Reflect era) => Field era (TxOutF era) Coin
txoutCoinF :: forall era.
(HasCallStack, Reflect era) =>
Field era (TxOutF era) Coin
txoutCoinF = forall era t s.
Era era =>
String -> Rep era t -> Rep era s -> Lens' s t -> Field era s t
Field String
"txoutCoin" forall era. Rep era Coin
CoinR (forall era. Era era => Proof era -> Rep era (TxOutF era)
TxOutR forall era. Reflect era => Proof era
reify) forall era. (HasCallStack, Reflect era) => Lens' (TxOutF era) Coin
outputCoinL
txoutCoin :: (HasCallStack, Reflect era) => Term era Coin
txoutCoin :: forall era. (HasCallStack, Reflect era) => Term era Coin
txoutCoin = forall era rec field. Field era rec field -> Term era field
fieldToTerm forall era.
(HasCallStack, Reflect era) =>
Field era (TxOutF era) Coin
txoutCoinF
txoutAmountF :: Reflect era => Field era (TxOutF era) (ValueF era)
txoutAmountF :: forall era. Reflect era => Field era (TxOutF era) (ValueF era)
txoutAmountF = forall era t s.
Era era =>
String -> Rep era t -> Rep era s -> Lens' s t -> Field era s t
Field String
"txoutAmount" (forall era. Era era => Proof era -> Rep era (ValueF era)
ValueR forall era. Reflect era => Proof era
reify) (forall era. Era era => Proof era -> Rep era (TxOutF era)
TxOutR forall era. Reflect era => Proof era
reify) (forall era. Lens' (TxOutF era) (TxOut era)
txOutFL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. EraTxOut era => Lens' (TxOut era) (Value era)
valueTxOutL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Reflect era => Lens' (Value era) (ValueF era)
valueFL)
txoutAmount :: Reflect era => Term era (ValueF era)
txoutAmount :: forall era. Reflect era => Term era (ValueF era)
txoutAmount = forall era rec field. Field era rec field -> Term era field
fieldToTerm forall era. Reflect era => Field era (TxOutF era) (ValueF era)
txoutAmountF
scriptWits :: Reflect era => Term era (Map ScriptHash (ScriptF era))
scriptWits :: forall era. Reflect era => Term era (Map ScriptHash (ScriptF era))
scriptWits = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"scriptWits" (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Era era => Rep era ScriptHash
ScriptHashR (forall era. Era era => Proof era -> Rep era (ScriptF era)
ScriptR forall era. Reflect era => Proof era
reify)) forall era s t. Access era s t
No
redeemers :: Reflect era => Term era (Map (PlutusPointerF era) (Data era, ExUnits))
redeemers :: forall era.
Reflect era =>
Term era (Map (PlutusPointerF era) (Data era, ExUnits))
redeemers = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"redeemers" (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR (forall era. Era era => Proof era -> Rep era (PlutusPointerF era)
RdmrPtrR forall era. Reflect era => Proof era
reify) (forall era a b. Rep era a -> Rep era b -> Rep era (a, b)
PairR forall era. Era era => Rep era (Data era)
DataR forall era. Rep era ExUnits
ExUnitsR)) forall era s t. Access era s t
No
bootWits :: forall era. Reflect era => Term era (Set BootstrapWitness)
bootWits :: forall era. Reflect era => Term era (Set BootstrapWitness)
bootWits = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"bootWits" (forall a era. Ord a => Rep era a -> Rep era (Set a)
SetR (forall era. Era era => Rep era BootstrapWitness
BootstrapWitnessR @era)) forall era s t. Access era s t
No
dataWits :: Reflect era => Term era (Map DataHash (Data era))
dataWits :: forall era. Reflect era => Term era (Map DataHash (Data era))
dataWits = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"dataWits" (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Era era => Rep era DataHash
DataHashR forall era. Era era => Rep era (Data era)
DataR) forall era s t. Access era s t
No
keyWits :: Reflect era => Term era (Set (WitVKey 'Witness))
keyWits :: forall era. Reflect era => Term era (Set (WitVKey 'Witness))
keyWits = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"keyWits" (forall a era. Ord a => Rep era a -> Rep era (Set a)
SetR (forall era. Era era => Proof era -> Rep era (WitVKey 'Witness)
WitVKeyR forall era. Reflect era => Proof era
reify)) forall era s t. Access era s t
No
witsTarget ::
Reflect era =>
Term era (Set BootstrapWitness) ->
Term era (Set (WitVKey 'Witness)) ->
Target era (TxWits era)
witsTarget :: forall era.
Reflect era =>
Term era (Set BootstrapWitness)
-> Term era (Set (WitVKey 'Witness)) -> Target era (TxWits era)
witsTarget Term era (Set BootstrapWitness)
bootWitsParam Term era (Set (WitVKey 'Witness))
keyWitsParam =
forall a b era. String -> (a -> b) -> RootTarget era Void (a -> b)
Constr String
"TxWits" Map ScriptHash (ScriptF era)
-> Map (PlutusPointerF era) (Data era, ExUnits)
-> Set BootstrapWitness
-> Map DataHash (Data era)
-> Set (WitVKey 'Witness)
-> TxWits era
witsf forall era a t. Target era (a -> t) -> Term era a -> Target era t
^$ forall era. Reflect era => Term era (Map ScriptHash (ScriptF era))
scriptWits forall era a t. Target era (a -> t) -> Term era a -> Target era t
^$ forall era.
Reflect era =>
Term era (Map (PlutusPointerF era) (Data era, ExUnits))
redeemers forall era a t. Target era (a -> t) -> Term era a -> Target era t
^$ Term era (Set BootstrapWitness)
bootWitsParam forall era a t. Target era (a -> t) -> Term era a -> Target era t
^$ forall era. Reflect era => Term era (Map DataHash (Data era))
dataWits forall era a t. Target era (a -> t) -> Term era a -> Target era t
^$ Term era (Set (WitVKey 'Witness))
keyWitsParam
where
proof :: Proof era
proof = forall era. Reflect era => Proof era
reify
witsf :: Map ScriptHash (ScriptF era)
-> Map (PlutusPointerF era) (Data era, ExUnits)
-> Set BootstrapWitness
-> Map DataHash (Data era)
-> Set (WitVKey 'Witness)
-> TxWits era
witsf Map ScriptHash (ScriptF era)
script Map (PlutusPointerF era) (Data era, ExUnits)
redeem Set BootstrapWitness
boot Map DataHash (Data era)
dataw Set (WitVKey 'Witness)
key =
forall era.
Policy -> Proof era -> [WitnessesField era] -> TxWits era
newWitnesses
Policy
merge
Proof era
proof
[ forall era. Set (WitVKey 'Witness) -> WitnessesField era
AddrWits Set (WitVKey 'Witness)
key
, forall era. Set BootstrapWitness -> WitnessesField era
BootWits Set BootstrapWitness
boot
, forall era. Map ScriptHash (Script era) -> WitnessesField era
ScriptWits (forall a b k. (a -> b) -> Map k a -> Map k b
Map.map forall era. ScriptF era -> Script era
unScriptF Map ScriptHash (ScriptF era)
script)
, forall era. TxDats era -> WitnessesField era
DataWits (forall era. Era era => Map DataHash (Data era) -> TxDats era
TxDats Map DataHash (Data era)
dataw)
, forall era. Redeemers era -> WitnessesField era
RdmrWits (forall era.
Proof era
-> [(PlutusPurpose AsIx era, (Data era, ExUnits))] -> Redeemers era
mkRedeemers Proof era
proof forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map (forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (b, d) (c, d)
first forall era. PlutusPointerF era -> PlutusPurpose AsIx era
unPlutusPointerF) forall a b. (a -> b) -> a -> b
$ forall k a. Map k a -> [(k, a)]
Map.toList forall a b. (a -> b) -> a -> b
$ Map (PlutusPointerF era) (Data era, ExUnits)
redeem)
]
txTarget ::
Reflect era =>
Term era (TxBodyF era) ->
Term era (Set BootstrapWitness) ->
Term era (Set (WitVKey 'Witness)) ->
Target era (TxF era)
txTarget :: forall era.
Reflect era =>
Term era (TxBodyF era)
-> Term era (Set BootstrapWitness)
-> Term era (Set (WitVKey 'Witness))
-> Target era (TxF era)
txTarget Term era (TxBodyF era)
bodyparam Term era (Set BootstrapWitness)
bootWitsParam Term era (Set (WitVKey 'Witness))
keyWitsParam =
forall a b era. String -> (a -> b) -> RootTarget era Void (a -> b)
Constr String
"tx" forall {era}.
TxBodyF era
-> TxWits era -> Maybe (TxAuxDataF era) -> IsValid -> TxF era
txf forall era a t. Target era (a -> t) -> Term era a -> Target era t
^$ Term era (TxBodyF era)
bodyparam forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ Target era (TxWits era)
wits forall era a t. Target era (a -> t) -> Term era a -> Target era t
^$ forall era. Reflect era => Term era (Maybe (TxAuxDataF era))
txauxdata forall era a t. Target era (a -> t) -> Term era a -> Target era t
^$ forall era. Era era => Term era IsValid
txisvalid
where
wits :: Target era (TxWits era)
wits = forall era.
Reflect era =>
Term era (Set BootstrapWitness)
-> Term era (Set (WitVKey 'Witness)) -> Target era (TxWits era)
witsTarget Term era (Set BootstrapWitness)
bootWitsParam Term era (Set (WitVKey 'Witness))
keyWitsParam
txf :: TxBodyF era
-> TxWits era -> Maybe (TxAuxDataF era) -> IsValid -> TxF era
txf (TxBodyF Proof era
proof TxBody era
txb) TxWits era
w Maybe (TxAuxDataF era)
auxs IsValid
isvalid =
forall era. Proof era -> Tx era -> TxF era
TxF Proof era
proof (forall era. Proof era -> [TxField era] -> Tx era
newTx Proof era
proof [forall era. TxBody era -> TxField era
Body TxBody era
txb, forall era. TxWits era -> TxField era
TxWits TxWits era
w, forall era. [TxAuxData era] -> TxField era
AuxData' (forall {era}. Maybe (TxAuxDataF era) -> [TxAuxData era]
fixM Maybe (TxAuxDataF era)
auxs), forall era. IsValid -> TxField era
Valid IsValid
isvalid])
fixM :: Maybe (TxAuxDataF era) -> [TxAuxData era]
fixM Maybe (TxAuxDataF era)
Nothing = []
fixM (Just (TxAuxDataF Proof era
_ TxAuxData era
x)) = [TxAuxData era
x]
txbodyTarget ::
Reflect era =>
Term era Coin ->
Term era (Maybe ScriptIntegrityHash) ->
Term era Coin ->
Target era (TxBodyF era)
txbodyTarget :: forall era.
Reflect era =>
Term era Coin
-> Term era (Maybe (SafeHash EraIndependentScriptIntegrity))
-> Term era Coin
-> Target era (TxBodyF era)
txbodyTarget Term era Coin
feeparam Term era (Maybe (SafeHash EraIndependentScriptIntegrity))
wpphashparam Term era Coin
totalColParam =
forall a b era. String -> (a -> b) -> RootTarget era Void (a -> b)
Constr String
"txbody" Set TxIn
-> Set TxIn
-> Set TxIn
-> [TxOutF era]
-> TxOutF era
-> Coin
-> [TxCertF era]
-> Map RewardAccount Coin
-> SlotNo
-> ValidityInterval
-> Map ScriptHash (Map AssetName Integer)
-> Set (KeyHash 'Witness)
-> Maybe Network
-> Maybe TxAuxDataHash
-> Maybe (SafeHash EraIndependentScriptIntegrity)
-> Coin
-> Coin
-> TxBodyF era
txbodyf
forall era a t. Target era (a -> t) -> Term era a -> Target era t
^$ forall era. Era era => Term era (Set TxIn)
inputs
forall era a t. Target era (a -> t) -> Term era a -> Target era t
^$ forall era. Era era => Term era (Set TxIn)
collateral
forall era a t. Target era (a -> t) -> Term era a -> Target era t
^$ forall era. Era era => Term era (Set TxIn)
refInputs
forall era a t. Target era (a -> t) -> Term era a -> Target era t
^$ (forall era. Era era => Proof era -> Term era [TxOutF era]
outputs Proof era
proof)
forall era a t. Target era (a -> t) -> Term era a -> Target era t
^$ (forall era. Era era => Proof era -> Term era (TxOutF era)
collateralReturn Proof era
proof)
forall era a t. Target era (a -> t) -> Term era a -> Target era t
^$ Term era Coin
totalColParam
forall era a t. Target era (a -> t) -> Term era a -> Target era t
^$ forall era. Reflect era => Term era [TxCertF era]
certs
forall era a t. Target era (a -> t) -> Term era a -> Target era t
^$ forall era. Era era => Term era (Map RewardAccount Coin)
withdrawals
forall era a t. Target era (a -> t) -> Term era a -> Target era t
^$ forall era. Era era => Term era SlotNo
ttl
forall era a t. Target era (a -> t) -> Term era a -> Target era t
^$ forall era. Era era => Term era ValidityInterval
validityInterval
forall era a t. Target era (a -> t) -> Term era a -> Target era t
^$ forall era.
Era era =>
Term era (Map ScriptHash (Map AssetName Integer))
mint
forall era a t. Target era (a -> t) -> Term era a -> Target era t
^$ forall era. Era era => Term era (Set (KeyHash 'Witness))
reqSignerHashes
forall era a t. Target era (a -> t) -> Term era a -> Target era t
^$ forall era. Era era => Term era (Maybe Network)
networkID
forall era a t. Target era (a -> t) -> Term era a -> Target era t
^$ forall era. Era era => Term era (Maybe TxAuxDataHash)
adHash
forall era a t. Target era (a -> t) -> Term era a -> Target era t
^$ Term era (Maybe (SafeHash EraIndependentScriptIntegrity))
wpphashparam
forall era a t. Target era (a -> t) -> Term era a -> Target era t
^$ Term era Coin
feeparam
forall era a t. Target era (a -> t) -> Term era a -> Target era t
^$ forall era. Era era => Term era Coin
txDonation
where
proof :: Proof era
proof = forall era. Reflect era => Proof era
reify
txbodyf :: Set TxIn
-> Set TxIn
-> Set TxIn
-> [TxOutF era]
-> TxOutF era
-> Coin
-> [TxCertF era]
-> Map RewardAccount Coin
-> SlotNo
-> ValidityInterval
-> Map ScriptHash (Map AssetName Integer)
-> Set (KeyHash 'Witness)
-> Maybe Network
-> Maybe TxAuxDataHash
-> Maybe (SafeHash EraIndependentScriptIntegrity)
-> Coin
-> Coin
-> TxBodyF era
txbodyf
Set TxIn
ins
Set TxIn
col
Set TxIn
refs
[TxOutF era]
out
(TxOutF Proof era
_ TxOut era
colret)
Coin
totcol
[TxCertF era]
cs
Map RewardAccount Coin
ws
SlotNo
tt
ValidityInterval
vi
Map ScriptHash (Map AssetName Integer)
mnt
Set (KeyHash 'Witness)
req
Maybe Network
net
Maybe TxAuxDataHash
adh
Maybe (SafeHash EraIndependentScriptIntegrity)
wpp
Coin
fee
Coin
donate =
forall era. Proof era -> TxBody era -> TxBodyF era
TxBodyF
Proof era
proof
( forall era.
EraTxBody era =>
Proof era -> [TxBodyField era] -> TxBody era
newTxBody
Proof era
proof
[ forall era. Set TxIn -> TxBodyField era
Inputs Set TxIn
ins
, forall era. Set TxIn -> TxBodyField era
Collateral Set TxIn
col
, forall era. Set TxIn -> TxBodyField era
RefInputs Set TxIn
refs
, forall era. [TxOut era] -> TxBodyField era
Outputs' (forall a b. (a -> b) -> [a] -> [b]
map forall era. TxOutF era -> TxOut era
unTxOut [TxOutF era]
out)
, forall era. StrictMaybe (TxOut era) -> TxBodyField era
CollateralReturn (forall a. a -> StrictMaybe a
SJust TxOut era
colret)
,
forall era. StrictMaybe Coin -> TxBodyField era
TotalCol (forall a. a -> StrictMaybe a
SJust Coin
totcol)
, forall era. [TxCert era] -> TxBodyField era
Certs' (forall a b. (a -> b) -> [a] -> [b]
map forall era. TxCertF era -> TxCert era
unTxCertF [TxCertF era]
cs)
, forall era. Withdrawals -> TxBodyField era
Withdrawals' (Map RewardAccount Coin -> Withdrawals
Withdrawals Map RewardAccount Coin
ws)
, forall era. Coin -> TxBodyField era
Txfee Coin
fee
, forall era. SlotNo -> TxBodyField era
TTL SlotNo
tt
, forall era. ValidityInterval -> TxBodyField era
Vldt ValidityInterval
vi
, forall era. MultiAsset -> TxBodyField era
Fields.Mint (Map ScriptHash (Map AssetName Integer) -> MultiAsset
liftMultiAsset Map ScriptHash (Map AssetName Integer)
mnt)
, forall era. Set (KeyHash 'Witness) -> TxBodyField era
ReqSignerHashes Set (KeyHash 'Witness)
req
, forall era. StrictMaybe Network -> TxBodyField era
Txnetworkid (forall a. Maybe a -> StrictMaybe a
maybeToStrictMaybe Maybe Network
net)
, forall era. StrictMaybe TxAuxDataHash -> TxBodyField era
AdHash (forall a. Maybe a -> StrictMaybe a
maybeToStrictMaybe Maybe TxAuxDataHash
adh)
, forall era.
StrictMaybe (SafeHash EraIndependentScriptIntegrity)
-> TxBodyField era
WppHash (forall a. Maybe a -> StrictMaybe a
maybeToStrictMaybe Maybe (SafeHash EraIndependentScriptIntegrity)
wpp)
, forall era. Coin -> TxBodyField era
TreasuryDonation Coin
donate
]
)
allowMIRTransfer :: Proof era -> Term era Bool
allowMIRTransfer :: forall era. Proof era -> Term era Bool
allowMIRTransfer Proof era
p = forall era t. Rep era t -> t -> Term era t
Lit forall era. Rep era Bool
BoolR (ProtVer -> Bool
HardForks.allowMIRTransfer (forall era. Proof era -> ProtVer
protocolVersion Proof era
p))
constitution :: Era era => Term era (Constitution era)
constitution :: forall era. Era era => Term era (Constitution era)
constitution = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"constitution" forall era. Era era => Rep era (Constitution era)
ConstitutionR forall era s t. Access era s t
No
enactTreasury :: Era era => Term era Coin
enactTreasury :: forall era. Era era => Term era Coin
enactTreasury = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"enactTreasury" forall era. Rep era Coin
CoinR forall era s t. Access era s t
No
enactWithdrawals :: forall era. Era era => Term era (Map (Credential 'Staking) Coin)
enactWithdrawals :: forall era. Era era => Term era (Map (Credential 'Staking) Coin)
enactWithdrawals = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"enactWithdrawals" (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Era era => Rep era (Credential 'Staking)
CredR forall era. Rep era Coin
CoinR) forall era s t. Access era s t
No
currentGovActionStates ::
Era era => Term era (Map GovActionId (GovActionState era))
currentGovActionStates :: forall era.
Era era =>
Term era (Map GovActionId (GovActionState era))
currentGovActionStates = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"currentGovActionStates" (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Era era => Rep era GovActionId
GovActionIdR forall era. Era era => Rep era (GovActionState era)
GovActionStateR) forall era s t. Access era s t
No
currentProposalOrder :: Era era => Term era [GovActionId]
currentProposalOrder :: forall era. Era era => Term era [GovActionId]
currentProposalOrder = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"currentProposalOrder" (forall era a. Rep era a -> Rep era [a]
ListR forall era. Era era => Rep era GovActionId
GovActionIdR) forall era s t. Access era s t
No
prevGovActionStates :: Era era => Term era (Map GovActionId (GovActionState era))
prevGovActionStates :: forall era.
Era era =>
Term era (Map GovActionId (GovActionState era))
prevGovActionStates = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"prevGovActionStates" (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Era era => Rep era GovActionId
GovActionIdR forall era. Era era => Rep era (GovActionState era)
GovActionStateR) forall era s t. Access era s t
No
prevProposalOrder :: Era era => Term era [GovActionId]
prevProposalOrder :: forall era. Era era => Term era [GovActionId]
prevProposalOrder = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"prevProposalOrder" (forall era a. Rep era a -> Rep era [a]
ListR forall era. Era era => Rep era GovActionId
GovActionIdR) forall era s t. Access era s t
No
previousCommitteeState ::
Era era =>
Term
era
( Map
(Credential 'ColdCommitteeRole)
(Maybe (Credential 'HotCommitteeRole))
)
previousCommitteeState :: forall era.
Era era =>
Term
era
(Map
(Credential 'ColdCommitteeRole)
(Maybe (Credential 'HotCommitteeRole)))
previousCommitteeState = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"previousCommitteeState" (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Era era => Rep era (Credential 'ColdCommitteeRole)
CommColdCredR (forall era t1. Rep era t1 -> Rep era (Maybe t1)
MaybeR forall era. Era era => Rep era (Credential 'HotCommitteeRole)
CommHotCredR)) forall era s t. Access era s t
No
commMembers :: Era era => Term era (Map (Credential 'ColdCommitteeRole) EpochNo)
commMembers :: forall era.
Era era =>
Term era (Map (Credential 'ColdCommitteeRole) EpochNo)
commMembers = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"commMembers" (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Era era => Rep era (Credential 'ColdCommitteeRole)
CommColdCredR forall era. Rep era EpochNo
EpochR) forall era s t. Access era s t
No
commQuorum :: Era era => Term era UnitInterval
commQuorum :: forall era. Era era => Term era UnitInterval
commQuorum = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"commQuorum" forall era. Rep era UnitInterval
UnitIntervalR forall era s t. Access era s t
No
committeeVar :: Era era => Term era (Maybe (Committee era))
committeeVar :: forall era. Era era => Term era (Maybe (Committee era))
committeeVar = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"committeeVar" (forall era t1. Rep era t1 -> Rep era (Maybe t1)
MaybeR forall era. Era era => Rep era (Committee era)
CommitteeR) forall era s t. Access era s t
No
type UtxoPulse era =
(Map TxIn (TxOutF era), DRepPulser era Identity (RatifyState era))
utxoPulse :: (RunConwayRatify era, Reflect era) => Proof era -> Term era (UtxoPulse era)
utxoPulse :: forall era.
(RunConwayRatify era, Reflect era) =>
Proof era -> Term era (UtxoPulse era)
utxoPulse Proof era
p = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"utxoPulse" (forall era a b. Rep era a -> Rep era b -> Rep era (a, b)
PairR (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Era era => Rep era TxIn
TxInR (forall era. Era era => Proof era -> Rep era (TxOutF era)
TxOutR Proof era
p)) forall era.
(RunConwayRatify era, Reflect era) =>
Rep era (DRepPulser era Identity (RatifyState era))
DRepPulserR) forall era s t. Access era s t
No
pulsingPairT ::
forall era.
(RunConwayRatify era, Reflect era) =>
Proof era ->
RootTarget era (UtxoPulse era) (UtxoPulse era)
pulsingPairT :: forall era.
(RunConwayRatify era, Reflect era) =>
Proof era -> RootTarget era (UtxoPulse era) (UtxoPulse era)
pulsingPairT Proof era
proof =
forall root a b era.
String -> TypeRep root -> (a -> b) -> RootTarget era root (a -> b)
Invert
String
"DRepPulser"
(forall {k} (a :: k). Typeable a => TypeRep a
typeRep @(UtxoPulse era))
(\Map TxIn (TxOutF era)
utx Map (Credential 'Staking) DRep
a Map (KeyHash 'StakePool) IndividualPoolStake
b Map (Credential 'DRepRole) DRepState
c EpochNo
d Map (Credential 'ColdCommitteeRole) CommitteeAuthorization
e EnactState era
f [GovActionState era]
g Map (KeyHash 'StakePool) PoolParams
h -> (Map TxIn (TxOutF era)
utx, forall era.
(Reflect era, RunConwayRatify era) =>
Proof era
-> Map TxIn (TxOutF era)
-> Map (Credential 'Staking) DRep
-> Map (KeyHash 'StakePool) IndividualPoolStake
-> Map (Credential 'DRepRole) DRepState
-> EpochNo
-> Map (Credential 'ColdCommitteeRole) CommitteeAuthorization
-> EnactState era
-> [GovActionState era]
-> Map (KeyHash 'StakePool) PoolParams
-> DRepPulser era Identity (RatifyState era)
initPulser Proof era
proof Map TxIn (TxOutF era)
utx Map (Credential 'Staking) DRep
a Map (KeyHash 'StakePool) IndividualPoolStake
b Map (Credential 'DRepRole) DRepState
c EpochNo
d Map (Credential 'ColdCommitteeRole) CommitteeAuthorization
e EnactState era
f [GovActionState era]
g Map (KeyHash 'StakePool) PoolParams
h))
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed (forall era.
Era era =>
Proof era -> Term era (Map TxIn (TxOutF era))
utxo Proof era
proof) forall s t a b. Field1 s t a b => Lens s t a b
_1
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> PDoc -> Lens' root t -> RootTarget era root t
Virtual forall era. Era era => Term era (Map (Credential 'Staking) DRep)
drepDelegation (forall a. String -> Doc a
ppString String
"prevDRepDelegations") (forall s t a b. Field2 s t a b => Lens s t a b
_2 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era.
Lens'
(DRepPulser era Identity (RatifyState era))
(Map (Credential 'Staking) DRep)
prevDRepDelegationsL)
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> PDoc -> Lens' root t -> RootTarget era root t
Virtual forall era.
Era era =>
Term era (Map (KeyHash 'StakePool) IndividualPoolStake)
poolDistr (forall a. String -> Doc a
ppString String
"prevPoolDistr") (forall s t a b. Field2 s t a b => Lens s t a b
_2 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era.
Lens'
(DRepPulser era Identity (RatifyState era))
(Map (KeyHash 'StakePool) IndividualPoolStake)
prevPoolDistrL)
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> PDoc -> Lens' root t -> RootTarget era root t
Virtual forall era.
Era era =>
Term era (Map (Credential 'DRepRole) DRepState)
currentDRepState (forall a. String -> Doc a
ppString String
"prevDRepState") (forall s t a b. Field2 s t a b => Lens s t a b
_2 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era.
Lens'
(DRepPulser era Identity (RatifyState era))
(Map (Credential 'DRepRole) DRepState)
prevDRepStateL)
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> PDoc -> Lens' root t -> RootTarget era root t
Virtual forall era. Era era => Term era EpochNo
currentEpoch (forall a. String -> Doc a
ppString String
"prevEpoch") (forall s t a b. Field2 s t a b => Lens s t a b
_2 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era.
Lens' (DRepPulser era Identity (RatifyState era)) EpochNo
prevEpochL)
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> PDoc -> Lens' root t -> RootTarget era root t
Virtual forall era.
Era era =>
Term
era (Map (Credential 'ColdCommitteeRole) CommitteeAuthorization)
committeeState (forall a. String -> Doc a
ppString String
"prevCommitteeState") (forall s t a b. Field2 s t a b => Lens s t a b
_2 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era.
Lens'
(DRepPulser era Identity (RatifyState era))
(Map (Credential 'ColdCommitteeRole) CommitteeAuthorization)
prevCommitteeStateL)
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era root2 t root.
RootTarget era root2 t -> Lens' root root2 -> RootTarget era root t
Shift forall era.
Reflect era =>
RootTarget era (EnactState era) (EnactState era)
enactStateT (forall s t a b. Field2 s t a b => Lens s t a b
_2 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era.
Lens' (DRepPulser era Identity (RatifyState era)) (EnactState era)
prevEnactStateL)
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> PDoc -> Lens' root t -> RootTarget era root t
Virtual forall era. Era era => Term era [GovActionState era]
currGovStates (forall a. String -> Doc a
ppString String
"prevProposals") (forall s t a b. Field2 s t a b => Lens s t a b
_2 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era.
Lens'
(DRepPulser era Identity (RatifyState era)) [GovActionState era]
ratifyGovActionStatesL)
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> PDoc -> Lens' root t -> RootTarget era root t
Virtual forall era.
Era era =>
Term era (Map (KeyHash 'StakePool) PoolParams)
regPools (forall a. String -> Doc a
ppString String
"prevPoolParams") (forall s t a b. Field2 s t a b => Lens s t a b
_2 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era.
Lens'
(DRepPulser era Identity (RatifyState era))
(Map (KeyHash 'StakePool) PoolParams)
prevRegPoolsL)
justPulser ::
forall era.
(Reflect era, RunConwayRatify era) =>
Proof era ->
RootTarget
era
(DRepPulser era Identity (RatifyState era))
(DRepPulser era Identity (RatifyState era))
justPulser :: forall era.
(Reflect era, RunConwayRatify era) =>
Proof era
-> RootTarget
era
(DRepPulser era Identity (RatifyState era))
(DRepPulser era Identity (RatifyState era))
justPulser Proof era
p =
forall root a b era.
String -> TypeRep root -> (a -> b) -> RootTarget era root (a -> b)
Invert String
"DRepPulser" (forall {k} (a :: k). Typeable a => TypeRep a
typeRep @(DRepPulser era Identity (RatifyState era))) (forall era.
(Reflect era, RunConwayRatify era) =>
Proof era
-> Map TxIn (TxOutF era)
-> Map (Credential 'Staking) DRep
-> Map (KeyHash 'StakePool) IndividualPoolStake
-> Map (Credential 'DRepRole) DRepState
-> EpochNo
-> Map (Credential 'ColdCommitteeRole) CommitteeAuthorization
-> EnactState era
-> [GovActionState era]
-> Map (KeyHash 'StakePool) PoolParams
-> DRepPulser era Identity (RatifyState era)
initPulser Proof era
p forall k a. Map k a
Map.empty)
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> PDoc -> Lens' root t -> RootTarget era root t
Virtual forall era. Era era => Term era (Map (Credential 'Staking) DRep)
drepDelegation (forall a. String -> Doc a
ppString String
"prevDRepDelegations") forall era.
Lens'
(DRepPulser era Identity (RatifyState era))
(Map (Credential 'Staking) DRep)
prevDRepDelegationsL
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> PDoc -> Lens' root t -> RootTarget era root t
Virtual forall era.
Era era =>
Term era (Map (KeyHash 'StakePool) IndividualPoolStake)
poolDistr (forall a. String -> Doc a
ppString String
"prevPoolDistr") forall era.
Lens'
(DRepPulser era Identity (RatifyState era))
(Map (KeyHash 'StakePool) IndividualPoolStake)
prevPoolDistrL
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> PDoc -> Lens' root t -> RootTarget era root t
Virtual forall era.
Era era =>
Term era (Map (Credential 'DRepRole) DRepState)
currentDRepState (forall a. String -> Doc a
ppString String
"prevDRepState") forall era.
Lens'
(DRepPulser era Identity (RatifyState era))
(Map (Credential 'DRepRole) DRepState)
prevDRepStateL
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> PDoc -> Lens' root t -> RootTarget era root t
Virtual forall era. Era era => Term era EpochNo
currentEpoch (forall a. String -> Doc a
ppString String
"prevEpoch") forall era.
Lens' (DRepPulser era Identity (RatifyState era)) EpochNo
prevEpochL
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> PDoc -> Lens' root t -> RootTarget era root t
Virtual forall era.
Era era =>
Term
era (Map (Credential 'ColdCommitteeRole) CommitteeAuthorization)
committeeState (forall a. String -> Doc a
ppString String
"prevCommitteeState") forall era.
Lens'
(DRepPulser era Identity (RatifyState era))
(Map (Credential 'ColdCommitteeRole) CommitteeAuthorization)
prevCommitteeStateL
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era root2 t root.
RootTarget era root2 t -> Lens' root root2 -> RootTarget era root t
Shift forall era.
Reflect era =>
RootTarget era (EnactState era) (EnactState era)
enactStateT forall era.
Lens' (DRepPulser era Identity (RatifyState era)) (EnactState era)
prevEnactStateL
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> PDoc -> Lens' root t -> RootTarget era root t
Virtual forall era. Era era => Term era [GovActionState era]
currGovStates (forall a. String -> Doc a
ppString String
"prevProposals") forall era.
Lens'
(DRepPulser era Identity (RatifyState era)) [GovActionState era]
ratifyGovActionStatesL
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> PDoc -> Lens' root t -> RootTarget era root t
Virtual forall era.
Era era =>
Term era (Map (KeyHash 'StakePool) PoolParams)
regPools (forall a. String -> Doc a
ppString String
"prevPoolParams") forall era.
Lens'
(DRepPulser era Identity (RatifyState era))
(Map (KeyHash 'StakePool) PoolParams)
prevRegPoolsL
drepPulser ::
(RunConwayRatify era, Reflect era) => Term era (DRepPulser era Identity (RatifyState era))
drepPulser :: forall era.
(RunConwayRatify era, Reflect era) =>
Term era (DRepPulser era Identity (RatifyState era))
drepPulser = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"drepPulser" forall era.
(RunConwayRatify era, Reflect era) =>
Rep era (DRepPulser era Identity (RatifyState era))
DRepPulserR forall era s t. Access era s t
No
prevPulsingPreds :: (RunConwayRatify era, Reflect era) => Proof era -> [Pred era]
prevPulsingPreds :: forall era.
(RunConwayRatify era, Reflect era) =>
Proof era -> [Pred era]
prevPulsingPreds Proof era
p =
[ forall t era. Sizeable t => Term era Size -> Term era t -> Pred era
Sized (forall era. Era era => Int -> Term era Size
ExactSize Int
0) (forall a era b. Ord a => Term era (Map a b) -> Term era (Set a)
Dom forall era. Era era => Term era (Map (Credential 'Staking) Coin)
enactWithdrawals)
, forall era t. Rep era t -> t -> Term era t
Lit forall era. Rep era Coin
CoinR (Integer -> Coin
Coin Integer
0) forall a era. Eq a => Term era a -> Term era a -> Pred era
:=: forall era. Era era => Term era Coin
enactTreasury
, forall era.
(RunConwayRatify era, Reflect era) =>
Proof era -> Term era (UtxoPulse era)
utxoPulse Proof era
p forall era t r. Term era t -> RootTarget era r t -> Pred era
:<-: forall era.
(RunConwayRatify era, Reflect era) =>
Proof era -> RootTarget era (UtxoPulse era) (UtxoPulse era)
pulsingPairT Proof era
p
, forall era. Reflect era => Term era (GovRelation StrictMaybe era)
prevGovActionIds
forall era t r. Term era t -> RootTarget era r t -> Pred era
:<-: ( forall a b era. String -> (a -> b) -> RootTarget era Void (a -> b)
Constr String
"PrevGovActionIdsFromProposals" (\Proposals era
cp -> forall era. GovRelation PRoot era -> GovRelation StrictMaybe era
toPrevGovActionIds (Proposals era
cp forall s a. s -> Getting a s a -> a
^. forall era. Lens' (Proposals era) (GovRelation PRoot era)
pRootsL))
forall era a t. Target era (a -> t) -> Term era a -> Target era t
^$ (forall era. Era era => Proof era -> Term era (Proposals era)
currProposals Proof era
p)
)
, forall era. Era era => Term era [GovActionState era]
currGovStates forall era t r. Term era t -> RootTarget era r t -> Pred era
:<-: (forall a b era. String -> (a -> b) -> RootTarget era Void (a -> b)
Constr String
"proposalsActions" (forall (t :: * -> *) a. Foldable t => t a -> [a]
toList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Proposals era -> StrictSeq (GovActionState era)
proposalsActions) forall era a t. Target era (a -> t) -> Term era a -> Target era t
^$ forall era. Era era => Proof era -> Term era (Proposals era)
currProposals Proof era
p)
, forall t era big.
(Eq t, Era era) =>
Term era t -> Term era big -> Lens' big t -> Pred era
select forall era.
(RunConwayRatify era, Reflect era) =>
Term era (DRepPulser era Identity (RatifyState era))
drepPulser (forall era.
(RunConwayRatify era, Reflect era) =>
Proof era -> Term era (UtxoPulse era)
utxoPulse Proof era
p) forall s t a b. Field2 s t a b => Lens s t a b
_2
, forall t era big.
(Eq t, Era era) =>
Term era t -> Term era big -> Lens' big t -> Pred era
select forall era. Era era => Term era (Map DRep Coin)
partialDRepDistr forall era.
(RunConwayRatify era, Reflect era) =>
Term era (DRepPulser era Identity (RatifyState era))
drepPulser forall era.
Lens' (DRepPulser era Identity (RatifyState era)) (Map DRep Coin)
partialDRepDistrL
, forall t era big.
(Eq t, Era era) =>
Term era t -> Term era big -> Lens' big t -> Pred era
select forall era. Era era => Term era (Map (Credential 'Staking) DRep)
prevDRepDelegations forall era.
(RunConwayRatify era, Reflect era) =>
Term era (DRepPulser era Identity (RatifyState era))
drepPulser forall era.
Lens'
(DRepPulser era Identity (RatifyState era))
(Map (Credential 'Staking) DRep)
prevDRepDelegationsL
, forall t era big.
(Eq t, Era era) =>
Term era t -> Term era big -> Lens' big t -> Pred era
select forall era.
Era era =>
Term era (Map (KeyHash 'StakePool) IndividualPoolStake)
prevPoolDistr forall era.
(RunConwayRatify era, Reflect era) =>
Term era (DRepPulser era Identity (RatifyState era))
drepPulser forall era.
Lens'
(DRepPulser era Identity (RatifyState era))
(Map (KeyHash 'StakePool) IndividualPoolStake)
prevPoolDistrL
, forall t era big.
(Eq t, Era era) =>
Term era t -> Term era big -> Lens' big t -> Pred era
select forall era.
Era era =>
Term era (Map (Credential 'DRepRole) DRepState)
prevDRepState forall era.
(RunConwayRatify era, Reflect era) =>
Term era (DRepPulser era Identity (RatifyState era))
drepPulser forall era.
Lens'
(DRepPulser era Identity (RatifyState era))
(Map (Credential 'DRepRole) DRepState)
prevDRepStateL
, forall t era big.
(Eq t, Era era) =>
Term era t -> Term era big -> Lens' big t -> Pred era
select forall era. Era era => Term era EpochNo
prevEpoch forall era.
(RunConwayRatify era, Reflect era) =>
Term era (DRepPulser era Identity (RatifyState era))
drepPulser forall era.
Lens' (DRepPulser era Identity (RatifyState era)) EpochNo
prevEpochL
, forall t era big.
(Eq t, Era era) =>
Term era t -> Term era big -> Lens' big t -> Pred era
select forall era.
Era era =>
Term
era (Map (Credential 'ColdCommitteeRole) CommitteeAuthorization)
prevCommitteeState forall era.
(RunConwayRatify era, Reflect era) =>
Term era (DRepPulser era Identity (RatifyState era))
drepPulser forall era.
Lens'
(DRepPulser era Identity (RatifyState era))
(Map (Credential 'ColdCommitteeRole) CommitteeAuthorization)
prevCommitteeStateL
, forall t era big.
(Eq t, Era era) =>
Term era t -> Term era big -> Lens' big t -> Pred era
select forall era. Reflect era => Term era (EnactState era)
prevEnactState forall era.
(RunConwayRatify era, Reflect era) =>
Term era (DRepPulser era Identity (RatifyState era))
drepPulser forall era.
Lens' (DRepPulser era Identity (RatifyState era)) (EnactState era)
prevEnactStateL
, forall era. Era era => Proof era -> Term era (Proposals era)
currProposals Proof era
p forall a era. Eq a => Term era a -> Term era a -> Pred era
:=: forall era. Era era => Proof era -> Term era (Proposals era)
prevProposals Proof era
p
]
pulsingPulsingStateT ::
forall era.
(RunConwayRatify era, Reflect era) =>
RootTarget era (DRepPulsingState era) (DRepPulsingState era)
pulsingPulsingStateT :: forall era.
(RunConwayRatify era, Reflect era) =>
RootTarget era (DRepPulsingState era) (DRepPulsingState era)
pulsingPulsingStateT =
forall root a b era.
String -> TypeRep root -> (a -> b) -> RootTarget era root (a -> b)
Invert String
"DRPulsing" (forall {k} (a :: k). Typeable a => TypeRep a
typeRep @(DRepPulsingState era)) forall era.
DRepPulser era Identity (RatifyState era) -> DRepPulsingState era
DRPulsing
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> PDoc -> Lens' root t -> RootTarget era root t
Virtual forall era.
(RunConwayRatify era, Reflect era) =>
Term era (DRepPulser era Identity (RatifyState era))
drepPulser (forall era r t. RootTarget era r t -> PDoc
ppTarget (forall era.
(Reflect era, RunConwayRatify era) =>
Proof era
-> RootTarget
era
(DRepPulser era Identity (RatifyState era))
(DRepPulser era Identity (RatifyState era))
justPulser @era forall era. Reflect era => Proof era
reify)) forall era.
Lens'
(DRepPulsingState era) (DRepPulser era Identity (RatifyState era))
pulsingStatePulserL
pulsingStatePulserL :: Lens' (DRepPulsingState era) (DRepPulser era Identity (RatifyState era))
pulsingStatePulserL :: forall era.
Lens'
(DRepPulsingState era) (DRepPulser era Identity (RatifyState era))
pulsingStatePulserL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall {era}.
DRepPulsingState era -> DRepPulser era Identity (RatifyState era)
getter forall {era} {era}.
DRepPulsingState era
-> DRepPulser era Identity (RatifyState era)
-> DRepPulsingState era
setter
where
getter :: DRepPulsingState era -> DRepPulser era Identity (RatifyState era)
getter (DRPulsing DRepPulser era Identity (RatifyState era)
x) = DRepPulser era Identity (RatifyState era)
x
getter (DRComplete PulsingSnapshot era
_ RatifyState era
_) =
forall a. HasCallStack => String -> a
error (String
"Can't turn a DRCompete into a DRPulsing in pulsingStatePulserL lens.")
setter :: DRepPulsingState era
-> DRepPulser era Identity (RatifyState era)
-> DRepPulsingState era
setter (DRPulsing DRepPulser era Identity (RatifyState era)
_) DRepPulser era Identity (RatifyState era)
x = forall era.
DRepPulser era Identity (RatifyState era) -> DRepPulsingState era
DRPulsing DRepPulser era Identity (RatifyState era)
x
setter (DRComplete PulsingSnapshot era
_ RatifyState era
_) DRepPulser era Identity (RatifyState era)
x = forall era.
DRepPulser era Identity (RatifyState era) -> DRepPulsingState era
DRPulsing DRepPulser era Identity (RatifyState era)
x
initPulser ::
forall era.
(Reflect era, RunConwayRatify era) =>
Proof era ->
Map TxIn (TxOutF era) ->
Map (Credential 'Staking) DRep ->
Map (KeyHash 'StakePool) IndividualPoolStake ->
Map (Credential 'DRepRole) DRepState ->
EpochNo ->
Map (Credential 'ColdCommitteeRole) CommitteeAuthorization ->
EnactState era ->
[GovActionState era] ->
Map (KeyHash 'StakePool) PoolParams ->
DRepPulser era Identity (RatifyState era)
initPulser :: forall era.
(Reflect era, RunConwayRatify era) =>
Proof era
-> Map TxIn (TxOutF era)
-> Map (Credential 'Staking) DRep
-> Map (KeyHash 'StakePool) IndividualPoolStake
-> Map (Credential 'DRepRole) DRepState
-> EpochNo
-> Map (Credential 'ColdCommitteeRole) CommitteeAuthorization
-> EnactState era
-> [GovActionState era]
-> Map (KeyHash 'StakePool) PoolParams
-> DRepPulser era Identity (RatifyState era)
initPulser Proof era
proof Map TxIn (TxOutF era)
utx Map (Credential 'Staking) DRep
credDRepMap Map (KeyHash 'StakePool) IndividualPoolStake
poold Map (Credential 'DRepRole) DRepState
credDRepStateMap EpochNo
epoch Map (Credential 'ColdCommitteeRole) CommitteeAuthorization
commstate EnactState era
enactstate [GovActionState era]
govstates Map (KeyHash 'StakePool) PoolParams
poolParams =
let umap :: UMap
umap = Map (Credential 'Staking) RDPair
-> Map Ptr (Credential 'Staking)
-> Map (Credential 'Staking) (KeyHash 'StakePool)
-> Map (Credential 'Staking) DRep
-> UMap
unify forall k a. Map k a
Map.empty forall k a. Map k a
Map.empty forall k a. Map k a
Map.empty Map (Credential 'Staking) DRep
credDRepMap
umapSize :: Int
umapSize = forall k a. Map k a -> Int
Map.size Map (Credential 'Staking) DRep
credDRepMap
k :: Word64
k = Globals -> Word64
securityParameter Globals
testGlobals
pp :: PParams era
pp :: PParams era
pp = forall a. Default a => a
def forall a b. a -> (a -> b) -> b
& forall era. EraPParams era => Lens' (PParams era) ProtVer
ppProtocolVersionL forall s t a b. ASetter s t a b -> b -> s -> t
.~ forall era. Proof era -> ProtVer
protocolVersion Proof era
proof
IStake Map (Credential 'Staking) (CompactForm Coin)
stakeDistr Map Ptr (CompactForm Coin)
_ = forall era.
EraTxOut era =>
PParams era
-> IncrementalStake -> UTxO era -> UTxO era -> IncrementalStake
updateStakeDistribution PParams era
pp forall a. Monoid a => a
mempty forall a. Monoid a => a
mempty (Map TxIn (TxOutF era)
utx forall s a. s -> Getting a s a -> a
^. forall era. Proof era -> Lens' (Map TxIn (TxOutF era)) (UTxO era)
utxoFL Proof era
proof)
in forall era ans (m :: * -> *).
(ans ~ RatifyState era, m ~ Identity, RunConwayRatify era) =>
Int
-> UMap
-> Int
-> Map (Credential 'Staking) (CompactForm Coin)
-> PoolDistr
-> Map DRep (CompactForm Coin)
-> Map (Credential 'DRepRole) DRepState
-> EpochNo
-> CommitteeState era
-> EnactState era
-> StrictSeq (GovActionState era)
-> Map (Credential 'Staking) (CompactForm Coin)
-> Globals
-> Map (KeyHash 'StakePool) PoolParams
-> DRepPulser era m ans
DRepPulser
(forall a. Ord a => a -> a -> a
max Int
1 (forall a b. (RealFrac a, Integral b) => a -> b
ceiling (forall a. Integral a => a -> Integer
toInteger Int
umapSize forall a. Integral a => a -> a -> Ratio a
% (Integer
8 forall a. Num a => a -> a -> a
* forall a. Integral a => a -> Integer
toInteger Word64
k))))
UMap
umap
Int
0
Map (Credential 'Staking) (CompactForm Coin)
stakeDistr
(Map (KeyHash 'StakePool) IndividualPoolStake
-> CompactForm Coin -> PoolDistr
PoolDistr Map (KeyHash 'StakePool) IndividualPoolStake
poold forall a b. (a -> b) -> a -> b
$ Word64 -> CompactForm Coin
CompactCoin Word64
1)
forall k a. Map k a
Map.empty
Map (Credential 'DRepRole) DRepState
credDRepStateMap
EpochNo
epoch
(forall era.
Map (Credential 'ColdCommitteeRole) CommitteeAuthorization
-> CommitteeState era
CommitteeState Map (Credential 'ColdCommitteeRole) CommitteeAuthorization
commstate)
EnactState era
enactstate
(forall a. [a] -> StrictSeq a
SS.fromList [GovActionState era]
govstates)
(forall era.
Proposals era -> Map (Credential 'Staking) (CompactForm Coin)
proposalsDeposits forall a b. (a -> b) -> a -> b
$ forall a. Default a => a
def forall a b. a -> (a -> b) -> b
& forall era.
Lens' (Proposals era) (OMap GovActionId (GovActionState era))
pPropsL forall s t a b. ASetter s t a b -> b -> s -> t
.~ forall (f :: * -> *) k v.
(Foldable f, HasOKey k v) =>
f v -> OMap k v
OMap.fromFoldable [GovActionState era]
govstates)
Globals
testGlobals
Map (KeyHash 'StakePool) PoolParams
poolParams
proposalsT :: forall era. Era era => Proof era -> RootTarget era (Proposals era) (Proposals era)
proposalsT :: forall era.
Era era =>
Proof era -> RootTarget era (Proposals era) (Proposals era)
proposalsT Proof era
proof =
forall root a b era.
String -> TypeRep root -> (a -> b) -> RootTarget era root (a -> b)
Invert String
"Proposals" (forall {k} (a :: k). Typeable a => TypeRep a
typeRep @(Proposals era)) forall a. a -> a
id
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed (forall era. Era era => Proof era -> Term era (Proposals era)
currProposals Proof era
proof) (forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall a. a -> a
id forall a b. (a -> b) -> a -> b
$ forall a b. a -> b -> a
const forall a. a -> a
id)
pulsingSnapshotT ::
forall era. Era era => RootTarget era (PulsingSnapshot era) (PulsingSnapshot era)
pulsingSnapshotT :: forall era.
Era era =>
RootTarget era (PulsingSnapshot era) (PulsingSnapshot era)
pulsingSnapshotT =
forall root a b era.
String -> TypeRep root -> (a -> b) -> RootTarget era root (a -> b)
Invert
String
"PulsingSnapshot"
(forall {k} (a :: k). Typeable a => TypeRep a
typeRep @(PulsingSnapshot era))
( \[GovActionState era]
a Map DRep Coin
b Map (Credential 'DRepRole) DRepState
c Map (KeyHash 'StakePool) Coin
d -> forall era.
StrictSeq (GovActionState era)
-> Map DRep (CompactForm Coin)
-> Map (Credential 'DRepRole) DRepState
-> Map (KeyHash 'StakePool) (CompactForm Coin)
-> PulsingSnapshot era
PulsingSnapshot (forall a. [a] -> StrictSeq a
SS.fromList [GovActionState era]
a) (forall a b k. (a -> b) -> Map k a -> Map k b
Map.map HasCallStack => Coin -> CompactForm Coin
compactCoinOrError Map DRep Coin
b) Map (Credential 'DRepRole) DRepState
c (forall a b k. (a -> b) -> Map k a -> Map k b
Map.map HasCallStack => Coin -> CompactForm Coin
compactCoinOrError Map (KeyHash 'StakePool) Coin
d)
)
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed forall era. Era era => Term era [GovActionState era]
currGovStates (forall era.
Lens' (PulsingSnapshot era) (StrictSeq (GovActionState era))
psProposalsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Lens' (StrictSeq a) [a]
strictSeqListL)
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed forall era. Era era => Term era (Map DRep Coin)
partialDRepDistr (forall era.
Lens' (PulsingSnapshot era) (Map DRep (CompactForm Coin))
psDRepDistrL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Lens' (Map a (CompactForm Coin)) (Map a Coin)
mapCompactFormCoinL)
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed forall era.
Era era =>
Term era (Map (Credential 'DRepRole) DRepState)
prevDRepState forall era.
Lens' (PulsingSnapshot era) (Map (Credential 'DRepRole) DRepState)
psDRepStateL
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed forall era. Era era => Term era (Map (KeyHash 'StakePool) Coin)
partialIndividualPoolStake (forall era.
Lens'
(PulsingSnapshot era) (Map (KeyHash 'StakePool) (CompactForm Coin))
psPoolDistrL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Lens' (Map a (CompactForm Coin)) (Map a Coin)
mapCompactFormCoinL)
pulsingSnapshotL :: Lens' (DRepPulsingState era) (PulsingSnapshot era)
pulsingSnapshotL :: forall era. Lens' (DRepPulsingState era) (PulsingSnapshot era)
pulsingSnapshotL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall {era}. DRepPulsingState era -> PulsingSnapshot era
getter forall {era}.
DRepPulsingState era -> PulsingSnapshot era -> DRepPulsingState era
setter
where
getter :: DRepPulsingState era -> PulsingSnapshot era
getter (DRComplete PulsingSnapshot era
x RatifyState era
_) = PulsingSnapshot era
x
getter DRepPulsingState era
other = forall a b. (a, b) -> a
fst (forall era.
DRepPulsingState era -> (PulsingSnapshot era, RatifyState era)
finishDRepPulser DRepPulsingState era
other)
setter :: DRepPulsingState era -> PulsingSnapshot era -> DRepPulsingState era
setter (DRComplete PulsingSnapshot era
_ RatifyState era
y) PulsingSnapshot era
x = forall era.
PulsingSnapshot era -> RatifyState era -> DRepPulsingState era
DRComplete PulsingSnapshot era
x RatifyState era
y
setter DRepPulsingState era
other PulsingSnapshot era
x = forall era.
PulsingSnapshot era -> RatifyState era -> DRepPulsingState era
DRComplete PulsingSnapshot era
x RatifyState era
y
where
(PulsingSnapshot era
_, RatifyState era
y) = forall era.
DRepPulsingState era -> (PulsingSnapshot era, RatifyState era)
finishDRepPulser DRepPulsingState era
other
completePulsingStateT ::
forall era.
Reflect era =>
Proof era ->
RootTarget era (DRepPulsingState era) (DRepPulsingState era)
completePulsingStateT :: forall era.
Reflect era =>
Proof era
-> RootTarget era (DRepPulsingState era) (DRepPulsingState era)
completePulsingStateT Proof era
_p =
forall root a b era.
String -> TypeRep root -> (a -> b) -> RootTarget era root (a -> b)
Invert String
"DRComplete" (forall {k} (a :: k). Typeable a => TypeRep a
typeRep @(DRepPulsingState era)) forall era.
PulsingSnapshot era -> RatifyState era -> DRepPulsingState era
DRComplete
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era root2 t root.
RootTarget era root2 t -> Lens' root root2 -> RootTarget era root t
Shift forall era.
Era era =>
RootTarget era (PulsingSnapshot era) (PulsingSnapshot era)
pulsingSnapshotT forall era. Lens' (DRepPulsingState era) (PulsingSnapshot era)
pulsingSnapshotL
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed forall era. Reflect era => Term era (RatifyState era)
ratifyState forall era. Lens' (DRepPulsingState era) (RatifyState era)
ratifyStateL
ratifyState :: Reflect era => Term era (RatifyState era)
ratifyState :: forall era. Reflect era => Term era (RatifyState era)
ratifyState = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"ratifyState" forall era. Reflect era => Rep era (RatifyState era)
RatifyStateR forall era s t. Access era s t
No
ratifyStateL :: Lens' (DRepPulsingState era) (RatifyState era)
ratifyStateL :: forall era. Lens' (DRepPulsingState era) (RatifyState era)
ratifyStateL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall {era}. DRepPulsingState era -> RatifyState era
getter forall {era}.
DRepPulsingState era -> RatifyState era -> DRepPulsingState era
setter
where
getter :: DRepPulsingState era -> RatifyState era
getter (DRComplete PulsingSnapshot era
_ RatifyState era
y) = RatifyState era
y
getter (x :: DRepPulsingState era
x@(DRPulsing {})) = forall a b. (a, b) -> b
snd (forall era.
DRepPulsingState era -> (PulsingSnapshot era, RatifyState era)
finishDRepPulser DRepPulsingState era
x)
setter :: DRepPulsingState era -> RatifyState era -> DRepPulsingState era
setter (DRComplete PulsingSnapshot era
x RatifyState era
_) RatifyState era
y = forall era.
PulsingSnapshot era -> RatifyState era -> DRepPulsingState era
DRComplete PulsingSnapshot era
x RatifyState era
y
setter (z :: DRepPulsingState era
z@(DRPulsing {})) RatifyState era
y = case forall era.
DRepPulsingState era -> (PulsingSnapshot era, RatifyState era)
finishDRepPulser DRepPulsingState era
z of
(PulsingSnapshot era
x, RatifyState era
_) -> forall era.
PulsingSnapshot era -> RatifyState era -> DRepPulsingState era
DRComplete PulsingSnapshot era
x RatifyState era
y
prevProposals :: Era era => Proof era -> Term era (Proposals era)
prevProposals :: forall era. Era era => Proof era -> Term era (Proposals era)
prevProposals Proof era
p = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"prevProposals" (forall era. Era era => Proof era -> Rep era (Proposals era)
ProposalsR Proof era
p) forall era s t. Access era s t
No
ratifyGovActionStatesL :: Lens' (DRepPulser era Identity (RatifyState era)) [GovActionState era]
ratifyGovActionStatesL :: forall era.
Lens'
(DRepPulser era Identity (RatifyState era)) [GovActionState era]
ratifyGovActionStatesL =
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens
(\DRepPulser era Identity (RatifyState era)
x -> forall (t :: * -> *) a. Foldable t => t a -> [a]
F.toList (forall era ans (m :: * -> *).
DRepPulser era m ans -> StrictSeq (GovActionState era)
dpProposals DRepPulser era Identity (RatifyState era)
x))
(\DRepPulser era Identity (RatifyState era)
x [GovActionState era]
y -> DRepPulser era Identity (RatifyState era)
x {dpProposals :: StrictSeq (GovActionState era)
dpProposals = forall a. [a] -> StrictSeq a
SS.fromList [GovActionState era]
y})
partialDRepDistr :: Era era => Term era (Map DRep Coin)
partialDRepDistr :: forall era. Era era => Term era (Map DRep Coin)
partialDRepDistr = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"partialDRepDistr" (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Era era => Rep era DRep
DRepR forall era. Rep era Coin
CoinR) forall era s t. Access era s t
No
partialDRepDistrL ::
Lens' (DRepPulser era Identity (RatifyState era)) (Map DRep Coin)
partialDRepDistrL :: forall era.
Lens' (DRepPulser era Identity (RatifyState era)) (Map DRep Coin)
partialDRepDistrL =
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens
(\DRepPulser era Identity (RatifyState era)
x -> forall a b k. (a -> b) -> Map k a -> Map k b
Map.map forall a. Compactible a => CompactForm a -> a
fromCompact (forall era ans (m :: * -> *).
DRepPulser era m ans -> Map DRep (CompactForm Coin)
dpDRepDistr DRepPulser era Identity (RatifyState era)
x))
(\DRepPulser era Identity (RatifyState era)
x Map DRep Coin
y -> DRepPulser era Identity (RatifyState era)
x {dpDRepDistr :: Map DRep (CompactForm Coin)
dpDRepDistr = forall a b k. (a -> b) -> Map k a -> Map k b
Map.map HasCallStack => Coin -> CompactForm Coin
compactCoinOrError Map DRep Coin
y})
prevDRepState ::
Era era => Term era (Map (Credential 'DRepRole) DRepState)
prevDRepState :: forall era.
Era era =>
Term era (Map (Credential 'DRepRole) DRepState)
prevDRepState = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"prevDRepState" (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Era era => Rep era (Credential 'DRepRole)
VCredR forall era. Era era => Rep era DRepState
DRepStateR) forall era s t. Access era s t
No
prevDRepStateL ::
Lens'
(DRepPulser era Identity (RatifyState era))
(Map (Credential 'DRepRole) DRepState)
prevDRepStateL :: forall era.
Lens'
(DRepPulser era Identity (RatifyState era))
(Map (Credential 'DRepRole) DRepState)
prevDRepStateL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall era ans (m :: * -> *).
DRepPulser era m ans -> Map (Credential 'DRepRole) DRepState
dpDRepState (\DRepPulser era Identity (RatifyState era)
x Map (Credential 'DRepRole) DRepState
y -> DRepPulser era Identity (RatifyState era)
x {dpDRepState :: Map (Credential 'DRepRole) DRepState
dpDRepState = Map (Credential 'DRepRole) DRepState
y})
prevPoolDistr ::
Era era => Term era (Map (KeyHash 'StakePool) IndividualPoolStake)
prevPoolDistr :: forall era.
Era era =>
Term era (Map (KeyHash 'StakePool) IndividualPoolStake)
prevPoolDistr = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"prevPoolDistr" (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Era era => Rep era (KeyHash 'StakePool)
PoolHashR forall era. Era era => Rep era IndividualPoolStake
IPoolStakeR) forall era s t. Access era s t
No
prevPoolDistrL ::
Lens'
(DRepPulser era Identity (RatifyState era))
(Map (KeyHash 'StakePool) IndividualPoolStake)
prevPoolDistrL :: forall era.
Lens'
(DRepPulser era Identity (RatifyState era))
(Map (KeyHash 'StakePool) IndividualPoolStake)
prevPoolDistrL =
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens
(\DRepPulser era Identity (RatifyState era)
x -> PoolDistr -> Map (KeyHash 'StakePool) IndividualPoolStake
unPoolDistr (forall era ans (m :: * -> *). DRepPulser era m ans -> PoolDistr
dpStakePoolDistr DRepPulser era Identity (RatifyState era)
x))
(\DRepPulser era Identity (RatifyState era)
x Map (KeyHash 'StakePool) IndividualPoolStake
y -> DRepPulser era Identity (RatifyState era)
x {dpStakePoolDistr :: PoolDistr
dpStakePoolDistr = Map (KeyHash 'StakePool) IndividualPoolStake
-> CompactForm Coin -> PoolDistr
PoolDistr Map (KeyHash 'StakePool) IndividualPoolStake
y forall a b. (a -> b) -> a -> b
$ Word64 -> CompactForm Coin
CompactCoin Word64
1})
prevDRepDelegations ::
Era era => Term era (Map (Credential 'Staking) DRep)
prevDRepDelegations :: forall era. Era era => Term era (Map (Credential 'Staking) DRep)
prevDRepDelegations = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"prevDRepDelegations" (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Era era => Rep era (Credential 'Staking)
CredR forall era. Era era => Rep era DRep
DRepR) forall era s t. Access era s t
No
prevDRepDelegationsL ::
Lens'
(DRepPulser era Identity (RatifyState era))
(Map (Credential 'Staking) DRep)
prevDRepDelegationsL :: forall era.
Lens'
(DRepPulser era Identity (RatifyState era))
(Map (Credential 'Staking) DRep)
prevDRepDelegationsL =
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens
(\DRepPulser era Identity (RatifyState era)
x -> forall era ans (m :: * -> *). DRepPulser era m ans -> UMap
dpUMap DRepPulser era Identity (RatifyState era)
x forall s a. s -> Getting a s a -> a
^. Lens' UMap (Map (Credential 'Staking) DRep)
drepUMapL)
( \DRepPulser era Identity (RatifyState era)
x Map (Credential 'Staking) DRep
y ->
DRepPulser era Identity (RatifyState era)
x
{ dpUMap :: UMap
dpUMap =
Map (Credential 'Staking) RDPair
-> Map Ptr (Credential 'Staking)
-> Map (Credential 'Staking) (KeyHash 'StakePool)
-> Map (Credential 'Staking) DRep
-> UMap
unify
(UMap -> Map (Credential 'Staking) RDPair
rdPairMap (forall era ans (m :: * -> *). DRepPulser era m ans -> UMap
dpUMap DRepPulser era Identity (RatifyState era)
x))
(UMap -> Map Ptr (Credential 'Staking)
ptrMap (forall era ans (m :: * -> *). DRepPulser era m ans -> UMap
dpUMap DRepPulser era Identity (RatifyState era)
x))
(UMap -> Map (Credential 'Staking) (KeyHash 'StakePool)
sPoolMap (forall era ans (m :: * -> *). DRepPulser era m ans -> UMap
dpUMap DRepPulser era Identity (RatifyState era)
x))
Map (Credential 'Staking) DRep
y
}
)
prevCommitteeState ::
Era era =>
Term
era
(Map (Credential 'ColdCommitteeRole) CommitteeAuthorization)
prevCommitteeState :: forall era.
Era era =>
Term
era (Map (Credential 'ColdCommitteeRole) CommitteeAuthorization)
prevCommitteeState = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"prevCommitteeState" (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Era era => Rep era (Credential 'ColdCommitteeRole)
CommColdCredR forall era. Era era => Rep era CommitteeAuthorization
CommitteeAuthorizationR) forall era s t. Access era s t
No
prevCommitteeStateL ::
Lens'
(DRepPulser era Identity (RatifyState era))
(Map (Credential 'ColdCommitteeRole) CommitteeAuthorization)
prevCommitteeStateL :: forall era.
Lens'
(DRepPulser era Identity (RatifyState era))
(Map (Credential 'ColdCommitteeRole) CommitteeAuthorization)
prevCommitteeStateL =
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens
(forall era.
CommitteeState era
-> Map (Credential 'ColdCommitteeRole) CommitteeAuthorization
csCommitteeCreds forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era ans (m :: * -> *).
DRepPulser era m ans -> CommitteeState era
dpCommitteeState)
(\DRepPulser era Identity (RatifyState era)
x Map (Credential 'ColdCommitteeRole) CommitteeAuthorization
y -> DRepPulser era Identity (RatifyState era)
x {dpCommitteeState :: CommitteeState era
dpCommitteeState = forall era.
Map (Credential 'ColdCommitteeRole) CommitteeAuthorization
-> CommitteeState era
CommitteeState Map (Credential 'ColdCommitteeRole) CommitteeAuthorization
y})
prevEnactState :: Reflect era => Term era (EnactState era)
prevEnactState :: forall era. Reflect era => Term era (EnactState era)
prevEnactState = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"prevEnactState" forall era. Reflect era => Rep era (EnactState era)
EnactStateR forall era s t. Access era s t
No
prevEnactStateL :: Lens' (DRepPulser era Identity (RatifyState era)) (EnactState era)
prevEnactStateL :: forall era.
Lens' (DRepPulser era Identity (RatifyState era)) (EnactState era)
prevEnactStateL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall era ans (m :: * -> *).
DRepPulser era m ans -> EnactState era
dpEnactState (\DRepPulser era Identity (RatifyState era)
x EnactState era
y -> DRepPulser era Identity (RatifyState era)
x {dpEnactState :: EnactState era
dpEnactState = EnactState era
y})
prevEpoch :: Era era => Term era EpochNo
prevEpoch :: forall era. Era era => Term era EpochNo
prevEpoch = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"prevEpoch" forall era. Rep era EpochNo
EpochR forall era s t. Access era s t
No
prevEpochL :: Lens' (DRepPulser era Identity (RatifyState era)) EpochNo
prevEpochL :: forall era.
Lens' (DRepPulser era Identity (RatifyState era)) EpochNo
prevEpochL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall era ans (m :: * -> *). DRepPulser era m ans -> EpochNo
dpCurrentEpoch (\DRepPulser era Identity (RatifyState era)
x EpochNo
y -> DRepPulser era Identity (RatifyState era)
x {dpCurrentEpoch :: EpochNo
dpCurrentEpoch = EpochNo
y})
prevTreasury :: Era era => Term era Coin
prevTreasury :: forall era. Era era => Term era Coin
prevTreasury = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"prevTreasury" forall era. Rep era Coin
CoinR forall era s t. Access era s t
No
partialIndividualPoolStake :: Era era => Term era (Map (KeyHash 'StakePool) Coin)
partialIndividualPoolStake :: forall era. Era era => Term era (Map (KeyHash 'StakePool) Coin)
partialIndividualPoolStake = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"partialIndividualPoolStake" (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Era era => Rep era (KeyHash 'StakePool)
PoolHashR forall era. Rep era Coin
CoinR) forall era s t. Access era s t
No
prevRegPools ::
Era era => Term era (Map (KeyHash 'StakePool) PoolParams)
prevRegPools :: forall era.
Era era =>
Term era (Map (KeyHash 'StakePool) PoolParams)
prevRegPools = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"prevRegPools" (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Era era => Rep era (KeyHash 'StakePool)
PoolHashR forall era. Era era => Rep era PoolParams
PoolParamsR) forall era s t. Access era s t
No
prevRegPoolsL ::
Lens'
(DRepPulser era Identity (RatifyState era))
(Map (KeyHash 'StakePool) PoolParams)
prevRegPoolsL :: forall era.
Lens'
(DRepPulser era Identity (RatifyState era))
(Map (KeyHash 'StakePool) PoolParams)
prevRegPoolsL =
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens
forall era ans (m :: * -> *).
DRepPulser era m ans -> Map (KeyHash 'StakePool) PoolParams
dpPoolParams
(\DRepPulser era Identity (RatifyState era)
x Map (KeyHash 'StakePool) PoolParams
y -> DRepPulser era Identity (RatifyState era)
x {dpPoolParams :: Map (KeyHash 'StakePool) PoolParams
dpPoolParams = Map (KeyHash 'StakePool) PoolParams
y})
conwayGovStateT ::
forall era.
(RunConwayRatify era, Reflect era) =>
Proof era ->
RootTarget era (ConwayGovState era) (ConwayGovState era)
conwayGovStateT :: forall era.
(RunConwayRatify era, Reflect era) =>
Proof era
-> RootTarget era (ConwayGovState era) (ConwayGovState era)
conwayGovStateT Proof era
p =
forall root a b era.
String -> TypeRep root -> (a -> b) -> RootTarget era root (a -> b)
Invert
String
"ConwayGovState"
(forall {k} (a :: k). Typeable a => TypeRep a
typeRep @(ConwayGovState era))
( \Proposals era
pr Maybe (Committee era)
com Constitution era
con (PParamsF Proof era
_ PParams era
cpp) (PParamsF Proof era
_ PParams era
ppp) FuturePParams era
pu -> forall era.
Proposals era
-> StrictMaybe (Committee era)
-> Constitution era
-> PParams era
-> PParams era
-> FuturePParams era
-> DRepPulsingState era
-> ConwayGovState era
ConwayGovState Proposals era
pr (forall a. Maybe a -> StrictMaybe a
maybeToStrictMaybe Maybe (Committee era)
com) Constitution era
con PParams era
cpp PParams era
ppp FuturePParams era
pu
)
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed (forall era. Era era => Proof era -> Term era (Proposals era)
currProposals Proof era
p) forall era. Lens' (ConwayGovState era) (Proposals era)
cgsProposalsL
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed forall era. Era era => Term era (Maybe (Committee era))
committeeVar (forall era.
Lens' (ConwayGovState era) (StrictMaybe (Committee era))
cgsCommitteeL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall x. Lens' (StrictMaybe x) (Maybe x)
strictMaybeToMaybeL)
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed forall era. Era era => Term era (Constitution era)
constitution forall era. Lens' (ConwayGovState era) (Constitution era)
cgsConstitutionL
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed (forall era. Era era => Proof era -> Term era (PParamsF era)
currPParams forall era. Reflect era => Proof era
reify) (forall era. Lens' (ConwayGovState era) (PParams era)
cgsCurPParamsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Proof era -> Lens' (PParams era) (PParamsF era)
pparamsFL forall era. Reflect era => Proof era
reify)
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed (forall era. EraGov era => Proof era -> Term era (PParamsF era)
prevPParams forall era. Reflect era => Proof era
reify) (forall era. Lens' (ConwayGovState era) (PParams era)
cgsPrevPParamsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Proof era -> Lens' (PParams era) (PParamsF era)
pparamsFL forall era. Reflect era => Proof era
reify)
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed (forall era. Era era => Proof era -> Term era (FuturePParams era)
futurePParams forall era. Reflect era => Proof era
reify) forall era. Lens' (ConwayGovState era) (FuturePParams era)
cgsFuturePParamsL
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era root2 t root.
RootTarget era root2 t -> Lens' root root2 -> RootTarget era root t
Shift forall era.
(RunConwayRatify era, Reflect era) =>
RootTarget era (DRepPulsingState era) (DRepPulsingState era)
pulsingPulsingStateT forall era. Lens' (ConwayGovState era) (DRepPulsingState era)
cgsDRepPulsingStateL
proposalDeposits :: Era era => Term era Coin
proposalDeposits :: forall era. Era era => Term era Coin
proposalDeposits = forall era t. V era t -> Term era t
Var (forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"proposalDeposits" forall era. Rep era Coin
CoinR forall era s t. Access era s t
No)
drepDepositsView :: Era era => Term era (Map (Credential 'DRepRole) Coin)
drepDepositsView :: forall era. Era era => Term era (Map (Credential 'DRepRole) Coin)
drepDepositsView = forall era t. V era t -> Term era t
Var (forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"drepDepositsView" (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Era era => Rep era (Credential 'DRepRole)
VCredR forall era. Rep era Coin
CoinR) forall era s t. Access era s t
No)
currProposals :: Era era => Proof era -> Term era (Proposals era)
currProposals :: forall era. Era era => Proof era -> Term era (Proposals era)
currProposals Proof era
p = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"currProposals" (forall era. Era era => Proof era -> Rep era (Proposals era)
ProposalsR Proof era
p) forall era s t. Access era s t
No
prevGovActionIds :: forall era. Reflect era => Term era (GovRelation StrictMaybe era)
prevGovActionIds :: forall era. Reflect era => Term era (GovRelation StrictMaybe era)
prevGovActionIds = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"prevGovActionIds" forall era. Era era => Rep era (GovRelation StrictMaybe era)
PrevGovActionIdsR forall era s t. Access era s t
No
currGovStates :: Era era => Term era [GovActionState era]
currGovStates :: forall era. Era era => Term era [GovActionState era]
currGovStates = forall era t. V era t -> Term era t
Var (forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"currGovStates" (forall era a. Rep era a -> Rep era [a]
ListR forall era. Era era => Rep era (GovActionState era)
GovActionStateR) forall era s t. Access era s t
No)
enactStateT :: forall era. Reflect era => RootTarget era (EnactState era) (EnactState era)
enactStateT :: forall era.
Reflect era =>
RootTarget era (EnactState era) (EnactState era)
enactStateT =
forall root a b era.
String -> TypeRep root -> (a -> b) -> RootTarget era root (a -> b)
Invert
String
"EnactState"
(forall {k} (a :: k). Typeable a => TypeRep a
typeRep @(EnactState era))
(\Maybe (Committee era)
x Constitution era
y (PParamsF Proof era
_ PParams era
z) (PParamsF Proof era
_ PParams era
w) Coin
a Map (Credential 'Staking) Coin
b GovRelation StrictMaybe era
c -> forall era.
StrictMaybe (Committee era)
-> Constitution era
-> PParams era
-> PParams era
-> Coin
-> Map (Credential 'Staking) Coin
-> GovRelation StrictMaybe era
-> EnactState era
EnactState (forall a. Maybe a -> StrictMaybe a
maybeToStrictMaybe Maybe (Committee era)
x) Constitution era
y PParams era
z PParams era
w Coin
a Map (Credential 'Staking) Coin
b GovRelation StrictMaybe era
c)
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed forall era. Era era => Term era (Maybe (Committee era))
committeeVar (forall era. Lens' (EnactState era) (StrictMaybe (Committee era))
ensCommitteeL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall x. Lens' (StrictMaybe x) (Maybe x)
strictMaybeToMaybeL)
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed forall era. Era era => Term era (Constitution era)
constitution forall era. Lens' (EnactState era) (Constitution era)
ensConstitutionL
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed (forall era. Era era => Proof era -> Term era (PParamsF era)
currPParams forall era. Reflect era => Proof era
reify) (forall era. Lens' (EnactState era) (PParams era)
ensCurPParamsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Proof era -> Lens' (PParams era) (PParamsF era)
pparamsFL forall era. Reflect era => Proof era
reify)
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed (forall era. EraGov era => Proof era -> Term era (PParamsF era)
prevPParams forall era. Reflect era => Proof era
reify) (forall era. Lens' (EnactState era) (PParams era)
ensPrevPParamsL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall era. Proof era -> Lens' (PParams era) (PParamsF era)
pparamsFL forall era. Reflect era => Proof era
reify)
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed forall era. Era era => Term era Coin
enactTreasury forall era. Lens' (EnactState era) Coin
ensTreasuryL
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed forall era. Era era => Term era (Map (Credential 'Staking) Coin)
enactWithdrawals forall era. Lens' (EnactState era) (Map (Credential 'Staking) Coin)
ensWithdrawalsL
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed forall era. Reflect era => Term era (GovRelation StrictMaybe era)
prevGovActionIds forall era. Lens' (EnactState era) (GovRelation StrictMaybe era)
ensPrevGovActionIdsL
committeeT :: forall era. Era era => RootTarget era (Committee era) (Committee era)
committeeT :: forall era.
Era era =>
RootTarget era (Committee era) (Committee era)
committeeT =
forall root a b era.
String -> TypeRep root -> (a -> b) -> RootTarget era root (a -> b)
Invert String
"Committee" (forall {k} (a :: k). Typeable a => TypeRep a
typeRep @(Committee era)) forall era.
Map (Credential 'ColdCommitteeRole) EpochNo
-> UnitInterval -> Committee era
Committee
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed forall era.
Era era =>
Term era (Map (Credential 'ColdCommitteeRole) EpochNo)
commMembers forall era.
Lens' (Committee era) (Map (Credential 'ColdCommitteeRole) EpochNo)
committeeMembersL
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed forall era. Era era => Term era UnitInterval
commQuorum forall era. Lens' (Committee era) UnitInterval
committeeThresholdL
ppUpdateChildren :: Era era => Term era (Set GovActionId)
ppUpdateChildren :: forall era. Era era => Term era (Set GovActionId)
ppUpdateChildren = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"ppUpdateChildren" (forall a era. Ord a => Rep era a -> Rep era (Set a)
SetR forall era. Era era => Rep era GovActionId
GovActionIdR) forall era s t. Access era s t
No
hardForkChildren :: Era era => Term era (Set GovActionId)
hardForkChildren :: forall era. Era era => Term era (Set GovActionId)
hardForkChildren = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"hardForkChildren" (forall a era. Ord a => Rep era a -> Rep era (Set a)
SetR forall era. Era era => Rep era GovActionId
GovActionIdR) forall era s t. Access era s t
No
committeeChildren :: Era era => Term era (Set GovActionId)
committeeChildren :: forall era. Era era => Term era (Set GovActionId)
committeeChildren = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"committeeChildren" (forall a era. Ord a => Rep era a -> Rep era (Set a)
SetR forall era. Era era => Rep era GovActionId
GovActionIdR) forall era s t. Access era s t
No
constitutionChildren :: Era era => Term era (Set GovActionId)
constitutionChildren :: forall era. Era era => Term era (Set GovActionId)
constitutionChildren = forall era t. V era t -> Term era t
Var forall a b. (a -> b) -> a -> b
$ forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"constitutionChildren" (forall a era. Ord a => Rep era a -> Rep era (Set a)
SetR forall era. Era era => Rep era GovActionId
GovActionIdR) forall era s t. Access era s t
No
pparamsFL :: Proof era -> Lens' (PParams era) (PParamsF era)
pparamsFL :: forall era. Proof era -> Lens' (PParams era) (PParamsF era)
pparamsFL Proof era
p = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens (forall era. Proof era -> PParams era -> PParamsF era
PParamsF Proof era
p) (\PParams era
_ (PParamsF Proof era
_ PParams era
x) -> PParams era
x)
pparamsMaybeFL :: Proof era -> Lens' (Maybe (PParams era)) (Maybe (PParamsF era))
pparamsMaybeFL :: forall era.
Proof era -> Lens' (Maybe (PParams era)) (Maybe (PParamsF era))
pparamsMaybeFL Proof era
p =
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens
(forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall era. Proof era -> PParams era -> PParamsF era
PParamsF Proof era
p))
(\Maybe (PParams era)
_ -> forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(PParamsF Proof era
_ PParams era
x) -> PParams era
x))
smCommL :: Lens' (StrictMaybe (Committee era)) (Committee era)
smCommL :: forall era. Lens' (StrictMaybe (Committee era)) (Committee era)
smCommL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall {era}. StrictMaybe (Committee era) -> Committee era
getter (\StrictMaybe (Committee era)
_ Committee era
t -> forall a. a -> StrictMaybe a
SJust Committee era
t)
where
getter :: StrictMaybe (Committee era) -> Committee era
getter StrictMaybe (Committee era)
SNothing = forall era.
Map (Credential 'ColdCommitteeRole) EpochNo
-> UnitInterval -> Committee era
Committee forall k a. Map k a
Map.empty forall a. Bounded a => a
maxBound
getter (SJust Committee era
x) = Committee era
x
proposedMapL ::
Proof era ->
Lens' (ProposedPPUpdates era) (Map (KeyHash 'Genesis) (PParamsUpdateF era))
proposedMapL :: forall era.
Proof era
-> Lens'
(ProposedPPUpdates era)
(Map (KeyHash 'Genesis) (PParamsUpdateF era))
proposedMapL Proof era
p =
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens
(\(ProposedPPUpdates Map (KeyHash 'Genesis) (PParamsUpdate era)
x) -> forall a b k. (a -> b) -> Map k a -> Map k b
Map.map (forall era. Proof era -> PParamsUpdate era -> PParamsUpdateF era
PParamsUpdateF Proof era
p) Map (KeyHash 'Genesis) (PParamsUpdate era)
x)
(\(ProposedPPUpdates Map (KeyHash 'Genesis) (PParamsUpdate era)
_) Map (KeyHash 'Genesis) (PParamsUpdateF era)
y -> forall era.
Map (KeyHash 'Genesis) (PParamsUpdate era) -> ProposedPPUpdates era
ProposedPPUpdates (forall a b k. (a -> b) -> Map k a -> Map k b
Map.map forall era. PParamsUpdateF era -> PParamsUpdate era
unPParamsUpdate Map (KeyHash 'Genesis) (PParamsUpdateF era)
y))
pair1 :: Era era => Rep era a -> Term era a
pair1 :: forall era a. Era era => Rep era a -> Term era a
pair1 Rep era a
rep = forall era t. V era t -> Term era t
Var (forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"pair1" Rep era a
rep forall era s t. Access era s t
No)
pair2 :: Era era => Rep era b -> Term era b
pair2 :: forall era a. Era era => Rep era a -> Term era a
pair2 Rep era b
rep = forall era t. V era t -> Term era t
Var (forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"pair2" Rep era b
rep forall era s t. Access era s t
No)
pairT ::
forall era a b.
(Typeable a, Typeable b, Era era) =>
Rep era a ->
Rep era b ->
RootTarget era (a, b) (a, b)
pairT :: forall era a b.
(Typeable a, Typeable b, Era era) =>
Rep era a -> Rep era b -> RootTarget era (a, b) (a, b)
pairT Rep era a
repa Rep era b
repb =
forall root a b era.
String -> TypeRep root -> (a -> b) -> RootTarget era root (a -> b)
Invert String
"(,)" (forall {k} (a :: k). Typeable a => TypeRep a
typeRep @(a, b)) (,)
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed (forall era a. Era era => Rep era a -> Term era a
pair1 Rep era a
repa) forall a b. Lens' (a, b) a
fstL
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed (forall era a. Era era => Rep era a -> Term era a
pair2 Rep era b
repb) forall a b. Lens' (a, b) b
sndL
idV :: Era era => Term era GovActionId
idV :: forall era. Era era => Term era GovActionId
idV = forall era t. V era t -> Term era t
Var (forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"idV" forall era. Era era => Rep era GovActionId
GovActionIdR forall era s t. Access era s t
No)
committeeVotesV :: Era era => Term era (Map (Credential 'HotCommitteeRole) Vote)
committeeVotesV :: forall era.
Era era =>
Term era (Map (Credential 'HotCommitteeRole) Vote)
committeeVotesV = forall era t. V era t -> Term era t
Var (forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"committeeVotesV" (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Era era => Rep era (Credential 'HotCommitteeRole)
CommHotCredR forall era. Rep era Vote
VoteR) forall era s t. Access era s t
No)
drepVotesV :: Era era => Term era (Map (Credential 'DRepRole) Vote)
drepVotesV :: forall era. Era era => Term era (Map (Credential 'DRepRole) Vote)
drepVotesV = forall era t. V era t -> Term era t
Var (forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"drepVotesV" (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Era era => Rep era (Credential 'DRepRole)
VCredR forall era. Rep era Vote
VoteR) forall era s t. Access era s t
No)
stakePoolVotesV :: Era era => Term era (Map (KeyHash 'StakePool) Vote)
stakePoolVotesV :: forall era. Era era => Term era (Map (KeyHash 'StakePool) Vote)
stakePoolVotesV = forall era t. V era t -> Term era t
Var (forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"stakePoolVotesV" (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Era era => Rep era (KeyHash 'StakePool)
PoolHashR forall era. Rep era Vote
VoteR) forall era s t. Access era s t
No)
depositV :: Era era => Term era Coin
depositV :: forall era. Era era => Term era Coin
depositV = forall era t. V era t -> Term era t
Var (forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"depositV" forall era. Rep era Coin
CoinR forall era s t. Access era s t
No)
returnAddrV :: Era era => Term era RewardAccount
returnAddrV :: forall era. Era era => Term era RewardAccount
returnAddrV = forall era t. V era t -> Term era t
Var (forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"returnAddrV" forall era. Era era => Rep era RewardAccount
RewardAccountR forall era s t. Access era s t
No)
actionV :: Era era => Term era (GovAction era)
actionV :: forall era. Era era => Term era (GovAction era)
actionV = forall era t. V era t -> Term era t
Var (forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"actionV" forall era. Era era => Rep era (GovAction era)
GovActionR forall era s t. Access era s t
No)
proposedInV :: Era era => Term era EpochNo
proposedInV :: forall era. Era era => Term era EpochNo
proposedInV = forall era t. V era t -> Term era t
Var (forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"proposedInV" forall era. Rep era EpochNo
EpochR forall era s t. Access era s t
No)
expiresAfterV :: Era era => Term era EpochNo
expiresAfterV :: forall era. Era era => Term era EpochNo
expiresAfterV = forall era t. V era t -> Term era t
Var (forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"expiresAfterV" forall era. Rep era EpochNo
EpochR forall era s t. Access era s t
No)
childrenV :: Era era => Term era (Set GovActionId)
childrenV :: forall era. Era era => Term era (Set GovActionId)
childrenV = forall era t. V era t -> Term era t
Var (forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"childrenV" (forall a era. Ord a => Rep era a -> Rep era (Set a)
SetR forall era. Era era => Rep era GovActionId
GovActionIdR) forall era s t. Access era s t
No)
anchorV :: Era era => Term era Anchor
anchorV :: forall era. Era era => Term era Anchor
anchorV = forall era t. V era t -> Term era t
Var (forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"anchorV" forall era. Era era => Rep era Anchor
AnchorR forall era s t. Access era s t
No)
govActionStateTarget ::
forall era. Era era => RootTarget era (GovActionState era) (GovActionState era)
govActionStateTarget :: forall era.
Era era =>
RootTarget era (GovActionState era) (GovActionState era)
govActionStateTarget =
forall root a b era.
String -> TypeRep root -> (a -> b) -> RootTarget era root (a -> b)
Invert String
"GovActionState" (forall {k} (a :: k). Typeable a => TypeRep a
typeRep @(GovActionState era)) forall era.
GovActionId
-> Map (Credential 'HotCommitteeRole) Vote
-> Map (Credential 'DRepRole) Vote
-> Map (KeyHash 'StakePool) Vote
-> ProposalProcedure era
-> EpochNo
-> EpochNo
-> GovActionState era
GovActionState
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed forall era. Era era => Term era GovActionId
idV forall era. Lens' (GovActionState era) GovActionId
gasIdL
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed forall era.
Era era =>
Term era (Map (Credential 'HotCommitteeRole) Vote)
committeeVotesV forall era.
Lens'
(GovActionState era) (Map (Credential 'HotCommitteeRole) Vote)
gasCommitteeVotesL
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed forall era. Era era => Term era (Map (Credential 'DRepRole) Vote)
drepVotesV forall era.
Lens' (GovActionState era) (Map (Credential 'DRepRole) Vote)
gasDRepVotesL
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed forall era. Era era => Term era (Map (KeyHash 'StakePool) Vote)
stakePoolVotesV forall era.
Lens' (GovActionState era) (Map (KeyHash 'StakePool) Vote)
gasStakePoolVotesL
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era root2 t root.
RootTarget era root2 t -> Lens' root root2 -> RootTarget era root t
Shift
( forall root a b era.
String -> TypeRep root -> (a -> b) -> RootTarget era root (a -> b)
Invert String
"ProposalProcedure" (forall {k} (a :: k). Typeable a => TypeRep a
typeRep @(ProposalProcedure era)) forall era.
Coin
-> RewardAccount
-> GovAction era
-> Anchor
-> ProposalProcedure era
ProposalProcedure
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed forall era. Era era => Term era Coin
depositV forall era. Lens' (ProposalProcedure era) Coin
pProcDepositL
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed forall era. Era era => Term era RewardAccount
returnAddrV forall era. Lens' (ProposalProcedure era) RewardAccount
pProcReturnAddrL
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed forall era. Era era => Term era (GovAction era)
actionV forall era. Lens' (ProposalProcedure era) (GovAction era)
pProcGovActionL
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed forall era. Era era => Term era Anchor
anchorV forall era. Lens' (ProposalProcedure era) Anchor
pProcAnchorL
)
forall era. Lens' (GovActionState era) (ProposalProcedure era)
gasProposalProcedureL
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed forall era. Era era => Term era EpochNo
proposedInV forall era. Lens' (GovActionState era) EpochNo
gasProposedInL
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed forall era. Era era => Term era EpochNo
expiresAfterV forall era. Lens' (GovActionState era) EpochNo
gasExpiresAfterL
liftId :: Maybe GovActionId -> StrictMaybe (GovPurposeId p era)
liftId :: forall (p :: GovActionPurpose) era.
Maybe GovActionId -> StrictMaybe (GovPurposeId p era)
liftId Maybe GovActionId
x = forall (p :: GovActionPurpose) era.
GovActionId -> GovPurposeId p era
GovPurposeId forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall a. Maybe a -> StrictMaybe a
maybeToStrictMaybe Maybe GovActionId
x)
dropId :: StrictMaybe (GovPurposeId p era) -> Maybe GovActionId
dropId :: forall (p :: GovActionPurpose) era.
StrictMaybe (GovPurposeId p era) -> Maybe GovActionId
dropId StrictMaybe (GovPurposeId p era)
x = forall (p :: GovActionPurpose) era.
GovPurposeId p era -> GovActionId
unGovPurposeId forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall a. StrictMaybe a -> Maybe a
strictMaybeToMaybe StrictMaybe (GovPurposeId p era)
x)
gaPrevId :: Era era => Term era (Maybe GovActionId)
gaPrevId :: forall era. Era era => Term era (Maybe GovActionId)
gaPrevId = forall era t. V era t -> Term era t
Var (forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"gaPrevId" (forall era t1. Rep era t1 -> Rep era (Maybe t1)
MaybeR forall era. Era era => Rep era GovActionId
GovActionIdR) forall era s t. Access era s t
No)
gaPParamsUpdate :: Reflect era => Term era (PParamsUpdateF era)
gaPParamsUpdate :: forall era. Reflect era => Term era (PParamsUpdateF era)
gaPParamsUpdate = forall era t. V era t -> Term era t
Var (forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"gsPParamsUpdate" (forall era. Era era => Proof era -> Rep era (PParamsUpdateF era)
PParamsUpdateR forall era. Reflect era => Proof era
reify) forall era s t. Access era s t
No)
gaProtVer :: Reflect era => Term era ProtVer
gaProtVer :: forall era. Reflect era => Term era ProtVer
gaProtVer = forall era t. V era t -> Term era t
Var (forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"gaProtVer" (forall era. Era era => Proof era -> Rep era ProtVer
ProtVerR forall era. Reflect era => Proof era
reify) forall era s t. Access era s t
No)
gaRewardAccount :: Era era => Term era (Map RewardAccount Coin)
gaRewardAccount :: forall era. Era era => Term era (Map RewardAccount Coin)
gaRewardAccount = forall era t. V era t -> Term era t
Var (forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"gaRewardAccount" (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Era era => Rep era RewardAccount
RewardAccountR forall era. Rep era Coin
CoinR) forall era s t. Access era s t
No)
gaRemMember :: Era era => Term era (Set (Credential 'ColdCommitteeRole))
gaRemMember :: forall era.
Era era =>
Term era (Set (Credential 'ColdCommitteeRole))
gaRemMember = forall era t. V era t -> Term era t
Var (forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"gaRemMember" (forall a era. Ord a => Rep era a -> Rep era (Set a)
SetR forall era. Era era => Rep era (Credential 'ColdCommitteeRole)
CommColdCredR) forall era s t. Access era s t
No)
gaAddMember :: Era era => Term era (Map (Credential 'ColdCommitteeRole) EpochNo)
gaAddMember :: forall era.
Era era =>
Term era (Map (Credential 'ColdCommitteeRole) EpochNo)
gaAddMember = forall era t. V era t -> Term era t
Var (forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"gaAddMember" (forall a era b.
Ord a =>
Rep era a -> Rep era b -> Rep era (Map a b)
MapR forall era. Era era => Rep era (Credential 'ColdCommitteeRole)
CommColdCredR forall era. Rep era EpochNo
EpochR) forall era s t. Access era s t
No)
gaThreshold :: Era era => Term era UnitInterval
gaThreshold :: forall era. Era era => Term era UnitInterval
gaThreshold = forall era t. V era t -> Term era t
Var (forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"gaThreshold" forall era. Rep era UnitInterval
UnitIntervalR forall era s t. Access era s t
No)
gaPolicy :: Era era => Term era (Maybe ScriptHash)
gaPolicy :: forall era. Era era => Term era (Maybe ScriptHash)
gaPolicy = forall era t. V era t -> Term era t
Var (forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"gaPolicy" (forall era t1. Rep era t1 -> Rep era (Maybe t1)
MaybeR forall era. Era era => Rep era ScriptHash
ScriptHashR) forall era s t. Access era s t
No)
gaConstitutionAnchor :: Era era => Term era Anchor
gaConstitutionAnchor :: forall era. Era era => Term era Anchor
gaConstitutionAnchor = forall era t. V era t -> Term era t
Var (forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"gaConstitutionAnchor" forall era. Era era => Rep era Anchor
AnchorR forall era s t. Access era s t
No)
gaNewConstitution :: Era era => Term era (Constitution era)
gaNewConstitution :: forall era. Era era => Term era (Constitution era)
gaNewConstitution = forall era t. V era t -> Term era t
Var (forall era t s.
Era era =>
String -> Rep era t -> Access era s t -> V era t
V String
"gaNewConstitution" forall era. Era era => Rep era (Constitution era)
ConstitutionR forall era s t. Access era s t
No)
constitutionT :: forall era. Reflect era => RootTarget era (Constitution era) (Constitution era)
constitutionT :: forall era.
Reflect era =>
RootTarget era (Constitution era) (Constitution era)
constitutionT =
forall root a b era.
String -> TypeRep root -> (a -> b) -> RootTarget era root (a -> b)
Invert String
"Constitution" (forall {k} (a :: k). Typeable a => TypeRep a
typeRep @(Constitution era)) (\Anchor
x Maybe ScriptHash
y -> forall era. Anchor -> StrictMaybe ScriptHash -> Constitution era
Constitution Anchor
x forall a b. (a -> b) -> a -> b
$ forall a. Maybe a -> StrictMaybe a
maybeToStrictMaybe Maybe ScriptHash
y)
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed forall era. Era era => Term era Anchor
gaConstitutionAnchor forall era. Lens' (Constitution era) Anchor
constitutionAnchorL
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed forall era. Era era => Term era (Maybe ScriptHash)
gaPolicy (forall era. Lens' (Constitution era) (StrictMaybe ScriptHash)
constitutionScriptL forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall x. Lens' (StrictMaybe x) (Maybe x)
strictMaybeToMaybeL)
parameterChangeT :: forall era. Reflect era => RootTarget era (GovAction era) (GovAction era)
parameterChangeT :: forall era.
Reflect era =>
RootTarget era (GovAction era) (GovAction era)
parameterChangeT =
forall root a b era.
String -> TypeRep root -> (a -> b) -> RootTarget era root (a -> b)
Invert
String
"ParameterChange"
(forall {k} (a :: k). Typeable a => TypeRep a
typeRep @(GovAction era))
(\Maybe GovActionId
x PParamsUpdateF era
y Maybe ScriptHash
c -> forall era.
StrictMaybe (GovPurposeId 'PParamUpdatePurpose era)
-> PParamsUpdate era -> StrictMaybe ScriptHash -> GovAction era
ParameterChange (forall (p :: GovActionPurpose) era.
Maybe GovActionId -> StrictMaybe (GovPurposeId p era)
liftId Maybe GovActionId
x) (forall era. PParamsUpdateF era -> PParamsUpdate era
unPParamsUpdate PParamsUpdateF era
y) (forall a. Maybe a -> StrictMaybe a
maybeToStrictMaybe Maybe ScriptHash
c))
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> (root -> Maybe t) -> RootTarget era root t
Partial forall era. Era era => Term era (Maybe GovActionId)
gaPrevId (\case (ParameterChange StrictMaybe (GovPurposeId 'PParamUpdatePurpose era)
x PParamsUpdate era
_ StrictMaybe ScriptHash
_) -> forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall (p :: GovActionPurpose) era.
StrictMaybe (GovPurposeId p era) -> Maybe GovActionId
dropId StrictMaybe (GovPurposeId 'PParamUpdatePurpose era)
x; GovAction era
_ -> forall a. Maybe a
Nothing)
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> (root -> Maybe t) -> RootTarget era root t
Partial
forall era. Reflect era => Term era (PParamsUpdateF era)
gaPParamsUpdate
(\case (ParameterChange StrictMaybe (GovPurposeId 'PParamUpdatePurpose era)
_ PParamsUpdate era
y StrictMaybe ScriptHash
_) -> forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall era. Proof era -> PParamsUpdate era -> PParamsUpdateF era
PParamsUpdateF forall era. Reflect era => Proof era
reify PParamsUpdate era
y; GovAction era
_ -> forall a. Maybe a
Nothing)
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> (root -> Maybe t) -> RootTarget era root t
Partial forall era. Era era => Term era (Maybe ScriptHash)
gaPolicy (\case (ParameterChange StrictMaybe (GovPurposeId 'PParamUpdatePurpose era)
_ PParamsUpdate era
_ StrictMaybe ScriptHash
x) -> forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall a. StrictMaybe a -> Maybe a
strictMaybeToMaybe StrictMaybe ScriptHash
x; GovAction era
_ -> forall a. Maybe a
Nothing)
hardForkInitiationT :: forall era. Reflect era => RootTarget era (GovAction era) (GovAction era)
hardForkInitiationT :: forall era.
Reflect era =>
RootTarget era (GovAction era) (GovAction era)
hardForkInitiationT =
forall root a b era.
String -> TypeRep root -> (a -> b) -> RootTarget era root (a -> b)
Invert String
"HardForkInitiation" (forall {k} (a :: k). Typeable a => TypeRep a
typeRep @(GovAction era)) (\Maybe GovActionId
x ProtVer
y -> forall era.
StrictMaybe (GovPurposeId 'HardForkPurpose era)
-> ProtVer -> GovAction era
HardForkInitiation (forall (p :: GovActionPurpose) era.
Maybe GovActionId -> StrictMaybe (GovPurposeId p era)
liftId Maybe GovActionId
x) ProtVer
y)
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> (root -> Maybe t) -> RootTarget era root t
Partial forall era. Era era => Term era (Maybe GovActionId)
gaPrevId (\case (HardForkInitiation StrictMaybe (GovPurposeId 'HardForkPurpose era)
x ProtVer
_) -> forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall (p :: GovActionPurpose) era.
StrictMaybe (GovPurposeId p era) -> Maybe GovActionId
dropId StrictMaybe (GovPurposeId 'HardForkPurpose era)
x; GovAction era
_ -> forall a. Maybe a
Nothing)
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> (root -> Maybe t) -> RootTarget era root t
Partial forall era. Reflect era => Term era ProtVer
gaProtVer (\case (HardForkInitiation StrictMaybe (GovPurposeId 'HardForkPurpose era)
_ ProtVer
y) -> forall a. a -> Maybe a
Just ProtVer
y; GovAction era
_ -> forall a. Maybe a
Nothing)
treasuryWithdrawalsT :: forall era. Reflect era => RootTarget era (GovAction era) (GovAction era)
treasuryWithdrawalsT :: forall era.
Reflect era =>
RootTarget era (GovAction era) (GovAction era)
treasuryWithdrawalsT =
forall root a b era.
String -> TypeRep root -> (a -> b) -> RootTarget era root (a -> b)
Invert
String
"TreasuryWithdrawals"
(forall {k} (a :: k). Typeable a => TypeRep a
typeRep @(GovAction era))
(\Map RewardAccount Coin
x Maybe ScriptHash
y -> forall era.
Map RewardAccount Coin -> StrictMaybe ScriptHash -> GovAction era
TreasuryWithdrawals Map RewardAccount Coin
x forall a b. (a -> b) -> a -> b
$ forall a. Maybe a -> StrictMaybe a
maybeToStrictMaybe Maybe ScriptHash
y)
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> (root -> Maybe t) -> RootTarget era root t
Partial forall era. Era era => Term era (Map RewardAccount Coin)
gaRewardAccount (\case (TreasuryWithdrawals Map RewardAccount Coin
x StrictMaybe ScriptHash
_) -> forall a. a -> Maybe a
Just Map RewardAccount Coin
x; GovAction era
_ -> forall a. Maybe a
Nothing)
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> (root -> Maybe t) -> RootTarget era root t
Partial forall era. Era era => Term era (Maybe ScriptHash)
gaPolicy (\case (TreasuryWithdrawals Map RewardAccount Coin
_ StrictMaybe ScriptHash
y) -> forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall a. StrictMaybe a -> Maybe a
strictMaybeToMaybe StrictMaybe ScriptHash
y; GovAction era
_ -> forall a. Maybe a
Nothing)
noConfidenceT :: forall era. Reflect era => RootTarget era (GovAction era) (GovAction era)
noConfidenceT :: forall era.
Reflect era =>
RootTarget era (GovAction era) (GovAction era)
noConfidenceT =
forall root a b era.
String -> TypeRep root -> (a -> b) -> RootTarget era root (a -> b)
Invert String
"NoConfidence" (forall {k} (a :: k). Typeable a => TypeRep a
typeRep @(GovAction era)) (\Maybe GovActionId
x -> forall era.
StrictMaybe (GovPurposeId 'CommitteePurpose era) -> GovAction era
NoConfidence (forall (p :: GovActionPurpose) era.
Maybe GovActionId -> StrictMaybe (GovPurposeId p era)
liftId Maybe GovActionId
x))
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> (root -> Maybe t) -> RootTarget era root t
Partial forall era. Era era => Term era (Maybe GovActionId)
gaPrevId (\case (NoConfidence StrictMaybe (GovPurposeId 'CommitteePurpose era)
x) -> forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall (p :: GovActionPurpose) era.
StrictMaybe (GovPurposeId p era) -> Maybe GovActionId
dropId StrictMaybe (GovPurposeId 'CommitteePurpose era)
x; GovAction era
_ -> forall a. Maybe a
Nothing)
updateCommitteeT :: forall era. Reflect era => RootTarget era (GovAction era) (GovAction era)
updateCommitteeT :: forall era.
Reflect era =>
RootTarget era (GovAction era) (GovAction era)
updateCommitteeT =
forall root a b era.
String -> TypeRep root -> (a -> b) -> RootTarget era root (a -> b)
Invert String
"UpdateCommittee" (forall {k} (a :: k). Typeable a => TypeRep a
typeRep @(GovAction era)) (\Maybe GovActionId
w Set (Credential 'ColdCommitteeRole)
x Map (Credential 'ColdCommitteeRole) EpochNo
y UnitInterval
z -> forall era.
StrictMaybe (GovPurposeId 'CommitteePurpose era)
-> Set (Credential 'ColdCommitteeRole)
-> Map (Credential 'ColdCommitteeRole) EpochNo
-> UnitInterval
-> GovAction era
UpdateCommittee (forall (p :: GovActionPurpose) era.
Maybe GovActionId -> StrictMaybe (GovPurposeId p era)
liftId Maybe GovActionId
w) Set (Credential 'ColdCommitteeRole)
x Map (Credential 'ColdCommitteeRole) EpochNo
y UnitInterval
z)
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> (root -> Maybe t) -> RootTarget era root t
Partial forall era. Era era => Term era (Maybe GovActionId)
gaPrevId (\case (UpdateCommittee StrictMaybe (GovPurposeId 'CommitteePurpose era)
x Set (Credential 'ColdCommitteeRole)
_ Map (Credential 'ColdCommitteeRole) EpochNo
_ UnitInterval
_) -> forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall (p :: GovActionPurpose) era.
StrictMaybe (GovPurposeId p era) -> Maybe GovActionId
dropId StrictMaybe (GovPurposeId 'CommitteePurpose era)
x; GovAction era
_ -> forall a. Maybe a
Nothing)
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> (root -> Maybe t) -> RootTarget era root t
Partial forall era.
Era era =>
Term era (Set (Credential 'ColdCommitteeRole))
gaRemMember (\case (UpdateCommittee StrictMaybe (GovPurposeId 'CommitteePurpose era)
_ Set (Credential 'ColdCommitteeRole)
x Map (Credential 'ColdCommitteeRole) EpochNo
_ UnitInterval
_) -> forall a. a -> Maybe a
Just Set (Credential 'ColdCommitteeRole)
x; GovAction era
_ -> forall a. Maybe a
Nothing)
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> (root -> Maybe t) -> RootTarget era root t
Partial forall era.
Era era =>
Term era (Map (Credential 'ColdCommitteeRole) EpochNo)
gaAddMember (\case (UpdateCommittee StrictMaybe (GovPurposeId 'CommitteePurpose era)
_ Set (Credential 'ColdCommitteeRole)
_ Map (Credential 'ColdCommitteeRole) EpochNo
x UnitInterval
_) -> forall a. a -> Maybe a
Just Map (Credential 'ColdCommitteeRole) EpochNo
x; GovAction era
_ -> forall a. Maybe a
Nothing)
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> (root -> Maybe t) -> RootTarget era root t
Partial forall era. Era era => Term era UnitInterval
gaThreshold (\case (UpdateCommittee StrictMaybe (GovPurposeId 'CommitteePurpose era)
_ Set (Credential 'ColdCommitteeRole)
_ Map (Credential 'ColdCommitteeRole) EpochNo
_ UnitInterval
x) -> forall a. a -> Maybe a
Just UnitInterval
x; GovAction era
_ -> forall a. Maybe a
Nothing)
newConstitutionT :: forall era. Reflect era => RootTarget era (GovAction era) (GovAction era)
newConstitutionT :: forall era.
Reflect era =>
RootTarget era (GovAction era) (GovAction era)
newConstitutionT =
forall root a b era.
String -> TypeRep root -> (a -> b) -> RootTarget era root (a -> b)
Invert String
"NewConstitution" (forall {k} (a :: k). Typeable a => TypeRep a
typeRep @(GovAction era)) (\Maybe GovActionId
x Constitution era
y -> forall era.
StrictMaybe (GovPurposeId 'ConstitutionPurpose era)
-> Constitution era -> GovAction era
NewConstitution (forall (p :: GovActionPurpose) era.
Maybe GovActionId -> StrictMaybe (GovPurposeId p era)
liftId Maybe GovActionId
x) Constitution era
y)
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> (root -> Maybe t) -> RootTarget era root t
Partial forall era. Era era => Term era (Maybe GovActionId)
gaPrevId (\case (UpdateCommittee StrictMaybe (GovPurposeId 'CommitteePurpose era)
x Set (Credential 'ColdCommitteeRole)
_ Map (Credential 'ColdCommitteeRole) EpochNo
_ UnitInterval
_) -> forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall (p :: GovActionPurpose) era.
StrictMaybe (GovPurposeId p era) -> Maybe GovActionId
dropId StrictMaybe (GovPurposeId 'CommitteePurpose era)
x; GovAction era
_ -> forall a. Maybe a
Nothing)
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> (root -> Maybe t) -> RootTarget era root t
Partial forall era. Era era => Term era (Constitution era)
gaNewConstitution (\case (NewConstitution StrictMaybe (GovPurposeId 'ConstitutionPurpose era)
_ Constitution era
y) -> forall a. a -> Maybe a
Just Constitution era
y; GovAction era
_ -> forall a. Maybe a
Nothing)
infoActionT :: forall era. Reflect era => RootTarget era (GovAction era) (GovAction era)
infoActionT :: forall era.
Reflect era =>
RootTarget era (GovAction era) (GovAction era)
infoActionT =
forall root a b era.
String -> TypeRep root -> (a -> b) -> RootTarget era root (a -> b)
Invert String
"InfoAction" (forall {k} (a :: k). Typeable a => TypeRep a
typeRep @(GovAction era)) (\() -> forall era. GovAction era
InfoAction)
forall era root a t.
RootTarget era root (a -> t)
-> RootTarget era root a -> RootTarget era root t
:$ forall era t root.
Term era t -> SimpleGetter root t -> RootTarget era root t
Lensed (forall era t. Rep era t -> t -> Term era t
Lit forall era. Rep era ()
UnitR ()) (forall s a. (s -> a) -> SimpleGetter s a
to (forall a b. a -> b -> a
const ()))