webauthn-0.5.0.1: Relying party (server) implementation of the WebAuthn 2 specification
Stabilityexperimental
Safe HaskellSafe-Inferred
LanguageHaskell2010

Crypto.WebAuthn.Cose.SignAlg

Description

This module contains definitions for COSE registry entries that are relevant for Webauthn COSE public keys. All the types in this module implement the Serialise class, mapping them to the respective CBOR values/labels.

This modules sometimes uses this CBOR Grammar to describe CBOR value types corresponding to CBOR parameters

Synopsis

COSE Algorithms

data CoseSignAlg Source #

(spec) All the entries from the COSE Algorithms registry limited to the ones that are currently needed for Webauthn. Notably we only care about asymmetric signature algorithms

Constructors

CoseSignAlgEdDSA

(spec) EdDSA

RFC8032 describes the elliptic curve signature scheme Edwards-curve Digital Signature Algorithm (EdDSA). In that document, the signature algorithm is instantiated using parameters for edwards25519 and edwards448 curves. The document additionally describes two variants of the EdDSA algorithm: Pure EdDSA, where no hash function is applied to the content before signing, and HashEdDSA, where a hash function is applied to the content before signing and the result of that hash function is signed. For EdDSA, the content to be signed (either the message or the pre-hash value) is processed twice inside of the signature algorithm. For use with COSE, only the pure EdDSA version is used.

Security considerations are here

CoseSignAlgECDSA CoseHashAlgECDSA

(spec) ECDSA

ECDSA [DSS] defines a signature algorithm using ECC. Implementations SHOULD use a deterministic version of ECDSA such as the one defined in [RFC6979].

The ECDSA signature algorithm is parameterized with a hash function (h). In the event that the length of the hash function output is greater than the group of the key, the leftmost bytes of the hash output are used. ECDSA w/ SHA-256

This document defines ECDSA to work only with the curves P-256, P-384, and P-521. Future documents may define it to work with other curves and points in the future.

In order to promote interoperability, it is suggested that SHA-256 be used only with curve P-256, SHA-384 be used only with curve P-384, and SHA-512 be used with curve P-521. This is aligned with the recommendation in Section 4 of RFC5480

Security considerations are here

CoseSignAlgRSA CoseHashAlgRSA

(spec) The RSASSA-PKCS1-v1_5 signature algorithm is defined in RFC8017. The RSASSA-PKCS1-v1_5 signature algorithm is parameterized with a hash function (h).

A key of size 2048 bits or larger MUST be used with these algorithms.

Security considerations are here

Bundled Patterns

pattern CoseAlgorithmEdDSA :: CoseSignAlg

(spec) Cose Algorithm registry entry EdDSA. Alias for CoseSignAlgEdDSA

  • Name: EdDSA
  • Description: EdDSA
  • Recommended: Yes
pattern CoseAlgorithmES256 :: CoseSignAlg

(spec) Cose Algorithm registry entry ES256. Alias for CoseSignAlgECDSA CoseHashAlgECDSASHA256

  • Name: ES256
  • Description: ECDSA w/ SHA-256
  • Recommended: Yes
pattern CoseAlgorithmES384 :: CoseSignAlg

(spec) Cose Algorithm registry entry ES384. Alias for CoseSignAlgECDSA CoseHashAlgECDSASHA384

  • Name: ES384
  • Description: ECDSA w/ SHA-384
  • Recommended: Yes
pattern CoseAlgorithmES512 :: CoseSignAlg

(spec) Cose Algorithm registry entry ES512. Alias for CoseSignAlgECDSA CoseHashAlgECDSASHA512

  • Name: ES512
  • Description: ECDSA w/ SHA-512
  • Recommended: Yes
pattern CoseAlgorithmRS256 :: CoseSignAlg

(spec) Cose Algorithm registry entry RS256. Alias for CoseSignAlgRSA CoseHashAlgRSASHA256

  • Name: RS256
  • Description: RSASSA-PKCS1-v1_5 using SHA-256
  • Recommended: No
pattern CoseAlgorithmRS384 :: CoseSignAlg

(spec) Cose Algorithm registry entry RS384. Alias for CoseSignAlgRSA CoseHashAlgRSASHA384

  • Name: RS384
  • Description: RSASSA-PKCS1-v1_5 using SHA-384
  • Recommended: No
pattern CoseAlgorithmRS512 :: CoseSignAlg

(spec) Cose Algorithm registry entry RS512. Alias for CoseSignAlgRSA CoseHashAlgRSASHA512

  • Name: RS512
  • Description: RSASSA-PKCS1-v1_5 using SHA-512
  • Recommended: No
pattern CoseAlgorithmRS1 :: CoseSignAlg

(spec) Cose Algorithm registry entry RS1. Alias for CoseSignAlgRSA CoseHashAlgRSASHA1

  • Name: RS1
  • Description: RSASSA-PKCS1-v1_5 using SHA-1
  • Recommended: Deprecated

Instances

Instances details
ToJSON CoseSignAlg Source # 
Instance details

Defined in Crypto.WebAuthn.Cose.SignAlg

Generic CoseSignAlg Source # 
Instance details

Defined in Crypto.WebAuthn.Cose.SignAlg

Associated Types

type Rep CoseSignAlg :: Type -> Type #

