{-# LANGUAGE DataKinds #-}
{-# LANGUAGE MultiParamTypeClasses #-}
module Cardano.Ledger.BHeaderView where
import Cardano.Ledger.BaseTypes (BoundedRational (..), UnitInterval)
import Cardano.Ledger.Hashes (EraIndependentBlockBody)
import Cardano.Ledger.Keys (Hash, KeyHash, KeyRole (..))
import Cardano.Ledger.Slot (SlotNo (..), (-*))
import Numeric.Natural (Natural)
data crypto =
{
BHeaderView crypto -> KeyHash 'BlockIssuer crypto
bhviewID :: KeyHash 'BlockIssuer crypto,
BHeaderView crypto -> Natural
bhviewBSize :: Natural,
BHeaderView crypto -> Int
bhviewHSize :: Int,
BHeaderView crypto -> Hash crypto EraIndependentBlockBody
bhviewBHash :: Hash crypto EraIndependentBlockBody,
BHeaderView crypto -> SlotNo
bhviewSlot :: SlotNo
}
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 a b. (RealFrac a, Integral b) => a -> b
ceiling (Rational
x Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
* Rational
d)