Safe Haskell | None |
---|---|
Language | Haskell98 |
JSON Web Signature (JWS) represents content secured with digital signatures or Message Authentication Codes (MACs) using JavaScript Object Notation (JSON) based data structures.
- data Alg
- class HasJWSHeader c where
- data JWSHeader = JWSHeader {
- _jwsHeaderAlg :: HeaderParam Alg
- _jwsHeaderJku :: Maybe (HeaderParam URI)
- _jwsHeaderJwk :: Maybe (HeaderParam JWK)
- _jwsHeaderKid :: Maybe (HeaderParam String)
- _jwsHeaderX5u :: Maybe (HeaderParam URI)
- _jwsHeaderX5c :: Maybe (HeaderParam (NonEmpty Base64X509))
- _jwsHeaderX5t :: Maybe (HeaderParam Base64SHA1)
- _jwsHeaderX5tS256 :: Maybe (HeaderParam Base64SHA256)
- _jwsHeaderTyp :: Maybe (HeaderParam String)
- _jwsHeaderCty :: Maybe (HeaderParam String)
- _jwsHeaderCrit :: Maybe (NonEmpty Text)
- newJWSHeader :: (Protection, Alg) -> JWSHeader
- data Signature a
- header :: forall a a. Lens (Signature a) (Signature a) a a
- data JWS a = JWS Base64Octets [Signature a]
- newJWS :: ByteString -> JWS a
- jwsPayload :: JWS a -> ByteString
- signJWS :: (HasJWSHeader a, HasParams a, MonadRandom m, AsError e, MonadError e m) => JWS a -> a -> JWK -> m (JWS a)
- class HasValidationSettings c where
- class HasAlgorithms s where
- class HasValidationPolicy s where
- data ValidationPolicy
- data ValidationSettings
- defaultValidationSettings :: ValidationSettings
- verifyJWS :: (HasAlgorithms a, HasValidationPolicy a, AsError e, MonadError e m, HasJWSHeader h, HasParams h) => a -> JWK -> JWS h -> m ()
- module Crypto.JOSE.Header
Documentation
JWA §3.1. "alg" (Algorithm) Header Parameters for JWS
class HasJWSHeader c where Source #
jWSHeader :: Lens' c JWSHeader Source #
jwsHeaderAlg :: Lens' c (HeaderParam Alg) Source #
jwsHeaderCrit :: Lens' c (Maybe (NonEmpty Text)) Source #
jwsHeaderCty :: Lens' c (Maybe (HeaderParam String)) Source #
jwsHeaderJku :: Lens' c (Maybe (HeaderParam URI)) Source #
jwsHeaderJwk :: Lens' c (Maybe (HeaderParam JWK)) Source #
jwsHeaderKid :: Lens' c (Maybe (HeaderParam String)) Source #
jwsHeaderTyp :: Lens' c (Maybe (HeaderParam String)) Source #
jwsHeaderX5c :: Lens' c (Maybe (HeaderParam (NonEmpty Base64X509))) Source #
jwsHeaderX5t :: Lens' c (Maybe (HeaderParam Base64SHA1)) Source #
jwsHeaderX5tS256 :: Lens' c (Maybe (HeaderParam Base64SHA256)) Source #
jwsHeaderX5u :: Lens' c (Maybe (HeaderParam URI)) Source #
JWS Header data type.
JWSHeader | |
|
newJWSHeader :: (Protection, Alg) -> JWSHeader Source #
Construct a minimal header with the given algorithm
JSON Web Signature data type. Consists of a payload and a (possibly empty) list of signatures.
Parameterised by the header type.
JWS Base64Octets [Signature a] |
newJWS :: ByteString -> JWS a Source #
Construct a new (unsigned) JWS
jwsPayload :: JWS a -> ByteString Source #
Payload of a JWS, as a lazy bytestring.
:: (HasJWSHeader a, HasParams a, MonadRandom m, AsError e, MonadError e m) | |
=> JWS a | JWS to sign |
-> a | Header for signature |
-> JWK | Key with which to sign |
-> m (JWS a) | JWS with new signature appended |
Create a new signature on a JWS.
class HasValidationSettings c where Source #
class HasAlgorithms s where Source #
class HasValidationPolicy s where Source #
data ValidationPolicy Source #
Validation policy.
AnyValidated | One successfully validated signature is sufficient |
AllValidated | All signatures in all configured algorithms must be validated. No signatures in configured algorithms is also an error. |
verifyJWS :: (HasAlgorithms a, HasValidationPolicy a, AsError e, MonadError e m, HasJWSHeader h, HasParams h) => a -> JWK -> JWS h -> m () Source #
Verify a JWS.
Signatures made with an unsupported algorithms are ignored.
If the validation policy is AnyValidated
, a single successfully
validated signature is sufficient. If the validation policy is
AllValidated
then all remaining signatures (there must be at least one)
must be valid.
module Crypto.JOSE.Header