Skip to content

Commit

Permalink
jwt: support custom header types
Browse files Browse the repository at this point in the history
Generalise the types of `signJWT`, `verifyJWT`, and related
functions to accept custom JWS header types.  Add new type synonym
`SignedJWTWithHeader h` (keeping `SignedJWT` *as is*).  This change
could break some applications by introducing type ambiguity.  The
solution is to add a type annotation or apply a function like:

```haskell
fixType = id :: SignedJWT -> SignedJWT
```

I applied this technique in the test suite to address such
ambiguity.

Fixes: #122
  • Loading branch information
frasertweedale committed Feb 14, 2024
1 parent 853edcb commit 48ed92d
Show file tree
Hide file tree
Showing 4 changed files with 74 additions and 24 deletions.
8 changes: 8 additions & 0 deletions CHANGELOG.md
Original file line number Diff line number Diff line change
@@ -1,5 +1,12 @@
## Version NEXT

- Generalised the types of `signJWT`, `verifyJWT` and related
functions to accept custom JWS header types. Added new type
synonym `SignedJWTWithHeader h`. This change could break some
applications by introducing ambiguity. The solution will be
to add a type annotation or apply a function like `fixType = id ::
SignedJWT -> SignedJWT` to specify the header type. ([#122][]).

- Added `unsafeGetPayload`, `unsafeGetJWTPayload` and
`unsafeGetJWTClaimsSet` functions. These enable access to
the JWS/JWT payload without cryptographic verification. As
Expand Down Expand Up @@ -77,6 +84,7 @@
[#106]: https://github.com/frasertweedale/hs-jose/issues/106
[#107]: https://github.com/frasertweedale/hs-jose/issues/107
[#118]: https://github.com/frasertweedale/hs-jose/issues/118
[#122]: https://github.com/frasertweedale/hs-jose/issues/122


## Older versions
Expand Down
77 changes: 59 additions & 18 deletions src/Crypto/JWT.hs
Original file line number Diff line number Diff line change
Expand Up @@ -43,8 +43,9 @@ module Crypto.JWT
-- * API
-- ** Creating a JWT
SignedJWT
, signClaims
, SignedJWTWithHeader
, signJWT
, signClaims

-- ** Validating a JWT and extracting claims
, defaultJWTValidationSettings
Expand Down Expand Up @@ -155,8 +156,8 @@ verify k s = 'runJOSE' $ do
let
k' = 'fromOctets' k -- turn raw secret into symmetric JWK
audCheck = const True -- should be a proper audience check
jwt <- 'decodeCompact' s -- decode JWT
'verifyClaims' ('defaultJWTValidationSettings' audCheck) k' jwt
jwt <- 'decodeCompact' s -- decode JWT
'verifyClaims' ('defaultJWTValidationSettings' audCheck) k' (jwt :: 'SignedJWT')
@
-}
Expand Down Expand Up @@ -621,10 +622,16 @@ validateIssClaim conf =
unless (view issuerPredicate conf iss) (throwing_ _JWTNotInIssuer) )
. preview (claimIss . _Just)

-- | A digitally signed or MACed JWT
-- | A digitally signed or MAC'd JWT, with the JWS header type fixed
-- at 'JWSHeader'.
--
type SignedJWT = CompactJWS JWSHeader
type SignedJWT = SignedJWTWithHeader JWSHeader

-- | A digitally signed or MAC'd JWT, with caller-specified JWS
-- header type. For information about defining custom header types
-- see /Defining additional header parameters/ in "Crypto.JOSE.JWS".
--
type SignedJWTWithHeader h = CompactJWS h

newtype WrappedUTCTime = WrappedUTCTime { getUTCTime :: UTCTime }

Expand Down Expand Up @@ -678,13 +685,18 @@ verifyJWT
, HasIssuerPredicate a
, HasCheckIssuedAt a
, HasValidationSettings a
, HasJWSHeader h, HasParams h
, AsError e, AsJWTError e, MonadError e m
, VerificationKeyStore m (JWSHeader ()) payload k
, VerificationKeyStore m (h ()) payload k
, HasClaimsSet payload, FromJSON payload
)
=> a
-- ^ Validation settings
-> k
-> SignedJWT
-- ^ Key store
-> SignedJWTWithHeader h
-- ^ JWT. Simple use cases may find the 'SignedJWT' type synonym useful for
-- fixing the type of @h@.
-> m payload
verifyJWT conf k jws =
-- It is important, for security reasons, that the signature get
Expand All @@ -701,12 +713,17 @@ verifyClaims
, HasIssuerPredicate a
, HasCheckIssuedAt a
, HasValidationSettings a
, HasJWSHeader h, HasParams h
, AsError e, AsJWTError e, MonadError e m
, VerificationKeyStore m (JWSHeader ()) ClaimsSet k
, VerificationKeyStore m (h ()) ClaimsSet k
)
=> a
-- ^ Validation settings
-> k
-> SignedJWT
-- ^ Key store
-> SignedJWTWithHeader h
-- ^ JWT. Simple use cases may find the 'SignedJWT' type synonym useful for
-- fixing the type of @h@.
-> m ClaimsSet
verifyClaims = verifyJWT

Expand All @@ -720,14 +737,20 @@ verifyJWTAt
, HasIssuerPredicate a
, HasCheckIssuedAt a
, HasValidationSettings a
, HasJWSHeader h, HasParams h
, AsError e, AsJWTError e, MonadError e m
, VerificationKeyStore (ReaderT WrappedUTCTime m) (JWSHeader ()) payload k
, VerificationKeyStore (ReaderT WrappedUTCTime m) (h ()) payload k
, HasClaimsSet payload, FromJSON payload
)
=> a
-- ^ Validation settings
-> k
-- ^ Key store
-> UTCTime
-> SignedJWT
-- ^ Validation time
-> SignedJWTWithHeader h
-- ^ JWT. Simple use cases may find the 'SignedJWT' type synonym useful for
-- fixing the type of @h@.
-> m payload
verifyJWTAt a k t jwt = runReaderT (verifyJWT a k jwt) (WrappedUTCTime t)

Expand All @@ -740,13 +763,19 @@ verifyClaimsAt
, HasIssuerPredicate a
, HasCheckIssuedAt a
, HasValidationSettings a
, HasJWSHeader h, HasParams h
, AsError e, AsJWTError e, MonadError e m
, VerificationKeyStore (ReaderT WrappedUTCTime m) (JWSHeader ()) ClaimsSet k
, VerificationKeyStore (ReaderT WrappedUTCTime m) (h ()) ClaimsSet k
)
=> a
-- ^ Validation settings
-> k
-- ^ Key store
-> UTCTime
-> SignedJWT
-- ^ Validation time
-> SignedJWTWithHeader h
-- ^ JWT. Simple use cases may find the 'SignedJWT' type synonym useful for
-- fixing the type of @h@.
-> m ClaimsSet
verifyClaimsAt = verifyJWTAt

