Skip to content

Commit ea4b9f1

Browse files
committed
feat: Make jwt-aud config value a regular expression
1 parent 66a8d04 commit ea4b9f1

File tree

8 files changed

+84
-75
lines changed

8 files changed

+84
-75
lines changed

src/PostgREST/Auth/Jwt.hs

Lines changed: 24 additions & 20 deletions
Original file line numberDiff line numberDiff line change
@@ -35,14 +35,15 @@ import Data.Time.Clock.POSIX (utcTimeToPOSIXSeconds)
3535

3636
import PostgREST.Auth.Types (AuthResult (..))
3737
import PostgREST.Config (AppConfig (..), FilterExp (..), JSPath,
38-
JSPathExp (..))
38+
JSPathExp (..), audMatchesCfg)
3939
import PostgREST.Error (Error (..),
40-
JwtClaimsError (AudClaimNotStringOrArray, ExpClaimNotNumber, IatClaimNotNumber, JWTExpired, JWTIssuedAtFuture, JWTNotInAudience, JWTNotYetValid, NbfClaimNotNumber, ParsingClaimsFailed),
40+
JwtClaimsError (AudClaimNotStringOrURIOrArray, ExpClaimNotNumber, IatClaimNotNumber, JWTExpired, JWTIssuedAtFuture, JWTNotInAudience, JWTNotYetValid, NbfClaimNotNumber, ParsingClaimsFailed),
4141
JwtDecodeError (..), JwtError (..))
4242

4343
import Data.Aeson ((.:?))
4444
import Data.Aeson.Types (parseMaybe)
4545
import Jose.Jwk (JwkSet)
46+
import Network.URI (isURI)
4647
import Protolude hiding (first)
4748

4849
parseAndDecodeClaims :: (MonadError Error m, MonadIO m) => JwkSet -> ByteString -> m JSON.Object
@@ -52,22 +53,26 @@ decodeClaims :: MonadError Error m => JWT.JwtContent -> m JSON.Object
5253
decodeClaims (JWT.Jws (_, claims)) = maybe (throwError (JwtErr $ JwtClaimsErr ParsingClaimsFailed)) pure (JSON.decodeStrict claims)
5354
decodeClaims _ = throwError $ JwtErr $ JwtDecodeErr UnsupportedTokenType
5455

55-
validateClaims :: MonadError Error m => UTCTime -> Maybe Text -> JSON.Object -> m ()
56-
validateClaims time getConfigAud claims = liftEither $ maybeToLeft () (fmap JwtErr . getAlt $ JwtClaimsErr <$> checkForErrors time getConfigAud claims)
56+
validateClaims :: MonadError Error m => UTCTime -> (Text -> Bool) -> JSON.Object -> m ()
57+
validateClaims time audMatches claims = liftEither $ maybeToLeft () (fmap JwtErr . getAlt $ JwtClaimsErr <$> checkForErrors time audMatches claims)
5758

58-
data ValidAud = VANull | VAString Text | VAArray [Text] deriving Generic
59+
newtype StringOrURI = StringOrURI { unStringOrURI :: Text }
60+
instance JSON.FromJSON StringOrURI where
61+
parseJSON = fmap StringOrURI . mfilter isValidURI . JSON.parseJSON
62+
where
63+
isValidURI = (||) <$> not . T.isInfixOf ":" <*> isURI . T.unpack
64+
65+
data ValidAud = VANull | VAString StringOrURI | VAArray [StringOrURI] deriving Generic
5966
instance JSON.FromJSON ValidAud where
6067
parseJSON JSON.Null = pure VANull
6168
parseJSON o = JSON.genericParseJSON JSON.defaultOptions { JSON.sumEncoding = JSON.UntaggedValue } o
6269

