{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
module Cardano.Ledger.State.StakePool (
StakePoolState (..),
spsVrfL,
spsPledgeL,
spsCostL,
spsMarginL,
spsRewardAccountL,
spsOwnersL,
spsRelaysL,
spsMetadataL,
spsDelegatorsL,
spsDepositL,
mkStakePoolState,
stakePoolStateToStakePoolParams,
StakePoolParams (
..,
PoolParams,
ppId,
ppVrf,
ppPledge,
ppCost,
ppMargin,
ppRewardAccount,
ppOwners,
ppRelays,
ppMetadata
),
PoolMetadata (..),
StakePoolRelay (..),
SizeOfPoolRelays (..),
SizeOfPoolOwners (..),
sppCostL,
sppMetadataL,
sppVrfL,
) where
import Cardano.Ledger.Address (RewardAccount (..))
import Cardano.Ledger.BaseTypes (
DnsName,
Network,
Port,
StrictMaybe (..),
UnitInterval,
Url,
invalidKey,
)
import Cardano.Ledger.Binary (
CBORGroup (..),
DecCBOR (..),
DecCBORGroup (..),
DecShareCBOR (..),
EncCBOR (..),
EncCBORGroup (..),
Interns,
decodeNullStrictMaybe,
decodeRecordNamed,
decodeRecordNamedT,
decodeRecordSum,
encodeListLen,
encodeNullStrictMaybe,
)
import Cardano.Ledger.Binary.Coders (
Decode (..),
Encode (..),
decode,
encode,
(!>),
(<!),
)
import Cardano.Ledger.Coin (Coin (..), CompactForm)
import Cardano.Ledger.Credential (Credential)
import Cardano.Ledger.Keys (KeyHash (..), KeyRole (..), KeyRoleVRF (StakePoolVRF), VRFVerKeyHash)
import Cardano.Ledger.Orphans ()
import Control.DeepSeq (NFData)
import Control.Monad (unless)
import Control.Monad.Trans (lift)
import Data.Aeson (FromJSON (..), ToJSON (..), Value, (.!=), (.:), (.:?), (.=))
import qualified Data.Aeson as Aeson
import Data.Aeson.Types (Parser, explicitParseField)
import Data.ByteString (ByteString)
import qualified Data.ByteString.Base16 as B16
import Data.Default (Default (..))
import Data.Foldable (asum)
import Data.IP (IPv4, IPv6)
import Data.Sequence.Strict (StrictSeq)
import Data.Set (Set)
import qualified Data.Text as Text
import qualified Data.Text.Encoding as Text
import Data.Word (Word8)
import GHC.Generics (Generic)
import Lens.Micro
import NoThunks.Class (NoThunks (..))
data StakePoolState = StakePoolState
{ StakePoolState -> VRFVerKeyHash StakePoolVRF
spsVrf :: !(VRFVerKeyHash StakePoolVRF)
, StakePoolState -> Coin
spsPledge :: !Coin
, StakePoolState -> Coin
spsCost :: !Coin
, StakePoolState -> UnitInterval
spsMargin :: !UnitInterval
, StakePoolState -> Credential Staking
spsRewardAccount :: !(Credential Staking)
, StakePoolState -> Set (KeyHash Staking)
spsOwners :: !(Set (KeyHash Staking))
, StakePoolState -> StrictSeq StakePoolRelay
spsRelays :: !(StrictSeq StakePoolRelay)
, StakePoolState -> StrictMaybe PoolMetadata
spsMetadata :: !(StrictMaybe PoolMetadata)
, StakePoolState -> CompactForm Coin
spsDeposit :: !(CompactForm Coin)
, StakePoolState -> Set (Credential Staking)
spsDelegators :: !(Set (Credential Staking))
}
deriving (Int -> StakePoolState -> ShowS
[StakePoolState] -> ShowS
StakePoolState -> String
(Int -> StakePoolState -> ShowS)
-> (StakePoolState -> String)
-> ([StakePoolState] -> ShowS)
-> Show StakePoolState
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> StakePoolState -> ShowS
showsPrec :: Int -> StakePoolState -> ShowS
$cshow :: StakePoolState -> String
show :: StakePoolState -> String
$cshowList :: [StakePoolState] -> ShowS
showList :: [StakePoolState] -> ShowS
Show, (forall x. StakePoolState -> Rep StakePoolState x)
-> (forall x. Rep StakePoolState x -> StakePoolState)
-> Generic StakePoolState
forall x. Rep StakePoolState x -> StakePoolState
forall x. StakePoolState -> Rep StakePoolState x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. StakePoolState -> Rep StakePoolState x
from :: forall x. StakePoolState -> Rep StakePoolState x
$cto :: forall x. Rep StakePoolState x -> StakePoolState
to :: forall x. Rep StakePoolState x -> StakePoolState
Generic, StakePoolState -> StakePoolState -> Bool
(StakePoolState -> StakePoolState -> Bool)
-> (StakePoolState -> StakePoolState -> Bool) -> Eq StakePoolState
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: StakePoolState -> StakePoolState -> Bool
== :: StakePoolState -> StakePoolState -> Bool
$c/= :: StakePoolState -> StakePoolState -> Bool
/= :: StakePoolState -> StakePoolState -> Bool
Eq, Eq StakePoolState
Eq StakePoolState =>
(StakePoolState -> StakePoolState -> Ordering)
-> (StakePoolState -> StakePoolState -> Bool)
-> (StakePoolState -> StakePoolState -> Bool)
-> (StakePoolState -> StakePoolState -> Bool)
-> (StakePoolState -> StakePoolState -> Bool)
-> (StakePoolState -> StakePoolState -> StakePoolState)
-> (StakePoolState -> StakePoolState -> StakePoolState)
-> Ord StakePoolState
StakePoolState -> StakePoolState -> Bool
StakePoolState -> StakePoolState -> Ordering
StakePoolState -> StakePoolState -> StakePoolState
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: StakePoolState -> StakePoolState -> Ordering
compare :: StakePoolState -> StakePoolState -> Ordering
$c< :: StakePoolState -> StakePoolState -> Bool
< :: StakePoolState -> StakePoolState -> Bool
$c<= :: StakePoolState -> StakePoolState -> Bool
<= :: StakePoolState -> StakePoolState -> Bool
$c> :: StakePoolState -> StakePoolState -> Bool
> :: StakePoolState -> StakePoolState -> Bool
$c>= :: StakePoolState -> StakePoolState -> Bool
>= :: StakePoolState -> StakePoolState -> Bool
$cmax :: StakePoolState -> StakePoolState -> StakePoolState
max :: StakePoolState -> StakePoolState -> StakePoolState
$cmin :: StakePoolState -> StakePoolState -> StakePoolState
min :: StakePoolState -> StakePoolState -> StakePoolState
Ord, Context -> StakePoolState -> IO (Maybe ThunkInfo)
Proxy StakePoolState -> String
(Context -> StakePoolState -> IO (Maybe ThunkInfo))
-> (Context -> StakePoolState -> IO (Maybe ThunkInfo))
-> (Proxy StakePoolState -> String)
-> NoThunks StakePoolState
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
$cnoThunks :: Context -> StakePoolState -> IO (Maybe ThunkInfo)
noThunks :: Context -> StakePoolState -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> StakePoolState -> IO (Maybe ThunkInfo)
wNoThunks :: Context -> StakePoolState -> IO (Maybe ThunkInfo)
$cshowTypeOf :: Proxy StakePoolState -> String
showTypeOf :: Proxy StakePoolState -> String
NoThunks, StakePoolState -> ()
(StakePoolState -> ()) -> NFData StakePoolState
forall a. (a -> ()) -> NFData a
$crnf :: StakePoolState -> ()
rnf :: StakePoolState -> ()
NFData, Maybe StakePoolState
Value -> Parser [StakePoolState]
Value -> Parser StakePoolState
(Value -> Parser StakePoolState)
-> (Value -> Parser [StakePoolState])
-> Maybe StakePoolState
-> FromJSON StakePoolState
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser StakePoolState
parseJSON :: Value -> Parser StakePoolState
$cparseJSONList :: Value -> Parser [StakePoolState]
parseJSONList :: Value -> Parser [StakePoolState]
$comittedField :: Maybe StakePoolState
omittedField :: Maybe StakePoolState
FromJSON, [StakePoolState] -> Value
[StakePoolState] -> Encoding
StakePoolState -> Bool
StakePoolState -> Value
StakePoolState -> Encoding
(StakePoolState -> Value)
-> (StakePoolState -> Encoding)
-> ([StakePoolState] -> Value)
-> ([StakePoolState] -> Encoding)
-> (StakePoolState -> Bool)
-> ToJSON StakePoolState
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: StakePoolState -> Value
toJSON :: StakePoolState -> Value
$ctoEncoding :: StakePoolState -> Encoding
toEncoding :: StakePoolState -> Encoding
$ctoJSONList :: [StakePoolState] -> Value
toJSONList :: [StakePoolState] -> Value
$ctoEncodingList :: [StakePoolState] -> Encoding
toEncodingList :: [StakePoolState] -> Encoding
$comitField :: StakePoolState -> Bool
omitField :: StakePoolState -> Bool
ToJSON)
spsVrfL :: Lens' StakePoolState (VRFVerKeyHash StakePoolVRF)
spsVrfL :: Lens' StakePoolState (VRFVerKeyHash StakePoolVRF)
spsVrfL = (StakePoolState -> VRFVerKeyHash StakePoolVRF)
-> (StakePoolState -> VRFVerKeyHash StakePoolVRF -> StakePoolState)
-> Lens' StakePoolState (VRFVerKeyHash StakePoolVRF)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens StakePoolState -> VRFVerKeyHash StakePoolVRF
spsVrf (\StakePoolState
sps VRFVerKeyHash StakePoolVRF
u -> StakePoolState
sps {spsVrf = u})
spsPledgeL :: Lens' StakePoolState Coin
spsPledgeL :: Lens' StakePoolState Coin
spsPledgeL = (StakePoolState -> Coin)
-> (StakePoolState -> Coin -> StakePoolState)
-> Lens' StakePoolState Coin
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens StakePoolState -> Coin
spsPledge ((StakePoolState -> Coin -> StakePoolState)
-> Lens' StakePoolState Coin)
-> (StakePoolState -> Coin -> StakePoolState)
-> Lens' StakePoolState Coin
forall a b. (a -> b) -> a -> b
$ \StakePoolState
sps Coin
c -> StakePoolState
sps {spsPledge = c}
spsCostL :: Lens' StakePoolState Coin
spsCostL :: Lens' StakePoolState Coin
spsCostL = (StakePoolState -> Coin)
-> (StakePoolState -> Coin -> StakePoolState)
-> Lens' StakePoolState Coin
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens StakePoolState -> Coin
spsCost ((StakePoolState -> Coin -> StakePoolState)
-> Lens' StakePoolState Coin)
-> (StakePoolState -> Coin -> StakePoolState)
-> Lens' StakePoolState Coin
forall a b. (a -> b) -> a -> b
$ \StakePoolState
sps Coin
c -> StakePoolState
sps {spsCost = c}
spsMarginL :: Lens' StakePoolState UnitInterval
spsMarginL :: Lens' StakePoolState UnitInterval
spsMarginL = (StakePoolState -> UnitInterval)
-> (StakePoolState -> UnitInterval -> StakePoolState)
-> Lens' StakePoolState UnitInterval
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens StakePoolState -> UnitInterval
spsMargin ((StakePoolState -> UnitInterval -> StakePoolState)
-> Lens' StakePoolState UnitInterval)
-> (StakePoolState -> UnitInterval -> StakePoolState)
-> Lens' StakePoolState UnitInterval
forall a b. (a -> b) -> a -> b
$ \StakePoolState
sps UnitInterval
m -> StakePoolState
sps {spsMargin = m}
spsRewardAccountL :: Lens' StakePoolState (Credential Staking)
spsRewardAccountL :: Lens' StakePoolState (Credential Staking)
spsRewardAccountL = (StakePoolState -> Credential Staking)
-> (StakePoolState -> Credential Staking -> StakePoolState)
-> Lens' StakePoolState (Credential Staking)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens StakePoolState -> Credential Staking
spsRewardAccount ((StakePoolState -> Credential Staking -> StakePoolState)
-> Lens' StakePoolState (Credential Staking))
-> (StakePoolState -> Credential Staking -> StakePoolState)
-> Lens' StakePoolState (Credential Staking)
forall a b. (a -> b) -> a -> b
$ \StakePoolState
sps Credential Staking
sc -> StakePoolState
sps {spsRewardAccount = sc}
spsOwnersL :: Lens' StakePoolState (Set (KeyHash Staking))
spsOwnersL :: Lens' StakePoolState (Set (KeyHash Staking))
spsOwnersL = (StakePoolState -> Set (KeyHash Staking))
-> (StakePoolState -> Set (KeyHash Staking) -> StakePoolState)
-> Lens' StakePoolState (Set (KeyHash Staking))
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens StakePoolState -> Set (KeyHash Staking)
spsOwners ((StakePoolState -> Set (KeyHash Staking) -> StakePoolState)
-> Lens' StakePoolState (Set (KeyHash Staking)))
-> (StakePoolState -> Set (KeyHash Staking) -> StakePoolState)
-> Lens' StakePoolState (Set (KeyHash Staking))
forall a b. (a -> b) -> a -> b
$ \StakePoolState
sps Set (KeyHash Staking)
s -> StakePoolState
sps {spsOwners = s}
spsRelaysL :: Lens' StakePoolState (StrictSeq StakePoolRelay)
spsRelaysL :: Lens' StakePoolState (StrictSeq StakePoolRelay)
spsRelaysL = (StakePoolState -> StrictSeq StakePoolRelay)
-> (StakePoolState -> StrictSeq StakePoolRelay -> StakePoolState)
-> Lens' StakePoolState (StrictSeq StakePoolRelay)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens StakePoolState -> StrictSeq StakePoolRelay
spsRelays ((StakePoolState -> StrictSeq StakePoolRelay -> StakePoolState)
-> Lens' StakePoolState (StrictSeq StakePoolRelay))
-> (StakePoolState -> StrictSeq StakePoolRelay -> StakePoolState)
-> Lens' StakePoolState (StrictSeq StakePoolRelay)
forall a b. (a -> b) -> a -> b
$ \StakePoolState
sps StrictSeq StakePoolRelay
rs -> StakePoolState
sps {spsRelays = rs}
spsMetadataL :: Lens' StakePoolState (StrictMaybe PoolMetadata)
spsMetadataL :: Lens' StakePoolState (StrictMaybe PoolMetadata)
spsMetadataL = (StakePoolState -> StrictMaybe PoolMetadata)
-> (StakePoolState -> StrictMaybe PoolMetadata -> StakePoolState)
-> Lens' StakePoolState (StrictMaybe PoolMetadata)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens StakePoolState -> StrictMaybe PoolMetadata
spsMetadata ((StakePoolState -> StrictMaybe PoolMetadata -> StakePoolState)
-> Lens' StakePoolState (StrictMaybe PoolMetadata))
-> (StakePoolState -> StrictMaybe PoolMetadata -> StakePoolState)
-> Lens' StakePoolState (StrictMaybe PoolMetadata)
forall a b. (a -> b) -> a -> b
$ \StakePoolState
sps StrictMaybe PoolMetadata
md -> StakePoolState
sps {spsMetadata = md}
spsDepositL :: Lens' StakePoolState (CompactForm Coin)
spsDepositL :: Lens' StakePoolState (CompactForm Coin)
spsDepositL = (StakePoolState -> CompactForm Coin)
-> (StakePoolState -> CompactForm Coin -> StakePoolState)
-> Lens' StakePoolState (CompactForm Coin)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens StakePoolState -> CompactForm Coin
spsDeposit ((StakePoolState -> CompactForm Coin -> StakePoolState)
-> Lens' StakePoolState (CompactForm Coin))
-> (StakePoolState -> CompactForm Coin -> StakePoolState)
-> Lens' StakePoolState (CompactForm Coin)
forall a b. (a -> b) -> a -> b
$ \StakePoolState
sps CompactForm Coin
d -> StakePoolState
sps {spsDeposit = d}
spsDelegatorsL :: Lens' StakePoolState (Set (Credential Staking))
spsDelegatorsL :: Lens' StakePoolState (Set (Credential Staking))
spsDelegatorsL = (StakePoolState -> Set (Credential Staking))
-> (StakePoolState -> Set (Credential Staking) -> StakePoolState)
-> Lens' StakePoolState (Set (Credential Staking))
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens StakePoolState -> Set (Credential Staking)
spsDelegators ((StakePoolState -> Set (Credential Staking) -> StakePoolState)
-> Lens' StakePoolState (Set (Credential Staking)))
-> (StakePoolState -> Set (Credential Staking) -> StakePoolState)
-> Lens' StakePoolState (Set (Credential Staking))
forall a b. (a -> b) -> a -> b
$ \StakePoolState
sps Set (Credential Staking)
delegators -> StakePoolState
sps {spsDelegators = delegators}
instance EncCBOR StakePoolState where
encCBOR :: StakePoolState -> Encoding
encCBOR StakePoolState
sps =
Encode (Closed Dense) StakePoolState -> Encoding
forall (w :: Wrapped) t. Encode w t -> Encoding
encode (Encode (Closed Dense) StakePoolState -> Encoding)
-> Encode (Closed Dense) StakePoolState -> Encoding
forall a b. (a -> b) -> a -> b
$
(VRFVerKeyHash StakePoolVRF
-> Coin
-> Coin
-> UnitInterval
-> Credential Staking
-> Set (KeyHash Staking)
-> StrictSeq StakePoolRelay
-> StrictMaybe PoolMetadata
-> CompactForm Coin
-> Set (Credential Staking)
-> StakePoolState)
-> Encode
(Closed Dense)
(VRFVerKeyHash StakePoolVRF
-> Coin
-> Coin
-> UnitInterval
-> Credential Staking
-> Set (KeyHash Staking)
-> StrictSeq StakePoolRelay
-> StrictMaybe PoolMetadata
-> CompactForm Coin
-> Set (Credential Staking)
-> StakePoolState)
forall t. t -> Encode (Closed Dense) t
Rec VRFVerKeyHash StakePoolVRF
-> Coin
-> Coin
-> UnitInterval
-> Credential Staking
-> Set (KeyHash Staking)
-> StrictSeq StakePoolRelay
-> StrictMaybe PoolMetadata
-> CompactForm Coin
-> Set (Credential Staking)
-> StakePoolState
StakePoolState
Encode
(Closed Dense)
(VRFVerKeyHash StakePoolVRF
-> Coin
-> Coin
-> UnitInterval
-> Credential Staking
-> Set (KeyHash Staking)
-> StrictSeq StakePoolRelay
-> StrictMaybe PoolMetadata
-> CompactForm Coin
-> Set (Credential Staking)
-> StakePoolState)
-> Encode (Closed Dense) (VRFVerKeyHash StakePoolVRF)
-> Encode
(Closed Dense)
(Coin
-> Coin
-> UnitInterval
-> Credential Staking
-> Set (KeyHash Staking)
-> StrictSeq StakePoolRelay
-> StrictMaybe PoolMetadata
-> CompactForm Coin
-> Set (Credential Staking)
-> StakePoolState)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode (Closed r) a -> Encode w t
!> VRFVerKeyHash StakePoolVRF
-> Encode (Closed Dense) (VRFVerKeyHash StakePoolVRF)
forall t. EncCBOR t => t -> Encode (Closed Dense) t
To (StakePoolState -> VRFVerKeyHash StakePoolVRF
spsVrf StakePoolState
sps)
Encode
(Closed Dense)
(Coin
-> Coin
-> UnitInterval
-> Credential Staking
-> Set (KeyHash Staking)
-> StrictSeq StakePoolRelay
-> StrictMaybe PoolMetadata
-> CompactForm Coin
-> Set (Credential Staking)
-> StakePoolState)
-> Encode (Closed Dense) Coin
-> Encode
(Closed Dense)
(Coin
-> UnitInterval
-> Credential Staking
-> Set (KeyHash Staking)
-> StrictSeq StakePoolRelay
-> StrictMaybe PoolMetadata
-> CompactForm Coin
-> Set (Credential Staking)
-> StakePoolState)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode (Closed r) a -> Encode w t
!> Coin -> Encode (Closed Dense) Coin
forall t. EncCBOR t => t -> Encode (Closed Dense) t
To (StakePoolState -> Coin
spsPledge StakePoolState
sps)
Encode
(Closed Dense)
(Coin
-> UnitInterval
-> Credential Staking
-> Set (KeyHash Staking)
-> StrictSeq StakePoolRelay
-> StrictMaybe PoolMetadata
-> CompactForm Coin
-> Set (Credential Staking)
-> StakePoolState)
-> Encode (Closed Dense) Coin
-> Encode
(Closed Dense)
(UnitInterval
-> Credential Staking
-> Set (KeyHash Staking)
-> StrictSeq StakePoolRelay
-> StrictMaybe PoolMetadata
-> CompactForm Coin
-> Set (Credential Staking)
-> StakePoolState)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode (Closed r) a -> Encode w t
!> Coin -> Encode (Closed Dense) Coin
forall t. EncCBOR t => t -> Encode (Closed Dense) t
To (StakePoolState -> Coin
spsCost StakePoolState
sps)
Encode
(Closed Dense)
(UnitInterval
-> Credential Staking
-> Set (KeyHash Staking)
-> StrictSeq StakePoolRelay
-> StrictMaybe PoolMetadata
-> CompactForm Coin
-> Set (Credential Staking)
-> StakePoolState)
-> Encode (Closed Dense) UnitInterval
-> Encode
(Closed Dense)
(Credential Staking
-> Set (KeyHash Staking)
-> StrictSeq StakePoolRelay
-> StrictMaybe PoolMetadata
-> CompactForm Coin
-> Set (Credential Staking)
-> StakePoolState)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode (Closed r) a -> Encode w t
!> UnitInterval -> Encode (Closed Dense) UnitInterval
forall t. EncCBOR t => t -> Encode (Closed Dense) t
To (StakePoolState -> UnitInterval
spsMargin StakePoolState
sps)
Encode
(Closed Dense)
(Credential Staking
-> Set (KeyHash Staking)
-> StrictSeq StakePoolRelay
-> StrictMaybe PoolMetadata
-> CompactForm Coin
-> Set (Credential Staking)
-> StakePoolState)
-> Encode (Closed Dense) (Credential Staking)
-> Encode
(Closed Dense)
(Set (KeyHash Staking)
-> StrictSeq StakePoolRelay
-> StrictMaybe PoolMetadata
-> CompactForm Coin
-> Set (Credential Staking)
-> StakePoolState)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode (Closed r) a -> Encode w t
!> Credential Staking -> Encode (Closed Dense) (Credential Staking)
forall t. EncCBOR t => t -> Encode (Closed Dense) t
To (StakePoolState -> Credential Staking
spsRewardAccount StakePoolState
sps)
Encode
(Closed Dense)
(Set (KeyHash Staking)
-> StrictSeq StakePoolRelay
-> StrictMaybe PoolMetadata
-> CompactForm Coin
-> Set (Credential Staking)
-> StakePoolState)
-> Encode (Closed Dense) (Set (KeyHash Staking))
-> Encode
(Closed Dense)
(StrictSeq StakePoolRelay
-> StrictMaybe PoolMetadata
-> CompactForm Coin
-> Set (Credential Staking)
-> StakePoolState)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode (Closed r) a -> Encode w t
!> Set (KeyHash Staking)
-> Encode (Closed Dense) (Set (KeyHash Staking))
forall t. EncCBOR t => t -> Encode (Closed Dense) t
To (StakePoolState -> Set (KeyHash Staking)
spsOwners StakePoolState
sps)
Encode
(Closed Dense)
(StrictSeq StakePoolRelay
-> StrictMaybe PoolMetadata
-> CompactForm Coin
-> Set (Credential Staking)
-> StakePoolState)
-> Encode (Closed Dense) (StrictSeq StakePoolRelay)
-> Encode
(Closed Dense)
(StrictMaybe PoolMetadata
-> CompactForm Coin -> Set (Credential Staking) -> StakePoolState)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode (Closed r) a -> Encode w t
!> StrictSeq StakePoolRelay
-> Encode (Closed Dense) (StrictSeq StakePoolRelay)
forall t. EncCBOR t => t -> Encode (Closed Dense) t
To (StakePoolState -> StrictSeq StakePoolRelay
spsRelays StakePoolState
sps)
Encode
(Closed Dense)
(StrictMaybe PoolMetadata
-> CompactForm Coin -> Set (Credential Staking) -> StakePoolState)
-> Encode (Closed Dense) (StrictMaybe PoolMetadata)
-> Encode
(Closed Dense)
(CompactForm Coin -> Set (Credential Staking) -> StakePoolState)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode (Closed r) a -> Encode w t
!> StrictMaybe PoolMetadata
-> Encode (Closed Dense) (StrictMaybe PoolMetadata)
forall t. EncCBOR t => t -> Encode (Closed Dense) t
To (StakePoolState -> StrictMaybe PoolMetadata
spsMetadata StakePoolState
sps)
Encode
(Closed Dense)
(CompactForm Coin -> Set (Credential Staking) -> StakePoolState)
-> Encode (Closed Dense) (CompactForm Coin)
-> Encode
(Closed Dense) (Set (Credential Staking) -> StakePoolState)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode (Closed r) a -> Encode w t
!> CompactForm Coin -> Encode (Closed Dense) (CompactForm Coin)
forall t. EncCBOR t => t -> Encode (Closed Dense) t
To (StakePoolState -> CompactForm Coin
spsDeposit StakePoolState
sps)
Encode (Closed Dense) (Set (Credential Staking) -> StakePoolState)
-> Encode (Closed Dense) (Set (Credential Staking))
-> Encode (Closed Dense) StakePoolState
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode (Closed r) a -> Encode w t
!> Set (Credential Staking)
-> Encode (Closed Dense) (Set (Credential Staking))
forall t. EncCBOR t => t -> Encode (Closed Dense) t
To (StakePoolState -> Set (Credential Staking)
spsDelegators StakePoolState
sps)
instance DecCBOR StakePoolState where
decCBOR :: forall s. Decoder s StakePoolState
decCBOR =
Decode (Closed Dense) StakePoolState -> Decoder s StakePoolState
forall t (w :: Wrapped) s. Typeable t => Decode w t -> Decoder s t
decode (Decode (Closed Dense) StakePoolState -> Decoder s StakePoolState)
-> Decode (Closed Dense) StakePoolState -> Decoder s StakePoolState
forall a b. (a -> b) -> a -> b
$
(VRFVerKeyHash StakePoolVRF
-> Coin
-> Coin
-> UnitInterval
-> Credential Staking
-> Set (KeyHash Staking)
-> StrictSeq StakePoolRelay
-> StrictMaybe PoolMetadata
-> CompactForm Coin
-> Set (Credential Staking)
-> StakePoolState)
-> Decode
(Closed Dense)
(VRFVerKeyHash StakePoolVRF
-> Coin
-> Coin
-> UnitInterval
-> Credential Staking
-> Set (KeyHash Staking)
-> StrictSeq StakePoolRelay
-> StrictMaybe PoolMetadata
-> CompactForm Coin
-> Set (Credential Staking)
-> StakePoolState)
forall t. t -> Decode (Closed Dense) t
RecD VRFVerKeyHash StakePoolVRF
-> Coin
-> Coin
-> UnitInterval
-> Credential Staking
-> Set (KeyHash Staking)
-> StrictSeq StakePoolRelay
-> StrictMaybe PoolMetadata
-> CompactForm Coin
-> Set (Credential Staking)
-> StakePoolState
StakePoolState
Decode
(Closed Dense)
(VRFVerKeyHash StakePoolVRF
-> Coin
-> Coin
-> UnitInterval
-> Credential Staking
-> Set (KeyHash Staking)
-> StrictSeq StakePoolRelay
-> StrictMaybe PoolMetadata
-> CompactForm Coin
-> Set (Credential Staking)
-> StakePoolState)
-> Decode (Closed (ZonkAny 9)) (VRFVerKeyHash StakePoolVRF)
-> Decode
(Closed Dense)
(Coin
-> Coin
-> UnitInterval
-> Credential Staking
-> Set (KeyHash Staking)
-> StrictSeq StakePoolRelay
-> StrictMaybe PoolMetadata
-> CompactForm Coin
-> Set (Credential Staking)
-> StakePoolState)
forall a (w1 :: Wrapped) t (w :: Density).
Typeable a =>
Decode w1 (a -> t) -> Decode (Closed w) a -> Decode w1 t
<! Decode (Closed (ZonkAny 9)) (VRFVerKeyHash StakePoolVRF)
forall t (w :: Wrapped). DecCBOR t => Decode w t
From
Decode
(Closed Dense)
(Coin
-> Coin
-> UnitInterval
-> Credential Staking
-> Set (KeyHash Staking)
-> StrictSeq StakePoolRelay
-> StrictMaybe PoolMetadata
-> CompactForm Coin
-> Set (Credential Staking)
-> StakePoolState)
-> Decode (Closed (ZonkAny 8)) Coin
-> Decode
(Closed Dense)
(Coin
-> UnitInterval
-> Credential Staking
-> Set (KeyHash Staking)
-> StrictSeq StakePoolRelay
-> StrictMaybe PoolMetadata
-> CompactForm Coin
-> Set (Credential Staking)
-> StakePoolState)
forall a (w1 :: Wrapped) t (w :: Density).
Typeable a =>
Decode w1 (a -> t) -> Decode (Closed w) a -> Decode w1 t
<! Decode (Closed (ZonkAny 8)) Coin
forall t (w :: Wrapped). DecCBOR t => Decode w t
From
Decode
(Closed Dense)
(Coin
-> UnitInterval
-> Credential Staking
-> Set (KeyHash Staking)
-> StrictSeq StakePoolRelay
-> StrictMaybe PoolMetadata
-> CompactForm Coin
-> Set (Credential Staking)
-> StakePoolState)
-> Decode (Closed (ZonkAny 7)) Coin
-> Decode
(Closed Dense)
(UnitInterval
-> Credential Staking
-> Set (KeyHash Staking)
-> StrictSeq StakePoolRelay
-> StrictMaybe PoolMetadata
-> CompactForm Coin
-> Set (Credential Staking)
-> StakePoolState)
forall a (w1 :: Wrapped) t (w :: Density).
Typeable a =>
Decode w1 (a -> t) -> Decode (Closed w) a -> Decode w1 t
<! Decode (Closed (ZonkAny 7)) Coin
forall t (w :: Wrapped). DecCBOR t => Decode w t
From
Decode
(Closed Dense)
(UnitInterval
-> Credential Staking
-> Set (KeyHash Staking)
-> StrictSeq StakePoolRelay
-> StrictMaybe PoolMetadata
-> CompactForm Coin
-> Set (Credential Staking)
-> StakePoolState)
-> Decode (Closed (ZonkAny 6)) UnitInterval
-> Decode
(Closed Dense)
(Credential Staking
-> Set (KeyHash Staking)
-> StrictSeq StakePoolRelay
-> StrictMaybe PoolMetadata
-> CompactForm Coin
-> Set (Credential Staking)
-> StakePoolState)
forall a (w1 :: Wrapped) t (w :: Density).
Typeable a =>
Decode w1 (a -> t) -> Decode (Closed w) a -> Decode w1 t
<! Decode (Closed (ZonkAny 6)) UnitInterval
forall t (w :: Wrapped). DecCBOR t => Decode w t
From
Decode
(Closed Dense)
(Credential Staking
-> Set (KeyHash Staking)
-> StrictSeq StakePoolRelay
-> StrictMaybe PoolMetadata
-> CompactForm Coin
-> Set (Credential Staking)
-> StakePoolState)
-> Decode (Closed (ZonkAny 5)) (Credential Staking)
-> Decode
(Closed Dense)
(Set (KeyHash Staking)
-> StrictSeq StakePoolRelay
-> StrictMaybe PoolMetadata
-> CompactForm Coin
-> Set (Credential Staking)
-> StakePoolState)
forall a (w1 :: Wrapped) t (w :: Density).
Typeable a =>
Decode w1 (a -> t) -> Decode (Closed w) a -> Decode w1 t
<! Decode (Closed (ZonkAny 5)) (Credential Staking)
forall t (w :: Wrapped). DecCBOR t => Decode w t
From
Decode
(Closed Dense)
(Set (KeyHash Staking)
-> StrictSeq StakePoolRelay
-> StrictMaybe PoolMetadata
-> CompactForm Coin
-> Set (Credential Staking)
-> StakePoolState)
-> Decode (Closed (ZonkAny 4)) (Set (KeyHash Staking))
-> Decode
(Closed Dense)
(StrictSeq StakePoolRelay
-> StrictMaybe PoolMetadata
-> CompactForm Coin
-> Set (Credential Staking)
-> StakePoolState)
forall a (w1 :: Wrapped) t (w :: Density).
Typeable a =>
Decode w1 (a -> t) -> Decode (Closed w) a -> Decode w1 t
<! Decode (Closed (ZonkAny 4)) (Set (KeyHash Staking))
forall t (w :: Wrapped). DecCBOR t => Decode w t
From
Decode
(Closed Dense)
(StrictSeq StakePoolRelay
-> StrictMaybe PoolMetadata
-> CompactForm Coin
-> Set (Credential Staking)
-> StakePoolState)
-> Decode (Closed (ZonkAny 3)) (StrictSeq StakePoolRelay)
-> Decode
(Closed Dense)
(StrictMaybe PoolMetadata
-> CompactForm Coin -> Set (Credential Staking) -> StakePoolState)
forall a (w1 :: Wrapped) t (w :: Density).
Typeable a =>
Decode w1 (a -> t) -> Decode (Closed w) a -> Decode w1 t
<! Decode (Closed (ZonkAny 3)) (StrictSeq StakePoolRelay)
forall t (w :: Wrapped). DecCBOR t => Decode w t
From
Decode
(Closed Dense)
(StrictMaybe PoolMetadata
-> CompactForm Coin -> Set (Credential Staking) -> StakePoolState)
-> Decode (Closed (ZonkAny 2)) (StrictMaybe PoolMetadata)
-> Decode
(Closed Dense)
(CompactForm Coin -> Set (Credential Staking) -> StakePoolState)
forall a (w1 :: Wrapped) t (w :: Density).
Typeable a =>
Decode w1 (a -> t) -> Decode (Closed w) a -> Decode w1 t
<! Decode (Closed (ZonkAny 2)) (StrictMaybe PoolMetadata)
forall t (w :: Wrapped). DecCBOR t => Decode w t
From
Decode
(Closed Dense)
(CompactForm Coin -> Set (Credential Staking) -> StakePoolState)
-> Decode (Closed (ZonkAny 1)) (CompactForm Coin)
-> Decode
(Closed Dense) (Set (Credential Staking) -> StakePoolState)
forall a (w1 :: Wrapped) t (w :: Density).
Typeable a =>
Decode w1 (a -> t) -> Decode (Closed w) a -> Decode w1 t
<! Decode (Closed (ZonkAny 1)) (CompactForm Coin)
forall t (w :: Wrapped). DecCBOR t => Decode w t
From
Decode (Closed Dense) (Set (Credential Staking) -> StakePoolState)
-> Decode (Closed (ZonkAny 0)) (Set (Credential Staking))
-> Decode (Closed Dense) StakePoolState
forall a (w1 :: Wrapped) t (w :: Density).
Typeable a =>
Decode w1 (a -> t) -> Decode (Closed w) a -> Decode w1 t
<! Decode (Closed (ZonkAny 0)) (Set (Credential Staking))
forall t (w :: Wrapped). DecCBOR t => Decode w t
From
instance DecShareCBOR StakePoolState where
type Share StakePoolState = Interns (Credential Staking)
decSharePlusCBOR :: forall s. StateT (Share StakePoolState) (Decoder s) StakePoolState
decSharePlusCBOR =
Text
-> (StakePoolState -> Int)
-> StateT (Share StakePoolState) (Decoder s) StakePoolState
-> StateT (Share StakePoolState) (Decoder s) StakePoolState
forall (m :: (* -> *) -> * -> *) s a.
(MonadTrans m, Monad (m (Decoder s))) =>
Text -> (a -> Int) -> m (Decoder s) a -> m (Decoder s) a
decodeRecordNamedT Text
"StakePoolState" (Int -> StakePoolState -> Int
forall a b. a -> b -> a
const Int
10) (StateT (Share StakePoolState) (Decoder s) StakePoolState
-> StateT (Share StakePoolState) (Decoder s) StakePoolState)
-> StateT (Share StakePoolState) (Decoder s) StakePoolState
-> StateT (Share StakePoolState) (Decoder s) StakePoolState
forall a b. (a -> b) -> a -> b
$
VRFVerKeyHash StakePoolVRF
-> Coin
-> Coin
-> UnitInterval
-> Credential Staking
-> Set (KeyHash Staking)
-> StrictSeq StakePoolRelay
-> StrictMaybe PoolMetadata
-> CompactForm Coin
-> Set (Credential Staking)
-> StakePoolState
StakePoolState
(VRFVerKeyHash StakePoolVRF
-> Coin
-> Coin
-> UnitInterval
-> Credential Staking
-> Set (KeyHash Staking)
-> StrictSeq StakePoolRelay
-> StrictMaybe PoolMetadata
-> CompactForm Coin
-> Set (Credential Staking)
-> StakePoolState)
-> StateT
(Interns (Credential Staking))
(Decoder s)
(VRFVerKeyHash StakePoolVRF)
-> StateT
(Interns (Credential Staking))
(Decoder s)
(Coin
-> Coin
-> UnitInterval
-> Credential Staking
-> Set (KeyHash Staking)
-> StrictSeq StakePoolRelay
-> StrictMaybe PoolMetadata
-> CompactForm Coin
-> Set (Credential Staking)
-> StakePoolState)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Decoder s (VRFVerKeyHash StakePoolVRF)
-> StateT
(Interns (Credential Staking))
(Decoder s)
(VRFVerKeyHash StakePoolVRF)
forall (m :: * -> *) a.
Monad m =>
m a -> StateT (Interns (Credential Staking)) m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift Decoder s (VRFVerKeyHash StakePoolVRF)
forall s. Decoder s (VRFVerKeyHash StakePoolVRF)
forall a s. DecCBOR a => Decoder s a
decCBOR
StateT
(Interns (Credential Staking))
(Decoder s)
(Coin
-> Coin
-> UnitInterval
-> Credential Staking
-> Set (KeyHash Staking)
-> StrictSeq StakePoolRelay
-> StrictMaybe PoolMetadata
-> CompactForm Coin
-> Set (Credential Staking)
-> StakePoolState)
-> StateT (Interns (Credential Staking)) (Decoder s) Coin
-> StateT
(Interns (Credential Staking))
(Decoder s)
(Coin
-> UnitInterval
-> Credential Staking
-> Set (KeyHash Staking)
-> StrictSeq StakePoolRelay
-> StrictMaybe PoolMetadata
-> CompactForm Coin
-> Set (Credential Staking)
-> StakePoolState)
forall a b.
StateT (Interns (Credential Staking)) (Decoder s) (a -> b)
-> StateT (Interns (Credential Staking)) (Decoder s) a
-> StateT (Interns (Credential Staking)) (Decoder s) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Decoder s Coin
-> StateT (Interns (Credential Staking)) (Decoder s) Coin
forall (m :: * -> *) a.
Monad m =>
m a -> StateT (Interns (Credential Staking)) m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift Decoder s Coin
forall s. Decoder s Coin
forall a s. DecCBOR a => Decoder s a
decCBOR
StateT
(Interns (Credential Staking))
(Decoder s)
(Coin
-> UnitInterval
-> Credential Staking
-> Set (KeyHash Staking)
-> StrictSeq StakePoolRelay
-> StrictMaybe PoolMetadata
-> CompactForm Coin
-> Set (Credential Staking)
-> StakePoolState)
-> StateT (Interns (Credential Staking)) (Decoder s) Coin
-> StateT
(Interns (Credential Staking))
(Decoder s)
(UnitInterval
-> Credential Staking
-> Set (KeyHash Staking)
-> StrictSeq StakePoolRelay
-> StrictMaybe PoolMetadata
-> CompactForm Coin
-> Set (Credential Staking)
-> StakePoolState)
forall a b.
StateT (Interns (Credential Staking)) (Decoder s) (a -> b)
-> StateT (Interns (Credential Staking)) (Decoder s) a
-> StateT (Interns (Credential Staking)) (Decoder s) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Decoder s Coin
-> StateT (Interns (Credential Staking)) (Decoder s) Coin
forall (m :: * -> *) a.
Monad m =>
m a -> StateT (Interns (Credential Staking)) m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift Decoder s Coin
forall s. Decoder s Coin
forall a s. DecCBOR a => Decoder s a
decCBOR
StateT
(Interns (Credential Staking))
(Decoder s)
(UnitInterval
-> Credential Staking
-> Set (KeyHash Staking)
-> StrictSeq StakePoolRelay
-> StrictMaybe PoolMetadata
-> CompactForm Coin
-> Set (Credential Staking)
-> StakePoolState)
-> StateT (Interns (Credential Staking)) (Decoder s) UnitInterval
-> StateT
(Interns (Credential Staking))
(Decoder s)
(Credential Staking
-> Set (KeyHash Staking)
-> StrictSeq StakePoolRelay
-> StrictMaybe PoolMetadata
-> CompactForm Coin
-> Set (Credential Staking)
-> StakePoolState)
forall a b.
StateT (Interns (Credential Staking)) (Decoder s) (a -> b)
-> StateT (Interns (Credential Staking)) (Decoder s) a
-> StateT (Interns (Credential Staking)) (Decoder s) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Decoder s UnitInterval
-> StateT (Interns (Credential Staking)) (Decoder s) UnitInterval
forall (m :: * -> *) a.
Monad m =>
m a -> StateT (Interns (Credential Staking)) m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift Decoder s UnitInterval
forall s. Decoder s UnitInterval
forall a s. DecCBOR a => Decoder s a
decCBOR
StateT
(Interns (Credential Staking))
(Decoder s)
(Credential Staking
-> Set (KeyHash Staking)
-> StrictSeq StakePoolRelay
-> StrictMaybe PoolMetadata
-> CompactForm Coin
-> Set (Credential Staking)
-> StakePoolState)
-> StateT
(Interns (Credential Staking)) (Decoder s) (Credential Staking)
-> StateT
(Interns (Credential Staking))
(Decoder s)
(Set (KeyHash Staking)
-> StrictSeq StakePoolRelay
-> StrictMaybe PoolMetadata
-> CompactForm Coin
-> Set (Credential Staking)
-> StakePoolState)
forall a b.
StateT (Interns (Credential Staking)) (Decoder s) (a -> b)
-> StateT (Interns (Credential Staking)) (Decoder s) a
-> StateT (Interns (Credential Staking)) (Decoder s) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Decoder s (Credential Staking)
-> StateT
(Interns (Credential Staking)) (Decoder s) (Credential Staking)
forall (m :: * -> *) a.
Monad m =>
m a -> StateT (Interns (Credential Staking)) m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift Decoder s (Credential Staking)
forall s. Decoder s (Credential Staking)
forall a s. DecCBOR a => Decoder s a
decCBOR
StateT
(Interns (Credential Staking))
(Decoder s)
(Set (KeyHash Staking)
-> StrictSeq StakePoolRelay
-> StrictMaybe PoolMetadata
-> CompactForm Coin
-> Set (Credential Staking)
-> StakePoolState)
-> StateT
(Interns (Credential Staking)) (Decoder s) (Set (KeyHash Staking))
-> StateT
(Interns (Credential Staking))
(Decoder s)
(StrictSeq StakePoolRelay
-> StrictMaybe PoolMetadata
-> CompactForm Coin
-> Set (Credential Staking)
-> StakePoolState)
forall a b.
StateT (Interns (Credential Staking)) (Decoder s) (a -> b)
-> StateT (Interns (Credential Staking)) (Decoder s) a
-> StateT (Interns (Credential Staking)) (Decoder s) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Decoder s (Set (KeyHash Staking))
-> StateT
(Interns (Credential Staking)) (Decoder s) (Set (KeyHash Staking))
forall (m :: * -> *) a.
Monad m =>
m a -> StateT (Interns (Credential Staking)) m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift Decoder s (Set (KeyHash Staking))
forall s. Decoder s (Set (KeyHash Staking))
forall a s. DecCBOR a => Decoder s a
decCBOR
StateT
(Interns (Credential Staking))
(Decoder s)
(StrictSeq StakePoolRelay
-> StrictMaybe PoolMetadata
-> CompactForm Coin
-> Set (Credential Staking)
-> StakePoolState)
-> StateT
(Interns (Credential Staking))
(Decoder s)
(StrictSeq StakePoolRelay)
-> StateT
(Interns (Credential Staking))
(Decoder s)
(StrictMaybe PoolMetadata
-> CompactForm Coin -> Set (Credential Staking) -> StakePoolState)
forall a b.
StateT (Interns (Credential Staking)) (Decoder s) (a -> b)
-> StateT (Interns (Credential Staking)) (Decoder s) a
-> StateT (Interns (Credential Staking)) (Decoder s) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Decoder s (StrictSeq StakePoolRelay)
-> StateT
(Interns (Credential Staking))
(Decoder s)
(StrictSeq StakePoolRelay)
forall (m :: * -> *) a.
Monad m =>
m a -> StateT (Interns (Credential Staking)) m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift Decoder s (StrictSeq StakePoolRelay)
forall s. Decoder s (StrictSeq StakePoolRelay)
forall a s. DecCBOR a => Decoder s a
decCBOR
StateT
(Interns (Credential Staking))
(Decoder s)
(StrictMaybe PoolMetadata
-> CompactForm Coin -> Set (Credential Staking) -> StakePoolState)
-> StateT
(Interns (Credential Staking))
(Decoder s)
(StrictMaybe PoolMetadata)
-> StateT
(Interns (Credential Staking))
(Decoder s)
(CompactForm Coin -> Set (Credential Staking) -> StakePoolState)
forall a b.
StateT (Interns (Credential Staking)) (Decoder s) (a -> b)
-> StateT (Interns (Credential Staking)) (Decoder s) a
-> StateT (Interns (Credential Staking)) (Decoder s) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Decoder s (StrictMaybe PoolMetadata)
-> StateT
(Interns (Credential Staking))
(Decoder s)
(StrictMaybe PoolMetadata)
forall (m :: * -> *) a.
Monad m =>
m a -> StateT (Interns (Credential Staking)) m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift Decoder s (StrictMaybe PoolMetadata)
forall s. Decoder s (StrictMaybe PoolMetadata)
forall a s. DecCBOR a => Decoder s a
decCBOR
StateT
(Interns (Credential Staking))
(Decoder s)
(CompactForm Coin -> Set (Credential Staking) -> StakePoolState)
-> StateT
(Interns (Credential Staking)) (Decoder s) (CompactForm Coin)
-> StateT
(Interns (Credential Staking))
(Decoder s)
(Set (Credential Staking) -> StakePoolState)
forall a b.
StateT (Interns (Credential Staking)) (Decoder s) (a -> b)
-> StateT (Interns (Credential Staking)) (Decoder s) a
-> StateT (Interns (Credential Staking)) (Decoder s) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Decoder s (CompactForm Coin)
-> StateT
(Interns (Credential Staking)) (Decoder s) (CompactForm Coin)
forall (m :: * -> *) a.
Monad m =>
m a -> StateT (Interns (Credential Staking)) m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift Decoder s (CompactForm Coin)
forall s. Decoder s (CompactForm Coin)
forall a s. DecCBOR a => Decoder s a
decCBOR
StateT
(Interns (Credential Staking))
(Decoder s)
(Set (Credential Staking) -> StakePoolState)
-> StateT
(Interns (Credential Staking))
(Decoder s)
(Set (Credential Staking))
-> StateT (Interns (Credential Staking)) (Decoder s) StakePoolState
forall a b.
StateT (Interns (Credential Staking)) (Decoder s) (a -> b)
-> StateT (Interns (Credential Staking)) (Decoder s) a
-> StateT (Interns (Credential Staking)) (Decoder s) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> StateT
(Share (Set (Credential Staking)))
(Decoder s)
(Set (Credential Staking))
StateT
(Interns (Credential Staking))
(Decoder s)
(Set (Credential Staking))
forall s.
StateT
(Share (Set (Credential Staking)))
(Decoder s)
(Set (Credential Staking))
forall a s. DecShareCBOR a => StateT (Share a) (Decoder s) a
decSharePlusCBOR
instance Default StakePoolState where
def :: StakePoolState
def =
StakePoolState
{ spsVrf :: VRFVerKeyHash StakePoolVRF
spsVrf = VRFVerKeyHash StakePoolVRF
forall a. Default a => a
def
, spsPledge :: Coin
spsPledge = Integer -> Coin
Coin Integer
0
, spsCost :: Coin
spsCost = Integer -> Coin
Coin Integer
0
, spsMargin :: UnitInterval
spsMargin = UnitInterval
forall a. Default a => a
def
, spsRewardAccount :: Credential Staking
spsRewardAccount = Credential Staking
forall a. Default a => a
def
, spsOwners :: Set (KeyHash Staking)
spsOwners = Set (KeyHash Staking)
forall a. Default a => a
def
, spsRelays :: StrictSeq StakePoolRelay
spsRelays = StrictSeq StakePoolRelay
forall a. Default a => a
def
, spsMetadata :: StrictMaybe PoolMetadata
spsMetadata = StrictMaybe PoolMetadata
forall a. Default a => a
def
, spsDeposit :: CompactForm Coin
spsDeposit = CompactForm Coin
forall a. Monoid a => a
mempty
, spsDelegators :: Set (Credential Staking)
spsDelegators = Set (Credential Staking)
forall a. Default a => a
def
}
mkStakePoolState ::
CompactForm Coin -> Set (Credential Staking) -> StakePoolParams -> StakePoolState
mkStakePoolState :: CompactForm Coin
-> Set (Credential Staking) -> StakePoolParams -> StakePoolState
mkStakePoolState CompactForm Coin
deposit Set (Credential Staking)
delegators StakePoolParams
spp =
StakePoolState
{ spsVrf :: VRFVerKeyHash StakePoolVRF
spsVrf = StakePoolParams -> VRFVerKeyHash StakePoolVRF
sppVrf StakePoolParams
spp
, spsPledge :: Coin
spsPledge = StakePoolParams -> Coin
sppPledge StakePoolParams
spp
, spsCost :: Coin
spsCost = StakePoolParams -> Coin
sppCost StakePoolParams
spp
, spsMargin :: UnitInterval
spsMargin = StakePoolParams -> UnitInterval
sppMargin StakePoolParams
spp
, spsRewardAccount :: Credential Staking
spsRewardAccount = RewardAccount -> Credential Staking
raCredential (RewardAccount -> Credential Staking)
-> RewardAccount -> Credential Staking
forall a b. (a -> b) -> a -> b
$ StakePoolParams -> RewardAccount
sppRewardAccount StakePoolParams
spp
, spsOwners :: Set (KeyHash Staking)
spsOwners = StakePoolParams -> Set (KeyHash Staking)
sppOwners StakePoolParams
spp
, spsRelays :: StrictSeq StakePoolRelay
spsRelays = StakePoolParams -> StrictSeq StakePoolRelay
sppRelays StakePoolParams
spp
, spsMetadata :: StrictMaybe PoolMetadata
spsMetadata = StakePoolParams -> StrictMaybe PoolMetadata
sppMetadata StakePoolParams
spp
, spsDeposit :: CompactForm Coin
spsDeposit = CompactForm Coin
deposit
, spsDelegators :: Set (Credential Staking)
spsDelegators = Set (Credential Staking)
delegators
}
stakePoolStateToStakePoolParams :: KeyHash StakePool -> Network -> StakePoolState -> StakePoolParams
stakePoolStateToStakePoolParams :: KeyHash StakePool -> Network -> StakePoolState -> StakePoolParams
stakePoolStateToStakePoolParams KeyHash StakePool
poolId Network
networkId StakePoolState
sps =
StakePoolParams
{ sppId :: KeyHash StakePool
sppId = KeyHash StakePool
poolId
, sppVrf :: VRFVerKeyHash StakePoolVRF
sppVrf = StakePoolState -> VRFVerKeyHash StakePoolVRF
spsVrf StakePoolState
sps
, sppPledge :: Coin
sppPledge = StakePoolState -> Coin
spsPledge StakePoolState
sps
, sppCost :: Coin
sppCost = StakePoolState -> Coin
spsCost StakePoolState
sps
, sppMargin :: UnitInterval
sppMargin = StakePoolState -> UnitInterval
spsMargin StakePoolState
sps
, sppRewardAccount :: RewardAccount
sppRewardAccount = Network -> Credential Staking -> RewardAccount
RewardAccount Network
networkId (Credential Staking -> RewardAccount)
-> Credential Staking -> RewardAccount
forall a b. (a -> b) -> a -> b
$ StakePoolState -> Credential Staking
spsRewardAccount StakePoolState
sps
, sppOwners :: Set (KeyHash Staking)
sppOwners = StakePoolState -> Set (KeyHash Staking)
spsOwners StakePoolState
sps
, sppRelays :: StrictSeq StakePoolRelay
sppRelays = StakePoolState -> StrictSeq StakePoolRelay
spsRelays StakePoolState
sps
, sppMetadata :: StrictMaybe PoolMetadata
sppMetadata = StakePoolState -> StrictMaybe PoolMetadata
spsMetadata StakePoolState
sps
}
data PoolMetadata = PoolMetadata
{ PoolMetadata -> Url
pmUrl :: !Url
, PoolMetadata -> ByteString
pmHash :: !ByteString
}
deriving (PoolMetadata -> PoolMetadata -> Bool
(PoolMetadata -> PoolMetadata -> Bool)
-> (PoolMetadata -> PoolMetadata -> Bool) -> Eq PoolMetadata
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PoolMetadata -> PoolMetadata -> Bool
== :: PoolMetadata -> PoolMetadata -> Bool
$c/= :: PoolMetadata -> PoolMetadata -> Bool
/= :: PoolMetadata -> PoolMetadata -> Bool
Eq, Eq PoolMetadata
Eq PoolMetadata =>
(PoolMetadata -> PoolMetadata -> Ordering)
-> (PoolMetadata -> PoolMetadata -> Bool)
-> (PoolMetadata -> PoolMetadata -> Bool)
-> (PoolMetadata -> PoolMetadata -> Bool)
-> (PoolMetadata -> PoolMetadata -> Bool)
-> (PoolMetadata -> PoolMetadata -> PoolMetadata)
-> (PoolMetadata -> PoolMetadata -> PoolMetadata)
-> Ord PoolMetadata
PoolMetadata -> PoolMetadata -> Bool
PoolMetadata -> PoolMetadata -> Ordering
PoolMetadata -> PoolMetadata -> PoolMetadata
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: PoolMetadata -> PoolMetadata -> Ordering
compare :: PoolMetadata -> PoolMetadata -> Ordering
$c< :: PoolMetadata -> PoolMetadata -> Bool
< :: PoolMetadata -> PoolMetadata -> Bool
$c<= :: PoolMetadata -> PoolMetadata -> Bool
<= :: PoolMetadata -> PoolMetadata -> Bool
$c> :: PoolMetadata -> PoolMetadata -> Bool
> :: PoolMetadata -> PoolMetadata -> Bool
$c>= :: PoolMetadata -> PoolMetadata -> Bool
>= :: PoolMetadata -> PoolMetadata -> Bool
$cmax :: PoolMetadata -> PoolMetadata -> PoolMetadata
max :: PoolMetadata -> PoolMetadata -> PoolMetadata
$cmin :: PoolMetadata -> PoolMetadata -> PoolMetadata
min :: PoolMetadata -> PoolMetadata -> PoolMetadata
Ord, (forall x. PoolMetadata -> Rep PoolMetadata x)
-> (forall x. Rep PoolMetadata x -> PoolMetadata)
-> Generic PoolMetadata
forall x. Rep PoolMetadata x -> PoolMetadata
forall x. PoolMetadata -> Rep PoolMetadata x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. PoolMetadata -> Rep PoolMetadata x
from :: forall x. PoolMetadata -> Rep PoolMetadata x
$cto :: forall x. Rep PoolMetadata x -> PoolMetadata
to :: forall x. Rep PoolMetadata x -> PoolMetadata
Generic, Int -> PoolMetadata -> ShowS
[PoolMetadata] -> ShowS
PoolMetadata -> String
(Int -> PoolMetadata -> ShowS)
-> (PoolMetadata -> String)
-> ([PoolMetadata] -> ShowS)
-> Show PoolMetadata
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PoolMetadata -> ShowS
showsPrec :: Int -> PoolMetadata -> ShowS
$cshow :: PoolMetadata -> String
show :: PoolMetadata -> String
$cshowList :: [PoolMetadata] -> ShowS
showList :: [PoolMetadata] -> ShowS
Show)
deriving instance NFData PoolMetadata
instance ToJSON PoolMetadata where
toJSON :: PoolMetadata -> Value
toJSON PoolMetadata
pmd =
[Pair] -> Value
Aeson.object
[ Key
"url" Key -> Url -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= PoolMetadata -> Url
pmUrl PoolMetadata
pmd
, Key
"hash" Key -> Text -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= ByteString -> Text
Text.decodeLatin1 (ByteString -> ByteString
B16.encode (PoolMetadata -> ByteString
pmHash PoolMetadata
pmd))
]
instance FromJSON PoolMetadata where
parseJSON :: Value -> Parser PoolMetadata
parseJSON =
String
-> (Object -> Parser PoolMetadata) -> Value -> Parser PoolMetadata
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Aeson.withObject String
"PoolMetadata" ((Object -> Parser PoolMetadata) -> Value -> Parser PoolMetadata)
-> (Object -> Parser PoolMetadata) -> Value -> Parser PoolMetadata
forall a b. (a -> b) -> a -> b
$ \Object
obj -> do
url <- Object
obj Object -> Key -> Parser Url
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"url"
hash <- explicitParseField parseJsonBase16 obj "hash"
return $ PoolMetadata url hash
parseJsonBase16 :: Value -> Parser ByteString
parseJsonBase16 :: Value -> Parser ByteString
parseJsonBase16 Value
v = do
txt <- Value -> Parser Text
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v
unless (Text.isAscii txt) $ fail $ "Supplied text contains non-ASCII characters: " <> show txt
case B16.decode (Text.encodeUtf8 txt) of
Right ByteString
bs -> ByteString -> Parser ByteString
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
bs
Left String
msg -> String -> Parser ByteString
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
msg
instance NoThunks PoolMetadata
data StakePoolRelay
=
SingleHostAddr !(StrictMaybe Port) !(StrictMaybe IPv4) !(StrictMaybe IPv6)
|
SingleHostName !(StrictMaybe Port) !DnsName
|
MultiHostName !DnsName
deriving (StakePoolRelay -> StakePoolRelay -> Bool
(StakePoolRelay -> StakePoolRelay -> Bool)
-> (StakePoolRelay -> StakePoolRelay -> Bool) -> Eq StakePoolRelay
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: StakePoolRelay -> StakePoolRelay -> Bool
== :: StakePoolRelay -> StakePoolRelay -> Bool
$c/= :: StakePoolRelay -> StakePoolRelay -> Bool
/= :: StakePoolRelay -> StakePoolRelay -> Bool
Eq, Eq StakePoolRelay
Eq StakePoolRelay =>
(StakePoolRelay -> StakePoolRelay -> Ordering)
-> (StakePoolRelay -> StakePoolRelay -> Bool)
-> (StakePoolRelay -> StakePoolRelay -> Bool)
-> (StakePoolRelay -> StakePoolRelay -> Bool)
-> (StakePoolRelay -> StakePoolRelay -> Bool)
-> (StakePoolRelay -> StakePoolRelay -> StakePoolRelay)
-> (StakePoolRelay -> StakePoolRelay -> StakePoolRelay)
-> Ord StakePoolRelay
StakePoolRelay -> StakePoolRelay -> Bool
StakePoolRelay -> StakePoolRelay -> Ordering
StakePoolRelay -> StakePoolRelay -> StakePoolRelay
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: StakePoolRelay -> StakePoolRelay -> Ordering
compare :: StakePoolRelay -> StakePoolRelay -> Ordering
$c< :: StakePoolRelay -> StakePoolRelay -> Bool
< :: StakePoolRelay -> StakePoolRelay -> Bool
$c<= :: StakePoolRelay -> StakePoolRelay -> Bool
<= :: StakePoolRelay -> StakePoolRelay -> Bool
$c> :: StakePoolRelay -> StakePoolRelay -> Bool
> :: StakePoolRelay -> StakePoolRelay -> Bool
$c>= :: StakePoolRelay -> StakePoolRelay -> Bool
>= :: StakePoolRelay -> StakePoolRelay -> Bool
$cmax :: StakePoolRelay -> StakePoolRelay -> StakePoolRelay
max :: StakePoolRelay -> StakePoolRelay -> StakePoolRelay
$cmin :: StakePoolRelay -> StakePoolRelay -> StakePoolRelay
min :: StakePoolRelay -> StakePoolRelay -> StakePoolRelay
Ord, (forall x. StakePoolRelay -> Rep StakePoolRelay x)
-> (forall x. Rep StakePoolRelay x -> StakePoolRelay)
-> Generic StakePoolRelay
forall x. Rep StakePoolRelay x -> StakePoolRelay
forall x. StakePoolRelay -> Rep StakePoolRelay x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. StakePoolRelay -> Rep StakePoolRelay x
from :: forall x. StakePoolRelay -> Rep StakePoolRelay x
$cto :: forall x. Rep StakePoolRelay x -> StakePoolRelay
to :: forall x. Rep StakePoolRelay x -> StakePoolRelay
Generic, Int -> StakePoolRelay -> ShowS
[StakePoolRelay] -> ShowS
StakePoolRelay -> String
(Int -> StakePoolRelay -> ShowS)
-> (StakePoolRelay -> String)
-> ([StakePoolRelay] -> ShowS)
-> Show StakePoolRelay
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> StakePoolRelay -> ShowS
showsPrec :: Int -> StakePoolRelay -> ShowS
$cshow :: StakePoolRelay -> String
show :: StakePoolRelay -> String
$cshowList :: [StakePoolRelay] -> ShowS
showList :: [StakePoolRelay] -> ShowS
Show)
instance FromJSON StakePoolRelay where
parseJSON :: Value -> Parser StakePoolRelay
parseJSON =
String
-> (Object -> Parser StakePoolRelay)
-> Value
-> Parser StakePoolRelay
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Aeson.withObject String
"StakePoolRelay" ((Object -> Parser StakePoolRelay)
-> Value -> Parser StakePoolRelay)
-> (Object -> Parser StakePoolRelay)
-> Value
-> Parser StakePoolRelay
forall a b. (a -> b) -> a -> b
$ \Object
obj ->
[Parser StakePoolRelay] -> Parser StakePoolRelay
forall (t :: * -> *) (f :: * -> *) a.
(Foldable t, Alternative f) =>
t (f a) -> f a
asum
[ (Value -> Parser StakePoolRelay)
-> Object -> Key -> Parser StakePoolRelay
forall a. (Value -> Parser a) -> Object -> Key -> Parser a
explicitParseField Value -> Parser StakePoolRelay
parser1 Object
obj Key
"single host address"
, (Value -> Parser StakePoolRelay)
-> Object -> Key -> Parser StakePoolRelay
forall a. (Value -> Parser a) -> Object -> Key -> Parser a
explicitParseField Value -> Parser StakePoolRelay
parser2 Object
obj Key
"single host name"
, (Value -> Parser StakePoolRelay)
-> Object -> Key -> Parser StakePoolRelay
forall a. (Value -> Parser a) -> Object -> Key -> Parser a
explicitParseField Value -> Parser StakePoolRelay
parser3 Object
obj Key
"multi host name"
]
where
parser1 :: Value -> Parser StakePoolRelay
parser1 = String
-> (Object -> Parser StakePoolRelay)
-> Value
-> Parser StakePoolRelay
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Aeson.withObject String
"SingleHostAddr" ((Object -> Parser StakePoolRelay)
-> Value -> Parser StakePoolRelay)
-> (Object -> Parser StakePoolRelay)
-> Value
-> Parser StakePoolRelay
forall a b. (a -> b) -> a -> b
$ \Object
obj ->
StrictMaybe Port
-> StrictMaybe IPv4 -> StrictMaybe IPv6 -> StakePoolRelay
SingleHostAddr
(StrictMaybe Port
-> StrictMaybe IPv4 -> StrictMaybe IPv6 -> StakePoolRelay)
-> Parser (StrictMaybe Port)
-> Parser (StrictMaybe IPv4 -> StrictMaybe IPv6 -> StakePoolRelay)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
obj Object -> Key -> Parser (Maybe (StrictMaybe Port))
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"port" Parser (Maybe (StrictMaybe Port))
-> StrictMaybe Port -> Parser (StrictMaybe Port)
forall a. Parser (Maybe a) -> a -> Parser a
.!= StrictMaybe Port
forall a. StrictMaybe a
SNothing
Parser (StrictMaybe IPv4 -> StrictMaybe IPv6 -> StakePoolRelay)
-> Parser (StrictMaybe IPv4)
-> Parser (StrictMaybe IPv6 -> StakePoolRelay)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
obj Object -> Key -> Parser (Maybe (StrictMaybe IPv4))
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"IPv4" Parser (Maybe (StrictMaybe IPv4))
-> StrictMaybe IPv4 -> Parser (StrictMaybe IPv4)
forall a. Parser (Maybe a) -> a -> Parser a
.!= StrictMaybe IPv4
forall a. StrictMaybe a
SNothing
Parser (StrictMaybe IPv6 -> StakePoolRelay)
-> Parser (StrictMaybe IPv6) -> Parser StakePoolRelay
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
obj Object -> Key -> Parser (Maybe (StrictMaybe IPv6))
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"IPv6" Parser (Maybe (StrictMaybe IPv6))
-> StrictMaybe IPv6 -> Parser (StrictMaybe IPv6)
forall a. Parser (Maybe a) -> a -> Parser a
.!= StrictMaybe IPv6
forall a. StrictMaybe a
SNothing
parser2 :: Value -> Parser StakePoolRelay
parser2 = String
-> (Object -> Parser StakePoolRelay)
-> Value
-> Parser StakePoolRelay
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Aeson.withObject String
"SingleHostName" ((Object -> Parser StakePoolRelay)
-> Value -> Parser StakePoolRelay)
-> (Object -> Parser StakePoolRelay)
-> Value
-> Parser StakePoolRelay
forall a b. (a -> b) -> a -> b
$ \Object
obj ->
StrictMaybe Port -> DnsName -> StakePoolRelay
SingleHostName
(StrictMaybe Port -> DnsName -> StakePoolRelay)
-> Parser (StrictMaybe Port) -> Parser (DnsName -> StakePoolRelay)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
obj Object -> Key -> Parser (Maybe (StrictMaybe Port))
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"port" Parser (Maybe (StrictMaybe Port))
-> StrictMaybe Port -> Parser (StrictMaybe Port)
forall a. Parser (Maybe a) -> a -> Parser a
.!= StrictMaybe Port
forall a. StrictMaybe a
SNothing
Parser (DnsName -> StakePoolRelay)
-> Parser DnsName -> Parser StakePoolRelay
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
obj Object -> Key -> Parser DnsName
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"dnsName"
parser3 :: Value -> Parser StakePoolRelay
parser3 = String
-> (Object -> Parser StakePoolRelay)
-> Value
-> Parser StakePoolRelay
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Aeson.withObject String
"MultiHostName" ((Object -> Parser StakePoolRelay)
-> Value -> Parser StakePoolRelay)
-> (Object -> Parser StakePoolRelay)
-> Value
-> Parser StakePoolRelay
forall a b. (a -> b) -> a -> b
$ \Object
obj ->
DnsName -> StakePoolRelay
MultiHostName
(DnsName -> StakePoolRelay)
-> Parser DnsName -> Parser StakePoolRelay
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
obj Object -> Key -> Parser DnsName
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"dnsName"
instance ToJSON StakePoolRelay where
toJSON :: StakePoolRelay -> Value
toJSON (SingleHostAddr StrictMaybe Port
port StrictMaybe IPv4
ipv4 StrictMaybe IPv6
ipv6) =
[Pair] -> Value
Aeson.object
[ Key
"single host address"
Key -> Value -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= [Pair] -> Value
Aeson.object
[ Key
"port" Key -> StrictMaybe Port -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= StrictMaybe Port
port
, Key
"IPv4" Key -> StrictMaybe IPv4 -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= StrictMaybe IPv4
ipv4
, Key
"IPv6" Key -> StrictMaybe IPv6 -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= StrictMaybe IPv6
ipv6
]
]
toJSON (SingleHostName StrictMaybe Port
port DnsName
dnsName) =
[Pair] -> Value
Aeson.object
[ Key
"single host name"
Key -> Value -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= [Pair] -> Value
Aeson.object
[ Key
"port" Key -> StrictMaybe Port -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= StrictMaybe Port
port
, Key
"dnsName" Key -> DnsName -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= DnsName
dnsName
]
]
toJSON (MultiHostName DnsName
dnsName) =
[Pair] -> Value
Aeson.object
[ Key
"multi host name"
Key -> Value -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= [Pair] -> Value
Aeson.object
[ Key
"dnsName" Key -> DnsName -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= DnsName
dnsName
]
]
instance NoThunks StakePoolRelay
instance NFData StakePoolRelay
instance EncCBOR StakePoolRelay where
encCBOR :: StakePoolRelay -> Encoding
encCBOR (SingleHostAddr StrictMaybe Port
p StrictMaybe IPv4
ipv4 StrictMaybe IPv6
ipv6) =
Word -> Encoding
encodeListLen Word
4
Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Word8 -> Encoding
forall a. EncCBOR a => a -> Encoding
encCBOR (Word8
0 :: Word8)
Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> (Port -> Encoding) -> StrictMaybe Port -> Encoding
forall a. (a -> Encoding) -> StrictMaybe a -> Encoding
encodeNullStrictMaybe Port -> Encoding
forall a. EncCBOR a => a -> Encoding
encCBOR StrictMaybe Port
p
Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> (IPv4 -> Encoding) -> StrictMaybe IPv4 -> Encoding
forall a. (a -> Encoding) -> StrictMaybe a -> Encoding
encodeNullStrictMaybe IPv4 -> Encoding
forall a. EncCBOR a => a -> Encoding
encCBOR StrictMaybe IPv4
ipv4
Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> (IPv6 -> Encoding) -> StrictMaybe IPv6 -> Encoding
forall a. (a -> Encoding) -> StrictMaybe a -> Encoding
encodeNullStrictMaybe IPv6 -> Encoding
forall a. EncCBOR a => a -> Encoding
encCBOR StrictMaybe IPv6
ipv6
encCBOR (SingleHostName StrictMaybe Port
p DnsName
n) =
Word -> Encoding
encodeListLen Word
3
Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Word8 -> Encoding
forall a. EncCBOR a => a -> Encoding
encCBOR (Word8
1 :: Word8)
Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> (Port -> Encoding) -> StrictMaybe Port -> Encoding
forall a. (a -> Encoding) -> StrictMaybe a -> Encoding
encodeNullStrictMaybe Port -> Encoding
forall a. EncCBOR a => a -> Encoding
encCBOR StrictMaybe Port
p
Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> DnsName -> Encoding
forall a. EncCBOR a => a -> Encoding
encCBOR DnsName
n
encCBOR (MultiHostName DnsName
n) =
Word -> Encoding
encodeListLen Word
2
Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Word8 -> Encoding
forall a. EncCBOR a => a -> Encoding
encCBOR (Word8
2 :: Word8)
Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> DnsName -> Encoding
forall a. EncCBOR a => a -> Encoding
encCBOR DnsName
n
instance DecCBOR StakePoolRelay where
decCBOR :: forall s. Decoder s StakePoolRelay
decCBOR = Text
-> (Word -> Decoder s (Int, StakePoolRelay))
-> Decoder s StakePoolRelay
forall s a. Text -> (Word -> Decoder s (Int, a)) -> Decoder s a
decodeRecordSum Text
"StakePoolRelay" ((Word -> Decoder s (Int, StakePoolRelay))
-> Decoder s StakePoolRelay)
-> (Word -> Decoder s (Int, StakePoolRelay))
-> Decoder s StakePoolRelay
forall a b. (a -> b) -> a -> b
$
\case
Word
0 ->
(\StrictMaybe Port
x StrictMaybe IPv4
y StrictMaybe IPv6
z -> (Int
4, StrictMaybe Port
-> StrictMaybe IPv4 -> StrictMaybe IPv6 -> StakePoolRelay
SingleHostAddr StrictMaybe Port
x StrictMaybe IPv4
y StrictMaybe IPv6
z))
(StrictMaybe Port
-> StrictMaybe IPv4 -> StrictMaybe IPv6 -> (Int, StakePoolRelay))
-> Decoder s (StrictMaybe Port)
-> Decoder
s (StrictMaybe IPv4 -> StrictMaybe IPv6 -> (Int, StakePoolRelay))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Decoder s Port -> Decoder s (StrictMaybe Port)
forall s a. Decoder s a -> Decoder s (StrictMaybe a)
decodeNullStrictMaybe Decoder s Port
forall s. Decoder s Port
forall a s. DecCBOR a => Decoder s a
decCBOR
Decoder
s (StrictMaybe IPv4 -> StrictMaybe IPv6 -> (Int, StakePoolRelay))
-> Decoder s (StrictMaybe IPv4)
-> Decoder s (StrictMaybe IPv6 -> (Int, StakePoolRelay))
forall a b. Decoder s (a -> b) -> Decoder s a -> Decoder s b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Decoder s IPv4 -> Decoder s (StrictMaybe IPv4)
forall s a. Decoder s a -> Decoder s (StrictMaybe a)
decodeNullStrictMaybe Decoder s IPv4
forall s. Decoder s IPv4
forall a s. DecCBOR a => Decoder s a
decCBOR
Decoder s (StrictMaybe IPv6 -> (Int, StakePoolRelay))
-> Decoder s (StrictMaybe IPv6) -> Decoder s (Int, StakePoolRelay)
forall a b. Decoder s (a -> b) -> Decoder s a -> Decoder s b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Decoder s IPv6 -> Decoder s (StrictMaybe IPv6)
forall s a. Decoder s a -> Decoder s (StrictMaybe a)
decodeNullStrictMaybe Decoder s IPv6
forall s. Decoder s IPv6
forall a s. DecCBOR a => Decoder s a
decCBOR
Word
1 ->
(\StrictMaybe Port
x DnsName
y -> (Int
3, StrictMaybe Port -> DnsName -> StakePoolRelay
SingleHostName StrictMaybe Port
x DnsName
y))
(StrictMaybe Port -> DnsName -> (Int, StakePoolRelay))
-> Decoder s (StrictMaybe Port)
-> Decoder s (DnsName -> (Int, StakePoolRelay))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Decoder s Port -> Decoder s (StrictMaybe Port)
forall s a. Decoder s a -> Decoder s (StrictMaybe a)
decodeNullStrictMaybe Decoder s Port
forall s. Decoder s Port
forall a s. DecCBOR a => Decoder s a
decCBOR
Decoder s (DnsName -> (Int, StakePoolRelay))
-> Decoder s DnsName -> Decoder s (Int, StakePoolRelay)
forall a b. Decoder s (a -> b) -> Decoder s a -> Decoder s b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Decoder s DnsName
forall s. Decoder s DnsName
forall a s. DecCBOR a => Decoder s a
decCBOR
Word
2 -> do
x <- Decoder s DnsName
forall s. Decoder s DnsName
forall a s. DecCBOR a => Decoder s a
decCBOR
pure (2, MultiHostName x)
Word
k -> Word -> Decoder s (Int, StakePoolRelay)
forall a (m :: * -> *). (Typeable a, MonadFail m) => Word -> m a
invalidKey Word
k
data StakePoolParams = StakePoolParams
{ StakePoolParams -> KeyHash StakePool
sppId :: !(KeyHash StakePool)
, StakePoolParams -> VRFVerKeyHash StakePoolVRF
sppVrf :: !(VRFVerKeyHash StakePoolVRF)
, StakePoolParams -> Coin
sppPledge :: !Coin
, StakePoolParams -> Coin
sppCost :: !Coin
, StakePoolParams -> UnitInterval
sppMargin :: !UnitInterval
, StakePoolParams -> RewardAccount
sppRewardAccount :: !RewardAccount
, StakePoolParams -> Set (KeyHash Staking)
sppOwners :: !(Set (KeyHash Staking))
, StakePoolParams -> StrictSeq StakePoolRelay
sppRelays :: !(StrictSeq StakePoolRelay)
, StakePoolParams -> StrictMaybe PoolMetadata
sppMetadata :: !(StrictMaybe PoolMetadata)
}
deriving (Int -> StakePoolParams -> ShowS
[StakePoolParams] -> ShowS
StakePoolParams -> String
(Int -> StakePoolParams -> ShowS)
-> (StakePoolParams -> String)
-> ([StakePoolParams] -> ShowS)
-> Show StakePoolParams
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> StakePoolParams -> ShowS
showsPrec :: Int -> StakePoolParams -> ShowS
$cshow :: StakePoolParams -> String
show :: StakePoolParams -> String
$cshowList :: [StakePoolParams] -> ShowS
showList :: [StakePoolParams] -> ShowS
Show, (forall x. StakePoolParams -> Rep StakePoolParams x)
-> (forall x. Rep StakePoolParams x -> StakePoolParams)
-> Generic StakePoolParams
forall x. Rep StakePoolParams x -> StakePoolParams
forall x. StakePoolParams -> Rep StakePoolParams x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. StakePoolParams -> Rep StakePoolParams x
from :: forall x. StakePoolParams -> Rep StakePoolParams x
$cto :: forall x. Rep StakePoolParams x -> StakePoolParams
to :: forall x. Rep StakePoolParams x -> StakePoolParams
Generic, StakePoolParams -> StakePoolParams -> Bool
(StakePoolParams -> StakePoolParams -> Bool)
-> (StakePoolParams -> StakePoolParams -> Bool)
-> Eq StakePoolParams
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: StakePoolParams -> StakePoolParams -> Bool
== :: StakePoolParams -> StakePoolParams -> Bool
$c/= :: StakePoolParams -> StakePoolParams -> Bool
/= :: StakePoolParams -> StakePoolParams -> Bool
Eq, Eq StakePoolParams
Eq StakePoolParams =>
(StakePoolParams -> StakePoolParams -> Ordering)
-> (StakePoolParams -> StakePoolParams -> Bool)
-> (StakePoolParams -> StakePoolParams -> Bool)
-> (StakePoolParams -> StakePoolParams -> Bool)
-> (StakePoolParams -> StakePoolParams -> Bool)
-> (StakePoolParams -> StakePoolParams -> StakePoolParams)
-> (StakePoolParams -> StakePoolParams -> StakePoolParams)
-> Ord StakePoolParams
StakePoolParams -> StakePoolParams -> Bool
StakePoolParams -> StakePoolParams -> Ordering
StakePoolParams -> StakePoolParams -> StakePoolParams
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: StakePoolParams -> StakePoolParams -> Ordering
compare :: StakePoolParams -> StakePoolParams -> Ordering
$c< :: StakePoolParams -> StakePoolParams -> Bool
< :: StakePoolParams -> StakePoolParams -> Bool
$c<= :: StakePoolParams -> StakePoolParams -> Bool
<= :: StakePoolParams -> StakePoolParams -> Bool
$c> :: StakePoolParams -> StakePoolParams -> Bool
> :: StakePoolParams -> StakePoolParams -> Bool
$c>= :: StakePoolParams -> StakePoolParams -> Bool
>= :: StakePoolParams -> StakePoolParams -> Bool
$cmax :: StakePoolParams -> StakePoolParams -> StakePoolParams
max :: StakePoolParams -> StakePoolParams -> StakePoolParams
$cmin :: StakePoolParams -> StakePoolParams -> StakePoolParams
min :: StakePoolParams -> StakePoolParams -> StakePoolParams
Ord)
deriving (StakePoolParams -> Encoding
(StakePoolParams -> Encoding) -> EncCBOR StakePoolParams
forall a. (a -> Encoding) -> EncCBOR a
$cencCBOR :: StakePoolParams -> Encoding
encCBOR :: StakePoolParams -> Encoding
EncCBOR) via CBORGroup StakePoolParams
deriving (Typeable StakePoolParams
Typeable StakePoolParams =>
(forall s. Decoder s StakePoolParams)
-> (forall s. Proxy StakePoolParams -> Decoder s ())
-> (Proxy StakePoolParams -> Text)
-> DecCBOR StakePoolParams
Proxy StakePoolParams -> Text
forall s. Decoder s StakePoolParams
forall a.
Typeable a =>
(forall s. Decoder s a)
-> (forall s. Proxy a -> Decoder s ())
-> (Proxy a -> Text)
-> DecCBOR a
forall s. Proxy StakePoolParams -> Decoder s ()
$cdecCBOR :: forall s. Decoder s StakePoolParams
decCBOR :: forall s. Decoder s StakePoolParams
$cdropCBOR :: forall s. Proxy StakePoolParams -> Decoder s ()
dropCBOR :: forall s. Proxy StakePoolParams -> Decoder s ()
$clabel :: Proxy StakePoolParams -> Text
label :: Proxy StakePoolParams -> Text
DecCBOR) via CBORGroup StakePoolParams
sppVrfL :: Lens' StakePoolParams (VRFVerKeyHash StakePoolVRF)
sppVrfL :: Lens' StakePoolParams (VRFVerKeyHash StakePoolVRF)
sppVrfL = (StakePoolParams -> VRFVerKeyHash StakePoolVRF)
-> (StakePoolParams
-> VRFVerKeyHash StakePoolVRF -> StakePoolParams)
-> Lens' StakePoolParams (VRFVerKeyHash StakePoolVRF)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens StakePoolParams -> VRFVerKeyHash StakePoolVRF
sppVrf (\StakePoolParams
spp VRFVerKeyHash StakePoolVRF
u -> StakePoolParams
spp {sppVrf = u})
sppCostL :: Lens' StakePoolParams Coin
sppCostL :: Lens' StakePoolParams Coin
sppCostL = (StakePoolParams -> Coin)
-> (StakePoolParams -> Coin -> StakePoolParams)
-> Lens' StakePoolParams Coin
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens StakePoolParams -> Coin
sppCost (\StakePoolParams
spp Coin
u -> StakePoolParams
spp {sppCost = u})
sppMetadataL :: Lens' StakePoolParams (StrictMaybe PoolMetadata)
sppMetadataL :: Lens' StakePoolParams (StrictMaybe PoolMetadata)
sppMetadataL = (StakePoolParams -> StrictMaybe PoolMetadata)
-> (StakePoolParams -> StrictMaybe PoolMetadata -> StakePoolParams)
-> Lens' StakePoolParams (StrictMaybe PoolMetadata)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens StakePoolParams -> StrictMaybe PoolMetadata
sppMetadata (\StakePoolParams
spp StrictMaybe PoolMetadata
u -> StakePoolParams
spp {sppMetadata = u})
instance Default StakePoolParams where
def :: StakePoolParams
def = KeyHash StakePool
-> VRFVerKeyHash StakePoolVRF
-> Coin
-> Coin
-> UnitInterval
-> RewardAccount
-> Set (KeyHash Staking)
-> StrictSeq StakePoolRelay
-> StrictMaybe PoolMetadata
-> StakePoolParams
StakePoolParams KeyHash StakePool
forall a. Default a => a
def VRFVerKeyHash StakePoolVRF
forall a. Default a => a
def (Integer -> Coin
Coin Integer
0) (Integer -> Coin
Coin Integer
0) UnitInterval
forall a. Default a => a
def RewardAccount
forall a. Default a => a
def Set (KeyHash Staking)
forall a. Default a => a
def StrictSeq StakePoolRelay
forall a. Default a => a
def StrictMaybe PoolMetadata
forall a. Default a => a
def
instance NoThunks StakePoolParams
deriving instance NFData StakePoolParams
instance ToJSON StakePoolParams where
toJSON :: StakePoolParams -> Value
toJSON StakePoolParams
spp =
[Pair] -> Value
Aeson.object
[ Key
"publicKey" Key -> KeyHash StakePool -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= StakePoolParams -> KeyHash StakePool
sppId StakePoolParams
spp
, Key
"vrf" Key -> VRFVerKeyHash StakePoolVRF -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= StakePoolParams -> VRFVerKeyHash StakePoolVRF
sppVrf StakePoolParams
spp
, Key
"pledge" Key -> Coin -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= StakePoolParams -> Coin
sppPledge StakePoolParams
spp
, Key
"cost" Key -> Coin -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= StakePoolParams -> Coin
sppCost StakePoolParams
spp
, Key
"margin" Key -> UnitInterval -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= StakePoolParams -> UnitInterval
sppMargin StakePoolParams
spp
, Key
"rewardAccount" Key -> RewardAccount -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= StakePoolParams -> RewardAccount
sppRewardAccount StakePoolParams
spp
, Key
"owners" Key -> Set (KeyHash Staking) -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= StakePoolParams -> Set (KeyHash Staking)
sppOwners StakePoolParams
spp
, Key
"relays" Key -> StrictSeq StakePoolRelay -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= StakePoolParams -> StrictSeq StakePoolRelay
sppRelays StakePoolParams
spp
, Key
"metadata" Key -> StrictMaybe PoolMetadata -> Pair
forall v. ToJSON v => Key -> v -> Pair
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
.= StakePoolParams -> StrictMaybe PoolMetadata
sppMetadata StakePoolParams
spp
]
instance FromJSON StakePoolParams where
parseJSON :: Value -> Parser StakePoolParams
parseJSON =
String
-> (Object -> Parser StakePoolParams)
-> Value
-> Parser StakePoolParams
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Aeson.withObject String
"StakePoolParams" ((Object -> Parser StakePoolParams)
-> Value -> Parser StakePoolParams)
-> (Object -> Parser StakePoolParams)
-> Value
-> Parser StakePoolParams
forall a b. (a -> b) -> a -> b
$ \Object
obj ->
KeyHash StakePool
-> VRFVerKeyHash StakePoolVRF
-> Coin
-> Coin
-> UnitInterval
-> RewardAccount
-> Set (KeyHash Staking)
-> StrictSeq StakePoolRelay
-> StrictMaybe PoolMetadata
-> StakePoolParams
StakePoolParams
(KeyHash StakePool
-> VRFVerKeyHash StakePoolVRF
-> Coin
-> Coin
-> UnitInterval
-> RewardAccount
-> Set (KeyHash Staking)
-> StrictSeq StakePoolRelay
-> StrictMaybe PoolMetadata
-> StakePoolParams)
-> Parser (KeyHash StakePool)
-> Parser
(VRFVerKeyHash StakePoolVRF
-> Coin
-> Coin
-> UnitInterval
-> RewardAccount
-> Set (KeyHash Staking)
-> StrictSeq StakePoolRelay
-> StrictMaybe PoolMetadata
-> StakePoolParams)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
obj Object -> Key -> Parser (KeyHash StakePool)
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"publicKey"
Parser
(VRFVerKeyHash StakePoolVRF
-> Coin
-> Coin
-> UnitInterval
-> RewardAccount
-> Set (KeyHash Staking)
-> StrictSeq StakePoolRelay
-> StrictMaybe PoolMetadata
-> StakePoolParams)
-> Parser (VRFVerKeyHash StakePoolVRF)
-> Parser
(Coin
-> Coin
-> UnitInterval
-> RewardAccount
-> Set (KeyHash Staking)
-> StrictSeq StakePoolRelay
-> StrictMaybe PoolMetadata
-> StakePoolParams)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
obj Object -> Key -> Parser (VRFVerKeyHash StakePoolVRF)
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"vrf"
Parser
(Coin
-> Coin
-> UnitInterval
-> RewardAccount
-> Set (KeyHash Staking)
-> StrictSeq StakePoolRelay
-> StrictMaybe PoolMetadata
-> StakePoolParams)
-> Parser Coin
-> Parser
(Coin
-> UnitInterval
-> RewardAccount
-> Set (KeyHash Staking)
-> StrictSeq StakePoolRelay
-> StrictMaybe PoolMetadata
-> StakePoolParams)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
obj Object -> Key -> Parser Coin
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"pledge"
Parser
(Coin
-> UnitInterval
-> RewardAccount
-> Set (KeyHash Staking)
-> StrictSeq StakePoolRelay
-> StrictMaybe PoolMetadata
-> StakePoolParams)
-> Parser Coin
-> Parser
(UnitInterval
-> RewardAccount
-> Set (KeyHash Staking)
-> StrictSeq StakePoolRelay
-> StrictMaybe PoolMetadata
-> StakePoolParams)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
obj Object -> Key -> Parser Coin
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"cost"
Parser
(UnitInterval
-> RewardAccount
-> Set (KeyHash Staking)
-> StrictSeq StakePoolRelay
-> StrictMaybe PoolMetadata
-> StakePoolParams)
-> Parser UnitInterval
-> Parser
(RewardAccount
-> Set (KeyHash Staking)
-> StrictSeq StakePoolRelay
-> StrictMaybe PoolMetadata
-> StakePoolParams)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
obj Object -> Key -> Parser UnitInterval
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"margin"
Parser
(RewardAccount
-> Set (KeyHash Staking)
-> StrictSeq StakePoolRelay
-> StrictMaybe PoolMetadata
-> StakePoolParams)
-> Parser RewardAccount
-> Parser
(Set (KeyHash Staking)
-> StrictSeq StakePoolRelay
-> StrictMaybe PoolMetadata
-> StakePoolParams)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
obj Object -> Key -> Parser RewardAccount
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"rewardAccount"
Parser
(Set (KeyHash Staking)
-> StrictSeq StakePoolRelay
-> StrictMaybe PoolMetadata
-> StakePoolParams)
-> Parser (Set (KeyHash Staking))
-> Parser
(StrictSeq StakePoolRelay
-> StrictMaybe PoolMetadata -> StakePoolParams)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
obj Object -> Key -> Parser (Set (KeyHash Staking))
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"owners"
Parser
(StrictSeq StakePoolRelay
-> StrictMaybe PoolMetadata -> StakePoolParams)
-> Parser (StrictSeq StakePoolRelay)
-> Parser (StrictMaybe PoolMetadata -> StakePoolParams)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
obj Object -> Key -> Parser (StrictSeq StakePoolRelay)
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"relays"
Parser (StrictMaybe PoolMetadata -> StakePoolParams)
-> Parser (StrictMaybe PoolMetadata) -> Parser StakePoolParams
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
obj Object -> Key -> Parser (StrictMaybe PoolMetadata)
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"metadata"
type PoolParams = StakePoolParams
pattern PoolParams ::
KeyHash StakePool ->
VRFVerKeyHash StakePoolVRF ->
Coin ->
Coin ->
UnitInterval ->
RewardAccount ->
Set (KeyHash Staking) ->
StrictSeq StakePoolRelay ->
StrictMaybe PoolMetadata ->
PoolParams
pattern $mPoolParams :: forall {r}.
StakePoolParams
-> (KeyHash StakePool
-> VRFVerKeyHash StakePoolVRF
-> Coin
-> Coin
-> UnitInterval
-> RewardAccount
-> Set (KeyHash Staking)
-> StrictSeq StakePoolRelay
-> StrictMaybe PoolMetadata
-> r)
-> ((# #) -> r)
-> r
$bPoolParams :: KeyHash StakePool
-> VRFVerKeyHash StakePoolVRF
-> Coin
-> Coin
-> UnitInterval
-> RewardAccount
-> Set (KeyHash Staking)
-> StrictSeq StakePoolRelay
-> StrictMaybe PoolMetadata
-> StakePoolParams
PoolParams {StakePoolParams -> KeyHash StakePool
ppId, StakePoolParams -> VRFVerKeyHash StakePoolVRF
ppVrf, StakePoolParams -> Coin
ppPledge, StakePoolParams -> Coin
ppCost, StakePoolParams -> UnitInterval
ppMargin, StakePoolParams -> RewardAccount
ppRewardAccount, StakePoolParams -> Set (KeyHash Staking)
ppOwners, StakePoolParams -> StrictSeq StakePoolRelay
ppRelays, StakePoolParams -> StrictMaybe PoolMetadata
ppMetadata} =
StakePoolParams ppId ppVrf ppPledge ppCost ppMargin ppRewardAccount ppOwners ppRelays ppMetadata
{-# COMPLETE PoolParams #-}
{-# DEPRECATED PoolParams "In favor of `StakePoolParams`" #-}
{-# DEPRECATED
ppId
, ppVrf
, ppPledge
, ppCost
, ppMargin
, ppRewardAccount
, ppOwners
, ppRelays
, ppMetadata
"In favor of fields with `spp*` prefix"
#-}
instance EncCBOR PoolMetadata where
encCBOR :: PoolMetadata -> Encoding
encCBOR (PoolMetadata Url
u ByteString
h) =
Word -> Encoding
encodeListLen Word
2
Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Url -> Encoding
forall a. EncCBOR a => a -> Encoding
encCBOR Url
u
Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> ByteString -> Encoding
forall a. EncCBOR a => a -> Encoding
encCBOR ByteString
h
instance DecCBOR PoolMetadata where
decCBOR :: forall s. Decoder s PoolMetadata
decCBOR = do
Text
-> (PoolMetadata -> Int)
-> Decoder s PoolMetadata
-> Decoder s PoolMetadata
forall a s. Text -> (a -> Int) -> Decoder s a -> Decoder s a
decodeRecordNamed Text
"PoolMetadata" (Int -> PoolMetadata -> Int
forall a b. a -> b -> a
const Int
2) (Url -> ByteString -> PoolMetadata
PoolMetadata (Url -> ByteString -> PoolMetadata)
-> Decoder s Url -> Decoder s (ByteString -> PoolMetadata)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Decoder s Url
forall s. Decoder s Url
forall a s. DecCBOR a => Decoder s a
decCBOR Decoder s (ByteString -> PoolMetadata)
-> Decoder s ByteString -> Decoder s PoolMetadata
forall a b. Decoder s (a -> b) -> Decoder s a -> Decoder s b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Decoder s ByteString
forall s. Decoder s ByteString
forall a s. DecCBOR a => Decoder s a
decCBOR)
data SizeOfPoolOwners = SizeOfPoolOwners
instance EncCBOR SizeOfPoolOwners where
encCBOR :: SizeOfPoolOwners -> Encoding
encCBOR = String -> SizeOfPoolOwners -> Encoding
forall a. HasCallStack => String -> a
error String
"The `SizeOfPoolOwners` type cannot be encoded!"
data SizeOfPoolRelays = SizeOfPoolRelays
instance EncCBOR SizeOfPoolRelays where
encCBOR :: SizeOfPoolRelays -> Encoding
encCBOR = String -> SizeOfPoolRelays -> Encoding
forall a. HasCallStack => String -> a
error String
"The `SizeOfPoolRelays` type cannot be encoded!"
instance EncCBORGroup StakePoolParams where
encCBORGroup :: StakePoolParams -> Encoding
encCBORGroup StakePoolParams
poolParams =
KeyHash StakePool -> Encoding
forall a. EncCBOR a => a -> Encoding
encCBOR (StakePoolParams -> KeyHash StakePool
sppId StakePoolParams
poolParams)
Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> VRFVerKeyHash StakePoolVRF -> Encoding
forall a. EncCBOR a => a -> Encoding
encCBOR (StakePoolParams -> VRFVerKeyHash StakePoolVRF
sppVrf StakePoolParams
poolParams)
Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Coin -> Encoding
forall a. EncCBOR a => a -> Encoding
encCBOR (StakePoolParams -> Coin
sppPledge StakePoolParams
poolParams)
Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Coin -> Encoding
forall a. EncCBOR a => a -> Encoding
encCBOR (StakePoolParams -> Coin
sppCost StakePoolParams
poolParams)
Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> UnitInterval -> Encoding
forall a. EncCBOR a => a -> Encoding
encCBOR (StakePoolParams -> UnitInterval
sppMargin StakePoolParams
poolParams)
Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> RewardAccount -> Encoding
forall a. EncCBOR a => a -> Encoding
encCBOR (StakePoolParams -> RewardAccount
sppRewardAccount StakePoolParams
poolParams)
Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Set (KeyHash Staking) -> Encoding
forall a. EncCBOR a => a -> Encoding
encCBOR (StakePoolParams -> Set (KeyHash Staking)
sppOwners StakePoolParams
poolParams)
Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> StrictSeq StakePoolRelay -> Encoding
forall a. EncCBOR a => a -> Encoding
encCBOR (StakePoolParams -> StrictSeq StakePoolRelay
sppRelays StakePoolParams
poolParams)
Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> (PoolMetadata -> Encoding) -> StrictMaybe PoolMetadata -> Encoding
forall a. (a -> Encoding) -> StrictMaybe a -> Encoding
encodeNullStrictMaybe PoolMetadata -> Encoding
forall a. EncCBOR a => a -> Encoding
encCBOR (StakePoolParams -> StrictMaybe PoolMetadata
sppMetadata StakePoolParams
poolParams)
listLen :: StakePoolParams -> Word
listLen StakePoolParams
_ = Word
9
listLenBound :: Proxy StakePoolParams -> Word
listLenBound Proxy StakePoolParams
_ = Word
9
instance DecCBORGroup StakePoolParams where
decCBORGroup :: forall s. Decoder s StakePoolParams
decCBORGroup = do
hk <- Decoder s (KeyHash StakePool)
forall s. Decoder s (KeyHash StakePool)
forall a s. DecCBOR a => Decoder s a
decCBOR
vrf <- decCBOR
pledge <- decCBOR
cost <- decCBOR
margin <- decCBOR
ra <- decCBOR
owners <- decCBOR
relays <- decCBOR
md <- decodeNullStrictMaybe decCBOR
pure $
StakePoolParams
{ sppId = hk
, sppVrf = vrf
, sppPledge = pledge
, sppCost = cost
, sppMargin = margin
, sppRewardAccount = ra
, sppOwners = owners
, sppRelays = relays
, sppMetadata = md
}