module Jose.Jwt
( module Jose.Types
, encode
, decode
, decodeClaims
)
where
import Control.Monad (when, unless, liftM)
import Control.Monad.Trans (lift)
import Control.Monad.Trans.Either
import qualified Crypto.PubKey.ECC.ECDSA as ECDSA
import Crypto.PubKey.RSA (PrivateKey(..))
import Crypto.Random (MonadRandom)
import Data.Aeson (decodeStrict')
import Data.ByteString (ByteString)
import Data.List (find)
import Data.Maybe (fromJust, isJust, isNothing)
import qualified Data.ByteString.Char8 as BC
import qualified Jose.Internal.Base64 as B64
import Jose.Types
import Jose.Jwk
import Jose.Jwa
import qualified Jose.Jws as Jws
import qualified Jose.Jwe as Jwe
encode :: MonadRandom m
=> [Jwk]
-> JwtEncoding
-> Payload
-> m (Either JwtError Jwt)
encode jwks encoding msg = runEitherT $ case encoding of
JwsEncoding None -> case msg of
Claims p -> return $ Jwt $ BC.intercalate "." [unsecuredHdr, B64.encode p]
Nested _ -> left BadClaims
JwsEncoding a -> case filter (canEncodeJws a) jwks of
[] -> left (KeyError "No matching key found for JWS algorithm")
(k:_) -> hoistEither =<< lift (Jws.jwkEncode a k msg)
JweEncoding a e -> case filter (canEncodeJwe a) jwks of
[] -> left (KeyError "No matching key found for JWE algorithm")
(k:_) -> hoistEither =<< lift (Jwe.jwkEncode a e k msg)
where
unsecuredHdr = B64.encode (BC.pack "{\"alg\":\"none\"}")
decode :: MonadRandom m
=> [Jwk]
-> Maybe JwtEncoding
-> ByteString
-> m (Either JwtError JwtContent)
decode keySet encoding jwt = runEitherT $ do
let components = BC.split '.' jwt
when (length components < 3) $ left $ BadDots 2
hdr <- B64.decode (head components) >>= hoistEither . parseHeader
ks <- findDecodingKeys hdr keySet
decodings <- case hdr of
UnsecuredH -> do
unless (encoding == Just (JwsEncoding None)) $ left (BadAlgorithm "JWT is unsecured but expected 'alg' was not 'none'")
B64.decode (components !! 1) >>= \p -> return [Just (Unsecured p)]
JwsH h -> do
unless (isNothing encoding || encoding == Just (JwsEncoding (jwsAlg h))) $ left (BadAlgorithm "Expected 'alg' doesn't match JWS header")
mapM decodeWithJws ks
JweH h -> do
unless (isNothing encoding || encoding == Just (JweEncoding (jweAlg h) (jweEnc h))) $ left (BadAlgorithm "Expected encoding doesn't match JWE header")
mapM decodeWithJwe ks
maybe (left $ KeyError "None of the keys was able to decode the JWT") (return . fromJust) $ find isJust decodings
where
decodeWithJws :: MonadRandom m => Jwk -> EitherT JwtError m (Maybe JwtContent)
decodeWithJws k = either (const $ return Nothing) (return . Just . Jws) $ case k of
RsaPublicJwk kPub _ _ _ -> Jws.rsaDecode kPub jwt
RsaPrivateJwk kPr _ _ _ -> Jws.rsaDecode (private_pub kPr) jwt
EcPublicJwk kPub _ _ _ _ -> Jws.ecDecode kPub jwt
EcPrivateJwk kPr _ _ _ _ -> Jws.ecDecode (ECDSA.toPublicKey kPr) jwt
SymmetricJwk kb _ _ _ -> Jws.hmacDecode kb jwt
decodeWithJwe :: MonadRandom m => Jwk -> EitherT JwtError m (Maybe JwtContent)
decodeWithJwe k = liftM (either (const Nothing) Just) (lift (Jwe.jwkDecode k jwt))
decodeClaims :: ByteString
-> Either JwtError (JwtHeader, JwtClaims)
decodeClaims jwt = do
let components = BC.split '.' jwt
when (length components /= 3) $ Left $ BadDots 2
hdr <- B64.decode (head components) >>= parseHeader
claims <- B64.decode ((head . tail) components) >>= parseClaims
return (hdr, claims)
where
parseClaims bs = maybe (Left BadClaims) Right $ decodeStrict' bs
findDecodingKeys :: Monad m => JwtHeader -> [Jwk] -> EitherT JwtError m [Jwk]
findDecodingKeys hdr jwks = case hdr of
JweH h -> checkKeys $ filter (canDecodeJwe h) jwks
JwsH h -> checkKeys $ filter (canDecodeJws h) jwks
UnsecuredH -> return []
where
checkKeys [] = left $ KeyError "No suitable key was found to decode the JWT"
checkKeys ks = return ks