module Jose.Jws
( hmacEncode
, hmacDecode
, rsaEncode
, rsaDecode
)
where
import Data.ByteString (ByteString)
import qualified Data.ByteString as B
import qualified Data.ByteString.Char8 as BC
import Crypto.PubKey.RSA (PrivateKey, PublicKey)
import Jose.Types
import qualified Jose.Internal.Base64 as B64
import Jose.Internal.Crypto
import Jose.Jwa
hmacEncode :: JwsAlg
-> ByteString
-> ByteString
-> ByteString
hmacEncode a key = encode (hmacSign a key) $ defJwsHdr {jwsAlg = a}
hmacDecode :: ByteString
-> ByteString
-> Either JwtError Jws
hmacDecode key = decode (\alg -> hmacVerify alg key)
rsaEncode :: JwsAlg
-> PrivateKey
-> ByteString
-> ByteString
rsaEncode a k = encode (rsaSign a k) $ defJwsHdr {jwsAlg = a}
rsaDecode :: PublicKey
-> ByteString
-> Either JwtError Jws
rsaDecode key = decode (\alg -> rsaVerify alg key)
encode :: (ByteString -> ByteString) -> JwsHeader -> ByteString -> ByteString
encode sign hdr payload = B.intercalate "." [hdrPayload, B64.encode $ sign hdrPayload]
where
hdrPayload = B.intercalate "." $ map B64.encode [encodeHeader hdr, payload]
type JwsVerifier = JwsAlg -> ByteString -> ByteString -> Bool
decode :: JwsVerifier -> ByteString -> Either JwtError Jws
decode verify jwt = do
checkDots
let (hdrPayload, sig) = spanEndDot jwt
sigBytes <- B64.decode sig
[h, payload] <- mapM B64.decode $ BC.split '.' hdrPayload
hdr <- case parseHeader h of
Right (JwsH jwsHdr) -> return jwsHdr
_ -> Left BadHeader
if verify (jwsAlg hdr) hdrPayload sigBytes
then Right (hdr, payload)
else Left BadSignature
where
checkDots = case (BC.count '.' jwt) of
2 -> Right ()
_ -> Left $ BadDots 2
spanEndDot bs = let (toDot, end) = BC.spanEnd (/= '.') bs
in (B.init toDot, end)