Expand All @@ -760,11 +789,17 @@ verifyClaimsAt = verifyJWTAt
--
signJWT
:: ( MonadRandom m, MonadError e m, AsError e
, HasJWSHeader h, HasParams h
, ToJSON payload )
=> JWK
-> JWSHeader ()
-- ^ Signing key
-> h ()
-- ^ JWS Header. Commonly this will be 'JWSHeader'. If your application
-- uses additional header fields, see /Defining additional header parameters/
-- in "Crypto.JOSE.JWS".
-> payload
-> m SignedJWT
-- ^ The payload ('ClaimsSet' or a subtype).
-> m (SignedJWTWithHeader h)
signJWT k h c = signJWS (encode c) (Identity (h, k))

-- | Create a JWS JWT. Specialisation of 'signJWT' with payload type fixed
Expand All @@ -774,9 +809,15 @@ signJWT k h c = signJWS (encode c) (Identity (h, k))
-- ("Issued At") Claim. The payload is encoded as-is.
--
signClaims
:: (MonadRandom m, MonadError e m, AsError e)
:: ( MonadRandom m, MonadError e m, AsError e
, HasJWSHeader h, HasParams h )
=> JWK
-> JWSHeader ()
-- ^ Signing key
-> h ()
-- ^ JWS Header. Commonly this will be 'JWSHeader'. If your application
-- uses additional header fields, see /Defining additional header parameters/
-- in "Crypto.JOSE.JWS".
-> ClaimsSet
-> m SignedJWT
-- ^ Payload
-> m (SignedJWTWithHeader h)
signClaims = signJWT
2 changes: 1 addition & 1 deletion test/Examples.hs
Original file line number Diff line number Diff line change
Expand Up @@ -42,7 +42,7 @@ fromX509VerifySpec =
(do
es256jwk <- errorOrJWK
jwt <- decodeCompact es256token
verifyClaimsAt valSettings es256jwk now jwt) `shouldBe`
verifyClaimsAt valSettings es256jwk now (jwt :: SignedJWT)) `shouldBe`
Right expectedClaims