63-
checkForErrors :: (Monad m, forall a. Monoid (m a)) => UTCTime -> Maybe Text -> JSON.Object -> m JwtClaimsError
64-
checkForErrors time cfgAud = mconcat
65-
[
66-
claim "exp" ExpClaimNotNumber $ inThePast JWTExpired
67-
, claim "nbf" NbfClaimNotNumber $ inTheFuture JWTNotYetValid
68-
, claim "iat" IatClaimNotNumber $ inTheFuture JWTIssuedAtFuture
69-
, claim "aud" AudClaimNotStringOrArray checkAud
70-
]
70+
checkForErrors :: (Applicative m, Monoid (m JwtClaimsError)) => UTCTime -> (Text -> Bool) -> JSON.Object -> m JwtClaimsError
71+
checkForErrors time audMatches =
72+
claim "exp" ExpClaimNotNumber (inThePast JWTExpired)
73+
<> claim "nbf" NbfClaimNotNumber (inTheFuture JWTNotYetValid)
74+
<> claim "iat" IatClaimNotNumber (inTheFuture JWTIssuedAtFuture)
75+
<> claim "aud" AudClaimNotStringOrURIOrArray (checkValue (not . validAud) JWTNotInAudience)
7176
where
7277
allowedSkewSeconds = 30 :: Int64
7378
sciToInt = fromMaybe 0 . Sci.toBoundedInteger
@@ -79,12 +84,11 @@ checkForErrors time cfgAud = mconcat
7984

8085
checkTime cond = checkValue (cond. sciToInt)
8186

82-
checkAud = \case
83-
(VAString aud) -> liftMaybe cfgAud >>= checkValue (aud /=) JWTNotInAudience
84-
(VAArray auds) | (not . null) auds -> liftMaybe cfgAud >>= checkValue (not . (`elem` auds)) JWTNotInAudience
85-
_ -> mempty
86-
87-
liftMaybe = maybe mempty pure
87+
validAud = \case
88+
(VAString aud) -> validAudString aud
89+
(VAArray auds) -> null auds || any validAudString auds
90+
_ -> True
91+
validAudString = audMatches . unStringOrURI
8892

8993
checkValue invalid msg val =
9094
if invalid val then
@@ -123,7 +127,7 @@ parseToken secret tkn = do
123127

124128
parseClaims :: (MonadError Error m, MonadIO m) => AppConfig -> UTCTime -> JSON.Object -> m AuthResult
125129
parseClaims AppConfig{configJwtAudience, configJwtRoleClaimKey, configDbAnonRole} time mclaims = do
126-
validateClaims time configJwtAudience mclaims
130+
validateClaims time (audMatchesCfg configJwtAudience) mclaims
127131
-- role defaults to anon if not specified in jwt
128132
role <- liftEither . maybeToRight (JwtErr JwtTokenRequired) $
129133
unquoted <$> walkJSPath (Just $ JSON.Object mclaims) configJwtRoleClaimKey <|> configDbAnonRole

src/PostgREST/Config.hs

Lines changed: 25 additions & 19 deletions
Original file line numberDiff line numberDiff line change
@@ -19,6 +19,9 @@ module PostgREST.Config
1919
, LogLevel(..)
2020
, OpenAPIMode(..)
2121
, Proxy(..)
22+
, CfgAud
23+
, audMatchesCfg
24+
, parseCfgAud
2225
, toText
2326
, isMalformedProxyUri
2427
, readAppConfig
@@ -28,6 +31,7 @@ module PostgREST.Config
2831
, addFallbackAppName
2932
, addTargetSessionAttrs
3033
, exampleConfigFile
34+
, defaultCfgAud
3135
) where
3236

