diff --git a/src/PostgREST/Metrics.hs b/src/PostgREST/Metrics.hs index cbf56e03b2..d22dcf0e50 100644 --- a/src/PostgREST/Metrics.hs +++ b/src/PostgREST/Metrics.hs @@ -1,5 +1,4 @@ -{-# LANGUAGE NamedFieldPuns #-} -{-# LANGUAGE NumericUnderscores #-} +{-# LANGUAGE NamedFieldPuns #-} module PostgREST.Metrics ( init , MetricsState (..) @@ -21,6 +20,8 @@ data MetricsState = MetricsState , poolAvailable :: Prom.Gauge , poolWaiting :: Prom.Gauge , poolMaxSize :: Prom.Gauge + , schemaCacheLoads :: Prom.Counter + , schemaCacheQueryTime :: Prom.Gauge } init :: Int -> IO MetricsState @@ -29,11 +30,13 @@ init poolMaxSize = do available <- Prom.register $ Prom.gauge (Prom.Info "pgrst_db_pool_available" "Available connections in the pool") waiting <- Prom.register $ Prom.gauge (Prom.Info "pgrst_db_pool_waiting" "Requests waiting to acquire a pool connection") maxSize <- Prom.register $ Prom.gauge (Prom.Info "pgrst_db_pool_max" "Max pool connections") + sCacheLoads <- Prom.register $ Prom.counter (Prom.Info "pgrst_schema_cache_loads_total" "The total number of times the schema cache was loaded") + sCacheQTime <- Prom.register $ Prom.gauge (Prom.Info "pgrst_schema_cache_query_time_seconds" "The query time in seconds of the last schema cache load") Prom.setGauge maxSize (fromIntegral poolMaxSize) - pure $ MetricsState timeouts available waiting maxSize + pure $ MetricsState timeouts available waiting maxSize sCacheLoads sCacheQTime observationMetrics :: MetricsState -> ObservationHandler -observationMetrics MetricsState{poolTimeouts, poolAvailable, poolWaiting} obs = case obs of +observationMetrics MetricsState{poolTimeouts, poolAvailable, poolWaiting, schemaCacheLoads, schemaCacheQueryTime} obs = case obs of (PoolAcqTimeoutObs _) -> do Prom.incCounter poolTimeouts (HasqlPoolObs (SQL.ConnectionObservation _ status)) -> case status of @@ -48,6 +51,9 @@ observationMetrics MetricsState{poolTimeouts, poolAvailable, poolWaiting} obs = Prom.incGauge poolWaiting PoolRequestFullfilled -> Prom.decGauge poolWaiting + SchemaCacheLoadedObs resTime -> do + Prom.incCounter schemaCacheLoads + Prom.setGauge schemaCacheQueryTime resTime _ -> pure ()