webauthn-0.1.0.0: Relying party (server) implementation of the WebAuthn 2 specification
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Crypto.WebAuthn.Model.Types

Description

This module contains the same top-level definitions as JavaScript, but with the types containing a more Haskell-friendly structure.

Note: The ToJSON instances of these types are for pretty-printing purposes only.

TODO: (spec) This library does not currently implement 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.

Instances

Instances details
Bounded CredentialType Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Enum 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

Show 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 #

ToJSON CredentialType Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Convert CredentialType Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Convert

Associated Types

type IDL CredentialType Source #

Encode CredentialType Source #

https://www.w3.org/TR/webauthn-2/#enum-credentialType

Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Encoding

type Rep CredentialType Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

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

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Convert

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().

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.

Instances

Instances details
Bounded AuthenticatorTransport Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Enum 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

Show 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 #

ToJSON AuthenticatorTransport Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Convert [AuthenticatorTransport] Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Convert

Associated Types

type IDL [AuthenticatorTransport] Source #

Encode [AuthenticatorTransport] Source #

https://www.w3.org/TR/webauthn-2/#enumdef-authenticatortransport

Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Encoding

Decode [AuthenticatorTransport] Source #

(spec)

Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Decoding

type Rep AuthenticatorTransport Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

type Rep AuthenticatorTransport = D1 ('MetaData "AuthenticatorTransport" "Crypto.WebAuthn.Model.Types" "webauthn-0.1.0.0-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)))
type IDL [AuthenticatorTransport] Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Convert

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.

Instances

Instances details
Bounded AuthenticatorAttachment Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Enum 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

Show 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 #

ToJSON AuthenticatorAttachment Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Convert AuthenticatorAttachment Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Convert

Associated Types

type IDL AuthenticatorAttachment Source #

Encode AuthenticatorAttachment Source #

https://www.w3.org/TR/webauthn-2/#enumdef-authenticatorattachment

Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Encoding

type Rep AuthenticatorAttachment Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

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

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Convert

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):

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
Bounded ResidentKeyRequirement Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Enum 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

Show 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 #

ToJSON ResidentKeyRequirement Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Convert ResidentKeyRequirement Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Convert

Associated Types

type IDL ResidentKeyRequirement Source #

Encode ResidentKeyRequirement Source #

https://www.w3.org/TR/webauthn-2/#enum-residentKeyRequirement

Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Encoding

type Rep ResidentKeyRequirement Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

