{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}
module Ouroboros.Consensus.HardFork.History.EraParams (
EraParams (..)
, SafeZone (..)
, defaultEraParams
) where
import Codec.CBOR.Decoding (Decoder, decodeListLen, decodeWord8)
import Codec.CBOR.Encoding (Encoding, encodeListLen, encodeWord8)
import Codec.Serialise (Serialise (..))
import Control.Monad (void)
import Data.Word
import GHC.Generics (Generic)
import NoThunks.Class (NoThunks)
import Cardano.Binary (enforceSize)
import Ouroboros.Consensus.Block
import Ouroboros.Consensus.BlockchainTime.WallClock.Types
import Ouroboros.Consensus.Config.SecurityParam
data EraParams = EraParams {
EraParams -> EpochSize
eraEpochSize :: !EpochSize
, EraParams -> SlotLength
eraSlotLength :: !SlotLength
, EraParams -> SafeZone
eraSafeZone :: !SafeZone
}
deriving stock (Int -> EraParams -> ShowS
[EraParams] -> ShowS
EraParams -> String
(Int -> EraParams -> ShowS)
-> (EraParams -> String)
-> ([EraParams] -> ShowS)
-> Show EraParams
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EraParams] -> ShowS
$cshowList :: [EraParams] -> ShowS
show :: EraParams -> String
$cshow :: EraParams -> String
showsPrec :: Int -> EraParams -> ShowS
$cshowsPrec :: Int -> EraParams -> ShowS
Show, EraParams -> EraParams -> Bool
(EraParams -> EraParams -> Bool)
-> (EraParams -> EraParams -> Bool) -> Eq EraParams
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EraParams -> EraParams -> Bool
$c/= :: EraParams -> EraParams -> Bool
== :: EraParams -> EraParams -> Bool
$c== :: EraParams -> EraParams -> Bool
Eq, (forall x. EraParams -> Rep EraParams x)
-> (forall x. Rep EraParams x -> EraParams) -> Generic EraParams
forall x. Rep EraParams x -> EraParams
forall x. EraParams -> Rep EraParams x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep EraParams x -> EraParams
$cfrom :: forall x. EraParams -> Rep EraParams x
Generic)
deriving anyclass (Context -> EraParams -> IO (Maybe ThunkInfo)
Proxy EraParams -> String
(Context -> EraParams -> IO (Maybe ThunkInfo))
-> (Context -> EraParams -> IO (Maybe ThunkInfo))
-> (Proxy EraParams -> String)
-> NoThunks EraParams
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy EraParams -> String
$cshowTypeOf :: Proxy EraParams -> String
wNoThunks :: Context -> EraParams -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> EraParams -> IO (Maybe ThunkInfo)
noThunks :: Context -> EraParams -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> EraParams -> IO (Maybe ThunkInfo)
NoThunks)
defaultEraParams :: SecurityParam -> SlotLength -> EraParams
defaultEraParams :: SecurityParam -> SlotLength -> EraParams
defaultEraParams (SecurityParam Word64
k) SlotLength
slotLength = EraParams :: EpochSize -> SlotLength -> SafeZone -> EraParams
EraParams {
eraEpochSize :: EpochSize
eraEpochSize = Word64 -> EpochSize
EpochSize (Word64
k Word64 -> Word64 -> Word64
forall a. Num a => a -> a -> a
* Word64
10)
, eraSlotLength :: SlotLength
eraSlotLength = SlotLength
slotLength
, eraSafeZone :: SafeZone
eraSafeZone = Word64 -> SafeZone
StandardSafeZone (Word64
k Word64 -> Word64 -> Word64
forall a. Num a => a -> a -> a
* Word64
2)
}
data SafeZone =
StandardSafeZone !Word64
| UnsafeIndefiniteSafeZone
deriving stock (Int -> SafeZone -> ShowS
[SafeZone] -> ShowS
SafeZone -> String
(Int -> SafeZone -> ShowS)
-> (SafeZone -> String) -> ([SafeZone] -> ShowS) -> Show SafeZone
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SafeZone] -> ShowS
$cshowList :: [SafeZone] -> ShowS
show :: SafeZone -> String
$cshow :: SafeZone -> String
showsPrec :: Int -> SafeZone -> ShowS
$cshowsPrec :: Int -> SafeZone -> ShowS
Show, SafeZone -> SafeZone -> Bool
(SafeZone -> SafeZone -> Bool)
-> (SafeZone -> SafeZone -> Bool) -> Eq SafeZone
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SafeZone -> SafeZone -> Bool
$c/= :: SafeZone -> SafeZone -> Bool
== :: SafeZone -> SafeZone -> Bool
$c== :: SafeZone -> SafeZone -> Bool
Eq, (forall x. SafeZone -> Rep SafeZone x)
-> (forall x. Rep SafeZone x -> SafeZone) -> Generic SafeZone
forall x. Rep SafeZone x -> SafeZone
forall x. SafeZone -> Rep SafeZone x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SafeZone x -> SafeZone
$cfrom :: forall x. SafeZone -> Rep SafeZone x
Generic)
deriving anyclass (Context -> SafeZone -> IO (Maybe ThunkInfo)
Proxy SafeZone -> String
(Context -> SafeZone -> IO (Maybe ThunkInfo))
-> (Context -> SafeZone -> IO (Maybe ThunkInfo))
-> (Proxy SafeZone -> String)
-> NoThunks SafeZone
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy SafeZone -> String
$cshowTypeOf :: Proxy SafeZone -> String
wNoThunks :: Context -> SafeZone -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> SafeZone -> IO (Maybe ThunkInfo)
noThunks :: Context -> SafeZone -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> SafeZone -> IO (Maybe ThunkInfo)
NoThunks)
instance Serialise SafeZone where
encode :: SafeZone -> Encoding
encode = \case
StandardSafeZone Word64
safeFromTip -> [Encoding] -> Encoding
forall a. Monoid a => [a] -> a
mconcat [
Word -> Encoding
encodeListLen Word
3
, Word8 -> Encoding
encodeWord8 Word8
0
, Word64 -> Encoding
forall a. Serialise a => a -> Encoding
encode Word64
safeFromTip
, Encoding
encodeSafeBeforeEpoch
]
SafeZone
UnsafeIndefiniteSafeZone -> [Encoding] -> Encoding
forall a. Monoid a => [a] -> a
mconcat [
Word -> Encoding
encodeListLen Word
1
, Word8 -> Encoding
encodeWord8 Word8
1
]
decode :: Decoder s SafeZone
decode = do
Int
size <- Decoder s Int
forall s. Decoder s Int
decodeListLen
Word8
tag <- Decoder s Word8
forall s. Decoder s Word8
decodeWord8
case (Int
size, Word8
tag) of
(Int
3, Word8
0) -> Word64 -> SafeZone
StandardSafeZone (Word64 -> SafeZone) -> Decoder s Word64 -> Decoder s SafeZone
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Decoder s Word64
forall a s. Serialise a => Decoder s a
decode Decoder s SafeZone -> Decoder s () -> Decoder s SafeZone
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Decoder s ()
forall s. Decoder s ()
decodeSafeBeforeEpoch
(Int
1, Word8
1) -> SafeZone -> Decoder s SafeZone
forall (m :: * -> *) a. Monad m => a -> m a
return SafeZone
UnsafeIndefiniteSafeZone
(Int, Word8)
_ -> String -> Decoder s SafeZone
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Decoder s SafeZone) -> String -> Decoder s SafeZone
forall a b. (a -> b) -> a -> b
$ String
"SafeZone: invalid size and tag " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> (Int, Word8) -> String
forall a. Show a => a -> String
show (Int
size, Word8
tag)
encodeSafeBeforeEpoch :: Encoding
encodeSafeBeforeEpoch :: Encoding
encodeSafeBeforeEpoch = Word -> Encoding
encodeListLen Word
1 Encoding -> Encoding -> Encoding
forall a. Semigroup a => a -> a -> a
<> Word8 -> Encoding
encodeWord8 Word8
0
decodeSafeBeforeEpoch :: Decoder s ()
decodeSafeBeforeEpoch :: Decoder s ()
decodeSafeBeforeEpoch = do
Int
size <- Decoder s Int
forall s. Decoder s Int
decodeListLen
Word8
tag <- Decoder s Word8
forall s. Decoder s Word8
decodeWord8
case (Int
size, Word8
tag) of
(Int
1, Word8
0) -> () -> Decoder s ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
(Int
2, Word8
1) -> Decoder s EpochNo -> Decoder s ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Decoder s EpochNo -> Decoder s ())
-> Decoder s EpochNo -> Decoder s ()
forall a b. (a -> b) -> a -> b
$ forall s. Serialise EpochNo => Decoder s EpochNo
forall a s. Serialise a => Decoder s a
decode @EpochNo
(Int, Word8)
_ -> String -> Decoder s ()
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Decoder s ()) -> String -> Decoder s ()
forall a b. (a -> b) -> a -> b
$ String
"SafeBeforeEpoch: invalid size and tag " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> (Int, Word8) -> String
forall a. Show a => a -> String
show (Int
size, Word8
tag)
instance Serialise EraParams where
encode :: EraParams -> Encoding
encode EraParams{SlotLength
EpochSize
SafeZone
eraSafeZone :: SafeZone
eraSlotLength :: SlotLength
eraEpochSize :: EpochSize
eraSafeZone :: EraParams -> SafeZone
eraSlotLength :: EraParams -> SlotLength
eraEpochSize :: EraParams -> EpochSize
..} = [Encoding] -> Encoding
forall a. Monoid a => [a] -> a
mconcat [
Word -> Encoding
encodeListLen Word
3
, Word64 -> Encoding
forall a. Serialise a => a -> Encoding
encode (EpochSize -> Word64
unEpochSize EpochSize
eraEpochSize)
, SlotLength -> Encoding
forall a. Serialise a => a -> Encoding
encode SlotLength
eraSlotLength
, SafeZone -> Encoding
forall a. Serialise a => a -> Encoding
encode SafeZone
eraSafeZone
]
decode :: Decoder s EraParams
decode = do
Text -> Int -> Decoder s ()
forall s. Text -> Int -> Decoder s ()
enforceSize Text
"EraParams" Int
3
EpochSize
eraEpochSize <- Word64 -> EpochSize
EpochSize (Word64 -> EpochSize) -> Decoder s Word64 -> Decoder s EpochSize
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Decoder s Word64
forall a s. Serialise a => Decoder s a
decode
SlotLength
eraSlotLength <- Decoder s SlotLength
forall a s. Serialise a => Decoder s a
decode
SafeZone
eraSafeZone <- Decoder s SafeZone
forall a s. Serialise a => Decoder s a
decode
EraParams -> Decoder s EraParams
forall (m :: * -> *) a. Monad m => a -> m a
return EraParams :: EpochSize -> SlotLength -> SafeZone -> EraParams
EraParams{SlotLength
EpochSize
SafeZone
eraSafeZone :: SafeZone
eraSlotLength :: SlotLength
eraEpochSize :: EpochSize
eraSafeZone :: SafeZone
eraSlotLength :: SlotLength
eraEpochSize :: EpochSize
..}