@@ -41,15 +41,17 @@ import Data.Either.Combinators (mapLeft)
4141import Data.List (lookup )
4242import Data.Time.Clock (UTCTime , nominalDiffTimeToSeconds )
4343import Data.Time.Clock.POSIX (utcTimeToPOSIXSeconds )
44+ import GHC.DataSize (recursiveSizeNF )
4445import System.Clock (TimeSpec (.. ))
4546import System.IO.Unsafe (unsafePerformIO )
4647import System.TimeIt (timeItT )
4748
48- import PostgREST.AppState (AppState , AuthResult (.. ), getConfig ,
49- getJwtCache , getTime )
50- import PostgREST.Config (AppConfig (.. ), FilterExp (.. ), JSPath ,
51- JSPathExp (.. ))
52- import PostgREST.Error (Error (.. ))
49+ import PostgREST.AppState (AppState , AuthResult (.. ), getConfig ,
50+ getJwtCache , getObserver , getTime )
51+ import PostgREST.Config (AppConfig (.. ), FilterExp (.. ), JSPath ,
52+ JSPathExp (.. ))
53+ import PostgREST.Error (Error (.. ))
54+ import PostgREST.Observation (Observation (.. ))
5355
5456import Protolude
5557
@@ -153,7 +155,7 @@ middleware appState app req respond = do
153155 let token = fromMaybe " " $ Wai. extractBearerAuth =<< lookup HTTP. hAuthorization (Wai. requestHeaders req)
154156 parseJwt = runExceptT $ parseToken conf token time >>= parseClaims conf
155157
156- -- If DbPlanEnabled -> calculate JWT validation time
158+ -- If ServerTimingEnabled -> calculate JWT validation time
157159-- If JwtCacheMaxLifetime -> cache JWT validation result
158160 req' <- case (configServerTimingEnabled conf, configJwtCacheMaxLifetime conf) of
159161 (True , 0 ) -> do
@@ -177,14 +179,24 @@ middleware appState app req respond = do
177179-- | Used to retrieve and insert JWT to JWT Cache
178180getJWTFromCache :: AppState -> ByteString -> Int -> IO (Either Error AuthResult ) -> UTCTime -> IO (Either Error AuthResult )
179181getJWTFromCache appState token maxLifetime parseJwt utc = do
180- checkCache <- C. lookup (getJwtCache appState) token
182+
183+ checkCache <- C. lookup jwtCache token
181184 authResult <- maybe parseJwt (pure . Right ) checkCache
182185
186+ -- if token not found, add to cache and increment cache size metric
183187 case (authResult,checkCache) of
184- (Right res, Nothing ) -> C. insert' (getJwtCache appState) (getTimeSpec res maxLifetime utc) token res
188+ (Right res, Nothing ) -> do
189+ let tSpec = getTimeSpec res maxLifetime utc
190+ C. insert' jwtCache tSpec token res
191+ entrySize <- calcCacheEntrySizeInBytes (token, res, tSpec) -- adds to cache
192+ observer $ JWTCache entrySize
193+
185194 _ -> pure ()
186195
187196 return authResult
197+ where
198+ observer = getObserver appState
199+ jwtCache = getJwtCache appState
188200
189201-- Used to extract JWT exp claim and add to JWT Cache
190202getTimeSpec :: AuthResult -> Int -> UTCTime -> Maybe TimeSpec
@@ -196,6 +208,23 @@ getTimeSpec res maxLifetime utc = do
196208 Just (JSON. Number seconds) -> Just $ TimeSpec (sciToInt seconds - utcToSecs utc) 0
197209 _ -> Just $ TimeSpec (fromIntegral maxLifetime :: Int64 ) 0
198210
211+ -- | Calculate a single entry of JWT Cache Size in Bytes
212+ calcCacheEntrySizeInBytes :: (ByteString ,AuthResult ,Maybe TimeSpec ) -> IO Int
213+ calcCacheEntrySizeInBytes entry = do
214+ sz <- getSize entry
215+ return $ fromIntegral sz
216+ where
217+ getSize :: (ByteString , AuthResult ,Maybe TimeSpec ) -> IO Word
218+ getSize (bs, ar, ts) = do
219+ keySize <- recursiveSizeNF bs
220+ arClaimsSize <- recursiveSizeNF $ authClaims ar
221+ arRoleSize <- recursiveSizeNF $ authRole ar
222+ timeSpecSize <- case ts of
223+ Just TimeSpec {.. } -> liftA2 (+) (recursiveSizeNF sec) (recursiveSizeNF nsec)
224+ Nothing -> pure 0
225+
226+ return (keySize + arClaimsSize + arRoleSize + timeSpecSize)
227+
199228authResultKey :: Vault. Key (Either Error AuthResult )
200229authResultKey = unsafePerformIO Vault. newKey
201230{-# NOINLINE authResultKey #-}
0 commit comments