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

Crypto.WebAuthn.Model.Types

Description

This module contains Haskell-friendly types for structures used in WebAuthn that are used throughout this library. These types are modelled according to the following conventions:

  • If a structure has the same semantics for both the registration and authentication WebAuthn ceremonies, then its type is parametrized by a c parameter of kind CeremonyKind. If such types have differing fields, GADTs are used to distinguish between them, where the constructor name is the type name with a ...Registration or ...Authentication suffix
  • If the raw bytes are needed for verification purposes of a structure, then its type is parametrized by a raw parameter of kind Bool. Only if raw ~ True, the raw bytes of the necessary structures has to be present in the type. The type RawField is used as a helper type for this.
  • In order to avoid duplicate record fields, all fields are prefixed with the initials of the constructor name.
  • Every type should have a ToJSON instance for pretty-printing purposes. This JSON encoding doesn't correspond to any encoding used for sending/receiving these structures, it's only used for pretty-printing, which is why it doesn't need to be standardized. For encoding these structures fromto JSON for sendingreceiving, see the WebIDL module
  • Fields of the WebAuthn standard that are optional (for writing) but have defaults (making them non-optional for reading) are encoded as non-optional fields, while the defaults are exposed in the Defaults module. The alternative of making these fields optional would allow RP not having to specify them, which seems like a less safer option, since the defaults might not be what is really needed, and they might change. The root cause why this decision had to be made is that such assymetrical reading/writing fields don't map nicely to Haskell's records.

TODO: (spec) This library does not currently implement most extensions. In order to fully comply with level 2 of the webauthn spec extensions are required. At least, we wish the library to offer a typeclass implementable by relying parties to allow extensions in a scheme similar to the attestation statement formats. Ideally, we would implement all 8 extensions tracked by IANA.

Synopsis

Enumerations

data CredentialType Source #

(spec) This enumeration defines the valid credential types. It is an extension point; values can be added to it in the future, as more credential types are defined. The values of this enumeration are used for versioning the Authentication Assertion and attestation structures according to the type of the authenticator.

To decode/encode this type from/to its standard string, use decodeCredentialType/encodeCredentialType.

Instances

Instances details
ToJSON CredentialType Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Bounded CredentialType Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Enum CredentialType Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Generic CredentialType Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Associated Types

type Rep CredentialType :: Type -> Type #

Show CredentialType Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Eq CredentialType Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Ord CredentialType Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Encode CredentialType Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Associated Types

type JSON CredentialType Source #

Decode m CredentialType Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

type Rep CredentialType Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

