@@ -4,7 +4,7 @@ Description : PostgREST Jwt Authentication Result Cache.
4
4
5
5
This module provides functions to deal with the JWT cache
6
6
-}
7
- {-# LANGUAGE NamedFieldPuns #-}
7
+ {-# LANGUAGE CPP #-}
8
8
module PostgREST.Auth.JwtCache
9
9
( init
10
10
, JwtCacheState
@@ -18,30 +18,50 @@ import qualified Data.Scientific as Sci
18
18
19
19
import Data.Time.Clock (UTCTime , nominalDiffTimeToSeconds )
20
20
import Data.Time.Clock.POSIX (utcTimeToPOSIXSeconds )
21
- import System.Clock (TimeSpec (.. ))
21
+ #ifdef JWT_CACHE_METRIC /* Include this in a non-profiled postgrest build */
22
+ import GHC.DataSize (recursiveSizeNF )
23
+ #endif
24
+ import System.Clock (TimeSpec (.. ))
22
25
23
- import PostgREST.Auth.Types (AuthResult (.. ))
24
- import PostgREST.Error (Error (.. ))
26
+ import PostgREST.Auth.Types (AuthResult (.. ))
27
+ import PostgREST.Error (Error (.. ))
28
+ import PostgREST.Observation (Observation (.. ), ObservationHandler )
25
29
30
+ import Control.Debounce
26
31
import Protolude
27
32
28
- newtype JwtCacheState = JwtCacheState
29
- { jwtCache :: C. Cache ByteString AuthResult
33
+ -- Jwt Cache State
34
+ --
35
+ -- Calculating the size of each cache entry is an expensive operation. We don't
36
+ -- want to recalculate the size of each entry after the cache eviction/purging.
37
+ --
38
+ -- To avoid this, we store the size of each cache entry with the value of the
39
+ -- cache entry as a tuple (AuthResult,SizeInBytes). Now after the purging
40
+ -- operation, the size of cache entry will be evicted along with the entry and
41
+ -- updating the cache size becomes a simple sum of all sizes that are store in
42
+ -- the cache
43
+ data JwtCacheState = JwtCacheState
44
+ -- | Jwt Cache
45
+ { jwtCache :: C. Cache ByteString (AuthResult ,SizeInBytes )
46
+ -- | Calculate cache size with debounce
47
+ , cacheSizeCalcDebounceTimeout :: MVar (IO () )
30
48
}
31
49
50
+ type SizeInBytes = Int
51
+
32
52
-- | Initialize JwtCacheState
33
53
init :: IO JwtCacheState
34
54
init = do
35
55
cache <- C. newCache Nothing -- no default expiration
36
- return $ JwtCacheState cache
56
+ JwtCacheState cache <$> newEmptyMVar
37
57
38
58
-- | Used to retrieve and insert JWT to JWT Cache
39
- lookupJwtCache :: JwtCacheState -> ByteString -> Int -> IO (Either Error AuthResult ) -> UTCTime -> IO (Either Error AuthResult )
40
- lookupJwtCache JwtCacheState {jwtCache} token maxLifetime parseJwt utc = do
41
- checkCache <- C. lookup jwtCache token
42
- authResult <- maybe parseJwt (pure . Right ) checkCache
59
+ lookupJwtCache :: JwtCacheState -> ByteString -> Int -> IO (Either Error AuthResult ) -> UTCTime -> ObservationHandler -> IO (Either Error AuthResult )
60
+ lookupJwtCache jwtCacheState token maxLifetime parseJwt utc observer = do
61
+ checkCache <- C. lookup ( jwtCache jwtCacheState) token
62
+ authResult <- maybe parseJwt (pure . Right . fst ) checkCache
43
63
44
- case (authResult,checkCache) of
64
+ case (authResult, checkCache) of
45
65
-- From comment:
46
66
-- https://github.com/PostgREST/postgrest/pull/3801#discussion_r1857987914
47
67
--
@@ -56,13 +76,20 @@ lookupJwtCache JwtCacheState{jwtCache} token maxLifetime parseJwt utc = do
56
76
57
77
(Right res, Nothing ) -> do -- cache miss
58
78
79
+ -- get expiration time
59
80
let timeSpec = getTimeSpec res maxLifetime utc
60
81
61
82
-- purge expired cache entries
62
- C. purgeExpired jwtCache
83
+ C. purgeExpired (jwtCache jwtCacheState)
84
+
85
+ -- calculate size of the cache entry to store it with authResult
86
+ sz <- calcCacheEntrySizeInBytes (token,res,timeSpec)
63
87
64
- -- insert new cache entry
65
- C. insert' jwtCache (Just timeSpec) token res
88
+ -- insert new cache entry with byte size
89
+ C. insert' (jwtCache jwtCacheState) (Just timeSpec) token (res,sz)
90
+
91
+ -- calculate complete cache size with debounce and log it
92
+ updateCacheSizeWithDebounce jwtCacheState observer
66
93
67
94
_ -> pure ()
68
95
@@ -77,3 +104,60 @@ getTimeSpec res maxLifetime utc = do
77
104
case expireJSON of
78
105
Just (JSON. Number seconds) -> TimeSpec (sciToInt seconds - utcToSecs utc) 0
79
106
_ -> TimeSpec (fromIntegral maxLifetime :: Int64 ) 0
107
+
108
+ -- | Update JwtCacheSize Metric
109
+ --
110
+ -- Runs the cache size calculation with debounce
111
+ updateCacheSizeWithDebounce :: JwtCacheState -> ObservationHandler -> IO ()
112
+ updateCacheSizeWithDebounce jwtCacheState observer = do
113
+ cSizeDebouncer <- tryReadMVar $ cacheSizeCalcDebounceTimeout jwtCacheState
114
+ case cSizeDebouncer of
115
+ Just d -> d
116
+ Nothing -> do
117
+ newDebouncer <-
118
+ mkDebounce defaultDebounceSettings
119
+ -- debounceFreq is set to default 1 second
120
+ { debounceAction = calculateSizeThenLog
121
+ , debounceEdge = leadingEdge -- logs at the start and the end
122
+ }
123
+ putMVar (cacheSizeCalcDebounceTimeout jwtCacheState) newDebouncer
124
+ newDebouncer
125
+ where
126
+ calculateSizeThenLog :: IO ()
127
+ calculateSizeThenLog = do
128
+ entries <- C. toList $ jwtCache jwtCacheState
129
+ -- extract the size from each entry and sum them all
130
+ let size = sum [ sz | (_,(_,sz),_) <- entries]
131
+ observer $ JwtCache size -- updates and logs the metric
132
+
133
+ -- | Calculate JWT Cache Size in Bytes
134
+ --
135
+ -- The cache size is updated by calculating the size of every
136
+ -- cache entry and updating the metric.
137
+ --
138
+ -- The cache entry consists of
139
+ -- key :: ByteString
140
+ -- value :: AuthReult
141
+ -- expire value :: TimeSpec
142
+ --
143
+ -- We calculate the size of each cache entry component
144
+ -- by using recursiveSizeNF function which first evaluates
145
+ -- the data structure to Normal Form and then calculate size.
146
+ -- The normal form evaluation is necessary for accurate size
147
+ -- calculation because haskell is lazy and we dont wanna count
148
+ -- the size of large thunks (unevaluated expressions)
149
+ calcCacheEntrySizeInBytes :: (ByteString , AuthResult , TimeSpec ) -> IO Int
150
+ #ifdef JWT_CACHE_METRIC /* Include this in a non-profiled postgrest build */
151
+ calcCacheEntrySizeInBytes entry = fromIntegral <$> getSize entry
152
+ where
153
+ getSize :: (ByteString , AuthResult , TimeSpec ) -> IO Word
154
+ getSize (bs, ar, ts) = do
155
+ keySize <- recursiveSizeNF bs
156
+ arClaimsSize <- recursiveSizeNF $ authClaims ar
157
+ arRoleSize <- recursiveSizeNF $ authRole ar
158
+ timeSpecSize <- liftA2 (+) (recursiveSizeNF (sec ts)) (recursiveSizeNF (nsec ts))
159
+ let sizeOfSizeEntryItself = 8 -- a constant 8 bytes size of each size entry in the cache
160
+ return (keySize + arClaimsSize + arRoleSize + timeSpecSize + sizeOfSizeEntryItself)
161
+ #else /* otherwise set it to 0 for a profiled build (used in memory-tests) */
162
+ calcCacheEntrySizeInBytes _ = return 0
163
+ #endif
0 commit comments