type Rep ResidentKeyRequirement = D1 ('MetaData "ResidentKeyRequirement" "Crypto.WebAuthn.Model.Types" "webauthn-0.1.0.0-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 IDL ResidentKeyRequirement Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Convert

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.

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
Bounded UserVerificationRequirement Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Enum 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

Show 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 #

ToJSON UserVerificationRequirement Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Convert UserVerificationRequirement Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Convert

Encode UserVerificationRequirement Source #

https://www.w3.org/TR/webauthn-2/#enum-userVerificationRequirement

Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Encoding

Decode UserVerificationRequirement Source #

(spec) The value SHOULD be a member of UserVerificationRequirement but client platforms MUST ignore unknown values, treating an unknown value as if the member does not exist. The default is "preferred".

Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Decoding

type Rep UserVerificationRequirement Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

type Rep UserVerificationRequirement = D1 ('MetaData "UserVerificationRequirement" "Crypto.WebAuthn.Model.Types" "webauthn-0.1.0.0-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 IDL UserVerificationRequirement Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Convert

data AttestationConveyancePreference Source #

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

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
Bounded AttestationConveyancePreference Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Enum 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

Show 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 #

ToJSON AttestationConveyancePreference Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Convert AttestationConveyancePreference Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Convert

Encode AttestationConveyancePreference Source #

https://www.w3.org/TR/webauthn-2/#enum-attestation-convey

Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Encoding

Decode AttestationConveyancePreference Source #

(spec) Its values SHOULD be members of AttestationConveyancePreference. Client platforms MUST ignore unknown values, treating an unknown value as if the member does not exist. Its default value is "none".

Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Decoding

type Rep AttestationConveyancePreference Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

type Rep AttestationConveyancePreference = D1 ('MetaData "AttestationConveyancePreference" "Crypto.WebAuthn.Model.Types" "webauthn-0.1.0.0-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 IDL AttestationConveyancePreference Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Convert

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
Bounded VerifiableAttestationType Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Enum 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

Show 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 #

ToJSON 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.1.0.0-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
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 #

Show RpId Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Methods

showsPrec :: Int -> RpId -> ShowS #

show :: RpId -> String #

showList :: [RpId] -> ShowS #

IsString RpId Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Methods

fromString :: String -> RpId #

ToJSON RpId Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Convert RpId Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Convert

Associated Types

type IDL RpId Source #

Encode RpId Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Encoding

Methods

encode :: RpId -> IDL RpId Source #

Decode RpId Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Decoding

type IDL RpId Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Convert

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 

Instances

Instances details
Eq RelyingPartyName Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Show RelyingPartyName Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

IsString RelyingPartyName Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

ToJSON RelyingPartyName Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Convert RelyingPartyName Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Convert

Associated Types

type IDL RelyingPartyName Source #

Encode RelyingPartyName Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Encoding

Decode RelyingPartyName Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Decoding

type IDL RelyingPartyName Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Convert

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
Eq UserHandle Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Ord UserHandle Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Show UserHandle Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

ToJSON UserHandle Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Convert UserHandle Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Convert

Associated Types

type IDL UserHandle Source #

Encode UserHandle Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Encoding

Decode UserHandle Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Decoding

type IDL UserHandle Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Convert

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
Eq UserAccountDisplayName Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Show UserAccountDisplayName Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

IsString UserAccountDisplayName Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

ToJSON UserAccountDisplayName Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Convert UserAccountDisplayName Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Convert

Associated Types

type IDL UserAccountDisplayName Source #

Encode UserAccountDisplayName Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Encoding

Decode UserAccountDisplayName Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Decoding

type IDL UserAccountDisplayName Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Convert

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
Eq CredentialId Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Ord CredentialId Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Show CredentialId Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

ToJSON CredentialId Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Convert CredentialId Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Convert

Associated Types

type IDL CredentialId Source #

Encode CredentialId Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Encoding

Decode CredentialId Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Decoding

type IDL CredentialId Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Convert

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 

Instances

Instances details
Eq Challenge Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Ord Challenge Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Show Challenge Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

ToJSON Challenge Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Convert Challenge Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Convert

Associated Types

type IDL Challenge Source #

Encode Challenge Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Encoding

Decode Challenge Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Decoding

type IDL Challenge Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Convert

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

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
Eq RpIdHash Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Show RpIdHash Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

ToJSON RpIdHash Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

newtype Origin Source #

Constructors

Origin 

Fields

Instances

Instances details
Eq Origin Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Methods

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

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

Show 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 #

ToJSON Origin Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

newtype SignatureCounter Source #

Instances

Instances details
Eq SignatureCounter Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Num SignatureCounter Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Ord SignatureCounter Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Show SignatureCounter Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

ToJSON SignatureCounter Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Extensions (unimplemented, see module documentation)

data AuthenticationExtensionsClientInputs Source #

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

Instances

Instances details
Eq AuthenticationExtensionsClientInputs Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Show AuthenticationExtensionsClientInputs Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

ToJSON AuthenticationExtensionsClientInputs Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Convert AuthenticationExtensionsClientInputs Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Convert

Encode AuthenticationExtensionsClientInputs Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Encoding

type IDL AuthenticationExtensionsClientInputs Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Convert

data AuthenticationExtensionsClientOutputs Source #

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

Instances

Instances details
Eq AuthenticationExtensionsClientOutputs Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Show AuthenticationExtensionsClientOutputs Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

ToJSON AuthenticationExtensionsClientOutputs Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Convert AuthenticationExtensionsClientOutputs Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Convert

Decode AuthenticationExtensionsClientOutputs Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Decoding

type IDL AuthenticationExtensionsClientOutputs Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Convert

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
Eq CredentialRpEntity Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Show 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 #

ToJSON CredentialRpEntity Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Convert CredentialRpEntity Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Convert

Associated Types

type IDL CredentialRpEntity Source #

Encode CredentialRpEntity Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Encoding

Decode CredentialRpEntity Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Decoding

type Rep CredentialRpEntity Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

type Rep CredentialRpEntity = D1 ('MetaData "CredentialRpEntity" "Crypto.WebAuthn.Model.Types" "webauthn-0.1.0.0-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 IDL CredentialRpEntity Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Convert

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
Eq CredentialUserEntity Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Show 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 #

ToJSON CredentialUserEntity Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Convert CredentialUserEntity Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Convert

Associated Types

type IDL CredentialUserEntity Source #

Encode CredentialUserEntity Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Encoding

Decode CredentialUserEntity Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Decoding

type Rep CredentialUserEntity Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

type Rep CredentialUserEntity = D1 ('MetaData "CredentialUserEntity" "Crypto.WebAuthn.Model.Types" "webauthn-0.1.0.0-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 IDL CredentialUserEntity Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Convert

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
Eq CredentialParameters Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Show 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 #

ToJSON CredentialParameters Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Convert [CredentialParameters] Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Convert

Associated Types

type IDL [CredentialParameters] Source #

Encode [CredentialParameters] Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Encoding

Decode [CredentialParameters] Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Decoding

type Rep CredentialParameters Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

type Rep CredentialParameters = D1 ('MetaData "CredentialParameters" "Crypto.WebAuthn.Model.Types" "webauthn-0.1.0.0-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 IDL [CredentialParameters] Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Convert

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
Eq CredentialDescriptor Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Show 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 #

ToJSON CredentialDescriptor Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Convert CredentialDescriptor Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Convert

Associated Types

type IDL CredentialDescriptor Source #

Encode CredentialDescriptor Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Encoding

Convert [CredentialDescriptor] Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Convert

Associated Types

type IDL [CredentialDescriptor] Source #

Encode [CredentialDescriptor] Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Encoding

Decode [CredentialDescriptor] Source #

(spec) [The type] member contains the type of the public key credential the caller is referring to. The value SHOULD be a member of PublicKeyCredentialType but client platforms MUST ignore any PublicKeyCredentialDescriptor with an unknown type.

Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Decoding

type Rep CredentialDescriptor Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

type Rep CredentialDescriptor = D1 ('MetaData "CredentialDescriptor" "Crypto.WebAuthn.Model.Types" "webauthn-0.1.0.0-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 IDL CredentialDescriptor Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Convert

type IDL [CredentialDescriptor] Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Convert

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
Eq AuthenticatorSelectionCriteria Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Show 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 #

ToJSON AuthenticatorSelectionCriteria Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Convert AuthenticatorSelectionCriteria Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Convert

Encode AuthenticatorSelectionCriteria Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Encoding

Decode AuthenticatorSelectionCriteria Source #

(spec)

Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Decoding

type Rep AuthenticatorSelectionCriteria Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

type Rep AuthenticatorSelectionCriteria = D1 ('MetaData "AuthenticatorSelectionCriteria" "Crypto.WebAuthn.Model.Types" "webauthn-0.1.0.0-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 IDL AuthenticatorSelectionCriteria Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Convert

data AuthenticatorDataFlags Source #

Constructors

AuthenticatorDataFlags 

Fields

Instances

Instances details
Eq AuthenticatorDataFlags Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Show 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 #

ToJSON 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.1.0.0-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.

Constructors

CollectedClientData 

Fields

Instances

Instances details
Eq (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

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

Defined in Crypto.WebAuthn.Model.Types

Convert (CollectedClientData c 'True) Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Convert

Associated Types

type IDL (CollectedClientData c 'True) Source #

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

(spec)

Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Encoding

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

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Decoding

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

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Convert

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.

Instances

Instances details
Eq (AuthenticatorData c raw) Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Show (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 #

ToJSON (AuthenticatorData c raw) Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Convert (AuthenticatorData 'Authentication raw) Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Convert

Associated Types

type IDL (AuthenticatorData 'Authentication raw) Source #

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

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Decoding

type Rep (AuthenticatorData c raw) Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

type IDL (AuthenticatorData 'Authentication raw) Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Convert

data AttestationObject raw Source #

Constructors

forall a.AttestationStatementFormat a => AttestationObject 

Fields

  • aoAuthData :: AuthenticatorData 'Registration raw

    (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.

  • aoFmt :: a
  • aoAttStmt :: AttStmt a

Instances

Instances details
Eq (AttestationObject raw) Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Show (AttestationObject raw) Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

ToJSON (AttestationObject raw) Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Convert (AttestationObject 'True) Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Convert

Associated Types

type IDL (AttestationObject 'True) Source #

Encode (AttestationObject 'True) Source #

(spec)

Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Encoding

DecodeCreated (AttestationObject 'True) Source #

(spec)

Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Decoding

type IDL (AttestationObject 'True) Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Convert

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
Eq (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

ToJSON (AuthenticatorResponse c raw) Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Convert (AuthenticatorResponse 'Registration raw) Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Convert

Associated Types

type IDL (AuthenticatorResponse 'Registration raw) Source #

Convert (AuthenticatorResponse 'Authentication raw) Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Convert

Associated Types

type IDL (AuthenticatorResponse 'Authentication raw) Source #

Encode (AuthenticatorResponse 'Registration 'True) Source #

(spec)

Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Encoding

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

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Encoding

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

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Decoding

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

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Decoding

type IDL (AuthenticatorResponse 'Registration raw) Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Convert

type IDL (AuthenticatorResponse 'Authentication raw) Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Convert

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.TPM

AttestationStatementFormat Format Source # 
Instance details

Defined in Crypto.WebAuthn.AttestationStatementFormat.Packed

AttestationStatementFormat Format Source # 
Instance details

Defined in Crypto.WebAuthn.AttestationStatementFormat.None

AttestationStatementFormat Format Source # 
Instance details

Defined in Crypto.WebAuthn.AttestationStatementFormat.FidoU2F

AttestationStatementFormat Format Source # 
Instance details

Defined in Crypto.WebAuthn.AttestationStatementFormat.Apple

AttestationStatementFormat Format Source # 
Instance details

Defined in Crypto.WebAuthn.AttestationStatementFormat.AndroidSafetyNet

AttestationStatementFormat Format Source # 
Instance details

Defined in Crypto.WebAuthn.AttestationStatementFormat.AndroidKey

lookupAttestationStatementFormat :: Text -> SupportedAttestationStatementFormats -> Maybe SomeAttestationStatementFormat Source #

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
Eq (RawField raw) Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Methods

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

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

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 #

ToJSON (RawField raw) Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

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.

Constructors

CredentialOptionsRegistration

(spec)

Fields

CredentialOptionsAuthentication

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

Fields

Instances

Instances details
Eq (CredentialOptions c) Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Show (CredentialOptions c) Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

ToJSON (CredentialOptions c) Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Convert (CredentialOptions 'Registration) Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Convert

Associated Types

type IDL (CredentialOptions 'Registration) Source #

Convert (CredentialOptions 'Authentication) Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Convert

Associated Types

type IDL (CredentialOptions 'Authentication) Source #

Encode (CredentialOptions 'Registration) Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Encoding

Encode (CredentialOptions 'Authentication) Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Encoding

Decode (CredentialOptions 'Registration) Source #

(spec)

Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Decoding

Decode (CredentialOptions 'Authentication) Source #

(spec)

Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Decoding

type IDL (CredentialOptions 'Registration) Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Convert

type IDL (CredentialOptions 'Authentication) Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Convert

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.

Constructors

Credential 

Fields

Instances

Instances details
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 #

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 #

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 #

ToJSON (Credential c raw) Source # 
Instance details

Defined in Crypto.WebAuthn.Model.Types

Convert (Credential 'Registration raw) Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Convert

Associated Types

type IDL (Credential 'Registration raw) Source #

Convert (Credential 'Authentication raw) Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Convert

Associated Types

type IDL (Credential 'Authentication raw) Source #

Encode (Credential 'Registration 'True) Source #

(spec) Encodes the PublicKeyCredential for attestation, this instance is mostly used in the tests where we emulate the of the client.

Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Encoding

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

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Encoding

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

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Decoding

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

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Decoding

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.1.0.0-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 IDL (Credential 'Registration raw) Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Convert

type IDL (Credential 'Authentication raw) Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Internal.Convert

stripRawCredential :: forall c raw. SingI c => Credential c raw -> Credential c 'False Source #

Removes all raw fields from a Credential, useful for e.g. pretty-printing only the desired fields. This is the counterpart to encodeRawCredential