_ -> pure ()
Expand Down
11 changes: 6 additions & 5 deletions test/JWT.hs
Original file line number Diff line number Diff line change
Expand Up @@ -88,6 +88,7 @@ spec = do
(defaultJWTValidationSettings (const False))
headMay [] = Nothing
headMay (h:_) = Just h
fixType = id :: SignedJWT -> SignedJWT

describe "JWT Claims Set" $ do
it "parses from JSON correctly" $ do
Expand Down Expand Up @@ -339,9 +340,9 @@ spec = do
192,205,154,245,103,208,128,163]
now = utcTime "2010-01-01 00:00:00"
settings = defaultJWTValidationSettings (const True)
runReaderT (decodeCompact exampleJWT >>= verifyClaims settings k) now
runReaderT (decodeCompact exampleJWT >>= verifyClaims settings k . fixType) now
`shouldBe` (Right exampleClaimsSet :: Either JWTError ClaimsSet)
runReaderT (decodeCompact exampleJWT >>= verifyJWT settings k) now
runReaderT (decodeCompact exampleJWT >>= verifyJWT settings k . fixType) now
`shouldBe` (Right super :: Either JWTError Super)

describe "RFC 7519 §6.1. Example Unsecured JWT" $ do
Expand All @@ -357,17 +358,17 @@ spec = do

describe "when the current time is prior to the Expiration Time" $
it "can be decoded and validated" $
runReaderT (jwt >>= verifyClaims conf k) (utcTime "2010-01-01 00:00:00")
runReaderT (jwt >>= verifyClaims conf k . fixType) (utcTime "2010-01-01 00:00:00")
`shouldBe` (Right exampleClaimsSet :: Either JWTError ClaimsSet)

describe "when the current time is after the Expiration Time" $
it "can be decoded, but not validated" $
runReaderT (jwt >>= verifyClaims conf k) (utcTime "2012-01-01 00:00:00")
runReaderT (jwt >>= verifyClaims conf k . fixType) (utcTime "2012-01-01 00:00:00")
`shouldBe` Left JWTExpired

describe "when signature is invalid and token is expired" $
it "fails on sig validation (claim validation not reached)" $ do
let jwt' = decodeCompact (exampleJWT <> "badsig")
(runReaderT (jwt' >>= verifyClaims conf k) (utcTime "2012-01-01 00:00:00")
(runReaderT (jwt' >>= verifyClaims conf k . fixType) (utcTime "2012-01-01 00:00:00")
:: Either JWTError ClaimsSet)
`shouldSatisfy` is (_Left . _JWSInvalidSignature)

0 comments on commit 48ed92d

Please sign in to comment.