{-# LANGUAGE OverloadedStrings #-}
module Jose.Jws
( jwkEncode
, hmacEncode
, hmacDecode
, rsaEncode
, rsaDecode
, ecDecode
)
where
import Control.Applicative
import qualified Crypto.PubKey.ECC.ECDSA as ECDSA
import Crypto.PubKey.RSA (PrivateKey(..), PublicKey(..), generateBlinder)
import Crypto.Random (MonadRandom)
import Data.ByteString (ByteString)
import qualified Data.ByteString as B
import Jose.Types
import qualified Jose.Internal.Base64 as B64
import Jose.Internal.Crypto
import qualified Jose.Internal.Parser as P
import Jose.Jwa
import Jose.Jwk (Jwk (..))
jwkEncode :: MonadRandom m
=> JwsAlg
-> Jwk
-> Payload
-> m (Either JwtError Jwt)
jwkEncode a key payload = case key of
RsaPrivateJwk kPr kid _ _ -> rsaEncodeInternal a kPr (sigTarget a kid payload)
SymmetricJwk k kid _ _ -> return $ hmacEncodeInternal a k (sigTarget a kid payload)
_ -> return $ Left $ BadAlgorithm "EC signing is not supported"
hmacEncode :: JwsAlg
-> ByteString
-> ByteString
-> Either JwtError Jwt
hmacEncode a key payload = hmacEncodeInternal a key (sigTarget a Nothing (Claims payload))
hmacEncodeInternal :: JwsAlg
-> ByteString
-> ByteString
-> Either JwtError Jwt
hmacEncodeInternal a key st = Jwt . (\mac -> B.concat [st, ".", B64.encode mac]) <$> hmacSign a key st
hmacDecode :: ByteString
-> ByteString
-> Either JwtError Jws
hmacDecode key = decode (`hmacVerify` key)
rsaEncode :: MonadRandom m
=> JwsAlg
-> PrivateKey
-> ByteString
-> m (Either JwtError Jwt)
rsaEncode a pk payload = rsaEncodeInternal a pk (sigTarget a Nothing (Claims payload))
rsaEncodeInternal :: MonadRandom m
=> JwsAlg
-> PrivateKey
-> ByteString
-> m (Either JwtError Jwt)
rsaEncodeInternal a pk st = do
blinder <- generateBlinder (public_n $ private_pub pk)
return $ sign blinder
where
sign b = case rsaSign (Just b) a pk st of
Right sig -> Right . Jwt $ B.concat [st, ".", B64.encode sig]
Left e -> Left e
rsaDecode :: PublicKey
-> ByteString
-> Either JwtError Jws
rsaDecode key = decode (`rsaVerify` key)
ecDecode :: ECDSA.PublicKey
-> ByteString
-> Either JwtError Jws
ecDecode key = decode (`ecVerify` key)
sigTarget :: JwsAlg -> Maybe KeyId -> Payload -> ByteString
sigTarget a kid payload = B.intercalate "." $ map B64.encode [encodeHeader hdr, bytes]
where
hdr = defJwsHdr {jwsAlg = a, jwsKid = kid, jwsCty = contentType}
(contentType, bytes) = case payload of
Claims c -> (Nothing, c)
Nested (Jwt b) -> (Just "JWT", b)
type JwsVerifier = JwsAlg -> ByteString -> ByteString -> Bool
decode :: JwsVerifier -> ByteString -> Either JwtError Jws
decode verify jwt = do
decodableJwt <- P.parseJwt jwt
case decodableJwt of
P.DecodableJws hdr (P.Payload p) (P.Sig sig) (P.SigTarget signed) ->
if verify (jwsAlg hdr) signed sig
then Right (hdr, p)
else Left BadSignature
_ -> Left (BadHeader "JWT is not a JWS")