-- | Blockchain genesis

{-# LANGUAGE NumericUnderscores #-}

module Blockfrost.Types.Cardano.Genesis
  ( Genesis (..)
  ) where

import Deriving.Aeson
import Servant.Docs (ToSample (..), singleSample)

import Blockfrost.Types.Shared

-- | Information about blockchain genesis
data Genesis = Genesis
  { Genesis -> Double
_genesisActiveSlotsCoefficient :: Double -- ^ The proportion of slots in which blocks should be issued
  , Genesis -> Integer
_genesisUpdateQuorum           :: Integer -- ^ Determines the quorum needed for votes on the protocol parameter updates
  , Genesis -> Lovelaces
_genesisMaxLovelaceSupply      :: Lovelaces -- ^ The total number of lovelace in the system
  , Genesis -> Integer
_genesisNetworkMagic           :: Integer -- ^ Network identifier
  , Genesis -> Integer
_genesisEpochLength            :: Integer -- ^ Number of slots in an epoch
  , Genesis -> POSIXTime
_genesisSystemStart            :: POSIXTime -- ^ Time of slot 0 in UNIX time
  , Genesis -> Integer
_genesisSlotsPerKesPeriod      :: Integer -- ^ Number of slots in an KES period
  , Genesis -> Integer
_genesisSlotLength             :: Integer -- ^ Duration of one slot in seconds
  , Genesis -> Integer
_genesisMaxKesEvolutions       :: Integer -- ^ The maximum number of time a KES key can be evolved before a pool operator must create a new operational certificate
  , Genesis -> Integer
_genesisSecurityParam          :: Integer -- ^ Security parameter @k@
  }
  deriving stock (Int -> Genesis -> ShowS
[Genesis] -> ShowS
Genesis -> String
(Int -> Genesis -> ShowS)
-> (Genesis -> String) -> ([Genesis] -> ShowS) -> Show Genesis
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Genesis] -> ShowS
$cshowList :: [Genesis] -> ShowS
show :: Genesis -> String
$cshow :: Genesis -> String
showsPrec :: Int -> Genesis -> ShowS
$cshowsPrec :: Int -> Genesis -> ShowS
Show, Genesis -> Genesis -> Bool
(Genesis -> Genesis -> Bool)
-> (Genesis -> Genesis -> Bool) -> Eq Genesis
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Genesis -> Genesis -> Bool
$c/= :: Genesis -> Genesis -> Bool
== :: Genesis -> Genesis -> Bool
$c== :: Genesis -> Genesis -> Bool
Eq, (forall x. Genesis -> Rep Genesis x)
-> (forall x. Rep Genesis x -> Genesis) -> Generic Genesis
forall x. Rep Genesis x -> Genesis
forall x. Genesis -> Rep Genesis x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Genesis x -> Genesis
$cfrom :: forall x. Genesis -> Rep Genesis x
Generic)
  deriving (Value -> Parser [Genesis]
Value -> Parser Genesis
(Value -> Parser Genesis)
-> (Value -> Parser [Genesis]) -> FromJSON Genesis
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [Genesis]
$cparseJSONList :: Value -> Parser [Genesis]
parseJSON :: Value -> Parser Genesis
$cparseJSON :: Value -> Parser Genesis
FromJSON, [Genesis] -> Encoding
[Genesis] -> Value
Genesis -> Encoding
Genesis -> Value
(Genesis -> Value)
-> (Genesis -> Encoding)
-> ([Genesis] -> Value)
-> ([Genesis] -> Encoding)
-> ToJSON Genesis
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [Genesis] -> Encoding
$ctoEncodingList :: [Genesis] -> Encoding
toJSONList :: [Genesis] -> Value
$ctoJSONList :: [Genesis] -> Value
toEncoding :: Genesis -> Encoding
$ctoEncoding :: Genesis -> Encoding
toJSON :: Genesis -> Value
$ctoJSON :: Genesis -> Value
ToJSON)
  via CustomJSON '[FieldLabelModifier '[StripPrefix "_genesis", CamelToSnake]] Genesis

instance ToSample Genesis where
  toSamples :: Proxy Genesis -> [(Text, Genesis)]
toSamples Proxy Genesis
_ = Genesis -> [(Text, Genesis)]
forall a. a -> [(Text, a)]
singleSample (Genesis -> [(Text, Genesis)]) -> Genesis -> [(Text, Genesis)]
forall a b. (a -> b) -> a -> b
$
    Genesis :: Double
-> Integer
-> Lovelaces
-> Integer
-> Integer
-> POSIXTime
-> Integer
-> Integer
-> Integer
-> Integer
-> Genesis
Genesis
      { _genesisActiveSlotsCoefficient :: Double
_genesisActiveSlotsCoefficient = Double
0.05
      , _genesisUpdateQuorum :: Integer
_genesisUpdateQuorum = Integer
5
      , _genesisMaxLovelaceSupply :: Lovelaces
_genesisMaxLovelaceSupply = Lovelaces
45_000_000_000_000_000
      , _genesisNetworkMagic :: Integer
_genesisNetworkMagic = Integer
764824073
      , _genesisEpochLength :: Integer
_genesisEpochLength = Integer
432_000
      , _genesisSystemStart :: POSIXTime
_genesisSystemStart = POSIXTime
1506203091
      , _genesisSlotsPerKesPeriod :: Integer
_genesisSlotsPerKesPeriod = Integer
129600
      , _genesisSlotLength :: Integer
_genesisSlotLength = Integer
1
      , _genesisMaxKesEvolutions :: Integer
_genesisMaxKesEvolutions  = Integer
62
      , _genesisSecurityParam :: Integer
_genesisSecurityParam  = Integer
2160
      }