Skip to content

Commit

Permalink
Initial EWMA approximation to ∆Q
Browse files Browse the repository at this point in the history
  • Loading branch information
Neil Davies authored and karknu committed Jul 1, 2020
1 parent 44ed488 commit 0881c42
Showing 1 changed file with 42 additions and 5 deletions.
47 changes: 42 additions & 5 deletions ouroboros-network/src/Ouroboros/Network/DeltaQ.hs
Expand Up @@ -36,7 +36,7 @@ module Ouroboros.Network.DeltaQ (
fromSample
) where

import Control.Monad.Class.MonadTime (Time (..))
import Control.Monad.Class.MonadTime (Time (..), diffTime)
import Control.Monad.Class.MonadTimer (microsecondsAsIntToDiffTime)
import Data.Semigroup ((<>))
import Data.Time.Clock (DiffTime)
Expand Down Expand Up @@ -243,13 +243,48 @@ gsvTrailingEdgeArrive (GSV g s v) bytes =
-- | The 'GSV' for both directions with a peer, outbound and inbound.
--
data PeerGSV = PeerGSV {
sampleTime :: !Time,
outboundGSV :: !GSV,
inboundGSV :: !GSV
}
deriving Show

-- | The current tracking model is based on an EWMA
-- (https://en.wikipedia.org/wiki/Moving_average#Exponential_moving_average).
-- Typically implementations of EWMA assume a regular update, but EWMA is based
-- on Exponential Smoothing
-- (https://en.wikipedia.org/wiki/Exponential_smoothing). Such smoothing has a
-- time constant, which captures the time for a unit impulse to decay to 1 -
-- 1/e (~ 63.2%), the &#x1D6FC (smoothing factor) is a function of relative
-- frequency of the sample interval and this time constant.
--
-- The approach being taken here is one that does not assume a fixed sample
-- interval (and hence a fixed &#x1D6FC), instead we calculate, given the
-- interval from when the last sample was taken, the &#x1D6FC needed to ensure
-- that the old value has sufficiently decayed.
--
-- The exact calcuation involves exponentiation, however where the number of
-- samples within the time constant is sufficiently large a simple ratio of the
-- sample's interval over the time constant will suffice. The relative error of
-- this numerical approximation is, for our use case, small. Eg 1/50 (20s
-- between samples with a 1000s time constant) has a relative error of 1%. The
-- expected typical range of this relative error is between 5% (ratio of 1/10),
-- to 0.5% (1/100).
--
-- Given the inherent measurement noise in this measurement, the use of the
-- approximation is well justified. We choose (reaonably aribtarily) 1000s as
-- the time constant, it is unclear if this should be a configuration variable
-- or not.
instance Semigroup PeerGSV where
(<>) _ a = a -- TODO add propper EWMA based implementation
(<>) a b = let timeConstant = 1000 :: DiffTime
sampleInterval = (sampleTime b) `diffTime` (sampleTime a)
alpha = (sampleInterval / timeConstant) `min` 1
updateG (GSV g0 s v) (GSV g1 _ _)
= GSV (g0 + alpha * (g1 - g0)) s v
in PeerGSV { sampleTime = sampleTime b
, outboundGSV = updateG (outboundGSV a) (outboundGSV b)
, inboundGSV = updateG (inboundGSV a) (inboundGSV b)
}

-- | This is an example derived operation using the other 'GSV' and 'DeltaQ'
-- primitives.
Expand Down Expand Up @@ -283,23 +318,25 @@ gsvRequestResponseDuration PeerGSV{outboundGSV, inboundGSV}


defaultGSV :: PeerGSV
defaultGSV = PeerGSV { outboundGSV, inboundGSV }
defaultGSV = PeerGSV {sampleTime, outboundGSV, inboundGSV }
where
default_g = maxG -- start with an unreasonable large G.
default_s = 2e-6 -- 4Mbps.
inboundGSV = ballisticGSV default_g default_s (degenerateDistribution 0)
outboundGSV = inboundGSV
sampleTime = Time 0

maxG :: DiffTime
maxG = microsecondsAsIntToDiffTime maxBound / 4
--maxG = 500e-3 -- not unreasonable but old default value

fromSample :: Time -> Time -> SizeInBytes -> PeerGSV
fromSample (Time start) (Time end) _size =
PeerGSV { outboundGSV, inboundGSV }
fromSample t@(Time start) (Time end) _size =
PeerGSV {sampleTime, outboundGSV, inboundGSV }
where
g = (end - start) / 2

sampleTime = t
inboundGSV = ballisticGSV g 2e-6 (degenerateDistribution 0)
outboundGSV = inboundGSV

0 comments on commit 0881c42

Please sign in to comment.