{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
module Bcc.Api.GenesisParameters (
GenesisParameters(..),
EpochSize(..),
fromSophieGenesis,
) where
import Prelude
import Data.Time (NominalDiffTime, UTCTime)
import Data.Word (Word64)
import Bcc.Slotting.Slot (EpochSize (..))
import qualified Bcc.Ledger.BaseTypes as Ledger
import qualified Sophie.Spec.Ledger.Genesis as Sophie
import Bcc.Api.NetworkId
import Bcc.Api.ProtocolParameters
import Bcc.Api.Value
data GenesisParameters =
GenesisParameters {
GenesisParameters -> UTCTime
protocolParamSystemStart :: UTCTime,
GenesisParameters -> NetworkId
protocolParamNetworkId :: NetworkId,
GenesisParameters -> Rational
protocolParamActiveSlotsCoefficient :: Rational,
GenesisParameters -> Int
protocolParamSecurity :: Int,
GenesisParameters -> Word64
protocolVestMultiple :: Word64,
GenesisParameters -> EpochSize
protocolParamEpochLength :: EpochSize,
GenesisParameters -> NominalDiffTime
protocolParamSlotLength :: NominalDiffTime,
GenesisParameters -> Int
protocolParamSlotsPerKESPeriod :: Int,
GenesisParameters -> Int
protocolParamMaxKESEvolutions :: Int,
GenesisParameters -> Int
protocolParamUpdateQuorum :: Int,
GenesisParameters -> Entropic
protocolParamMaxEntropicSupply :: Entropic,
GenesisParameters -> ProtocolParameters
protocolInitialUpdateableProtocolParameters :: ProtocolParameters
}
fromSophieGenesis :: Sophie.SophieGenesis era -> GenesisParameters
fromSophieGenesis :: SophieGenesis era -> GenesisParameters
fromSophieGenesis
Sophie.SophieGenesis {
UTCTime
sgSystemStart :: forall era. SophieGenesis era -> UTCTime
sgSystemStart :: UTCTime
Sophie.sgSystemStart
, Word32
sgNetworkMagic :: forall era. SophieGenesis era -> Word32
sgNetworkMagic :: Word32
Sophie.sgNetworkMagic
, Network
sgNetworkId :: forall era. SophieGenesis era -> Network
sgNetworkId :: Network
Sophie.sgNetworkId
, PositiveUnitInterval
sgActiveSlotsCoeff :: forall era. SophieGenesis era -> PositiveUnitInterval
sgActiveSlotsCoeff :: PositiveUnitInterval
Sophie.sgActiveSlotsCoeff
, Word64
sgSecurityParam :: forall era. SophieGenesis era -> Word64
sgSecurityParam :: Word64
Sophie.sgSecurityParam
, Word64
sgVestMultiple :: forall era. SophieGenesis era -> Word64
sgVestMultiple :: Word64
Sophie.sgVestMultiple
, EpochSize
sgEpochLength :: forall era. SophieGenesis era -> EpochSize
sgEpochLength :: EpochSize
Sophie.sgEpochLength
, Word64
sgSlotsPerKESPeriod :: forall era. SophieGenesis era -> Word64
sgSlotsPerKESPeriod :: Word64
Sophie.sgSlotsPerKESPeriod
, Word64
sgMaxKESEvolutions :: forall era. SophieGenesis era -> Word64
sgMaxKESEvolutions :: Word64
Sophie.sgMaxKESEvolutions
, NominalDiffTime
sgSlotLength :: forall era. SophieGenesis era -> NominalDiffTime
sgSlotLength :: NominalDiffTime
Sophie.sgSlotLength
, Word64
sgUpdateQuorum :: forall era. SophieGenesis era -> Word64
sgUpdateQuorum :: Word64
Sophie.sgUpdateQuorum
, Word64
sgMaxEntropicSupply :: forall era. SophieGenesis era -> Word64
sgMaxEntropicSupply :: Word64
Sophie.sgMaxEntropicSupply
, PParams era
sgProtocolParams :: forall era. SophieGenesis era -> PParams era
sgProtocolParams :: PParams era
Sophie.sgProtocolParams
, sgGenDelegs :: forall era.
SophieGenesis era
-> Map (KeyHash 'Genesis (Crypto era)) (GenDelegPair (Crypto era))
Sophie.sgGenDelegs = Map (KeyHash 'Genesis (Crypto era)) (GenDelegPair (Crypto era))
_
, sgVestedDelegs :: forall era.
SophieGenesis era
-> Map
(KeyHash 'Vested (Crypto era)) (VestedDelegPair (Crypto era))
Sophie.sgVestedDelegs = Map (KeyHash 'Vested (Crypto era)) (VestedDelegPair (Crypto era))
_
, sgInitialFunds :: forall era. SophieGenesis era -> Map (Addr (Crypto era)) Coin
Sophie.sgInitialFunds = Map (Addr (Crypto era)) Coin
_
, sgStaking :: forall era. SophieGenesis era -> SophieGenesisStaking (Crypto era)
Sophie.sgStaking = SophieGenesisStaking (Crypto era)
_
} =
GenesisParameters :: UTCTime
-> NetworkId
-> Rational
-> Int
-> Word64
-> EpochSize
-> NominalDiffTime
-> Int
-> Int
-> Int
-> Entropic
-> ProtocolParameters
-> GenesisParameters
GenesisParameters {
protocolParamSystemStart :: UTCTime
protocolParamSystemStart = UTCTime
sgSystemStart
, protocolParamNetworkId :: NetworkId
protocolParamNetworkId = Network -> NetworkMagic -> NetworkId
fromSophieNetwork Network
sgNetworkId
(Word32 -> NetworkMagic
NetworkMagic Word32
sgNetworkMagic)
, protocolParamActiveSlotsCoefficient :: Rational
protocolParamActiveSlotsCoefficient = PositiveUnitInterval -> Rational
forall r. BoundedRational r => r -> Rational
Ledger.unboundRational
PositiveUnitInterval
sgActiveSlotsCoeff
, protocolParamSecurity :: Int
protocolParamSecurity = Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
sgSecurityParam
, protocolVestMultiple :: Word64
protocolVestMultiple = Word64
sgVestMultiple
, protocolParamEpochLength :: EpochSize
protocolParamEpochLength = EpochSize
sgEpochLength
, protocolParamSlotLength :: NominalDiffTime
protocolParamSlotLength = NominalDiffTime
sgSlotLength
, protocolParamSlotsPerKESPeriod :: Int
protocolParamSlotsPerKESPeriod = Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
sgSlotsPerKESPeriod
, protocolParamMaxKESEvolutions :: Int
protocolParamMaxKESEvolutions = Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
sgMaxKESEvolutions
, protocolParamUpdateQuorum :: Int
protocolParamUpdateQuorum = Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
sgUpdateQuorum
, protocolParamMaxEntropicSupply :: Entropic
protocolParamMaxEntropicSupply = Integer -> Entropic
Entropic
(Word64 -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
sgMaxEntropicSupply)
, protocolInitialUpdateableProtocolParameters :: ProtocolParameters
protocolInitialUpdateableProtocolParameters = PParams era -> ProtocolParameters
forall ledgerera. PParams ledgerera -> ProtocolParameters
fromSophiePParams
PParams era
sgProtocolParams
}