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

Safe HaskellNone
LanguageHaskell98

Crypto.JOSE.Header

Contents

Description

Types and functions for working with JOSE header parameters.

Synopsis

Defining header data types

data HeaderParam p a Source #

A header value, along with a protection indicator.

Constructors

HeaderParam p a 

Instances

(Eq a, Eq p) => Eq (HeaderParam p a) Source # 

Methods

(==) :: HeaderParam p a -> HeaderParam p a -> Bool #

(/=) :: HeaderParam p a -> HeaderParam p a -> Bool #

(Show a, Show p) => Show (HeaderParam p a) Source # 

Methods

showsPrec :: Int -> HeaderParam p a -> ShowS #

show :: HeaderParam p a -> String #

showList :: [HeaderParam p a] -> ShowS #

class Eq a => ProtectionIndicator a where Source #

Minimal complete definition

getProtected, getUnprotected

Methods

getProtected :: a Source #

Get a value for indicating protection.

getUnprotected :: Maybe a Source #

Get a Just a value for indicating no protection, or Nothing if the type does not support unprotected headers.

isProtected :: ProtectionIndicator p => Getter (HeaderParam p a) Bool Source #

Getter for whether a parameter is protected

param :: Lens' (HeaderParam p a) a Source #

Lens for a HeaderParam value

Defining header parsers

The parseParamsFor function defines the parser for a header type.

parseParamsFor
  :: (HasParams a, HasParams b)
  => Proxy b -> Maybe Object -> Maybe Object -> Parser a

It is defined over two objects: the protected header and the unprotected header. The following functions are provided for parsing header parameters:

headerOptional
An optional parameter that may be protected or unprotected.
headerRequired
A required parameter that may be protected or unprotected.
headerOptionalProtected
An optional parameter that, if present, MUST be carried in the protected header.
headerRequiredProtected
A required parameter that, if present, MUST be carried in the protected header.

Duplicate headers are forbidden. The above functions all perform duplicate header detection. If you do not use them, be sure to perform this detection yourself!

An example parser:

instance HasParams ACMEHeader where
  parseParamsFor proxy hp hu = ACMEHeader
    <$> parseParamsFor proxy hp hu
    <*> headerRequiredProtected "nonce" hp hu

class HasParams a where Source #

A thing with parameters.

Minimal complete definition

params, parseParamsFor

Methods

params :: ProtectionIndicator p => a p -> [(Bool, Pair)] Source #

Return a list of parameters, each paired with whether it is protected or not.

extensions :: Proxy a -> [Text] Source #

List of "known extensions", i.e. keys that may appear in the "crit" header parameter.

parseParamsFor :: (HasParams b, ProtectionIndicator p) => Proxy b -> Maybe Object -> Maybe Object -> Parser (a p) Source #

headerRequired :: (FromJSON a, ProtectionIndicator p) => Text -> Maybe Object -> Maybe Object -> Parser (HeaderParam p a) Source #

Parse a required parameter that may be carried in either the protected or the unprotected header.

headerRequiredProtected :: FromJSON a => Text -> Maybe Object -> Maybe Object -> Parser a Source #

Parse a required parameter that MUST be carried in the protected header.

headerOptional :: (FromJSON a, ProtectionIndicator p) => Text -> Maybe Object -> Maybe Object -> Parser (Maybe (HeaderParam p a)) Source #

Parse an optional parameter that may be carried in either the protected or the unprotected header.

headerOptionalProtected :: FromJSON a => Text -> Maybe Object -> Maybe Object -> Parser (Maybe a) Source #

Parse an optional parameter that, if present, MUST be carried in the protected header.

Parsing headers

parseParams Source #

Arguments

:: (HasParams a, ProtectionIndicator p) 
=> Maybe Object

protected header

-> Maybe Object

unprotected header

-> Parser (a p) 

Parse a pair of objects (protected and unprotected header)

This internally invokes parseParamsFor applied to a proxy for the target type. (This allows the parsing of the "crit" parameter to access "known extensions" understood by the target type.)

parseCrit Source #

Arguments

:: (Foldable t0, Foldable t1, Traversable t2, Traversable t3, Monad m) 
=> t0 Text

reserved header parameters

-> t1 Text

recognised extensions

-> Object

full header (union of protected and unprotected headers)

-> t2 (t3 Text)

crit header

-> m (t2 (t3 Text)) 

Parse a "crit" header param

Fails if:

  • any reserved header appears in "crit" header
  • any value in "crit" is not a recognised extension
  • any value in "crit" does not have a corresponding key in the object

Encoding headers

protectedParamsEncoded :: (HasParams a, ProtectionIndicator p) => a p -> ByteString Source #

Return the encoded protected parameters

unprotectedParams Source #

Arguments

:: (HasParams a, ProtectionIndicator p) 
=> a p 
-> Maybe Value

Object

Return unprotected params as a JSON Value (always an object)

Header fields shared by JWS and JWE

class HasAlg a where Source #

Minimal complete definition

alg

Methods

alg :: Lens' (a p) (HeaderParam p Alg) Source #

Instances

HasAlg JWSHeader Source # 

Methods

alg :: Functor f => (HeaderParam p Alg -> f (HeaderParam p Alg)) -> JWSHeader p -> f (JWSHeader p) Source #

class HasJku a where Source #

Minimal complete definition

jku

Methods

jku :: Lens' (a p) (Maybe (HeaderParam p URI)) Source #

Instances

class HasJwk a where Source #

Minimal complete definition

jwk

Methods

jwk :: Lens' (a p) (Maybe (HeaderParam p JWK)) Source #

Instances

class HasKid a where Source #

Minimal complete definition

kid

Methods

kid :: Lens' (a p) (Maybe (HeaderParam p String)) Source #

Instances

class HasX5u a where Source #

Minimal complete definition

x5u

Methods

x5u :: Lens' (a p) (Maybe (HeaderParam p URI)) Source #

Instances

class HasX5c a where Source #

Minimal complete definition

x5c

class HasX5t a where Source #

Minimal complete definition

x5t

Methods

x5t :: Lens' (a p) (Maybe (HeaderParam p Base64SHA1)) Source #

class HasX5tS256 a where Source #

Minimal complete definition

x5tS256

class HasTyp a where Source #

Minimal complete definition

typ

Methods

typ :: Lens' (a p) (Maybe (HeaderParam p String)) Source #

Instances

class HasCty a where Source #

Minimal complete definition

cty

Methods

cty :: Lens' (a p) (Maybe (HeaderParam p String)) Source #

Instances

class HasCrit a where Source #

Minimal complete definition

crit

Methods

crit :: Lens' (a p) (Maybe (NonEmpty Text)) Source #

Instances