jose-0.11: JSON Object Signing and Encryption (JOSE) and JSON Web Token (JWT) library
Safe HaskellSafe-Inferred
LanguageHaskell2010

Crypto.JOSE.JWK

Description

A JSON Web Key (JWK) is a JavaScript Object Notation (JSON) data structure that represents a cryptographic key. This module also defines a JSON Web Key Set (JWK Set) JSON data structure for representing a set of JWKs.

-- Generate RSA JWK and set "kid" param to
-- base64url-encoded SHA-256 thumbprint of key.
--
doGen :: IO JWK
doGen = do
  jwk <- genJWK (RSAGenParam (4096 `div` 8))
  let
    h = view thumbprint jwk :: Digest SHA256
    kid = view (re (base64url . digest) . utf8) h
  pure $ set jwkKid (Just kid) jwk
Synopsis

JWK generation

genJWK :: MonadRandom m => KeyMaterialGenParam -> m JWK Source #

Generate a JWK. Apart from key parameters, no other parameters are set.

data KeyMaterialGenParam Source #

Keygen parameters.

Constructors

ECGenParam Crv

Generate an EC key with specified curve.

RSAGenParam Int

Generate an RSA key with specified size in bytes.

OctGenParam Int

Generate a symmetric key with specified size in bytes.

OKPGenParam OKPCrv

Generate an EdDSA or Edwards ECDH key with specified curve.

data Crv Source #

"crv" (Curve) Parameter

Constructors

P_256 
P_384 
P_521 
Secp256k1 

Instances

Instances details
FromJSON Crv Source # 
Instance details

Defined in Crypto.JOSE.JWA.JWK

ToJSON Crv Source # 
Instance details

Defined in Crypto.JOSE.JWA.JWK

Show Crv Source # 
Instance details

Defined in Crypto.JOSE.JWA.JWK

Methods

showsPrec :: Int -> Crv -> ShowS #

show :: Crv -> String #

showList :: [Crv] -> ShowS #

Eq Crv Source # 
Instance details

Defined in Crypto.JOSE.JWA.JWK

Methods

(==) :: Crv -> Crv -> Bool #

(/=) :: Crv -> Crv -> Bool #

Ord Crv Source # 
Instance details

Defined in Crypto.JOSE.JWA.JWK

Methods

compare :: Crv -> Crv -> Ordering #

(<) :: Crv -> Crv -> Bool #

(<=) :: Crv -> Crv -> Bool #

(>) :: Crv -> Crv -> Bool #

(>=) :: Crv -> Crv -> Bool #

max :: Crv -> Crv -> Crv #

min :: Crv -> Crv -> Crv #

data OKPCrv Source #

Constructors

Ed25519 
Ed448 
X25519 
X448 

Instances

Instances details
Show OKPCrv Source # 
Instance details

Defined in Crypto.JOSE.JWA.JWK

Eq OKPCrv Source # 
Instance details

Defined in Crypto.JOSE.JWA.JWK

Methods

(==) :: OKPCrv -> OKPCrv -> Bool #

(/=) :: OKPCrv -> OKPCrv -> Bool #

data JWK Source #

RFC 7517 §4. JSON Web Key (JWK) Format

Instances

Instances details
FromJSON JWK Source # 
Instance details

Defined in Crypto.JOSE.JWK

ToJSON JWK Source # 
Instance details

Defined in Crypto.JOSE.JWK

Show JWK Source # 
Instance details

Defined in Crypto.JOSE.JWK

Methods

showsPrec :: Int -> JWK -> ShowS #

show :: JWK -> String #

showList :: [JWK] -> ShowS #

Eq JWK Source # 
Instance details

Defined in Crypto.JOSE.JWK

Methods

(==) :: JWK -> JWK -> Bool #

(/=) :: JWK -> JWK -> Bool #

AsPublicKey JWK Source # 
Instance details

Defined in Crypto.JOSE.JWK

Applicative m => VerificationKeyStore m h s JWK Source #

Use a JWK as a VerificationKeyStore. Can be used with any payload type. Header and payload are ignored. No filtering is performed.

Instance details

Defined in Crypto.JOSE.JWK.Store

Methods

getVerificationKeys :: h -> s -> JWK -> m [JWK] Source #

class AsPublicKey k where Source #

Keys that may have have public material

Methods

asPublicKey :: Getter k (Maybe k) Source #

Get the public key

Parts of a JWK

data KeyUse Source #

RFC 7517 §4.2. "use" (Public Key Use) Parameter

Constructors

Sig 
Enc 

Instances

Instances details
FromJSON KeyUse Source # 
Instance details

Defined in Crypto.JOSE.JWK

ToJSON KeyUse Source # 
Instance details

Defined in Crypto.JOSE.JWK

Show KeyUse Source # 
Instance details

Defined in Crypto.JOSE.JWK

Eq KeyUse Source # 
Instance details

Defined in Crypto.JOSE.JWK

Methods

(==) :: KeyUse -> KeyUse -> Bool #

(/=) :: KeyUse -> KeyUse -> Bool #

Ord KeyUse Source # 
Instance details

Defined in Crypto.JOSE.JWK

data KeyOp Source #

RFC 7517 §4.3. "key_ops" (Key Operations) Parameter

Instances

Instances details
FromJSON KeyOp Source # 
Instance details

Defined in Crypto.JOSE.JWK

ToJSON KeyOp Source # 
Instance details

Defined in Crypto.JOSE.JWK

Show KeyOp Source # 
Instance details

Defined in Crypto.JOSE.JWK

Methods

showsPrec :: Int -> KeyOp -> ShowS #

show :: KeyOp -> String #

showList :: [KeyOp] -> ShowS #

Eq KeyOp Source # 
Instance details

Defined in Crypto.JOSE.JWK

Methods

(==) :: KeyOp -> KeyOp -> Bool #

(/=) :: KeyOp -> KeyOp -> Bool #

Ord KeyOp Source # 
Instance details

Defined in Crypto.JOSE.JWK

Methods

compare :: KeyOp -> KeyOp -> Ordering #

(<) :: KeyOp -> KeyOp -> Bool #

(<=) :: KeyOp -> KeyOp -> Bool #

(>) :: KeyOp -> KeyOp -> Bool #

(>=) :: KeyOp -> KeyOp -> Bool #

max :: KeyOp -> KeyOp -> KeyOp #

min :: KeyOp -> KeyOp -> KeyOp #

data JWKAlg Source #

RFC 7517 §4.4. "alg" (Algorithm) Parameter

See also RFC 7518 §6.4. which states that for "oct" keys, an "alg" member SHOULD be present to identify the algorithm intended to be used with the key, unless the application uses another means or convention to determine the algorithm used.

Constructors

JWSAlg Alg 
JWEAlg Alg 

Instances

Instances details
FromJSON JWKAlg Source # 
Instance details

Defined in Crypto.JOSE.JWK

ToJSON JWKAlg Source # 
Instance details

Defined in Crypto.JOSE.JWK

Show JWKAlg Source # 
Instance details

Defined in Crypto.JOSE.JWK

Eq JWKAlg Source # 
Instance details

Defined in Crypto.JOSE.JWK

Methods

(==) :: JWKAlg -> JWKAlg -> Bool #

(/=) :: JWKAlg -> JWKAlg -> Bool #

jwkX5c :: Getter JWK (Maybe (NonEmpty SignedCertificate)) Source #

Get the certificate chain. Not a lens, because the key of the first certificate in the chain must correspond be the public key of the JWK. To set the certificate chain use setJWKX5c.

setJWKX5c :: Maybe (NonEmpty SignedCertificate) -> JWK -> Maybe JWK Source #

Set the "x5c" Certificate Chain parameter. If setting the list, checks that the key in the first certificate matches the JWK; returns Nothing if it does not.

Converting from other key formats

fromRSA :: PrivateKey -> JWK Source #

Convert RSA private key into a JWK

fromOctets :: Cons s s Word8 Word8 => s -> JWK Source #

Convert octet string into a JWK

fromX509Certificate :: (AsError e, MonadError e m) => SignedCertificate -> m JWK Source #

Convert an X.509 certificate into a JWK.

Supports RSA and ECDSA (when the curve is supported). Other key types will throw AlgorithmNotImplemented.

The "x5c" field of the resulting JWK contains the certificate.

JWK Thumbprint

thumbprint :: HashAlgorithm a => Getter JWK (Digest a) Source #

Compute the JWK Thumbprint of a JWK

digest :: HashAlgorithm a => Prism' ByteString (Digest a) Source #

Prism from ByteString to HashAlgorithm a => Digest a.

Use re digest to view the bytes of a digest

base64url :: (AsEmpty s1, AsEmpty s2, Cons s1 s1 Word8 Word8, Cons s2 s2 Word8 Word8) => Prism' s1 s2 Source #

Prism for encoding / decoding base64url.

To encode, review base64url. To decode, preview base64url.

Works with any combinations of strict/lazy ByteString.

JWK Set

newtype JWKSet Source #

RFC 7517 §5. JWK Set Format

Constructors

JWKSet [JWK] 

Instances

Instances details
FromJSON JWKSet Source # 
Instance details

Defined in Crypto.JOSE.JWK

ToJSON JWKSet Source # 
Instance details

Defined in Crypto.JOSE.JWK

Show JWKSet Source # 
Instance details

Defined in Crypto.JOSE.JWK

Eq JWKSet Source # 
Instance details

Defined in Crypto.JOSE.JWK

Methods

(==) :: JWKSet -> JWKSet -> Bool #

(/=) :: JWKSet -> JWKSet -> Bool #

Applicative m => VerificationKeyStore m h s JWKSet Source #

Use a JWKSet as a VerificationKeyStore. Can be used with any payload type. Returns all keys in the set; header and payload are ignored. No filtering is performed.

Instance details

Defined in Crypto.JOSE.JWK.Store

Methods

getVerificationKeys :: h -> s -> JWKSet -> m [JWK] Source #

checkJWK :: (MonadError e m, AsError e) => JWK -> m () Source #

Sanity-check a JWK.

Return an appropriate error if the key is size is too small to be used with any JOSE algorithm, or for other problems that mean the key cannot be used.

bestJWSAlg :: (MonadError e m, AsError e) => JWK -> m Alg Source #

Choose the cryptographically strongest JWS algorithm for a given key. The JWK "alg" algorithm parameter is ignored.