-- This file is part of the Wire Server implementation.
--
-- Copyright (C) 2022 Wire Swiss GmbH <opensource@wire.com>
--
-- This program is free software: you can redistribute it and/or modify it under
-- the terms of the GNU Affero General Public License as published by the Free
-- Software Foundation, either version 3 of the License, or (at your option) any
-- later version.
--
-- This program is distributed in the hope that it will be useful, but WITHOUT
-- ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS
-- FOR A PARTICULAR PURPOSE. See the GNU Affero General Public License for more
-- details.
--
-- You should have received a copy of the GNU Affero General Public License along
-- with this program. If not, see <https://www.gnu.org/licenses/>.

module Data.Metrics.Middleware.Prometheus
  ( waiPrometheusMiddlewarePaths,
    normalizeWaiRequestRoute,
  )
where

import Data.Id
import Data.Metrics.Types (Paths, treeLookup)
import Data.Text.Encoding qualified as T
import Imports
import Network.Wai qualified as Wai
import Network.Wai.Middleware.Prometheus qualified as Promth

-- | Helper function that should only be needed as long as we have wai-routing code left in
-- proxy: run 'treeToPaths' on old routing tables and 'routeToPaths' on the servant ones, and
-- feed both to this function.
waiPrometheusMiddlewarePaths :: Paths -> Wai.Middleware
waiPrometheusMiddlewarePaths :: Paths -> Middleware
waiPrometheusMiddlewarePaths Paths
paths =
  PrometheusSettings -> Middleware
Promth.prometheus PrometheusSettings
conf Middleware -> Middleware -> Middleware
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Request -> Text) -> Middleware
instrument (Paths -> Request -> Text
normalizeWaiRequestRoute Paths
paths)
  where
    -- See Note [Raw Response]
    instrument :: (Request -> Text) -> Middleware
instrument = (Response -> Maybe Response) -> (Request -> Text) -> Middleware
Promth.instrumentHandlerValueWithFilter Response -> Maybe Response
Promth.ignoreRawResponses
    conf :: PrometheusSettings
conf =
      PrometheusSettings
forall a. Default a => a
Promth.def
        { Promth.prometheusEndPoint = ["i", "metrics"],
          -- We provide our own instrumentation so we can normalize routes
          Promth.prometheusInstrumentApp = False
        }

-- | Compute a normalized route for a given request.
-- Normalized routes have route parameters replaced with their identifier
-- e.g. @/user/1234@ might become @/user/userid@
normalizeWaiRequestRoute :: Paths -> Wai.Request -> Text
normalizeWaiRequestRoute :: Paths -> Request -> Text
normalizeWaiRequestRoute Paths
paths Request
req = Text
pathInfo
  where
    mPathInfo :: Maybe ByteString
    mPathInfo :: Maybe ByteString
mPathInfo = Paths -> [ByteString] -> Maybe ByteString
treeLookup Paths
paths (Text -> ByteString
T.encodeUtf8 (Text -> ByteString) -> [Text] -> [ByteString]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Request -> [Text]
Wai.pathInfo Request
req)
    -- Use the normalized path info if available; otherwise dump the raw path info for
    -- debugging purposes
    pathInfo :: Text
    pathInfo :: Text
pathInfo = ByteString -> Text
T.decodeUtf8 (ByteString -> Text) -> ByteString -> Text
forall a b. (a -> b) -> a -> b
$ ByteString -> Maybe ByteString -> ByteString
forall a. a -> Maybe a -> a
fromMaybe ByteString
forall s. IsString s => s
defRequestId Maybe ByteString
mPathInfo