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

Safe HaskellNone
LanguageHaskell98

Crypto.JOSE.JWS

Description

JSON Web Signature (JWS) represents content secured with digital signatures or Message Authentication Codes (MACs) using JavaScript Object Notation (JSON) based data structures.

Synopsis

Documentation

data Alg Source #

JWA §3.1. "alg" (Algorithm) Header Parameters for JWS

Instances

Eq Alg Source # 

Methods

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

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

Ord Alg Source # 

Methods

compare :: Alg -> Alg -> Ordering #

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

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

(>) :: Alg -> Alg -> Bool #

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

max :: Alg -> Alg -> Alg #

min :: Alg -> Alg -> Alg #

Show Alg Source # 

Methods

showsPrec :: Int -> Alg -> ShowS #

show :: Alg -> String #

showList :: [Alg] -> ShowS #

FromJSON Alg Source # 
ToJSON Alg Source # 

class HasJWSHeader c where Source #

Minimal complete definition

jWSHeader

data JWSHeader Source #

JWS Header data type.

newJWSHeader :: (Protection, Alg) -> JWSHeader Source #

Construct a minimal header with the given algorithm

header :: forall a a. Lens (Signature a) (Signature a) a a Source #

data JWS a Source #

JSON Web Signature data type. Consists of a payload and a (possibly empty) list of signatures.

Parameterised by the header type.

Constructors

JWS Base64Octets [Signature a] 

Instances

(Eq a, HasParams a) => Eq (JWS a) Source # 

Methods

(==) :: JWS a -> JWS a -> Bool #

(/=) :: JWS a -> JWS a -> Bool #

Show a => Show (JWS a) Source # 

Methods

showsPrec :: Int -> JWS a -> ShowS #

show :: JWS a -> String #

showList :: [JWS a] -> ShowS #

HasParams a => FromJSON (JWS a) Source # 

Methods

parseJSON :: Value -> Parser (JWS a) #

parseJSONList :: Value -> Parser [JWS a] #

HasParams a => ToJSON (JWS a) Source # 

Methods

toJSON :: JWS a -> Value #

toEncoding :: JWS a -> Encoding #

toJSONList :: [JWS a] -> Value #

toEncodingList :: [JWS a] -> Encoding #

HasParams a => ToCompact (JWS a) Source # 

Methods

toCompact :: (AsError e, MonadError e m) => JWS a -> m [ByteString] Source #

HasParams a => FromCompact (JWS a) Source # 

Methods

fromCompact :: (AsError e, MonadError e m) => [ByteString] -> m (JWS a) Source #

newJWS :: ByteString -> JWS a Source #

Construct a new (unsigned) JWS

jwsPayload :: JWS a -> ByteString Source #

Payload of a JWS, as a lazy bytestring.

signJWS Source #

Arguments

:: (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 HasAlgorithms s where Source #

Minimal complete definition

algorithms

Methods

algorithms :: Lens' s (Set Alg) Source #

data ValidationPolicy Source #

Validation policy.

Constructors

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.

Verification succeeds if any signature on the JWS is successfully validated with the given Key.

If only specific signatures need to be validated, and the ValidationPolicy argument is not enough to express this, the caller is responsible for removing irrelevant signatures prior to calling verifyJWS.