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

Crypto.WebAuthn.Model.WebIDL.Types

Description

This module models direct representations of JavaScript objects interacting with the create() and get() methods, as used by Webauthn2. Note that these types don't encode the semantics of their values. E.g. if the JavaScript object has a DOMString field, but only values "foo" and "bar" are possible, the type is still encoded as a generic DOMString. This allows us to match the specification very closely, deferring decoding of these values to another module. This module also implements FromJSON and ToJSON instances of its types, which are compatible with webauthn-json's JSON schema.

The defined types are

Synopsis

Top-level types

data PublicKeyCredentialCreationOptions Source #

Instances

Instances details
Eq PublicKeyCredentialCreationOptions Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Types

Show PublicKeyCredentialCreationOptions Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Types

Generic PublicKeyCredentialCreationOptions Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Types

Associated Types

type Rep PublicKeyCredentialCreationOptions :: Type -> Type #

ToJSON PublicKeyCredentialCreationOptions Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Types

FromJSON PublicKeyCredentialCreationOptions Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Types

type Rep PublicKeyCredentialCreationOptions Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Types

data PublicKeyCredentialRequestOptions Source #

Instances

Instances details
Eq PublicKeyCredentialRequestOptions Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Types

Show PublicKeyCredentialRequestOptions Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Types

Generic PublicKeyCredentialRequestOptions Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Types

Associated Types

type Rep PublicKeyCredentialRequestOptions :: Type -> Type #

ToJSON PublicKeyCredentialRequestOptions Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Types

FromJSON PublicKeyCredentialRequestOptions Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Types

type Rep PublicKeyCredentialRequestOptions Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Types

data PublicKeyCredential response Source #

Instances

Instances details
Eq response => Eq (PublicKeyCredential response) Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Types

Methods

(==) :: PublicKeyCredential response -> PublicKeyCredential response -> Bool #

(/=) :: PublicKeyCredential response -> PublicKeyCredential response -> Bool #

Show response => Show (PublicKeyCredential response) Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Types

Methods

showsPrec :: Int -> PublicKeyCredential response -> ShowS #

show :: PublicKeyCredential response -> String #

showList :: [PublicKeyCredential response] -> ShowS #

Generic (PublicKeyCredential response) Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Types

Associated Types

type Rep (PublicKeyCredential response) :: Type -> Type #

Methods

from :: PublicKeyCredential response -> Rep (PublicKeyCredential response) x #

to :: Rep (PublicKeyCredential response) x -> PublicKeyCredential response #

ToJSON response => ToJSON (PublicKeyCredential response) Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Types

FromJSON response => FromJSON (PublicKeyCredential response) Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Types

type Rep (PublicKeyCredential response) Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Types

