module Data.Metrics.Histogram.Internal (
  Histogram,
  histogram,
  clear,
  update,
  mean,
  stddev,
  variance,
  minVal,
  maxVal,
  count,
  snapshot
) where
import Data.Time.Clock
import qualified Data.Metrics.Reservoir as R
import Data.Metrics.Snapshot (Snapshot)
data Histogram = Histogram
  { _histogramReservoir :: !R.Reservoir
  , _histogramCount :: !Int
  , _histogramMinVal :: !Double
  , _histogramMaxVal :: !Double
  , _histogramSum :: !Double
  , _histogramVariance :: !(Double, Double)
  }
histogram :: R.Reservoir -> Histogram
histogram r = Histogram r 0 nan nan 0 (0, 0)
nan :: Double
nan = 0 / 0
clear :: NominalDiffTime -> Histogram -> Histogram
clear = go
  where
    go t s = s
      { _histogramReservoir = R.clear t $ _histogramReservoir s
      , _histogramCount = 0
      , _histogramMinVal = nan
      , _histogramMaxVal = nan
      , _histogramSum = 0
      , _histogramVariance = (1, 0)
      }
update :: Double -> NominalDiffTime -> Histogram -> Histogram
update = go
  where
    go v t s = s
      { _histogramReservoir = updatedReservoir
      , _histogramCount = updatedCount
      , _histogramMinVal = updateMin (_histogramMinVal s) v
      , _histogramMaxVal = updateMax (_histogramMaxVal s) v
      , _histogramSum = _histogramSum s + v
      , _histogramVariance = updateVariance updatedCount v $ _histogramVariance s
      }
      where 
        updatedCount = succ $ _histogramCount s
        updatedReservoir = R.update v t $ _histogramReservoir s
updateMin :: Double -> Double -> Double
updateMin ox x = if isNaN ox || ox > x then x else ox
updateMax :: Double -> Double -> Double
updateMax ox x = if isNaN ox || ox < x then x else ox
mean :: Histogram -> Double
mean = go
  where
    go s = if _histogramCount s > 0
      then _histogramSum s / fromIntegral (_histogramCount s)
      else 0
stddev :: Histogram -> Double
stddev = go
  where
    go s = if c > 0
      then (calculateVariance c $ snd $ _histogramVariance s) ** 0.5
      else 0
      where c = _histogramCount s
variance :: Histogram -> Double
variance = go
  where
    go s = if c <= 1
      then 0
      else calculateVariance c $ snd $ _histogramVariance s
      where c = _histogramCount s
minVal :: Histogram -> Double
minVal = _histogramMinVal
maxVal :: Histogram -> Double
maxVal = _histogramMaxVal
count :: Histogram -> Int
count = _histogramCount
snapshot :: Histogram -> Snapshot
snapshot = R.snapshot . _histogramReservoir
calculateVariance :: Int -> Double -> Double
calculateVariance c v = if c <= 1 then 0 else v / (fromIntegral c  1)
updateVariance :: Int -> Double -> (Double, Double) -> (Double, Double)
updateVariance _ c (1, y) = (c, 0)
updateVariance count c (x, y) = (l, r)
  where
    c' = fromIntegral count
    diff = c  x
    l = x + diff / c'
    r = y + diff * (c  l)