{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE StandaloneDeriving #-}
module Ouroboros.Network.DeltaQ
(
DeltaQ (..)
, deltaqQ99thPercentile
, deltaqQ50thPercentile
, deltaqProbabilityMassBeforeDeadline
, GSV (..)
, SizeInBytes (..)
, ballisticGSV
, gsvLeadingEdgeArrive
, gsvTrailingEdgeDepart
, gsvTrailingEdgeArrive
, Distribution
, degenerateDistribution
, PeerGSV (..)
, gsvRequestResponseDuration
, defaultGSV
, fromSample
) where
import Control.Monad.Class.MonadTime.SI (DiffTime, Time (..), diffTime)
import Ouroboros.Network.SizeInBytes (SizeInBytes (..))
newtype DeltaQ = DeltaQ (Distribution DiffTime)
deriving instance Semigroup DeltaQ
deltaqQ99thPercentile :: DeltaQ -> DiffTime
deltaqQ99thPercentile :: DeltaQ -> DiffTime
deltaqQ99thPercentile (DeltaQ (DegenerateDistribution DiffTime
t)) = DiffTime
t
deltaqQ50thPercentile :: DeltaQ -> DiffTime
deltaqQ50thPercentile :: DeltaQ -> DiffTime
deltaqQ50thPercentile (DeltaQ (DegenerateDistribution DiffTime
t)) = DiffTime
t
deltaqProbabilityMassBeforeDeadline :: DiffTime
-> DeltaQ
-> Double
deltaqProbabilityMassBeforeDeadline :: DiffTime -> DeltaQ -> Double
deltaqProbabilityMassBeforeDeadline DiffTime
deadline (DeltaQ (DegenerateDistribution DiffTime
t))
| DiffTime
t DiffTime -> DiffTime -> Bool
forall a. Ord a => a -> a -> Bool
< DiffTime
deadline = Double
1
| Bool
otherwise = Double
0
data Distribution n = DegenerateDistribution n
instance Num n => Semigroup (Distribution n) where
<> :: Distribution n -> Distribution n -> Distribution n
(<>) = Distribution n -> Distribution n -> Distribution n
forall n.
Num n =>
Distribution n -> Distribution n -> Distribution n
convolveDistribution
degenerateDistribution :: n -> Distribution n
degenerateDistribution :: forall n. n -> Distribution n
degenerateDistribution = n -> Distribution n
forall n. n -> Distribution n
DegenerateDistribution
convolveDistribution :: Num n
=> Distribution n -> Distribution n -> Distribution n
convolveDistribution :: forall n.
Num n =>
Distribution n -> Distribution n -> Distribution n
convolveDistribution (DegenerateDistribution n
d)
(DegenerateDistribution n
d') =
n -> Distribution n
forall n. n -> Distribution n
DegenerateDistribution (n
dn -> n -> n
forall a. Num a => a -> a -> a
+n
d')
shiftDistribution :: Num n => n -> Distribution n -> Distribution n
shiftDistribution :: forall n. Num n => n -> Distribution n -> Distribution n
shiftDistribution n
n (DegenerateDistribution n
d) = n -> Distribution n
forall n. n -> Distribution n
DegenerateDistribution (n
nn -> n -> n
forall a. Num a => a -> a -> a
+n
d)
data GSV = GSV !DiffTime
!(SizeInBytes -> DiffTime)
!(Distribution DiffTime)
instance Semigroup GSV where
GSV DiffTime
g1 SizeInBytes -> DiffTime
s1 Distribution DiffTime
v1 <> :: GSV -> GSV -> GSV
<> GSV DiffTime
g2 SizeInBytes -> DiffTime
s2 Distribution DiffTime
v2 = DiffTime
-> (SizeInBytes -> DiffTime) -> Distribution DiffTime -> GSV
GSV (DiffTime
g1DiffTime -> DiffTime -> DiffTime
forall a. Num a => a -> a -> a
+DiffTime
g2) (\SizeInBytes
sz -> SizeInBytes -> DiffTime
s1 SizeInBytes
sz DiffTime -> DiffTime -> DiffTime
forall a. Num a => a -> a -> a
+ SizeInBytes -> DiffTime
s2 SizeInBytes
sz) (Distribution DiffTime
v1 Distribution DiffTime
-> Distribution DiffTime -> Distribution DiffTime
forall a. Semigroup a => a -> a -> a
<> Distribution DiffTime
v2)
instance Show GSV where
show :: GSV -> String
show (GSV DiffTime
g SizeInBytes -> DiffTime
s (DegenerateDistribution DiffTime
v)) =
String
"GSV g " String -> ShowS
forall a. [a] -> [a] -> [a]
++ DiffTime -> String
forall a. Show a => a -> String
show DiffTime
g String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" s " String -> ShowS
forall a. [a] -> [a] -> [a]
++ DiffTime -> String
forall a. Show a => a -> String
show (SizeInBytes -> DiffTime
s SizeInBytes
1) String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" v " String -> ShowS
forall a. [a] -> [a] -> [a]
++ DiffTime -> String
forall a. Show a => a -> String
show DiffTime
v
ballisticGSV :: DiffTime
-> DiffTime
-> Distribution DiffTime
-> GSV
ballisticGSV :: DiffTime -> DiffTime -> Distribution DiffTime -> GSV
ballisticGSV DiffTime
g DiffTime
s Distribution DiffTime
v = DiffTime
-> (SizeInBytes -> DiffTime) -> Distribution DiffTime -> GSV
GSV DiffTime
g (\SizeInBytes
sz -> DiffTime
s DiffTime -> DiffTime -> DiffTime
forall a. Num a => a -> a -> a
* SizeInBytes -> DiffTime
forall a b. (Integral a, Num b) => a -> b
fromIntegral SizeInBytes
sz) Distribution DiffTime
v
gsvLeadingEdgeArrive :: GSV -> DeltaQ
gsvTrailingEdgeDepart :: GSV -> SizeInBytes -> DeltaQ
gsvTrailingEdgeArrive :: GSV -> SizeInBytes -> DeltaQ
gsvLeadingEdgeArrive :: GSV -> DeltaQ
gsvLeadingEdgeArrive (GSV DiffTime
g SizeInBytes -> DiffTime
_s Distribution DiffTime
v) =
Distribution DiffTime -> DeltaQ
DeltaQ (DiffTime -> Distribution DiffTime -> Distribution DiffTime
forall n. Num n => n -> Distribution n -> Distribution n
shiftDistribution DiffTime
g Distribution DiffTime
v)
gsvTrailingEdgeDepart :: GSV -> SizeInBytes -> DeltaQ
gsvTrailingEdgeDepart (GSV DiffTime
_g SizeInBytes -> DiffTime
s Distribution DiffTime
v) SizeInBytes
bytes =
Distribution DiffTime -> DeltaQ
DeltaQ (DiffTime -> Distribution DiffTime -> Distribution DiffTime
forall n. Num n => n -> Distribution n -> Distribution n
shiftDistribution (SizeInBytes -> DiffTime
s SizeInBytes
bytes) Distribution DiffTime
v)
gsvTrailingEdgeArrive :: GSV -> SizeInBytes -> DeltaQ
gsvTrailingEdgeArrive (GSV DiffTime
g SizeInBytes -> DiffTime
s Distribution DiffTime
v) SizeInBytes
bytes =
Distribution DiffTime -> DeltaQ
DeltaQ (DiffTime -> Distribution DiffTime -> Distribution DiffTime
forall n. Num n => n -> Distribution n -> Distribution n
shiftDistribution (DiffTime
g DiffTime -> DiffTime -> DiffTime
forall a. Num a => a -> a -> a
+ SizeInBytes -> DiffTime
s SizeInBytes
bytes) Distribution DiffTime
v)
data PeerGSV = PeerGSV {
PeerGSV -> Time
sampleTime :: !Time,
PeerGSV -> GSV
outboundGSV :: !GSV,
PeerGSV -> GSV
inboundGSV :: !GSV
}
deriving Int -> PeerGSV -> ShowS
[PeerGSV] -> ShowS
PeerGSV -> String
(Int -> PeerGSV -> ShowS)
-> (PeerGSV -> String) -> ([PeerGSV] -> ShowS) -> Show PeerGSV
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PeerGSV -> ShowS
showsPrec :: Int -> PeerGSV -> ShowS
$cshow :: PeerGSV -> String
show :: PeerGSV -> String
$cshowList :: [PeerGSV] -> ShowS
showList :: [PeerGSV] -> ShowS
Show
instance Semigroup PeerGSV where
<> :: PeerGSV -> PeerGSV -> PeerGSV
(<>) PeerGSV
a PeerGSV
b = let timeConstant :: DiffTime
timeConstant = DiffTime
1000 :: DiffTime
sampleInterval :: DiffTime
sampleInterval = PeerGSV -> Time
sampleTime PeerGSV
a Time -> Time -> DiffTime
`diffTime` PeerGSV -> Time
sampleTime PeerGSV
b
alpha :: DiffTime
alpha = (DiffTime
sampleInterval DiffTime -> DiffTime -> DiffTime
forall a. Fractional a => a -> a -> a
/ DiffTime
timeConstant) DiffTime -> DiffTime -> DiffTime
forall a. Ord a => a -> a -> a
`min` DiffTime
1
updateG :: GSV -> GSV -> GSV
updateG (GSV DiffTime
g1 SizeInBytes -> DiffTime
s Distribution DiffTime
v) (GSV DiffTime
g0 SizeInBytes -> DiffTime
_ Distribution DiffTime
_)
= DiffTime
-> (SizeInBytes -> DiffTime) -> Distribution DiffTime -> GSV
GSV (DiffTime
g0 DiffTime -> DiffTime -> DiffTime
forall a. Num a => a -> a -> a
+ DiffTime
alpha DiffTime -> DiffTime -> DiffTime
forall a. Num a => a -> a -> a
* (DiffTime
g1 DiffTime -> DiffTime -> DiffTime
forall a. Num a => a -> a -> a
- DiffTime
g0)) SizeInBytes -> DiffTime
s Distribution DiffTime
v
in PeerGSV { sampleTime :: Time
sampleTime = PeerGSV -> Time
sampleTime PeerGSV
a
, outboundGSV :: GSV
outboundGSV = GSV -> GSV -> GSV
updateG (PeerGSV -> GSV
outboundGSV PeerGSV
a) (PeerGSV -> GSV
outboundGSV PeerGSV
b)
, inboundGSV :: GSV
inboundGSV = GSV -> GSV -> GSV
updateG (PeerGSV -> GSV
inboundGSV PeerGSV
a) (PeerGSV -> GSV
inboundGSV PeerGSV
b)
}
gsvRequestResponseDuration :: PeerGSV
-> SizeInBytes
-> SizeInBytes
-> DiffTime
gsvRequestResponseDuration :: PeerGSV -> SizeInBytes -> SizeInBytes -> DiffTime
gsvRequestResponseDuration PeerGSV{GSV
outboundGSV :: PeerGSV -> GSV
outboundGSV :: GSV
outboundGSV, GSV
inboundGSV :: PeerGSV -> GSV
inboundGSV :: GSV
inboundGSV}
SizeInBytes
reqSize SizeInBytes
respSize =
DeltaQ -> DiffTime
deltaqQ99thPercentile (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
defaultGSV :: PeerGSV
defaultGSV :: PeerGSV
defaultGSV = PeerGSV {Time
sampleTime :: Time
sampleTime :: Time
sampleTime, GSV
outboundGSV :: GSV
outboundGSV :: GSV
outboundGSV, GSV
inboundGSV :: GSV
inboundGSV :: GSV
inboundGSV }
where
default_g :: DiffTime
default_g = DiffTime
500e-3
default_s :: DiffTime
default_s = DiffTime
2e-6
inboundGSV :: GSV
inboundGSV = DiffTime -> DiffTime -> Distribution DiffTime -> GSV
ballisticGSV DiffTime
default_g DiffTime
default_s (DiffTime -> Distribution DiffTime
forall n. n -> Distribution n
degenerateDistribution DiffTime
0)
outboundGSV :: GSV
outboundGSV = GSV
inboundGSV
sampleTime :: Time
sampleTime = DiffTime -> Time
Time DiffTime
0
fromSample :: Time -> Time -> SizeInBytes -> PeerGSV
fromSample :: Time -> Time -> SizeInBytes -> PeerGSV
fromSample t :: Time
t@(Time DiffTime
start) (Time DiffTime
end) SizeInBytes
_size =
PeerGSV {Time
sampleTime :: Time
sampleTime :: Time
sampleTime, GSV
outboundGSV :: GSV
outboundGSV :: GSV
outboundGSV, GSV
inboundGSV :: GSV
inboundGSV :: GSV
inboundGSV }
where
g :: DiffTime
g = (DiffTime
end DiffTime -> DiffTime -> DiffTime
forall a. Num a => a -> a -> a
- DiffTime
start) DiffTime -> DiffTime -> DiffTime
forall a. Fractional a => a -> a -> a
/ DiffTime
2
sampleTime :: Time
sampleTime = Time
t
inboundGSV :: GSV
inboundGSV = DiffTime -> DiffTime -> Distribution DiffTime -> GSV
ballisticGSV DiffTime
g DiffTime
2e-6 (DiffTime -> Distribution DiffTime
forall n. n -> Distribution n
degenerateDistribution DiffTime
0)
outboundGSV :: GSV
outboundGSV = GSV
inboundGSV