type Rep (PublicKeyCredential response) = D1 ('MetaData "PublicKeyCredential" "Crypto.WebAuthn.Model.WebIDL.Types" "webauthn-0.1.0.0-inplace" 'False) (C1 ('MetaCons "PublicKeyCredential" 'PrefixI 'True) (S1 ('MetaSel ('Just "rawId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ArrayBuffer) :*: (S1 ('MetaSel ('Just "response") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 response) :*: S1 ('MetaSel ('Just "clientExtensionResults") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map Text Value)))))

Nested types

data AuthenticatorAttestationResponse Source #

Instances

Instances details
Eq AuthenticatorAttestationResponse Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Types

Show AuthenticatorAttestationResponse Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Types

Generic AuthenticatorAttestationResponse Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Types

Associated Types

type Rep AuthenticatorAttestationResponse :: Type -> Type #

ToJSON AuthenticatorAttestationResponse Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Types

FromJSON AuthenticatorAttestationResponse Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Types

type Rep AuthenticatorAttestationResponse Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Types

type Rep AuthenticatorAttestationResponse = D1 ('MetaData "AuthenticatorAttestationResponse" "Crypto.WebAuthn.Model.WebIDL.Types" "webauthn-0.1.0.0-inplace" 'False) (C1 ('MetaCons "AuthenticatorAttestationResponse" 'PrefixI 'True) (S1 ('MetaSel ('Just "clientDataJSON") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ArrayBuffer) :*: S1 ('MetaSel ('Just "attestationObject") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ArrayBuffer)))

data AuthenticatorAssertionResponse Source #

Instances

Instances details
Eq AuthenticatorAssertionResponse Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Types

Show AuthenticatorAssertionResponse Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Types

Generic AuthenticatorAssertionResponse Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Types

Associated Types

type Rep AuthenticatorAssertionResponse :: Type -> Type #

ToJSON AuthenticatorAssertionResponse Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Types

FromJSON AuthenticatorAssertionResponse Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Types

type Rep AuthenticatorAssertionResponse Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Types

type Rep AuthenticatorAssertionResponse = D1 ('MetaData "AuthenticatorAssertionResponse" "Crypto.WebAuthn.Model.WebIDL.Types" "webauthn-0.1.0.0-inplace" 'False) (C1 ('MetaCons "AuthenticatorAssertionResponse" 'PrefixI 'True) ((S1 ('MetaSel ('Just "clientDataJSON") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ArrayBuffer) :*: S1 ('MetaSel ('Just "authenticatorData") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ArrayBuffer)) :*: (S1 ('MetaSel ('Just "signature") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ArrayBuffer) :*: S1 ('MetaSel ('Just "userHandle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ArrayBuffer)))))

data PublicKeyCredentialRpEntity Source #

Instances

Instances details
Eq PublicKeyCredentialRpEntity Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Types

Show PublicKeyCredentialRpEntity Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Types

Generic PublicKeyCredentialRpEntity Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Types

Associated Types

type Rep PublicKeyCredentialRpEntity :: Type -> Type #

ToJSON PublicKeyCredentialRpEntity Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Types

FromJSON PublicKeyCredentialRpEntity Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Types

type Rep PublicKeyCredentialRpEntity Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Types

type Rep PublicKeyCredentialRpEntity = D1 ('MetaData "PublicKeyCredentialRpEntity" "Crypto.WebAuthn.Model.WebIDL.Types" "webauthn-0.1.0.0-inplace" 'False) (C1 ('MetaCons "PublicKeyCredentialRpEntity" 'PrefixI 'True) (S1 ('MetaSel ('Just "id") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe DOMString)) :*: S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DOMString)))

data PublicKeyCredentialUserEntity Source #

Instances

Instances details
Eq PublicKeyCredentialUserEntity Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Types

Show PublicKeyCredentialUserEntity Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Types

Generic PublicKeyCredentialUserEntity Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Types

Associated Types

type Rep PublicKeyCredentialUserEntity :: Type -> Type #

ToJSON PublicKeyCredentialUserEntity Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Types

FromJSON PublicKeyCredentialUserEntity Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Types

type Rep PublicKeyCredentialUserEntity Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Types

type Rep PublicKeyCredentialUserEntity = D1 ('MetaData "PublicKeyCredentialUserEntity" "Crypto.WebAuthn.Model.WebIDL.Types" "webauthn-0.1.0.0-inplace" 'False) (C1 ('MetaCons "PublicKeyCredentialUserEntity" 'PrefixI 'True) (S1 ('MetaSel ('Just "id") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BufferSource) :*: (S1 ('MetaSel ('Just "displayName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DOMString) :*: S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DOMString))))

data PublicKeyCredentialParameters Source #

Instances

Instances details
Eq PublicKeyCredentialParameters Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Types

Show PublicKeyCredentialParameters Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Types

Generic PublicKeyCredentialParameters Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Types

Associated Types

type Rep PublicKeyCredentialParameters :: Type -> Type #

ToJSON PublicKeyCredentialParameters Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Types

FromJSON PublicKeyCredentialParameters Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Types

type Rep PublicKeyCredentialParameters Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Types

type Rep PublicKeyCredentialParameters = D1 ('MetaData "PublicKeyCredentialParameters" "Crypto.WebAuthn.Model.WebIDL.Types" "webauthn-0.1.0.0-inplace" 'False) (C1 ('MetaCons "PublicKeyCredentialParameters" 'PrefixI 'True) (S1 ('MetaSel ('Just "littype") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DOMString) :*: S1 ('MetaSel ('Just "alg") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 COSEAlgorithmIdentifier)))

data PublicKeyCredentialDescriptor Source #

Instances

Instances details
Eq PublicKeyCredentialDescriptor Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Types

Show PublicKeyCredentialDescriptor Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Types

Generic PublicKeyCredentialDescriptor Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Types

Associated Types

type Rep PublicKeyCredentialDescriptor :: Type -> Type #

ToJSON PublicKeyCredentialDescriptor Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Types

FromJSON PublicKeyCredentialDescriptor Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Types

type Rep PublicKeyCredentialDescriptor Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Types

type Rep PublicKeyCredentialDescriptor = D1 ('MetaData "PublicKeyCredentialDescriptor" "Crypto.WebAuthn.Model.WebIDL.Types" "webauthn-0.1.0.0-inplace" 'False) (C1 ('MetaCons "PublicKeyCredentialDescriptor" 'PrefixI 'True) (S1 ('MetaSel ('Just "littype") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DOMString) :*: (S1 ('MetaSel ('Just "id") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BufferSource) :*: S1 ('MetaSel ('Just "transports") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [DOMString])))))

data AuthenticatorSelectionCriteria Source #

Instances

Instances details
Eq AuthenticatorSelectionCriteria Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Types

Show AuthenticatorSelectionCriteria Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Types

Generic AuthenticatorSelectionCriteria Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Types

Associated Types

type Rep AuthenticatorSelectionCriteria :: Type -> Type #

ToJSON AuthenticatorSelectionCriteria Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Types

FromJSON AuthenticatorSelectionCriteria Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Types

type Rep AuthenticatorSelectionCriteria Source # 
Instance details

Defined in Crypto.WebAuthn.Model.WebIDL.Types

type Rep AuthenticatorSelectionCriteria = D1 ('MetaData "AuthenticatorSelectionCriteria" "Crypto.WebAuthn.Model.WebIDL.Types" "webauthn-0.1.0.0-inplace" 'False) (C1 ('MetaCons "AuthenticatorSelectionCriteria" 'PrefixI 'True) ((S1 ('MetaSel ('Just "authenticatorAttachment") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe DOMString)) :*: S1 ('MetaSel ('Just "residentKey") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe DOMString))) :*: (S1 ('MetaSel ('Just "requireResidentKey") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Boolean)) :*: S1 ('MetaSel ('Just "userVerification") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe DOMString)))))