{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeFamilies #-}
module Ouroboros.Network.BlockFetch.DeltaQ
( GSV
, Distribution
, DeltaQ
, PeerGSV (..)
, SizeInBytes
, PeerFetchInFlightLimits (..)
, calculatePeerFetchInFlightLimits
, estimateResponseDeadlineProbability
, estimateExpectedResponseDuration
, comparePeerGSV
, comparePeerGSV'
) where
import Control.Monad.Class.MonadTime
import Data.Fixed as Fixed (Pico)
import Data.Hashable
import Data.Set (Set)
import qualified Data.Set as Set
import Ouroboros.Network.DeltaQ
data PeerFetchInFlightLimits = PeerFetchInFlightLimits {
PeerFetchInFlightLimits -> SizeInBytes
inFlightBytesHighWatermark :: SizeInBytes,
PeerFetchInFlightLimits -> SizeInBytes
inFlightBytesLowWatermark :: SizeInBytes
}
deriving Int -> PeerFetchInFlightLimits -> ShowS
[PeerFetchInFlightLimits] -> ShowS
PeerFetchInFlightLimits -> String
(Int -> PeerFetchInFlightLimits -> ShowS)
-> (PeerFetchInFlightLimits -> String)
-> ([PeerFetchInFlightLimits] -> ShowS)
-> Show PeerFetchInFlightLimits
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PeerFetchInFlightLimits] -> ShowS
$cshowList :: [PeerFetchInFlightLimits] -> ShowS
show :: PeerFetchInFlightLimits -> String
$cshow :: PeerFetchInFlightLimits -> String
showsPrec :: Int -> PeerFetchInFlightLimits -> ShowS
$cshowsPrec :: Int -> PeerFetchInFlightLimits -> ShowS
Show
comparePeerGSV :: forall peer.
( Hashable peer
, Ord peer
)
=> Set peer
-> Int
-> (PeerGSV, peer)
-> (PeerGSV, peer)
-> Ordering
comparePeerGSV :: Set peer -> Int -> (PeerGSV, peer) -> (PeerGSV, peer) -> Ordering
comparePeerGSV Set peer
activePeers Int
salt (PeerGSV
a, peer
a_p) (PeerGSV
b, peer
b_p) =
let gs_a :: DiffTime
gs_a = if peer -> Bool
isActive peer
a_p then DiffTime
activeAdvantage DiffTime -> DiffTime -> DiffTime
forall a. Num a => a -> a -> a
* PeerGSV -> DiffTime
gs PeerGSV
a
else PeerGSV -> DiffTime
gs PeerGSV
a
gs_b :: DiffTime
gs_b = if peer -> Bool
isActive peer
b_p then DiffTime
activeAdvantage DiffTime -> DiffTime -> DiffTime
forall a. Num a => a -> a -> a
* PeerGSV -> DiffTime
gs PeerGSV
b
else PeerGSV -> DiffTime
gs PeerGSV
b in
if DiffTime -> DiffTime
forall a. Num a => a -> a
abs (DiffTime
gs_a DiffTime -> DiffTime -> DiffTime
forall a. Num a => a -> a -> a
- DiffTime
gs_b) DiffTime -> DiffTime -> Bool
forall a. Ord a => a -> a -> Bool
< DiffTime
0.05 DiffTime -> DiffTime -> DiffTime
forall a. Num a => a -> a -> a
* DiffTime -> DiffTime -> DiffTime
forall a. Ord a => a -> a -> a
max DiffTime
gs_a DiffTime
gs_b
then Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (Int -> peer -> Int
forall a. Hashable a => Int -> a -> Int
hashWithSalt Int
salt peer
a_p) (Int -> peer -> Int
forall a. Hashable a => Int -> a -> Int
hashWithSalt Int
salt peer
b_p)
else DiffTime -> DiffTime -> Ordering
forall a. Ord a => a -> a -> Ordering
compare DiffTime
gs_a DiffTime
gs_b
where
activeAdvantage :: DiffTime
activeAdvantage :: DiffTime
activeAdvantage = DiffTime
0.8
isActive :: peer -> Bool
isActive :: peer -> Bool
isActive peer
p = peer -> Set peer -> Bool
forall a. Ord a => a -> Set a -> Bool
Set.member peer
p Set peer
activePeers
gs :: PeerGSV -> DiffTime
gs :: PeerGSV -> DiffTime
gs PeerGSV { outboundGSV :: PeerGSV -> GSV
outboundGSV = GSV DiffTime
g_out SizeInBytes -> DiffTime
_s_out Distribution DiffTime
_v_out,
inboundGSV :: PeerGSV -> GSV
inboundGSV = GSV DiffTime
g_in SizeInBytes -> DiffTime
_s_in Distribution DiffTime
_v_in
} = DiffTime
g_out DiffTime -> DiffTime -> DiffTime
forall a. Num a => a -> a -> a
+ DiffTime
g_in
comparePeerGSV' :: forall peer.
( Hashable peer
, Ord peer
)
=> Int
-> (PeerGSV, peer)
-> (PeerGSV, peer)
-> Ordering
comparePeerGSV' :: Int -> (PeerGSV, peer) -> (PeerGSV, peer) -> Ordering
comparePeerGSV' = Set peer -> Int -> (PeerGSV, peer) -> (PeerGSV, peer) -> Ordering
forall peer.
(Hashable peer, Ord peer) =>
Set peer -> Int -> (PeerGSV, peer) -> (PeerGSV, peer) -> Ordering
comparePeerGSV Set peer
forall a. Set a
Set.empty
calculatePeerFetchInFlightLimits :: PeerGSV -> PeerFetchInFlightLimits
calculatePeerFetchInFlightLimits :: PeerGSV -> PeerFetchInFlightLimits
calculatePeerFetchInFlightLimits PeerGSV {
outboundGSV :: PeerGSV -> GSV
outboundGSV = GSV DiffTime
g_out SizeInBytes -> DiffTime
_s_out Distribution DiffTime
_v_out,
inboundGSV :: PeerGSV -> GSV
inboundGSV = GSV DiffTime
g_in SizeInBytes -> DiffTime
s_in Distribution DiffTime
_v_in
} =
PeerFetchInFlightLimits :: SizeInBytes -> SizeInBytes -> PeerFetchInFlightLimits
PeerFetchInFlightLimits {
SizeInBytes
inFlightBytesLowWatermark :: SizeInBytes
inFlightBytesLowWatermark :: SizeInBytes
inFlightBytesLowWatermark,
SizeInBytes
inFlightBytesHighWatermark :: SizeInBytes
inFlightBytesHighWatermark :: SizeInBytes
inFlightBytesHighWatermark
}
where
inFlightBytesLowWatermark :: SizeInBytes
inFlightBytesLowWatermark =
SizeInBytes -> SizeInBytes -> SizeInBytes
forall a. Ord a => a -> a -> a
max SizeInBytes
minLowWaterMark (Pico -> SizeInBytes
forall a b. (RealFrac a, Integral b) => a -> b
ceiling (DiffTime -> Pico
seconds (DiffTime
g_out DiffTime -> DiffTime -> DiffTime
forall a. Num a => a -> a -> a
+ DiffTime
g_in DiffTime -> DiffTime -> DiffTime
forall a. Num a => a -> a -> a
+ DiffTime
d) Pico -> Pico -> Pico
forall a. Fractional a => a -> a -> a
/ DiffTime -> Pico
seconds (SizeInBytes -> DiffTime
s_in SizeInBytes
1)))
where
minLowWaterMark :: SizeInBytes
minLowWaterMark :: SizeInBytes
minLowWaterMark = SizeInBytes
3 SizeInBytes -> SizeInBytes -> SizeInBytes
forall a. Num a => a -> a -> a
* SizeInBytes
64 SizeInBytes -> SizeInBytes -> SizeInBytes
forall a. Num a => a -> a -> a
* SizeInBytes
1024
seconds :: DiffTime -> Fixed.Pico
seconds :: DiffTime -> Pico
seconds = DiffTime -> Pico
forall a b. (Real a, Fractional b) => a -> b
realToFrac
d :: DiffTime
d = DiffTime
2e-2
inFlightBytesHighWatermark :: SizeInBytes
inFlightBytesHighWatermark = SizeInBytes
inFlightBytesLowWatermark SizeInBytes -> SizeInBytes -> SizeInBytes
forall a. Num a => a -> a -> a
* SizeInBytes
2
estimateResponseDeadlineProbability :: PeerGSV
-> SizeInBytes
-> SizeInBytes
-> DiffTime
-> Double
estimateResponseDeadlineProbability :: PeerGSV -> SizeInBytes -> SizeInBytes -> DiffTime -> Double
estimateResponseDeadlineProbability PeerGSV{GSV
outboundGSV :: GSV
outboundGSV :: PeerGSV -> GSV
outboundGSV, GSV
inboundGSV :: GSV
inboundGSV :: PeerGSV -> GSV
inboundGSV}
SizeInBytes
bytesInFlight SizeInBytes
bytesRequested DiffTime
deadline =
DiffTime -> DeltaQ -> Double
deltaqProbabilityMassBeforeDeadline DiffTime
deadline (DeltaQ -> Double) -> DeltaQ -> Double
forall a b. (a -> b) -> a -> b
$
GSV -> SizeInBytes -> DeltaQ
gsvTrailingEdgeArrive GSV
outboundGSV SizeInBytes
reqSize
DeltaQ -> DeltaQ -> DeltaQ
forall a. Semigroup a => a -> a -> a
<> GSV -> SizeInBytes -> DeltaQ
gsvTrailingEdgeArrive GSV
inboundGSV SizeInBytes
respSize
where
reqSize :: SizeInBytes
reqSize = SizeInBytes
100
respSize :: SizeInBytes
respSize = SizeInBytes
bytesInFlight SizeInBytes -> SizeInBytes -> SizeInBytes
forall a. Num a => a -> a -> a
+ SizeInBytes
bytesRequested
estimateExpectedResponseDuration :: PeerGSV
-> SizeInBytes
-> SizeInBytes
-> DiffTime
estimateExpectedResponseDuration :: PeerGSV -> SizeInBytes -> SizeInBytes -> DiffTime
estimateExpectedResponseDuration PeerGSV{GSV
outboundGSV :: GSV
outboundGSV :: PeerGSV -> GSV
outboundGSV, GSV
inboundGSV :: GSV
inboundGSV :: PeerGSV -> GSV
inboundGSV}
SizeInBytes
bytesInFlight SizeInBytes
bytesRequested =
DeltaQ -> DiffTime
deltaqQ50thPercentile (DeltaQ -> DiffTime) -> DeltaQ -> DiffTime
forall a b. (a -> b) -> a -> b
$
GSV -> SizeInBytes -> DeltaQ
gsvTrailingEdgeArrive GSV
outboundGSV SizeInBytes
reqSize
DeltaQ -> DeltaQ -> DeltaQ
forall a. Semigroup a => a -> a -> a
<> GSV -> SizeInBytes -> DeltaQ
gsvTrailingEdgeArrive GSV
inboundGSV SizeInBytes
respSize
where
reqSize :: SizeInBytes
reqSize = SizeInBytes
100
respSize :: SizeInBytes
respSize = SizeInBytes
bytesInFlight SizeInBytes -> SizeInBytes -> SizeInBytes
forall a. Num a => a -> a -> a
+ SizeInBytes
bytesRequested