Skip to content

Commit

Permalink
feat(sut): add metrics app that displays service time in real-time
Browse files Browse the repository at this point in the history
  • Loading branch information
symbiont-stevan-andjelkovic committed Mar 10, 2022
1 parent ef2b6c3 commit d8c776e
Show file tree
Hide file tree
Showing 5 changed files with 64 additions and 4 deletions.
10 changes: 8 additions & 2 deletions src/journal/src/Journal/Internal/Metrics.hs
Original file line number Diff line number Diff line change
Expand Up @@ -130,8 +130,8 @@ percentile (Metrics _ hbuf) label p
then return Nothing
else do
let d = realToFrac count * (p * 0.01)
let target :: Double
target | d == 0.0 = 1.0
target :: Double
target | d == 0.0 = 1.0
| otherwise = d
go offsetBucket target
where
Expand All @@ -150,6 +150,12 @@ percentile (Metrics _ hbuf) label p
then return (Just (decompress idx))
else go' (succ idx) sum'

count :: Enum h => Metrics c h -> h -> IO Int
count (Metrics _cbuf hbuf) label = do
let offsetHistogram = sizeOfAHistogram * fromEnum label
offsetHistogramCount = offsetHistogram + sizeOf (8 :: Int)
readIntOffArrayIx hbuf offsetHistogramCount

-- * Example

data MyMetricsCounter = Connections
Expand Down
8 changes: 8 additions & 0 deletions src/sut/dumblog/app/metrics/Main.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,8 @@
module Main where

import Dumblog.Metrics.Main

------------------------------------------------------------------------

main :: IO ()
main = metricsMain
6 changes: 6 additions & 0 deletions src/sut/dumblog/dumblog.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -77,6 +77,7 @@ library
Dumblog.ZeroCopy.HttpServer
Dumblog.ZeroCopy.Main
Dumblog.ZeroCopy.State
Dumblog.Metrics.Main
if flag(persistent-sqlite)
exposed-modules: Dumblog.SQLite.DBPersistent

Expand Down Expand Up @@ -112,6 +113,11 @@ executable dumblog-zero-copy
hs-source-dirs: app/zero-copy
main-is: Main.hs

executable metrics
import: executable-common
hs-source-dirs: app/metrics
main-is: Main.hs

common bench-common
hs-source-dirs: bench
build-depends:
Expand Down
6 changes: 4 additions & 2 deletions src/sut/dumblog/src/Dumblog/Journal/Worker.hs
Original file line number Diff line number Diff line change
Expand Up @@ -33,8 +33,10 @@ timeIt metrics action = do
!startTime <- getCurrentTime
result <- action
!endTime <- getCurrentTime
-- dunno what timescale we are measuring
Metrics.measure metrics ServiceTime (realToFrac . (*1000) $ diffUTCTime endTime startTime)
Metrics.measure metrics ServiceTime
-- `diffUTCTime` has a precision of 10^-12 s, so after multiplying with 10^9
-- we get milliseconds.
(realToFrac (diffUTCTime endTime startTime * 1e9))
return result

wakeUpFrontend :: Blocker (Either Response Response) -> Int -> Either Response Response
Expand Down
38 changes: 38 additions & 0 deletions src/sut/dumblog/src/Dumblog/Metrics/Main.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,38 @@
{-# LANGUAGE NumericUnderscores #-}

module Dumblog.Metrics.Main where

import Control.Monad (forever)
import Control.Concurrent (threadDelay)
import Text.Printf (printf)

import Dumblog.Journal.Metrics
import Journal.Internal.Metrics

------------------------------------------------------------------------

metricsMain :: IO ()
metricsMain = forever $ do
metrics <- newMetrics dumblogSchema "/tmp/dumblog.metrics"
putStrLn ansiClearScreen
mMin <- percentile metrics ServiceTime 0
mMed <- percentile metrics ServiceTime 50
m90 <- percentile metrics ServiceTime 90
m99 <- percentile metrics ServiceTime 99
m999 <- percentile metrics ServiceTime 99.9
m9999 <- percentile metrics ServiceTime 99.99
mMax <- percentile metrics ServiceTime 100
putStrLn "Service time:"
putStrLn (maybe "N/A" (printf " min %10.2f ms") mMin)
putStrLn (maybe "N/A" (printf " med %10.2f ms") mMed)
putStrLn (maybe "N/A" (printf " 90 %10.2f ms") m90)
putStrLn (maybe "N/A" (printf " 99 %10.2f ms") m99)
putStrLn (maybe "N/A" (printf " 99.9 %10.2f ms") m999)
putStrLn (maybe "N/A" (printf " 99.99 %10.2f ms") m9999)
putStrLn (maybe "N/A" (printf " max %10.2f ms") mMax)
cnt <- count metrics ServiceTime
putStrLn (printf " count %10d" cnt)
threadDelay 1_000_000

ansiClearScreen :: String
ansiClearScreen = "\ESC[2J"

0 comments on commit d8c776e

Please sign in to comment.