| Safe Haskell | None |
|---|---|
| Language | GHC2021 |
Crypto.JOSE.Header
Description
Types and functions for working with JOSE header parameters.
Synopsis
- data HeaderParam p a = HeaderParam p a
- newHeaderParamProtected :: ProtectionIndicator p => a -> HeaderParam p a
- newHeaderParamUnprotected :: a -> HeaderParam OptionalProtection a
- class Eq a => ProtectionSupport a where
- getProtected :: a
- getUnprotected :: Maybe a
- type ProtectionIndicator = ProtectionSupport
- data OptionalProtection
- data RequiredProtection = RequiredProtection
- type Protection = OptionalProtection
- protection :: forall p a f. Functor f => (p -> f p) -> HeaderParam p a -> f (HeaderParam p a)
- isProtected :: ProtectionSupport p => Getter (HeaderParam p a) Bool
- param :: forall p a f. Functor f => (a -> f a) -> HeaderParam p a -> f (HeaderParam p a)
- class HasParams (a :: Type -> Type) where
- params :: ProtectionSupport p => a p -> [(Bool, Pair)]
- extensions :: Proxy a -> [Text]
- parseParamsFor :: forall (b :: Type -> Type) p. (HasParams b, ProtectionSupport p) => Proxy b -> Maybe Object -> Maybe Object -> Parser (a p)
- headerRequired :: (FromJSON a, ProtectionSupport p) => Text -> Maybe Object -> Maybe Object -> Parser (HeaderParam p a)
- headerRequiredProtected :: FromJSON a => Text -> Maybe Object -> Maybe Object -> Parser a
- headerOptional :: (FromJSON a, ProtectionSupport p) => Text -> Maybe Object -> Maybe Object -> Parser (Maybe (HeaderParam p a))
- headerOptional' :: ProtectionSupport p => (Value -> Parser a) -> Text -> Maybe Object -> Maybe Object -> Parser (Maybe (HeaderParam p a))
- headerOptionalProtected :: FromJSON a => Text -> Maybe Object -> Maybe Object -> Parser (Maybe a)
- parseParams :: (HasParams a, ProtectionSupport p) => Maybe Object -> Maybe Object -> Parser (a p)
- parseCrit :: (Foldable t0, Foldable t1, Traversable t2, Traversable t3, MonadFail m) => t0 Text -> t1 Text -> Object -> t2 (t3 Text) -> m (t2 (t3 Text))
- protectedParamsEncoded :: (HasParams a, ProtectionSupport p) => a p -> ByteString
- unprotectedParams :: (HasParams a, ProtectionSupport p) => a p -> Maybe Value
- class HasAlg (a :: Type -> Type) where
- alg :: Lens' (a p) (HeaderParam p Alg)
- class HasJku (a :: Type -> Type) where
- jku :: Lens' (a p) (Maybe (HeaderParam p URI))
- class HasJwk (a :: Type -> Type) where
- jwk :: Lens' (a p) (Maybe (HeaderParam p JWK))
- class HasKid (a :: Type -> Type) where
- kid :: Lens' (a p) (Maybe (HeaderParam p Text))
- class HasX5u (a :: Type -> Type) where
- x5u :: Lens' (a p) (Maybe (HeaderParam p URI))
- class HasX5c (a :: Type -> Type) where
- x5c :: Lens' (a p) (Maybe (HeaderParam p (NonEmpty SignedCertificate)))
- class HasX5t (a :: Type -> Type) where
- x5t :: Lens' (a p) (Maybe (HeaderParam p Base64SHA1))
- class HasX5tS256 (a :: Type -> Type) where
- x5tS256 :: Lens' (a p) (Maybe (HeaderParam p Base64SHA256))
- class HasTyp (a :: Type -> Type) where
- typ :: Lens' (a p) (Maybe (HeaderParam p Text))
- class HasCty (a :: Type -> Type) where
- cty :: Lens' (a p) (Maybe (HeaderParam p Text))
- class HasCrit (a :: k -> Type) where
Constructing header parameters
data HeaderParam p a Source #
A header value, along with a protection indicator.
Constructors
| HeaderParam p a |
Instances
| Functor (HeaderParam p) Source # | |
Defined in Crypto.JOSE.Header Methods fmap :: (a -> b) -> HeaderParam p a -> HeaderParam p b # (<$) :: a -> HeaderParam p b -> HeaderParam p a # | |
| (Show p, Show a) => Show (HeaderParam p a) Source # | |
Defined in Crypto.JOSE.Header Methods showsPrec :: Int -> HeaderParam p a -> ShowS # show :: HeaderParam p a -> String # showList :: [HeaderParam p a] -> ShowS # | |
| (Eq p, Eq a) => Eq (HeaderParam p a) Source # | |
Defined in Crypto.JOSE.Header Methods (==) :: HeaderParam p a -> HeaderParam p a -> Bool # (/=) :: HeaderParam p a -> HeaderParam p a -> Bool # | |
newHeaderParamProtected :: ProtectionIndicator p => a -> HeaderParam p a Source #
Convenience constructor for a protected HeaderParam.
newHeaderParamUnprotected :: a -> HeaderParam OptionalProtection a Source #
Convenience constructor for a protected HeaderParam.
Header protection support
class Eq a => ProtectionSupport a where Source #
Class that defines the protected and (if supported) unprotected values for a protection indicator data type.
Methods
getProtected :: a Source #
Get a value for indicating protection.
getUnprotected :: Maybe a Source #
Instances
| ProtectionSupport OptionalProtection Source # | |
Defined in Crypto.JOSE.Header | |
| ProtectionSupport RequiredProtection Source # | |
Defined in Crypto.JOSE.Header | |
type ProtectionIndicator = ProtectionSupport Source #
Deprecated: renamed to 'ProtectionSupport.
data OptionalProtection Source #
Use this protection type when the serialisation supports both protected and unprotected headers.
Constructors
| Protected | |
| Unprotected |
Instances
| Show OptionalProtection Source # | |
Defined in Crypto.JOSE.Header Methods showsPrec :: Int -> OptionalProtection -> ShowS # show :: OptionalProtection -> String # showList :: [OptionalProtection] -> ShowS # | |
| Eq OptionalProtection Source # | |
Defined in Crypto.JOSE.Header Methods (==) :: OptionalProtection -> OptionalProtection -> Bool # (/=) :: OptionalProtection -> OptionalProtection -> Bool # | |
| ProtectionSupport OptionalProtection Source # | |
Defined in Crypto.JOSE.Header | |
data RequiredProtection Source #
Use this protection type when the serialisation only supports protected headers.
Constructors
| RequiredProtection |
Instances
| Show RequiredProtection Source # | |
Defined in Crypto.JOSE.Header Methods showsPrec :: Int -> RequiredProtection -> ShowS # show :: RequiredProtection -> String # showList :: [RequiredProtection] -> ShowS # | |
| Eq RequiredProtection Source # | |
Defined in Crypto.JOSE.Header Methods (==) :: RequiredProtection -> RequiredProtection -> Bool # (/=) :: RequiredProtection -> RequiredProtection -> Bool # | |
| ProtectionSupport RequiredProtection Source # | |
Defined in Crypto.JOSE.Header | |
| HasParams a => FromCompact (JWS Identity RequiredProtection a) Source # | |
Defined in Crypto.JOSE.JWS Methods fromCompact :: (AsError e, MonadError e m) => [ByteString] -> m (JWS Identity RequiredProtection a) Source # | |
| HasParams a => ToCompact (JWS Identity RequiredProtection a) Source # | |
Defined in Crypto.JOSE.JWS Methods toCompact :: JWS Identity RequiredProtection a -> [ByteString] Source # | |
type Protection = OptionalProtection Source #
Deprecated: renamed to OptionalProtection.
protection :: forall p a f. Functor f => (p -> f p) -> HeaderParam p a -> f (HeaderParam p a) Source #
Lens for the Protection of a HeaderParam
isProtected :: ProtectionSupport p => Getter (HeaderParam p a) Bool Source #
Getter for whether a parameter is protected
param :: forall p a f. Functor f => (a -> f a) -> HeaderParam p a -> f (HeaderParam p a) Source #
Lens for a HeaderParam value
Defining header parsers
The parseParamsFor function defines the parser for a header type.
parseParamsFor:: (HasParamsa, HasParams b) => Proxy b -> Maybe Object -> Maybe Object ->Parsera
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 whereparseParamsForproxy hp hu = ACMEHeader <$>parseParamsForproxy hp hu <*>headerRequiredProtected"nonce" hp hu
class HasParams (a :: Type -> Type) where Source #
A thing with parameters.
Minimal complete definition
Methods
params :: ProtectionSupport 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 :: forall (b :: Type -> Type) p. (HasParams b, ProtectionSupport p) => Proxy b -> Maybe Object -> Maybe Object -> Parser (a p) Source #
Instances
| HasParams JWEHeader Source # | |
Defined in Crypto.JOSE.JWE | |
| HasParams JWSHeader Source # | |
Defined in Crypto.JOSE.JWS | |
headerRequired :: (FromJSON a, ProtectionSupport 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, ProtectionSupport 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.
headerOptional' :: ProtectionSupport p => (Value -> Parser a) -> 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. Like headerOptional,
but with an explicit argument for the parser.
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
Arguments
| :: (HasParams a, ProtectionSupport 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.)
Arguments
| :: (Foldable t0, Foldable t1, Traversable t2, Traversable t3, MonadFail 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, ProtectionSupport p) => a p -> ByteString Source #
Return the base64url-encoded protected parameters
Arguments
| :: (HasParams a, ProtectionSupport 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 :: Type -> Type) where Source #
Instances
| HasJWSHeader a => HasAlg a Source # | |
Defined in Crypto.JOSE.JWS | |
class HasJku (a :: Type -> Type) where Source #
Instances
| HasJWSHeader a => HasJku a Source # | |
Defined in Crypto.JOSE.JWS | |
class HasJwk (a :: Type -> Type) where Source #
Instances
| HasJWSHeader a => HasJwk a Source # | |
Defined in Crypto.JOSE.JWS | |
class HasKid (a :: Type -> Type) where Source #
Instances
| HasJWSHeader a => HasKid a Source # | |
Defined in Crypto.JOSE.JWS | |
class HasX5u (a :: Type -> Type) where Source #
Instances
| HasJWSHeader a => HasX5u a Source # | |
Defined in Crypto.JOSE.JWS | |
class HasX5c (a :: Type -> Type) where Source #
Methods
x5c :: Lens' (a p) (Maybe (HeaderParam p (NonEmpty SignedCertificate))) Source #
Instances
| HasJWSHeader a => HasX5c a Source # | |
Defined in Crypto.JOSE.JWS Methods x5c :: Lens' (a p) (Maybe (HeaderParam p (NonEmpty SignedCertificate))) Source # | |
class HasX5t (a :: Type -> Type) where Source #
Methods
x5t :: Lens' (a p) (Maybe (HeaderParam p Base64SHA1)) Source #
Instances
| HasJWSHeader a => HasX5t a Source # | |
Defined in Crypto.JOSE.JWS Methods x5t :: Lens' (a p) (Maybe (HeaderParam p Base64SHA1)) Source # | |
class HasX5tS256 (a :: Type -> Type) where Source #
Methods
x5tS256 :: Lens' (a p) (Maybe (HeaderParam p Base64SHA256)) Source #
Instances
| HasJWSHeader a => HasX5tS256 a Source # | |
Defined in Crypto.JOSE.JWS Methods x5tS256 :: Lens' (a p) (Maybe (HeaderParam p Base64SHA256)) Source # | |
class HasTyp (a :: Type -> Type) where Source #
Instances
| HasJWSHeader a => HasTyp a Source # | |
Defined in Crypto.JOSE.JWS | |
class HasCty (a :: Type -> Type) where Source #
Instances
| HasJWSHeader a => HasCty a Source # | |
Defined in Crypto.JOSE.JWS | |