type Rep CredentialType = D1 ('MetaData "CredentialType" "Crypto.WebAuthn.Model.Types" "webauthn-0.6.0.1-inplace" 'False) (C1 ('MetaCons "CredentialTypePublicKey" 'PrefixI 'False) (U1 :: Type -> Type))
type JSON CredentialType Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

data AuthenticatorTransport Source #

(spec) Authenticators may implement various transports for communicating with clients. This enumeration defines hints as to how clients might communicate with a particular authenticator in order to obtain an assertion for a specific credential. Note that these hints represent the WebAuthn Relying Party's best belief as to how an authenticator may be reached. A Relying Party will typically learn of the supported transports for a public key credential via getTransports().

To decode/encode this type from/to its standard string, use decodeAuthenticatorTransport/encodeAuthenticatorTransport.

Constructors

AuthenticatorTransportUSB

(spec) Indicates the respective authenticator can be contacted over removable USB.

AuthenticatorTransportNFC

(spec) Indicates the respective authenticator can be contacted over Near Field Communication (NFC).

AuthenticatorTransportBLE

(spec) Indicates the respective authenticator can be contacted over Bluetooth Smart (Bluetooth Low Energy / BLE).

AuthenticatorTransportInternal

(spec) Indicates the respective authenticator is contacted using a client device-specific transport, i.e., it is a platform authenticator. These authenticators are not removable from the client device.

AuthenticatorTransportUnknown Text

(spec) An unknown authenticator transport. Note that according to the current version 2 of the WebAuthn standard, unknown fields must be ignored, which is a bit misleading because such unknown values still need to be stored. Draft version 3 of the standard fixes this.

Instances

Instances details
ToJSON AuthenticatorTransport Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Generic AuthenticatorTransport Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Associated Types

type Rep AuthenticatorTransport :: Type -> Type #

Show AuthenticatorTransport Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Eq AuthenticatorTransport Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Ord AuthenticatorTransport Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Encode AuthenticatorTransport Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Associated Types

type JSON AuthenticatorTransport Source #

Decode m AuthenticatorTransport Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

type Rep AuthenticatorTransport Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

type Rep AuthenticatorTransport = D1 ('MetaData "AuthenticatorTransport" "Crypto.WebAuthn.Model.Types" "webauthn-0.6.0.1-inplace" 'False) ((C1 ('MetaCons "AuthenticatorTransportUSB" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AuthenticatorTransportNFC" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "AuthenticatorTransportBLE" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "AuthenticatorTransportInternal" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AuthenticatorTransportUnknown" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))))
type JSON AuthenticatorTransport Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

data AuthenticatorAttachment Source #

(spec) This enumeration’s values describe authenticators' attachment modalities. Relying Parties use this to express a preferred authenticator attachment modality when calling navigator.credentials.create() to create a credential.

To decode/encode this type from/to its standard string, use decodeAuthenticatorAttachment/encodeAuthenticatorAttachment.

Instances

Instances details
ToJSON AuthenticatorAttachment Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Bounded AuthenticatorAttachment Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Enum AuthenticatorAttachment Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Generic AuthenticatorAttachment Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Associated Types

type Rep AuthenticatorAttachment :: Type -> Type #

Show AuthenticatorAttachment Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Eq AuthenticatorAttachment Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Ord AuthenticatorAttachment Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Encode AuthenticatorAttachment Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Associated Types

type JSON AuthenticatorAttachment Source #

Decode m AuthenticatorAttachment Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

type Rep AuthenticatorAttachment Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

type Rep AuthenticatorAttachment = D1 ('MetaData "AuthenticatorAttachment" "Crypto.WebAuthn.Model.Types" "webauthn-0.6.0.1-inplace" 'False) (C1 ('MetaCons "AuthenticatorAttachmentPlatform" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AuthenticatorAttachmentCrossPlatform" 'PrefixI 'False) (U1 :: Type -> Type))
type JSON AuthenticatorAttachment Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

data ResidentKeyRequirement Source #

(spec) This enumeration’s values describe the Relying Party's requirements for client-side discoverable credentials (formerly known as resident credentials or resident keys):

To decode/encode this type from/to its standard string, use decodeResidentKeyRequirement/encodeResidentKeyRequirement.

Constructors

ResidentKeyRequirementDiscouraged

(spec) This value indicates the Relying Party prefers creating a server-side credential, but will accept a client-side discoverable credential.

ResidentKeyRequirementPreferred

(spec) This value indicates the Relying Party strongly prefers creating a client-side discoverable credential, but will accept a server-side credential. For example, user agents SHOULD guide the user through setting up user verification if needed to create a client-side discoverable credential in this case. This takes precedence over the setting of coaUserVerification.

ResidentKeyRequirementRequired

(spec) This value indicates the Relying Party requires a client-side discoverable credential, and is prepared to receive an error if a client-side discoverable credential cannot be created.

Instances

Instances details
ToJSON ResidentKeyRequirement Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Bounded ResidentKeyRequirement Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Enum ResidentKeyRequirement Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Generic ResidentKeyRequirement Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Associated Types

type Rep ResidentKeyRequirement :: Type -> Type #

Show ResidentKeyRequirement Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Eq ResidentKeyRequirement Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Ord ResidentKeyRequirement Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Encode ResidentKeyRequirement Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Associated Types

type JSON ResidentKeyRequirement Source #

Decode m ResidentKeyRequirement Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

type Rep ResidentKeyRequirement Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

type Rep ResidentKeyRequirement = D1 ('MetaData "ResidentKeyRequirement" "Crypto.WebAuthn.Model.Types" "webauthn-0.6.0.1-inplace" 'False) (C1 ('MetaCons "ResidentKeyRequirementDiscouraged" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ResidentKeyRequirementPreferred" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ResidentKeyRequirementRequired" 'PrefixI 'False) (U1 :: Type -> Type)))
type JSON ResidentKeyRequirement Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

data UserVerificationRequirement Source #

(spec) A WebAuthn Relying Party may require user verification for some of its operations but not for others, and may use this type to express its needs.

To decode/encode this type from/to its standard string, use decodeUserVerificationRequirement/encodeUserVerificationRequirement.

Constructors

UserVerificationRequirementRequired

(spec) This value indicates that the Relying Party requires user verification for the operation and will fail the operation if the response does not have the UV flag set.

UserVerificationRequirementPreferred

(spec) This value indicates that the Relying Party prefers user verification for the operation if possible, but will not fail the operation if the response does not have the UV flag set.

UserVerificationRequirementDiscouraged

(spec) This value indicates that the Relying Party does not want user verification employed during the operation (e.g., in the interest of minimizing disruption to the user interaction flow).

Instances

Instances details
ToJSON UserVerificationRequirement Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Bounded UserVerificationRequirement Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Enum UserVerificationRequirement Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Generic UserVerificationRequirement Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Associated Types

type Rep UserVerificationRequirement :: Type -> Type #

Show UserVerificationRequirement Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Eq UserVerificationRequirement Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Ord UserVerificationRequirement Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Encode UserVerificationRequirement Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Decode m UserVerificationRequirement Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

type Rep UserVerificationRequirement Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

type Rep UserVerificationRequirement = D1 ('MetaData "UserVerificationRequirement" "Crypto.WebAuthn.Model.Types" "webauthn-0.6.0.1-inplace" 'False) (C1 ('MetaCons "UserVerificationRequirementRequired" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "UserVerificationRequirementPreferred" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UserVerificationRequirementDiscouraged" 'PrefixI 'False) (U1 :: Type -> Type)))
type JSON UserVerificationRequirement Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

data AttestationConveyancePreference Source #

(spec) WebAuthn Relying Parties may use AttestationConveyancePreference to specify their preference regarding attestation conveyance during credential generation.

To decode/encode this type from/to its standard string, use decodeAttestationConveyancePreference/encodeAttestationConveyancePreference.

Constructors

AttestationConveyancePreferenceNone

(spec) This value indicates that the Relying Party is not interested in authenticator attestation. For example, in order to potentially avoid having to obtain user consent to relay identifying information to the Relying Party, or to save a roundtrip to an Attestation CA or Anonymization CA. This is the default value.

AttestationConveyancePreferenceIndirect

(spec) This value indicates that the Relying Party prefers an attestation conveyance yielding verifiable attestation statements, but allows the client to decide how to obtain such attestation statements. The client MAY replace the authenticator-generated attestation statements with attestation statements generated by an Anonymization CA, in order to protect the user’s privacy, or to assist Relying Parties with attestation verification in a heterogeneous ecosystem.

Note: There is no guarantee that the Relying Party will obtain a verifiable attestation statement in this case. For example, in the case that the authenticator employs self attestation.

AttestationConveyancePreferenceDirect

(spec) This value indicates that the Relying Party wants to receive the attestation statement as generated by the authenticator.

AttestationConveyancePreferenceEnterprise

(spec) This value indicates that the Relying Party wants to receive an attestation statement that may include uniquely identifying information. This is intended for controlled deployments within an enterprise where the organization wishes to tie registrations to specific authenticators. User agents MUST NOT provide such an attestation unless the user agent or authenticator configuration permits it for the requested RpId.

If permitted, the user agent SHOULD signal to the authenticator (at invocation time) that enterprise attestation is requested, and convey the resulting AAGUID and attestation statement, unaltered, to the Relying Party.

Instances

Instances details
ToJSON AttestationConveyancePreference Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Bounded AttestationConveyancePreference Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Enum AttestationConveyancePreference Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Generic AttestationConveyancePreference Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Associated Types

type Rep AttestationConveyancePreference :: Type -> Type #

Show AttestationConveyancePreference Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Eq AttestationConveyancePreference Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Ord AttestationConveyancePreference Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Encode AttestationConveyancePreference Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Decode m AttestationConveyancePreference Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

type Rep AttestationConveyancePreference Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

type Rep AttestationConveyancePreference = D1 ('MetaData "AttestationConveyancePreference" "Crypto.WebAuthn.Model.Types" "webauthn-0.6.0.1-inplace" 'False) ((C1 ('MetaCons "AttestationConveyancePreferenceNone" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AttestationConveyancePreferenceIndirect" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "AttestationConveyancePreferenceDirect" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AttestationConveyancePreferenceEnterprise" 'PrefixI 'False) (U1 :: Type -> Type)))
type JSON AttestationConveyancePreference Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

data AttestationChain (p :: ProtocolKind) where Source #

An X.509 certificate chain that can be used to verify an attestation statement

Constructors

Fido2Chain :: NonEmpty SignedCertificate -> AttestationChain 'Fido2

For Fido 2, we can have a chain consisting of multiple certificates.

FidoU2FCert :: SignedCertificate -> AttestationChain 'FidoU2F

For Fido U2F, we can only have a single certificate, which is then also used to generate the SubjectKeyIdentifier from

data AttestationKind Source #

A Haskell kind for the attestation type, indicating whether we have verifiable information about the authenticator that created the public key credential.

Constructors

Unverifiable

An unverifiable attestation type. This includes None and Self attestation. This kind indicates that we do not have any information about the authenticator model used.

Verifiable ProtocolKind

A verifiable attestation type. This includes Basic, AttCA and AnonCA attestation. This kind indicates that we have verifiable information about the authenticator model used.

data AttestationType (k :: AttestationKind) where Source #

(spec) WebAuthn supports several attestation types, defining the semantics of attestation statements and their underlying trust models:

Constructors

AttestationTypeNone :: AttestationType 'Unverifiable

(spec) In this case, no attestation information is available. See also § 8.7 None Attestation Statement Format.

AttestationTypeSelf :: AttestationType 'Unverifiable

(spec) In the case of self attestation, also known as surrogate basic attestation UAFProtocol, the Authenticator does not have any specific attestation key pair. Instead it uses the credential private key to create the attestation signature. Authenticators without meaningful protection measures for an attestation private key typically use this attestation type.

AttestationTypeVerifiable

Grouping of attestations that are verifiable by a certificate chain

Fields

data VerifiableAttestationType Source #

An attestation type that is verifiable, indicating that we can have trusted information about the authenticator that created the public key credential

Constructors

VerifiableAttestationTypeUncertain

Attestation statements conveying attestations of type AttCA or AnonCA use the same data structure as those of type Basic, so the three attestation types are, in general, distinguishable only with externally provided knowledge regarding the contents of the attestation certificates conveyed in the attestation statement.

VerifiableAttestationTypeBasic

(spec) In the case of basic attestation UAFProtocol, the authenticator’s attestation key pair is specific to an authenticator "model", i.e., a "batch" of authenticators. Thus, authenticators of the same, or similar, model often share the same attestation key pair. See § 14.4.1 Attestation Privacy for further information.

VerifiableAttestationTypeAttCA

(spec) In this case, an authenticator is based on a Trusted Platform Module (TPM) and holds an authenticator-specific "endorsement key" (EK). This key is used to securely communicate with a trusted third party, the Attestation CA TCG-CMCProfile-AIKCertEnroll (formerly known as a "Privacy CA"). The authenticator can generate multiple attestation identity key pairs (AIK) and requests an Attestation CA to issue an AIK certificate for each. Using this approach, such an authenticator can limit the exposure of the EK (which is a global correlation handle) to Attestation CA(s). AIKs can be requested for each authenticator-generated public key credential individually, and conveyed to Relying Parties as attestation certificates.

VerifiableAttestationTypeAnonCA

(spec) In this case, the authenticator uses an Anonymization CA which dynamically generates per-[credential](https:/w3c.github.iowebappsec-credential-management/#concept-credential) attestation certificates such that the attestation statements presented to Relying Parties do not provide uniquely identifiable information, e.g., that might be used for tracking purposes.

Instances

Instances details
ToJSON VerifiableAttestationType Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Bounded VerifiableAttestationType Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Enum VerifiableAttestationType Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Generic VerifiableAttestationType Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Associated Types

type Rep VerifiableAttestationType :: Type -> Type #

Show VerifiableAttestationType Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Eq VerifiableAttestationType Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Ord VerifiableAttestationType Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

type Rep VerifiableAttestationType Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

type Rep VerifiableAttestationType = D1 ('MetaData "VerifiableAttestationType" "Crypto.WebAuthn.Model.Types" "webauthn-0.6.0.1-inplace" 'False) ((C1 ('MetaCons "VerifiableAttestationTypeUncertain" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "VerifiableAttestationTypeBasic" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "VerifiableAttestationTypeAttCA" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "VerifiableAttestationTypeAnonCA" 'PrefixI 'False) (U1 :: Type -> Type)))

Newtypes

newtype RpId Source #

(spec) A valid domain string identifying the WebAuthn Relying Party on whose behalf a given registration or authentication ceremony is being performed. A public key credential can only be used for authentication with the same entity (as identified by RpId) it was registered with.

By default, the RpId for a WebAuthn operation is set to the caller’s origin's effective domain. This default MAY be overridden by the caller, as long as the caller-specified RpId value is a registrable domain suffix of or is equal to the caller’s origin's effective domain.

TODO: RpId is used for both https://www.w3.org/TR/webauthn-2/#dom-publickeycredentialrpentity-id and https://www.w3.org/TR/webauthn-2/#dom-publickeycredentialrequestoptions-rpid, but the former uses DOMString, while the latter uses USVString. Is this a bug in the spec or is there an actual difference?

Constructors

RpId 

Fields

Instances

Instances details
ToJSON RpId Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

IsString RpId Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Methods

fromString :: String -> RpId #

Show RpId Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Methods

showsPrec :: Int -> RpId -> ShowS #

show :: RpId -> String #

showList :: [RpId] -> ShowS #

Eq RpId Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Methods

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

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

Ord RpId Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Methods

compare :: RpId -> RpId -> Ordering #

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

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

(>) :: RpId -> RpId -> Bool #

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

max :: RpId -> RpId -> RpId #

min :: RpId -> RpId -> RpId #

Encode RpId Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Associated Types

type JSON RpId Source #

Methods

encode :: RpId -> JSON RpId Source #

Decode m RpId Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Methods

decode :: JSON RpId -> m RpId Source #

type JSON RpId Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

type JSON RpId = Text

newtype RelyingPartyName Source #

(spec) A human-palatable identifier for the Relying Party, intended only for display. For example, "ACME Corporation", "Wonderful Widgets, Inc." or "ОАО Примертех".

Constructors

RelyingPartyName 

newtype UserHandle Source #

(spec) The user handle is specified by a Relying Party, as the value of id, and used to map a specific public key credential to a specific user account with the Relying Party. Authenticators in turn map RP IDs and user handle pairs to public key credential sources. A user handle is an opaque byte sequence with a maximum size of 64 bytes, and is not meant to be displayed to the user.

Constructors

UserHandle 

Instances

Instances details
ToJSON UserHandle Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Show UserHandle Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Eq UserHandle Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Ord UserHandle Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Encode UserHandle Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Associated Types

type JSON UserHandle Source #

Decode m UserHandle Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

type JSON UserHandle Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

generateUserHandle :: MonadRandom m => m UserHandle Source #

(spec) A user handle is an opaque byte sequence with a maximum size of 64 bytes, and is not meant to be displayed to the user.

newtype UserAccountDisplayName Source #

(spec) A human-palatable name for the user account, intended only for display. For example, "Alex Müller" or "田中倫". The Relying Party SHOULD let the user choose this, and SHOULD NOT restrict the choice more than necessary.

Instances

Instances details
ToJSON UserAccountDisplayName Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

IsString UserAccountDisplayName Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Show UserAccountDisplayName Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Eq UserAccountDisplayName Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Encode UserAccountDisplayName Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Associated Types

type JSON UserAccountDisplayName Source #

Decode m UserAccountDisplayName Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

type JSON UserAccountDisplayName Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

newtype UserAccountName Source #

(spec) A human-palatable identifier for a user account. It is intended only for display, i.e., aiding the user in determining the difference between user accounts with similar cueDisplayNames. For example, "alexm", "alex.mueller@example.com" or "+14255551234".

Constructors

UserAccountName 

newtype CredentialId Source #

(spec) A probabilistically-unique byte sequence identifying a public key credential source and its authentication assertions.

Constructors

CredentialId 

Instances

Instances details
ToJSON CredentialId Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Show CredentialId Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Eq CredentialId Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Ord CredentialId Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Encode CredentialId Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Associated Types

type JSON CredentialId Source #

Decode m CredentialId Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

type JSON CredentialId Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

generateCredentialId :: MonadRandom m => m CredentialId Source #

(spec) Generates a random CredentialId using 16 random bytes. This is only useful for authenticators, not for relying parties. This function is only included for completeness and testing purposes.

newtype Challenge Source #

(spec) This member contains a challenge intended to be used for generating the newly created credential’s attestation object. See the § 13.4.3 Cryptographic Challenges security consideration.

Constructors

Challenge 

generateChallenge :: MonadRandom m => m Challenge Source #

(spec) In order to prevent replay attacks, the challenges MUST contain enough entropy to make guessing them infeasible. Challenges SHOULD therefore be at least 16 bytes long.

newtype Timeout Source #

(spec) This member specifies a time, in milliseconds, that the caller is willing to wait for the call to complete. This is treated as a hint, and MAY be overridden by the client.

Constructors

Timeout 

Fields

Instances

Instances details
ToJSON Timeout Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Show Timeout Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Eq Timeout Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Methods

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

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

Encode Timeout Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Associated Types

type JSON Timeout Source #

Decode m Timeout Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

type JSON Timeout Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

newtype AssertionSignature Source #

(spec) An assertion signature is produced when the authenticatorGetAssertion method is invoked. It represents an assertion by the authenticator that the user has consented to a specific transaction, such as logging in, or completing a purchase. Thus, an assertion signature asserts that the authenticator possessing a particular credential private key has established, to the best of its ability, that the user requesting this transaction is the same user who consented to creating that particular public key credential. It also asserts additional information, termed client data, that may be useful to the caller, such as the means by which user consent was provided, and the prompt shown to the user by the authenticator. The assertion signature format is illustrated in Figure 4, below.

newtype RpIdHash Source #

(spec) SHA-256 hash of the RP ID the credential is scoped to.

Constructors

RpIdHash 

Instances

Instances details
ToJSON RpIdHash Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Show RpIdHash Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Eq RpIdHash Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

newtype Origin Source #

Constructors

Origin 

Fields

Instances

Instances details
ToJSON Origin Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

IsString Origin Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Methods

fromString :: String -> Origin #

Show Origin Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Eq Origin Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Methods

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

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

newtype SignatureCounter Source #

Instances

Instances details
ToJSON SignatureCounter Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Num SignatureCounter Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Show SignatureCounter Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Eq SignatureCounter Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Ord SignatureCounter Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Extensions (unimplemented, see module documentation)

newtype AuthenticationExtensionsClientInputs Source #

(spec) This is a dictionary containing the client extension input values for zero or more WebAuthn Extensions. TODO: Most extensions are not implemented by this library, see Crypto.WebAuthn.Model.Types.

Constructors

AuthenticationExtensionsClientInputs 

Fields

Instances

Instances details
ToJSON AuthenticationExtensionsClientInputs Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Show AuthenticationExtensionsClientInputs Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Eq AuthenticationExtensionsClientInputs Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Encode AuthenticationExtensionsClientInputs Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Decode m AuthenticationExtensionsClientInputs Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

type JSON AuthenticationExtensionsClientInputs Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

newtype CredentialPropertiesOutput Source #

(spec) This is a dictionary containing the client properties output.

Constructors

CredentialPropertiesOutput 

Fields

  • cpoRk :: Maybe Bool

    (spec) The resident key credential property (i.e., client-side discoverable credential property), indicating whether the `PublicKeyCredential` returned as a result of a registration ceremony is a client-side discoverable credential.

Instances

Instances details
ToJSON CredentialPropertiesOutput Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Show CredentialPropertiesOutput Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Eq CredentialPropertiesOutput Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Encode CredentialPropertiesOutput Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Decode m CredentialPropertiesOutput Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

type JSON CredentialPropertiesOutput Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

newtype AuthenticationExtensionsClientOutputs Source #

(spec) This is a dictionary containing the client extension output values for zero or more WebAuthn Extensions. TODO: Most extensions are not implemented by this library, see Crypto.WebAuthn.Model.Types.

Constructors

AuthenticationExtensionsClientOutputs 

Fields

Instances

Instances details
ToJSON AuthenticationExtensionsClientOutputs Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Show AuthenticationExtensionsClientOutputs Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Eq AuthenticationExtensionsClientOutputs Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Encode AuthenticationExtensionsClientOutputs Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Decode m AuthenticationExtensionsClientOutputs Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

type JSON AuthenticationExtensionsClientOutputs Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Dictionaries

data CredentialRpEntity Source #

(spec) The CredentialRpEntity dictionary is used to supply additional Relying Party attributes when creating a new credential.

Constructors

CredentialRpEntity 

Fields

Instances

Instances details
ToJSON CredentialRpEntity Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Generic CredentialRpEntity Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Associated Types

type Rep CredentialRpEntity :: Type -> Type #

Show CredentialRpEntity Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Eq CredentialRpEntity Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Encode CredentialRpEntity Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Associated Types

type JSON CredentialRpEntity Source #

Decode m CredentialRpEntity Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

type Rep CredentialRpEntity Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

type Rep CredentialRpEntity = D1 ('MetaData "CredentialRpEntity" "Crypto.WebAuthn.Model.Types" "webauthn-0.6.0.1-inplace" 'False) (C1 ('MetaCons "CredentialRpEntity" 'PrefixI 'True) (S1 ('MetaSel ('Just "creId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe RpId)) :*: S1 ('MetaSel ('Just "creName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RelyingPartyName)))
type JSON CredentialRpEntity Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

data CredentialUserEntity Source #

(spec) The CredentialUserEntity dictionary is used to supply additional user account attributes when creating a new credential.

Constructors

CredentialUserEntity 

Fields

Instances

Instances details
ToJSON CredentialUserEntity Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Generic CredentialUserEntity Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Associated Types

type Rep CredentialUserEntity :: Type -> Type #

Show CredentialUserEntity Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Eq CredentialUserEntity Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Encode CredentialUserEntity Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Associated Types

type JSON CredentialUserEntity Source #

Decode m CredentialUserEntity Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

type Rep CredentialUserEntity Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

type Rep CredentialUserEntity = D1 ('MetaData "CredentialUserEntity" "Crypto.WebAuthn.Model.Types" "webauthn-0.6.0.1-inplace" 'False) (C1 ('MetaCons "CredentialUserEntity" 'PrefixI 'True) (S1 ('MetaSel ('Just "cueId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UserHandle) :*: (S1 ('MetaSel ('Just "cueDisplayName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UserAccountDisplayName) :*: S1 ('MetaSel ('Just "cueName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UserAccountName))))
type JSON CredentialUserEntity Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

data CredentialParameters Source #

(spec) This dictionary is used to supply additional parameters when creating a new credential.

Constructors

CredentialParameters 

Fields

  • cpTyp :: CredentialType

    (spec) This member specifies the type of credential to be created.

  • cpAlg :: CoseSignAlg

    (spec) This member specifies the cryptographic signature algorithm with which the newly generated credential will be used, and thus also the type of asymmetric key pair to be generated, e.g., RSA or Elliptic Curve.

Instances

Instances details
ToJSON CredentialParameters Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Generic CredentialParameters Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Associated Types

type Rep CredentialParameters :: Type -> Type #

Show CredentialParameters Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Eq CredentialParameters Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Encode CredentialParameters Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Associated Types

type JSON CredentialParameters Source #

Decode m CredentialParameters Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

type Rep CredentialParameters Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

type Rep CredentialParameters = D1 ('MetaData "CredentialParameters" "Crypto.WebAuthn.Model.Types" "webauthn-0.6.0.1-inplace" 'False) (C1 ('MetaCons "CredentialParameters" 'PrefixI 'True) (S1 ('MetaSel ('Just "cpTyp") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CredentialType) :*: S1 ('MetaSel ('Just "cpAlg") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CoseSignAlg)))
type JSON CredentialParameters Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

data CredentialDescriptor Source #

(spec) This dictionary contains the attributes that are specified by a caller when referring to a public key credential as an input parameter to the create() or get() methods. It mirrors the fields of the Credential object returned by the latter methods.

Constructors

CredentialDescriptor 

Fields

Instances

Instances details
ToJSON CredentialDescriptor Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Generic CredentialDescriptor Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Associated Types

type Rep CredentialDescriptor :: Type -> Type #

Show CredentialDescriptor Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Eq CredentialDescriptor Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Encode CredentialDescriptor Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Associated Types

type JSON CredentialDescriptor Source #

Decode m CredentialDescriptor Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

type Rep CredentialDescriptor Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

type Rep CredentialDescriptor = D1 ('MetaData "CredentialDescriptor" "Crypto.WebAuthn.Model.Types" "webauthn-0.6.0.1-inplace" 'False) (C1 ('MetaCons "CredentialDescriptor" 'PrefixI 'True) (S1 ('MetaSel ('Just "cdTyp") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CredentialType) :*: (S1 ('MetaSel ('Just "cdId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CredentialId) :*: S1 ('MetaSel ('Just "cdTransports") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [AuthenticatorTransport])))))
type JSON CredentialDescriptor Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

data AuthenticatorSelectionCriteria Source #

(spec) WebAuthn Relying Parties may use the AuthenticatorSelectionCriteria dictionary to specify their requirements regarding authenticator attributes.

Constructors

AuthenticatorSelectionCriteria 

Fields

Instances

Instances details
ToJSON AuthenticatorSelectionCriteria Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Generic AuthenticatorSelectionCriteria Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Associated Types

type Rep AuthenticatorSelectionCriteria :: Type -> Type #

Show AuthenticatorSelectionCriteria Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Eq AuthenticatorSelectionCriteria Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Encode AuthenticatorSelectionCriteria Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Decode m AuthenticatorSelectionCriteria Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

type Rep AuthenticatorSelectionCriteria Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

type Rep AuthenticatorSelectionCriteria = D1 ('MetaData "AuthenticatorSelectionCriteria" "Crypto.WebAuthn.Model.Types" "webauthn-0.6.0.1-inplace" 'False) (C1 ('MetaCons "AuthenticatorSelectionCriteria" 'PrefixI 'True) (S1 ('MetaSel ('Just "ascAuthenticatorAttachment") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe AuthenticatorAttachment)) :*: (S1 ('MetaSel ('Just "ascResidentKey") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ResidentKeyRequirement) :*: S1 ('MetaSel ('Just "ascUserVerification") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UserVerificationRequirement))))
type JSON AuthenticatorSelectionCriteria Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

data AuthenticatorDataFlags Source #

Constructors

AuthenticatorDataFlags 

Fields

Instances

Instances details
ToJSON AuthenticatorDataFlags Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Generic AuthenticatorDataFlags Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Associated Types

type Rep AuthenticatorDataFlags :: Type -> Type #

Show AuthenticatorDataFlags Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Eq AuthenticatorDataFlags Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

type Rep AuthenticatorDataFlags Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

type Rep AuthenticatorDataFlags = D1 ('MetaData "AuthenticatorDataFlags" "Crypto.WebAuthn.Model.Types" "webauthn-0.6.0.1-inplace" 'False) (C1 ('MetaCons "AuthenticatorDataFlags" 'PrefixI 'True) (S1 ('MetaSel ('Just "adfUserPresent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "adfUserVerified") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))

data CollectedClientData (c :: CeremonyKind) raw Source #

(spec) The client data represents the contextual bindings of both the WebAuthn Relying Party and the client.

For binary serialization of thes type, see Crypto.WebAuthn.Encoding.Binary. If decoded with decodeCollectedClientData, the ccdRawData field is filled out with the raw bytes, while encodeRawCollectedClientData can be used to fill out this field when constructing this value otherwise. Unchecked invariant: If raw ~ True, then 'Crypto.WebAuthn.Encoding.Binary.encodeRawCollectedClientData c = c', ensuring that the ccdRawData field should always correspond to its encoding. This means that if raw ~ True, it's not safe to modify individual fields. To make changes, first use stripRawCollectedClientData, make the changes on the result, then call encodeRawCollectedClientData on that. Note however that any modifications also invalidate signatures over the binary data, specifically araSignature and aoAttStmt.

Constructors

CollectedClientData 

Fields

Instances

Instances details
SingI c => Decode m (CollectedClientData c 'True) Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

SingI c => ToJSON (CollectedClientData c raw) Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Show (CollectedClientData c raw) Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Eq (CollectedClientData c raw) Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

SingI c => Encode (CollectedClientData c 'True) Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Associated Types

type JSON (CollectedClientData c 'True) Source #

type JSON (CollectedClientData c 'True) Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

data AuthenticatorData (c :: CeremonyKind) raw Source #

(spec) The authenticator data structure encodes contextual bindings made by the authenticator. These bindings are controlled by the authenticator itself, and derive their trust from the WebAuthn Relying Party's assessment of the security properties of the authenticator. In one extreme case, the authenticator may be embedded in the client, and its bindings may be no more trustworthy than the client data. At the other extreme, the authenticator may be a discrete entity with high-security hardware and software, connected to the client over a secure channel. In both cases, the Relying Party receives the authenticator data in the same format, and uses its knowledge of the authenticator to make trust decisions.

For the binary serialization of this type, see Crypto.WebAuthn.Encoding.Binary. If decoded with decodeAuthenticatorData, the adRawData field is filled out with the binary serialization, while encodeRawAuthenticatorData can be used to fill out this field when constructing this value otherwise. This also applies to raw acdCredentialPublicKeyBytes field in adAttestedCredentialData. Unchecked invariant: If raw ~ True, then 'Crypto.WebAuthn.Encoding.Binary.encodeRawAuthenticatorData d = d', ensuring that the adRawData and acdCredentialPublicKeyBytes fields should always correspond to their respective binary serializations. This means that if raw ~ True, it's not safe to modify individual fields. To make changes, first use stripRawAuthenticatorData, make the changes on the result, then call encodeRawAuthenticatorData on that. Note however that any modifications also invalidate signatures over the binary data, specifically araSignature and aoAttStmt.

Instances

Instances details
Decode m (AuthenticatorData 'Authentication 'True) Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

ToJSON (AuthenticatorData c raw) Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Generic (AuthenticatorData c raw) Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Associated Types

type Rep (AuthenticatorData c raw) :: Type -> Type #

Methods

from :: AuthenticatorData c raw -> Rep (AuthenticatorData c raw) x #

to :: Rep (AuthenticatorData c raw) x -> AuthenticatorData c raw #

Show (AuthenticatorData c raw) Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Eq (AuthenticatorData c raw) Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Encode (AuthenticatorData 'Authentication 'True) Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

type Rep (AuthenticatorData c raw) Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

type JSON (AuthenticatorData 'Authentication 'True) Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

data AttestationObject raw Source #

(spec)

For the binary serialization of this type, see Crypto.WebAuthn.Encoding.Binary. If decoded with decodeAttestationObject, the aoAuthData field is filled out with the binary serialization of its fields, while encodeRawAttestationObject can be used to fill out this field when constructing this value otherwise. Unchecked invariant: If raw ~ True, then 'Crypto.WebAuthn.Encoding.Binary.encodeRawAttestationObject o = o', ensuring that the binary fields of the aoAuthData field should always correspond to their respective serializations. This means that if raw ~ True, it's not safe to modify individual fields. To make changes, first use stripRawAttestationObject, make the changes on the result, then call encodeRawAttestationObject on that. Note however that any modifications also invalidate signatures over the binary data, specifically aoAttStmt. The encodeAttestationObject can be used to get the binary encoding of this type when raw ~ True.

Constructors

forall a.AttestationStatementFormat a => AttestationObject 

Fields

data AuthenticatorResponse (c :: CeremonyKind) raw where Source #

(spec) Authenticators respond to Relying Party requests by returning an object derived from the `AuthenticatorResponse` interface

Constructors

AuthenticatorResponseRegistration

(spec) The AuthenticatorAttestationResponse interface represents the authenticator's response to a client’s request for the creation of a new public key credential. It contains information about the new credential that can be used to identify it for later use, and metadata that can be used by the WebAuthn Relying Party to assess the characteristics of the credential during registration.

Fields

AuthenticatorResponseAuthentication

(spec) The AuthenticatorAssertionResponse interface represents an authenticator's response to a client’s request for generation of a new authentication assertion given the WebAuthn Relying Party's challenge and OPTIONAL list of credentials it is aware of. This response contains a cryptographic signature proving possession of the credential private key, and optionally evidence of user consent to a specific transaction.

Fields

Instances

Instances details
Decode m (AuthenticatorResponse 'Authentication 'True) Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

MonadReader SupportedAttestationStatementFormats m => Decode m (AuthenticatorResponse 'Registration 'True) Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

ToJSON (AuthenticatorResponse c raw) Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Show (AuthenticatorResponse c raw) Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Eq (AuthenticatorResponse c raw) Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Encode (AuthenticatorResponse 'Authentication 'True) Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Encode (AuthenticatorResponse 'Registration 'True) Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

type JSON (AuthenticatorResponse 'Authentication 'True) Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

type JSON (AuthenticatorResponse 'Registration 'True) Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Attestation Statement Formats

data SomeAttestationType Source #

The result from verifying an attestation statement. Either the result is verifiable, in which case k ~ Verifiable, the AttestationType contains a verifiable certificate chain. Or the result is not verifiable, in which case k ~ Unverifiable, the AttestationType is None or Self.

Constructors

forall k. SomeAttestationType (AttestationType k) 

class (Eq (AttStmt a), Show (AttStmt a), ToJSON (AttStmt a), Typeable a, Show a, Exception (AttStmtVerificationError a)) => AttestationStatementFormat a where Source #

Associated Types

type AttStmt a :: Type Source #

The type of a fully-decoded and structurally valid attestation statement

type AttStmtVerificationError a :: Type Source #

The type of verification errors that can occur when verifying this attestation statement using asfVerify

Methods

asfIdentifier :: a -> Text Source #

(spec) Attestation statement formats are identified by a string, called an attestation statement format identifier, chosen by the author of the attestation statement format.

Attestation statement format identifiers SHOULD be registered in the IANA "WebAuthn Attestation Statement Format Identifiers" registry IANA-WebAuthn-Registries established by RFC8809. All registered attestation statement format identifiers are unique amongst themselves as a matter of course.

Unregistered attestation statement format identifiers SHOULD use lowercase reverse domain-name naming, using a domain name registered by the developer, in order to assure uniqueness of the identifier. All attestation statement format identifiers MUST be a maximum of 32 octets in length and MUST consist only of printable USASCII characters, excluding backslash and doublequote, i.e., VCHAR as defined in RFC5234 but without %x22 and %x5c.

Note: This means attestation statement format identifiers based on domain names MUST incorporate only LDH Labels RFC5890.

Attestation statement formats that may exist in multiple versions SHOULD include a version in their identifier. In effect, different versions are thus treated as different formats, e.g., packed2 as a new version of the § 8.2 Packed Attestation Statement Format.

asfVerify :: a -> DateTime -> AttStmt a -> AuthenticatorData 'Registration 'True -> ClientDataHash -> Validation (NonEmpty (AttStmtVerificationError a)) SomeAttestationType Source #

(spec) The procedure to verify an attestation statement

asfTrustAnchors :: a -> VerifiableAttestationType -> CertificateStore Source #

The trusted root certificates specifically for this attestation statement format. For attestation statement chain validation, these certificates are used, in addition to the ones from the metadata registry

(spec) step 20: If validation is successful, obtain a list of acceptable trust anchors (i.e. attestation root certificates) for that attestation type and attestation statement format fmt, from a trusted source or from policy.

While for the attestation statement formats we implement, none of them use the VerifiableAttestationType, it is implied that it could be used by the above sentence from the spec.

asfDecode :: a -> HashMap Text Term -> Either Text (AttStmt a) Source #

A decoder for the attestation statement syntax. The attStmt CBOR map is given as an input. See Generating an Attestation Object

asfEncode :: a -> AttStmt a -> Term Source #

An encoder for the attestation statement syntax. The attStmt CBOR map is expected as the result. See Generating an Attestation Object

Instances

Instances details
AttestationStatementFormat Format Source # 
Instance details

Defined in Crypto.WebAuthn.AttestationStatementFormat.AndroidKey

AttestationStatementFormat Format Source # 
Instance details

Defined in Crypto.WebAuthn.AttestationStatementFormat.AndroidSafetyNet

AttestationStatementFormat Format Source # 
Instance details

Defined in Crypto.WebAuthn.AttestationStatementFormat.Apple

AttestationStatementFormat Format Source # 
Instance details

Defined in Crypto.WebAuthn.AttestationStatementFormat.FidoU2F

AttestationStatementFormat Format Source # 
Instance details

Defined in Crypto.WebAuthn.AttestationStatementFormat.None

AttestationStatementFormat Format Source # 
Instance details

Defined in Crypto.WebAuthn.AttestationStatementFormat.Packed

AttestationStatementFormat Format Source # 
Instance details

Defined in Crypto.WebAuthn.AttestationStatementFormat.TPM

lookupAttestationStatementFormat Source #

Arguments

:: Text

The desired format, e.g. "android-safetynet" or "none"

-> SupportedAttestationStatementFormats

The attestation statement formats that should be supported. The value of allSupportedFormats can be passed here, but additional or custom formats may also be used if needed.

-> Maybe SomeAttestationStatementFormat 

Attempt to find the desired attestation statement format in a map of supported formats. Can then be used to perform attestation.

Raw fields

data RawField (raw :: Bool) where Source #

A model field parametrized by whether it's empty (False) or contains raw bytes (True)

Constructors

NoRaw :: RawField 'False 
WithRaw 

Fields

Instances

Instances details
ToJSON (RawField raw) Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Show (RawField raw) Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Methods

showsPrec :: Int -> RawField raw -> ShowS #

show :: RawField raw -> String #

showList :: [RawField raw] -> ShowS #

Eq (RawField raw) Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Methods

(==) :: RawField raw -> RawField raw -> Bool #

(/=) :: RawField raw -> RawField raw -> Bool #

Top-level types

data CredentialOptions (c :: CeremonyKind) where Source #

A type encompassing the credential options, both for creation and requesting. The CeremonyKind araument specifies which.

Values of this type are send to the client to create and get a credential. After they have been sent, they have to be stored awaiting the response from the client for further validation. At least the following fields have to be stored, the others are not currently used.

For verifyRegistrationResponse:

For verifyAuthenticationResponse:

Depending on implementation choices by the RP, some of these fields might additionally be constants, and could thus also be omitted when storing.

Constructors

CredentialOptionsRegistration

(spec)

Fields

CredentialOptionsAuthentication

(spec) The CredentialOptionsAuthentication dictionary supplies `get()` with the data it needs to generate an assertion.

Fields

Instances

Instances details
Decode m (CredentialOptions 'Authentication) Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Decode m (CredentialOptions 'Registration) Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

ToJSON (CredentialOptions c) Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Show (CredentialOptions c) Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Eq (CredentialOptions c) Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Encode (CredentialOptions 'Authentication) Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Associated Types

type JSON (CredentialOptions 'Authentication) Source #

Encode (CredentialOptions 'Registration) Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Associated Types

type JSON (CredentialOptions 'Registration) Source #

type JSON (CredentialOptions 'Authentication) Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

type JSON (CredentialOptions 'Registration) Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

data Credential (c :: CeremonyKind) raw Source #

(spec) The Credential interface contains the attributes that are returned to the caller when a new credential is created, or a new assertion is requested.

This type has nested fields which use a binary encoding that needs to be preserved for verification purposes. The binary encoding of these fields can be removed or recomputed using functions from Crypto.WebAuthn.Encoding.Binary. Specifically stripRawCredential and encodeRawCredential respectively. Unchecked invariant: If raw ~ True, then 'Crypto.WebAuthn.Encoding.Binary.encodeRawCredential c = c', ensuring that the binary fields should always correspond to the values respective serializations. This means that if raw ~ True, it's not safe to modify individual fields. To make changes, first use stripRawCredential, make the changes on the result, then call encodeRawCredential on that. Note however that any modifications also invalidate signatures over the binary data, specifically araSignature and aoAttStmt.

Constructors

Credential 

Fields

Instances

Instances details
Decode m (Credential 'Authentication 'True) Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

MonadReader SupportedAttestationStatementFormats m => Decode m (Credential 'Registration 'True) Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

ToJSON (Credential c raw) Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Generic (Credential c raw) Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Associated Types

type Rep (Credential c raw) :: Type -> Type #

Methods

from :: Credential c raw -> Rep (Credential c raw) x #

to :: Rep (Credential c raw) x -> Credential c raw #

Show (Credential c raw) Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Methods

showsPrec :: Int -> Credential c raw -> ShowS #

show :: Credential c raw -> String #

showList :: [Credential c raw] -> ShowS #

Eq (Credential c raw) Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Methods

(==) :: Credential c raw -> Credential c raw -> Bool #

(/=) :: Credential c raw -> Credential c raw -> Bool #

Encode (Credential 'Authentication 'True) Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Associated Types

type JSON (Credential 'Authentication 'True) Source #

Encode (Credential 'Registration 'True) Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Associated Types

type JSON (Credential 'Registration 'True) Source #

type Rep (Credential c raw) Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

type Rep (Credential c raw) = D1 ('MetaData "Credential" "Crypto.WebAuthn.Model.Types" "webauthn-0.6.0.1-inplace" 'False) (C1 ('MetaCons "Credential" 'PrefixI 'True) (S1 ('MetaSel ('Just "cIdentifier") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CredentialId) :*: (S1 ('MetaSel ('Just "cResponse") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (AuthenticatorResponse c raw)) :*: S1 ('MetaSel ('Just "cClientExtensionResults") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AuthenticationExtensionsClientOutputs))))
type JSON (Credential 'Authentication 'True) Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

type JSON (Credential 'Registration 'True) Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson