jose-0.6.0.3: Javascript Object Signing and Encryption and JSON Web Token library

Safe HaskellNone
LanguageHaskell98

Crypto.JOSE.JWK

Contents

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 

Instances

Eq Crv Source # 

Methods

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

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

Ord Crv Source # 

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 #

Show Crv Source # 

Methods

showsPrec :: Int -> Crv -> ShowS #

show :: Crv -> String #

showList :: [Crv] -> ShowS #

Arbitrary Crv Source # 

Methods

arbitrary :: Gen Crv #

shrink :: Crv -> [Crv] #

ToJSON Crv Source # 
FromJSON Crv Source # 

data JWK Source #

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

Parts of a JWK

data KeyUse Source #

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

Constructors

Sig 
Enc 

data KeyOp Source #

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

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 

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

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] 

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.