Show CoseSignAlg Source # 
Instance details

Defined in Crypto.WebAuthn.Cose.SignAlg

Eq CoseSignAlg Source # 
Instance details

Defined in Crypto.WebAuthn.Cose.SignAlg

Ord CoseSignAlg Source # 
Instance details

Defined in Crypto.WebAuthn.Cose.SignAlg

Serialise CoseSignAlg Source #

Serialises COSE Algorithms using the Value column from the COSE Algorithms registry. This uses the fromCoseSignAlg and toCoseSignAlg functions to do the encoding and decoding respectively.

Instance details

Defined in Crypto.WebAuthn.Cose.SignAlg

Encode CoseSignAlg Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Associated Types

type JSON CoseSignAlg Source #

Decode m CoseSignAlg Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

type Rep CoseSignAlg Source # 
Instance details

Defined in Crypto.WebAuthn.Cose.SignAlg

type Rep CoseSignAlg = D1 ('MetaData "CoseSignAlg" "Crypto.WebAuthn.Cose.SignAlg" "webauthn-0.5.0.1-inplace" 'False) (C1 ('MetaCons "CoseSignAlgEdDSA" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CoseSignAlgECDSA" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CoseHashAlgECDSA)) :+: C1 ('MetaCons "CoseSignAlgRSA" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CoseHashAlgRSA))))
type JSON CoseSignAlg Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

fromCoseSignAlg :: Num p => CoseSignAlg -> p Source #

Converts a CoseSignAlg to the corresponding integer value from the COSE Algorithms registry. The inverse operation is toCoseSignAlg

toCoseSignAlg :: (Eq a, Num a, Show a) => a -> Either Text CoseSignAlg Source #

Converts an integer value to the corresponding CoseSignAlg from the COSE Algorithms registry. Returns an error if the integer doesn't represent a known algorithm. The inverse operation is fromCoseSignAlg

Hash Algorithms

data CoseHashAlgECDSA Source #

Hash algorithms that can be used with the ECDSA signature algorithm

Instances

Instances details
ToJSON CoseHashAlgECDSA Source # 
Instance details

Defined in Crypto.WebAuthn.Cose.SignAlg

Bounded CoseHashAlgECDSA Source # 
Instance details

Defined in Crypto.WebAuthn.Cose.SignAlg

Enum CoseHashAlgECDSA Source # 
Instance details

Defined in Crypto.WebAuthn.Cose.SignAlg

Generic CoseHashAlgECDSA Source # 
Instance details

Defined in Crypto.WebAuthn.Cose.SignAlg

Associated Types

type Rep CoseHashAlgECDSA :: Type -> Type #

Show CoseHashAlgECDSA Source # 
Instance details

Defined in Crypto.WebAuthn.Cose.SignAlg

Eq CoseHashAlgECDSA Source # 
Instance details

Defined in Crypto.WebAuthn.Cose.SignAlg

Ord CoseHashAlgECDSA Source # 
Instance details

Defined in Crypto.WebAuthn.Cose.SignAlg

type Rep CoseHashAlgECDSA Source # 
Instance details

Defined in Crypto.WebAuthn.Cose.SignAlg

type Rep CoseHashAlgECDSA = D1 ('MetaData "CoseHashAlgECDSA" "Crypto.WebAuthn.Cose.SignAlg" "webauthn-0.5.0.1-inplace" 'False) (C1 ('MetaCons "CoseHashAlgECDSASHA256" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CoseHashAlgECDSASHA384" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CoseHashAlgECDSASHA512" 'PrefixI 'False) (U1 :: Type -> Type)))

data CoseHashAlgRSA Source #

Hash algorithms that can be used with the RSA signature algorithm

Instances

Instances details
ToJSON CoseHashAlgRSA Source # 
Instance details

Defined in Crypto.WebAuthn.Cose.SignAlg

Bounded CoseHashAlgRSA Source # 
Instance details

Defined in Crypto.WebAuthn.Cose.SignAlg

Enum CoseHashAlgRSA Source # 
Instance details

Defined in Crypto.WebAuthn.Cose.SignAlg

Generic CoseHashAlgRSA Source # 
Instance details

Defined in Crypto.WebAuthn.Cose.SignAlg

Associated Types

type Rep CoseHashAlgRSA :: Type -> Type #

Show CoseHashAlgRSA Source # 
Instance details

Defined in Crypto.WebAuthn.Cose.SignAlg

Eq CoseHashAlgRSA Source # 
Instance details

Defined in Crypto.WebAuthn.Cose.SignAlg

Ord CoseHashAlgRSA Source # 
Instance details

Defined in Crypto.WebAuthn.Cose.SignAlg

type Rep CoseHashAlgRSA Source # 
Instance details

Defined in Crypto.WebAuthn.Cose.SignAlg

type Rep CoseHashAlgRSA = D1 ('MetaData "CoseHashAlgRSA" "Crypto.WebAuthn.Cose.SignAlg" "webauthn-0.5.0.1-inplace" 'False) ((C1 ('MetaCons "CoseHashAlgRSASHA1" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CoseHashAlgRSASHA256" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CoseHashAlgRSASHA384" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CoseHashAlgRSASHA512" 'PrefixI 'False) (U1 :: Type -> Type)))