3337
import qualified Data.Aeson as JSON
@@ -49,7 +53,7 @@ import Data.List.NonEmpty (fromList, toList)
4953
import Data.Maybe (fromJust)
5054
import Data.Scientific (floatingOrInteger)
5155
import Jose.Jwk (Jwk, JwkSet)
52-
import Network.URI (escapeURIString, isURI,
56+
import Network.URI (escapeURIString,
5357
isUnescapedInURIComponent)
5458
import Numeric (readOct, showOct)
5559
import System.Environment (getEnvironment)
@@ -65,8 +69,24 @@ import PostgREST.Config.Proxy (Proxy (..),
6569
import PostgREST.SchemaCache.Identifiers (QualifiedIdentifier, dumpQi,
6670
toQi)
6771

68-
import Protolude hiding (Proxy, toList)
72+
import Protolude hiding (Proxy, toList)
73+
import qualified Text.Regex.TDFA as R
6974

75+
data ParsedValue a = ParsedValue {
76+
sourceValue :: Text,
77+
parsedValue :: a
78+
}
79+
80+
newtype CfgAud = CfgAud { unCfgAud :: ParsedValue R.Regex }
81+
82+
parseCfgAud :: Text -> CfgAud
83+
parseCfgAud = CfgAud . (ParsedValue <*> (R.makeRegex . ("\\`(" <>) . (<> "\\')")))
84+
85+
defaultCfgAud :: CfgAud
86+
defaultCfgAud = parseCfgAud ""
87+
88+
audMatchesCfg :: CfgAud -> Text -> Bool
89+
audMatchesCfg = R.matchTest . parsedValue . unCfgAud
7090

7191
data AppConfig = AppConfig
7292
{ configAppSettings :: [(Text, Text)]
@@ -94,7 +114,7 @@ data AppConfig = AppConfig
94114
, configDbUri :: Text
95115
, configFilePath :: Maybe FilePath
96116
, configJWKS :: Maybe JwkSet
97-
, configJwtAudience :: Maybe Text
117+
, configJwtAudience :: CfgAud
98118
, configJwtRoleClaimKey :: JSPath
99119
, configJwtSecret :: Maybe BS.ByteString
100120
, configJwtSecretIsBase64 :: Bool
@@ -166,7 +186,7 @@ toText conf =
166186
,("db-pre-config", q . maybe mempty dumpQi . configDbPreConfig)
167187
,("db-tx-end", q . showTxEnd)
168188
,("db-uri", q . configDbUri)
169-
,("jwt-aud", q . fromMaybe mempty . configJwtAudience)
189+
,("jwt-aud", q . sourceValue . unCfgAud . configJwtAudience)
170190
,("jwt-role-claim-key", q . T.intercalate mempty . fmap dumpJSPath . configJwtRoleClaimKey)
171191
,("jwt-secret", q . T.decodeUtf8 . showJwtSecret)
172192
,("jwt-secret-is-base64", T.toLower . show . configJwtSecretIsBase64)
@@ -274,7 +294,7 @@ parser optPath env dbSettings roleSettings roleIsolationLvl =
274294
<*> (fromMaybe "postgresql://" <$> optString "db-uri")
275295
<*> pure optPath
276296
<*> pure Nothing
277-
<*> optStringOrURI "jwt-aud"
297+
<*> (maybe defaultCfgAud parseCfgAud <$> optString "jwt-aud")
278298
<*> parseRoleClaimKey "jwt-role-claim-key" "role-claim-key"
279299
<*> (fmap encodeUtf8 <$> optString "jwt-secret")
280300
<*> (fromMaybe False <$> optWithAlias
@@ -392,20 +412,6 @@ parser optPath env dbSettings roleSettings roleIsolationLvl =
392412
optStringEmptyable :: C.Key -> C.Parser C.Config (Maybe Text)
393413
optStringEmptyable k = overrideFromDbOrEnvironment C.optional k coerceText
394414

395-
optStringOrURI :: C.Key -> C.Parser C.Config (Maybe Text)
396-
optStringOrURI k = do
397-
stringOrURI <- mfilter (/= "") <$> overrideFromDbOrEnvironment C.optional k coerceText
398-
-- If the string contains ':' then it should
399-
-- be a valid URI according to RFC 3986
400-
case stringOrURI of
401-
Just s -> if T.isInfixOf ":" s then validateURI s else return (Just s)
402-
Nothing -> return Nothing
403-
where
404-
validateURI :: Text -> C.Parser C.Config (Maybe Text)
405-
validateURI s = if isURI (T.unpack s)
406-
then return $ Just s
407-
else fail "jwt-aud should be a string or a valid URI"
408-
409415
optInt :: (Read i, Integral i) => C.Key -> C.Parser C.Config (Maybe i)
410416
optInt k = join <$> overrideFromDbOrEnvironment C.optional k coerceInt
411417

src/PostgREST/Error.hs

Lines changed: 10 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -675,7 +675,7 @@ data JwtClaimsError
675675
| ExpClaimNotNumber
676676
| NbfClaimNotNumber
677677
| IatClaimNotNumber
678-
| AudClaimNotStringOrArray
678+
| AudClaimNotStringOrURIOrArray
679679
deriving Show
680680

681681
instance PgrstError Error where
@@ -752,15 +752,15 @@ instance ErrorBody JwtError where
752752
UnreachableDecodeError -> "JWT couldn't be decoded"
753753
message JwtTokenRequired = "Anonymous access is disabled"
754754
message (JwtClaimsErr e) = case e of
755-
JWTExpired -> "JWT expired"
756-
JWTNotYetValid -> "JWT not yet valid"
757-
JWTIssuedAtFuture -> "JWT issued at future"
758-
JWTNotInAudience -> "JWT not in audience"
759-
ParsingClaimsFailed -> "Parsing claims failed"
760-
ExpClaimNotNumber -> "The JWT 'exp' claim must be a number"
761-
NbfClaimNotNumber -> "The JWT 'nbf' claim must be a number"
762-
IatClaimNotNumber -> "The JWT 'iat' claim must be a number"
763-
AudClaimNotStringOrArray -> "The JWT 'aud' claim must be a string or an array of strings"
755+
JWTExpired -> "JWT expired"
756+
JWTNotYetValid -> "JWT not yet valid"
757+
JWTIssuedAtFuture -> "JWT issued at future"
758+
JWTNotInAudience -> "JWT not in audience"
759+
ParsingClaimsFailed -> "Parsing claims failed"
760+
ExpClaimNotNumber -> "The JWT 'exp' claim must be a number"
761+
NbfClaimNotNumber -> "The JWT 'nbf' claim must be a number"
762+
IatClaimNotNumber -> "The JWT 'iat' claim must be a number"
763+
AudClaimNotStringOrURIOrArray -> "The JWT 'aud' claim must be a string, URI or an array of mixed strings or URIs"
764764

765765
details (JwtDecodeErr jde) = case jde of
766766
KeyError dets -> Just $ JSON.String dets

test/io/fixtures.yaml

Lines changed: 0 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -41,11 +41,6 @@ cli:
4141
use_defaultenv: true
4242
env:
4343
PGRST_SERVER_UNIX_SOCKET_MODE: '778'
44-
- name: invalid jwt-aud
45-
expect: error
46-
use_defaultenv: true
47-
env:
48-
PGRST_JWT_AUD: 'http://%%localhorst.invalid'
4944
- name: invalid log-level
5045
expect: error
5146
use_defaultenv: true

test/io/test_cli.py

Lines changed: 0 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -266,17 +266,6 @@ def test_schema_cache_snapshot(baseenv, key, snapshot_yaml):
266266
assert formatted == snapshot_yaml
267267

268268

269-
def test_jwt_aud_config_set_to_invalid_uri(defaultenv):
270-
"PostgREST should exit with an error message in output if jwt-aud config is set to an invalid URI"
271-
env = {
272-
**defaultenv,
273-
"PGRST_JWT_AUD": "foo://%%$$^^.com",
274-
}
275-
276-
error = cli(["--dump-config"], env=env, expect_error=True)
277-
assert "jwt-aud should be a string or a valid URI" in error
278-
279-
280269
def test_jwt_secret_min_length(defaultenv):
281270
"Should log error and not load the config when the secret is shorter than the minimum admitted length"
282271

test/spec/Feature/Auth/AudienceJwtSecretSpec.hs

Lines changed: 20 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -40,6 +40,20 @@ spec = describe "test handling of aud claims in JWT when the jwt-aud config is s
4040
[json|{"code":"PGRST303","details":null,"hint":null,"message":"JWT not in audience"}|]
4141
{ matchStatus = 401 }
4242

43+
it "fails when the audience claim matches but is not a valid URI" $ do
44+
let jwtPayload = [json|
45+
{
46+
"exp": 9999999999,
47+
"role": "postgrest_test_author",
48+
"id": "jdoe",
49+
"aud": "urn:\\uriaudience"
50+
}|]
51+
auth = authHeaderJWT $ generateJWT jwtPayload
52+
request methodGet "/authors_only" [auth] ""
53+
`shouldRespondWith`
54+
[json|{"code":"PGRST303","details":null,"hint":null,"message":"The JWT 'aud' claim must be a string, URI or an array of mixed strings or URIs"}|]
55+
{ matchStatus = 401 }
56+
4357
it "fails when the audience claim is empty" $ do
4458
let jwtPayload = [json|
4559
{
@@ -151,7 +165,7 @@ disabledSpec :: SpecWith ((), Application)
151165
disabledSpec = describe "test handling of aud claims in JWT when the jwt-aud config is not set" $ do
152166

153167
context "when the audience claim is a string" $ do
154-
it "ignores the audience claim and suceeds" $ do
168+
it "fails when it is not empty" $ do
155169
let jwtPayload =
156170
[json|{
157171
"exp": 9999999999,
@@ -161,7 +175,7 @@ disabledSpec = describe "test handling of aud claims in JWT when the jwt-aud con
161175
}|]
162176
auth = authHeaderJWT $ generateJWT jwtPayload
163177
request methodGet "/authors_only" [auth] ""
164-
`shouldRespondWith` 200
178+
`shouldRespondWith` 401
165179

166180
it "ignores the audience claim and suceeds when it's empty" $ do
167181
let jwtPayload =
@@ -176,7 +190,7 @@ disabledSpec = describe "test handling of aud claims in JWT when the jwt-aud con
176190
`shouldRespondWith` 200
177191

178192
context "when the audience is an array of strings" $ do
179-
it "ignores the audience claim and suceeds when it has 1 element" $ do
193+
it "fails it has 1 element" $ do
180194
let jwtPayload = [json|
181195
{
182196
"exp": 9999999999,
@@ -186,9 +200,9 @@ disabledSpec = describe "test handling of aud claims in JWT when the jwt-aud con
186200
}|]
187201
auth = authHeaderJWT $ generateJWT jwtPayload
188202
request methodGet "/authors_only" [auth] ""
189-
`shouldRespondWith` 200
203+
`shouldRespondWith` 401
190204

191-
it "ignores the audience claim and suceeds when it has more than 1 element" $ do
205+
it "fails when it has more than 1 element" $ do
192206
let jwtPayload = [json|
193207
{
194208
"exp": 9999999999,
@@ -198,7 +212,7 @@ disabledSpec = describe "test handling of aud claims in JWT when the jwt-aud con
198212
}|]
199213
auth = authHeaderJWT $ generateJWT jwtPayload
200214
request methodGet "/authors_only" [auth] ""
201-
`shouldRespondWith` 200
215+
`shouldRespondWith` 401
202216

203217
it "ignores the audience claim and suceeds when it's empty" $ do
204218
let jwtPayload = [json|

test/spec/Feature/Auth/AuthSpec.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -182,7 +182,7 @@ spec = describe "authorization" $ do
182182
auth = authHeaderJWT $ generateJWT jwtPayload
183183
request methodGet "/authors_only" [auth] ""
184184
`shouldRespondWith`
185-
[json|{"code":"PGRST303","details":null,"hint":null,"message":"The JWT 'aud' claim must be a string or an array of strings"}|]
185+
[json|{"code":"PGRST303","details":null,"hint":null,"message":"The JWT 'aud' claim must be a string, URI or an array of mixed strings or URIs"}|]
186186
{ matchStatus = 401 }
187187

188188
it "fails when the aud claim is an array but it has non-string elements" $ do
@@ -194,7 +194,7 @@ spec = describe "authorization" $ do
194194
auth = authHeaderJWT $ generateJWT jwtPayload
195195
request methodGet "/authors_only" [auth] ""
196196
`shouldRespondWith`
197-
[json|{"code":"PGRST303","details":null,"hint":null,"message":"The JWT 'aud' claim must be a string or an array of strings"}|]
197+
[json|{"code":"PGRST303","details":null,"hint":null,"message":"The JWT 'aud' claim must be a string, URI or an array of mixed strings or URIs"}|]
198198
{ matchStatus = 401 }
199199

200200
describe "custom pre-request proc acting on id claim" $ do

test/spec/SpecHelper.hs

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -34,6 +34,7 @@ import PostgREST.Config (AppConfig (..),
3434
JSPathExp (..),
3535
LogLevel (..),
3636
OpenAPIMode (..),
37+
defaultCfgAud, parseCfgAud,
3738
parseSecret)
3839
import PostgREST.SchemaCache.Identifiers (QualifiedIdentifier (..))
3940
import Protolude hiding (get, toS)
@@ -135,7 +136,7 @@ baseCfg = let secret = encodeUtf8 "reallyreallyreallyreallyverysafe" in
135136
, configDbUri = "postgresql://"
136137
, configFilePath = Nothing
137138
, configJWKS = rightToMaybe $ parseSecret secret
138-
, configJwtAudience = Nothing
139+
, configJwtAudience = defaultCfgAud
139140
, configJwtRoleClaimKey = [JSPKey "role"]
140141
, configJwtSecret = Just secret
141142
, configJwtSecretIsBase64 = False
@@ -216,7 +217,7 @@ testCfgAudienceJWT :: AppConfig
216217
testCfgAudienceJWT =
217218
baseCfg {
218219
configJwtSecret = Just generateSecret
219-
, configJwtAudience = Just "youraudience"
220+
, configJwtAudience = parseCfgAud "urn..uriaudience|youraudience"
220221
, configJWKS = rightToMaybe $ parseSecret generateSecret
221222
}
222223

0 commit comments

Comments
 (0)