{-# LANGUAGE DeriveFunctor #-}
module Ouroboros.Consensus.Forecast (
Forecast (..)
, OutsideForecastRange (..)
, constantForecastOf
, mapForecast
, trivialForecast
, crossEraForecastBound
) where
import Control.Exception (Exception)
import Control.Monad.Except
import Data.Word (Word64)
import Ouroboros.Consensus.Block
import Ouroboros.Consensus.HardFork.History.Util (addSlots)
import Ouroboros.Consensus.Ledger.Basics (GetTip, getTipSlot)
import Ouroboros.Consensus.Ticked
data Forecast a = Forecast {
Forecast a -> WithOrigin SlotNo
forecastAt :: WithOrigin SlotNo
, Forecast a -> SlotNo -> Except OutsideForecastRange (Ticked a)
forecastFor :: SlotNo -> Except OutsideForecastRange (Ticked a)
}
mapForecast :: (Ticked a -> Ticked b) -> Forecast a -> Forecast b
mapForecast :: (Ticked a -> Ticked b) -> Forecast a -> Forecast b
mapForecast Ticked a -> Ticked b
f (Forecast WithOrigin SlotNo
at SlotNo -> Except OutsideForecastRange (Ticked a)
for) = Forecast :: forall a.
WithOrigin SlotNo
-> (SlotNo -> Except OutsideForecastRange (Ticked a)) -> Forecast a
Forecast{
forecastAt :: WithOrigin SlotNo
forecastAt = WithOrigin SlotNo
at
, forecastFor :: SlotNo -> Except OutsideForecastRange (Ticked b)
forecastFor = (Ticked a -> Ticked b)
-> Except OutsideForecastRange (Ticked a)
-> Except OutsideForecastRange (Ticked b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ticked a -> Ticked b
f (Except OutsideForecastRange (Ticked a)
-> Except OutsideForecastRange (Ticked b))
-> (SlotNo -> Except OutsideForecastRange (Ticked a))
-> SlotNo
-> Except OutsideForecastRange (Ticked b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SlotNo -> Except OutsideForecastRange (Ticked a)
for
}
trivialForecast :: GetTip b => b -> Forecast ()
trivialForecast :: b -> Forecast ()
trivialForecast b
x = Ticked () -> WithOrigin SlotNo -> Forecast ()
forall a. Ticked a -> WithOrigin SlotNo -> Forecast a
constantForecastOf Ticked ()
TickedTrivial (b -> WithOrigin SlotNo
forall l. GetTip l => l -> WithOrigin SlotNo
getTipSlot b
x)
constantForecastOf :: Ticked a -> WithOrigin SlotNo -> Forecast a
constantForecastOf :: Ticked a -> WithOrigin SlotNo -> Forecast a
constantForecastOf Ticked a
a WithOrigin SlotNo
at = Forecast :: forall a.
WithOrigin SlotNo
-> (SlotNo -> Except OutsideForecastRange (Ticked a)) -> Forecast a
Forecast {
forecastAt :: WithOrigin SlotNo
forecastAt = WithOrigin SlotNo
at
, forecastFor :: SlotNo -> Except OutsideForecastRange (Ticked a)
forecastFor = \SlotNo
for ->
if SlotNo -> WithOrigin SlotNo
forall t. t -> WithOrigin t
NotOrigin SlotNo
for WithOrigin SlotNo -> WithOrigin SlotNo -> Bool
forall a. Ord a => a -> a -> Bool
>= WithOrigin SlotNo
at
then Ticked a -> Except OutsideForecastRange (Ticked a)
forall (m :: * -> *) a. Monad m => a -> m a
return Ticked a
a
else [Char] -> Except OutsideForecastRange (Ticked a)
forall a. HasCallStack => [Char] -> a
error [Char]
"constantForecastOf: precondition violated"
}
data OutsideForecastRange =
OutsideForecastRange {
OutsideForecastRange -> WithOrigin SlotNo
outsideForecastAt :: !(WithOrigin SlotNo)
, OutsideForecastRange -> SlotNo
outsideForecastMaxFor :: !SlotNo
, OutsideForecastRange -> SlotNo
outsideForecastFor :: !SlotNo
}
deriving (Int -> OutsideForecastRange -> ShowS
[OutsideForecastRange] -> ShowS
OutsideForecastRange -> [Char]
(Int -> OutsideForecastRange -> ShowS)
-> (OutsideForecastRange -> [Char])
-> ([OutsideForecastRange] -> ShowS)
-> Show OutsideForecastRange
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [OutsideForecastRange] -> ShowS
$cshowList :: [OutsideForecastRange] -> ShowS
show :: OutsideForecastRange -> [Char]
$cshow :: OutsideForecastRange -> [Char]
showsPrec :: Int -> OutsideForecastRange -> ShowS
$cshowsPrec :: Int -> OutsideForecastRange -> ShowS
Show, OutsideForecastRange -> OutsideForecastRange -> Bool
(OutsideForecastRange -> OutsideForecastRange -> Bool)
-> (OutsideForecastRange -> OutsideForecastRange -> Bool)
-> Eq OutsideForecastRange
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OutsideForecastRange -> OutsideForecastRange -> Bool
$c/= :: OutsideForecastRange -> OutsideForecastRange -> Bool
== :: OutsideForecastRange -> OutsideForecastRange -> Bool
$c== :: OutsideForecastRange -> OutsideForecastRange -> Bool
Eq)
instance Exception OutsideForecastRange
crossEraForecastBound ::
WithOrigin SlotNo
-> SlotNo
-> Word64
-> Word64
-> SlotNo
crossEraForecastBound :: WithOrigin SlotNo -> SlotNo -> Word64 -> Word64 -> SlotNo
crossEraForecastBound WithOrigin SlotNo
currentTip SlotNo
transitionSlot Word64
currentLookahead Word64
nextLookahead =
SlotNo -> (SlotNo -> SlotNo) -> Maybe SlotNo -> SlotNo
forall b a. b -> (a -> b) -> Maybe a -> b
maybe SlotNo
boundFromNextEra (SlotNo -> SlotNo -> SlotNo
forall a. Ord a => a -> a -> a
min SlotNo
boundFromNextEra) Maybe SlotNo
boundFromCurrentEra
where
tipSucc :: SlotNo
tipSucc :: SlotNo
tipSucc = WithOrigin SlotNo -> SlotNo
forall t. (Bounded t, Enum t) => WithOrigin t -> t
succWithOrigin WithOrigin SlotNo
currentTip
boundFromCurrentEra :: Maybe SlotNo
boundFromCurrentEra :: Maybe SlotNo
boundFromCurrentEra = do
Bool -> Maybe ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (SlotNo
tipSucc SlotNo -> SlotNo -> Bool
forall a. Ord a => a -> a -> Bool
< SlotNo
transitionSlot)
SlotNo -> Maybe SlotNo
forall (m :: * -> *) a. Monad m => a -> m a
return (SlotNo -> Maybe SlotNo) -> SlotNo -> Maybe SlotNo
forall a b. (a -> b) -> a -> b
$ Word64 -> SlotNo -> SlotNo
addSlots Word64
currentLookahead SlotNo
tipSucc
boundFromNextEra :: SlotNo
boundFromNextEra :: SlotNo
boundFromNextEra = Word64 -> SlotNo -> SlotNo
addSlots Word64
nextLookahead SlotNo
transitionSlot