{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE MultiParamTypeClasses #-}
module Cardano.Ledger.BHeaderView where
import Cardano.Ledger.BaseTypes (BoundedRational (..), Nonce, UnitInterval)
import Cardano.Ledger.Hashes (EraIndependentBlockBody, HASH, Hash, KeyHash, KeyRole (..))
import Cardano.Ledger.Slot (SlotNo (..), (-*))
import Control.DeepSeq (NFData)
import Data.Word (Word32)
import GHC.Generics (Generic)
data =
{ BHeaderView -> KeyHash BlockIssuer
bhviewID :: KeyHash BlockIssuer
, BHeaderView -> Word32
bhviewBSize :: Word32
, BHeaderView -> Int
bhviewHSize :: Int
, BHeaderView -> Hash HASH EraIndependentBlockBody
bhviewBHash :: Hash HASH EraIndependentBlockBody
, BHeaderView -> SlotNo
bhviewSlot :: SlotNo
, BHeaderView -> Maybe Nonce
bhviewPrevEpochNonce :: Maybe Nonce
}
deriving ((forall x. BHeaderView -> Rep BHeaderView x)
-> (forall x. Rep BHeaderView x -> BHeaderView)
-> Generic BHeaderView
forall x. Rep BHeaderView x -> BHeaderView
forall x. BHeaderView -> Rep BHeaderView x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. BHeaderView -> Rep BHeaderView x
from :: forall x. BHeaderView -> Rep BHeaderView x
$cto :: forall x. Rep BHeaderView x -> BHeaderView
to :: forall x. Rep BHeaderView x -> BHeaderView
Generic)
instance NFData BHeaderView
isOverlaySlot ::
SlotNo ->
UnitInterval ->
SlotNo ->
Bool
isOverlaySlot :: SlotNo -> UnitInterval -> SlotNo -> Bool
isOverlaySlot SlotNo
firstSlotNo UnitInterval
dval SlotNo
slot = Rational -> Integer
step Rational
s Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Rational -> Integer
step (Rational
s Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
+ Rational
1)
where
s :: Rational
s = Duration -> Rational
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Duration -> Rational) -> Duration -> Rational
forall a b. (a -> b) -> a -> b
$ SlotNo
slot SlotNo -> SlotNo -> Duration
-* SlotNo
firstSlotNo
d :: Rational
d = UnitInterval -> Rational
forall r. BoundedRational r => r -> Rational
unboundRational UnitInterval
dval
step :: Rational -> Integer
step :: Rational -> Integer
step Rational
x = Rational -> Integer
forall b. Integral b => Rational -> b
forall a b. (RealFrac a, Integral b) => a -> b
ceiling (Rational
x Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
* Rational
d)