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

Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Description

This module implements decoding/encoding from/to webauthn-json JSON values to the Haskell types defined in Crypto.WebAuthn.Model.Types.

Synopsis

Top-level types

data PublicKeyCredentialCreationOptions Source #

Instances

Instances details
FromJSON PublicKeyCredentialCreationOptions Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

ToJSON PublicKeyCredentialCreationOptions Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Generic PublicKeyCredentialCreationOptions Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Associated Types

type Rep PublicKeyCredentialCreationOptions :: Type -> Type #

Show PublicKeyCredentialCreationOptions Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Eq PublicKeyCredentialCreationOptions Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

type Rep PublicKeyCredentialCreationOptions Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

data PublicKeyCredentialRequestOptions Source #

Instances

Instances details
FromJSON PublicKeyCredentialRequestOptions Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

ToJSON PublicKeyCredentialRequestOptions Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Generic PublicKeyCredentialRequestOptions Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Associated Types

type Rep PublicKeyCredentialRequestOptions :: Type -> Type #

Show PublicKeyCredentialRequestOptions Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Eq PublicKeyCredentialRequestOptions Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

type Rep PublicKeyCredentialRequestOptions Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

data PublicKeyCredential response Source #

Instances

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

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

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

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Generic (PublicKeyCredential response) Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Associated Types

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

Methods

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

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

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

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Methods

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

show :: PublicKeyCredential response -> String #

showList :: [PublicKeyCredential response] -> ShowS #

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

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Methods

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

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

type Rep (PublicKeyCredential response) Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

type Rep (PublicKeyCredential response) = D1 ('MetaData "PublicKeyCredential" "Crypto.WebAuthn.Encoding.Internal.WebAuthnJson" "webauthn-0.6.0.1-inplace" 'False) (C1 ('MetaCons "PublicKeyCredential" 'PrefixI 'True) (S1 ('MetaSel ('Just "rawId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Base64UrlString) :*: (S1 ('MetaSel ('Just "response") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 response) :*: S1 ('MetaSel ('Just "clientExtensionResults") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AuthenticationExtensionsClientOutputs))))

Nested types

data AuthenticatorAttestationResponse Source #

Constructors

AuthenticatorAttestationResponse 

Fields

Instances

Instances details
FromJSON AuthenticatorAttestationResponse Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

ToJSON AuthenticatorAttestationResponse Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Generic AuthenticatorAttestationResponse Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Associated Types

type Rep AuthenticatorAttestationResponse :: Type -> Type #

Show AuthenticatorAttestationResponse Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Eq AuthenticatorAttestationResponse Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

type Rep AuthenticatorAttestationResponse Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

type Rep AuthenticatorAttestationResponse = D1 ('MetaData "AuthenticatorAttestationResponse" "Crypto.WebAuthn.Encoding.Internal.WebAuthnJson" "webauthn-0.6.0.1-inplace" 'False) (C1 ('MetaCons "AuthenticatorAttestationResponse" 'PrefixI 'True) (S1 ('MetaSel ('Just "clientDataJSON") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Base64UrlString) :*: (S1 ('MetaSel ('Just "attestationObject") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Base64UrlString) :*: S1 ('MetaSel ('Just "transports") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [Text])))))

data AuthenticatorAssertionResponse Source #

Instances

Instances details
FromJSON AuthenticatorAssertionResponse Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

ToJSON AuthenticatorAssertionResponse Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Generic AuthenticatorAssertionResponse Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Associated Types

type Rep AuthenticatorAssertionResponse :: Type -> Type #

Show AuthenticatorAssertionResponse Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Eq AuthenticatorAssertionResponse Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

type Rep AuthenticatorAssertionResponse Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

type Rep AuthenticatorAssertionResponse = D1 ('MetaData "AuthenticatorAssertionResponse" "Crypto.WebAuthn.Encoding.Internal.WebAuthnJson" "webauthn-0.6.0.1-inplace" 'False) (C1 ('MetaCons "AuthenticatorAssertionResponse" 'PrefixI 'True) ((S1 ('MetaSel ('Just "clientDataJSON") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Base64UrlString) :*: S1 ('MetaSel ('Just "authenticatorData") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Base64UrlString)) :*: (S1 ('MetaSel ('Just "signature") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Base64UrlString) :*: S1 ('MetaSel ('Just "userHandle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Base64UrlString)))))

data PublicKeyCredentialRpEntity Source #

Instances

Instances details
FromJSON PublicKeyCredentialRpEntity Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

ToJSON PublicKeyCredentialRpEntity Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Generic PublicKeyCredentialRpEntity Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Associated Types

type Rep PublicKeyCredentialRpEntity :: Type -> Type #

Show PublicKeyCredentialRpEntity Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Eq PublicKeyCredentialRpEntity Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

type Rep PublicKeyCredentialRpEntity Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

type Rep PublicKeyCredentialRpEntity = D1 ('MetaData "PublicKeyCredentialRpEntity" "Crypto.WebAuthn.Encoding.Internal.WebAuthnJson" "webauthn-0.6.0.1-inplace" 'False) (C1 ('MetaCons "PublicKeyCredentialRpEntity" 'PrefixI 'True) (S1 ('MetaSel ('Just "id") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

data PublicKeyCredentialUserEntity Source #

Instances

Instances details
FromJSON PublicKeyCredentialUserEntity Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

ToJSON PublicKeyCredentialUserEntity Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Generic PublicKeyCredentialUserEntity Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Associated Types

type Rep PublicKeyCredentialUserEntity :: Type -> Type #

Show PublicKeyCredentialUserEntity Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Eq PublicKeyCredentialUserEntity Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

type Rep PublicKeyCredentialUserEntity Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

type Rep PublicKeyCredentialUserEntity = D1 ('MetaData "PublicKeyCredentialUserEntity" "Crypto.WebAuthn.Encoding.Internal.WebAuthnJson" "webauthn-0.6.0.1-inplace" 'False) (C1 ('MetaCons "PublicKeyCredentialUserEntity" 'PrefixI 'True) (S1 ('MetaSel ('Just "id") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Base64UrlString) :*: (S1 ('MetaSel ('Just "displayName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))))

data PublicKeyCredentialParameters Source #

Instances

Instances details
FromJSON PublicKeyCredentialParameters Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

ToJSON PublicKeyCredentialParameters Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Generic PublicKeyCredentialParameters Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Associated Types

type Rep PublicKeyCredentialParameters :: Type -> Type #

Show PublicKeyCredentialParameters Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Eq PublicKeyCredentialParameters Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

type Rep PublicKeyCredentialParameters Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

type Rep PublicKeyCredentialParameters = D1 ('MetaData "PublicKeyCredentialParameters" "Crypto.WebAuthn.Encoding.Internal.WebAuthnJson" "webauthn-0.6.0.1-inplace" 'False) (C1 ('MetaCons "PublicKeyCredentialParameters" 'PrefixI 'True) (S1 ('MetaSel ('Just "littype") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "alg") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 COSEAlgorithmIdentifier)))

newtype AuthenticationExtensionsClientInputs Source #

Instances

Instances details
FromJSON AuthenticationExtensionsClientInputs Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

ToJSON AuthenticationExtensionsClientInputs Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Generic AuthenticationExtensionsClientInputs Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Show AuthenticationExtensionsClientInputs Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Eq AuthenticationExtensionsClientInputs Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

type Rep AuthenticationExtensionsClientInputs Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

type Rep AuthenticationExtensionsClientInputs = D1 ('MetaData "AuthenticationExtensionsClientInputs" "Crypto.WebAuthn.Encoding.Internal.WebAuthnJson" "webauthn-0.6.0.1-inplace" 'True) (C1 ('MetaCons "AuthenticationExtensionsClientInputs" 'PrefixI 'True) (S1 ('MetaSel ('Just "credProps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool))))

newtype AuthenticationExtensionsClientOutputs Source #

Instances

Instances details
FromJSON AuthenticationExtensionsClientOutputs Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

ToJSON AuthenticationExtensionsClientOutputs Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Generic AuthenticationExtensionsClientOutputs Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Show AuthenticationExtensionsClientOutputs Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Eq AuthenticationExtensionsClientOutputs Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

type Rep AuthenticationExtensionsClientOutputs Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

type Rep AuthenticationExtensionsClientOutputs = D1 ('MetaData "AuthenticationExtensionsClientOutputs" "Crypto.WebAuthn.Encoding.Internal.WebAuthnJson" "webauthn-0.6.0.1-inplace" 'True) (C1 ('MetaCons "AuthenticationExtensionsClientOutputs" 'PrefixI 'True) (S1 ('MetaSel ('Just "credProps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe CredentialPropertiesOutput))))

newtype CredentialPropertiesOutput Source #

Instances

Instances details
FromJSON CredentialPropertiesOutput Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

ToJSON CredentialPropertiesOutput Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Generic CredentialPropertiesOutput Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Associated Types

type Rep CredentialPropertiesOutput :: Type -> Type #

Show CredentialPropertiesOutput Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Eq CredentialPropertiesOutput Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

type Rep CredentialPropertiesOutput Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

type Rep CredentialPropertiesOutput = D1 ('MetaData "CredentialPropertiesOutput" "Crypto.WebAuthn.Encoding.Internal.WebAuthnJson" "webauthn-0.6.0.1-inplace" 'True) (C1 ('MetaCons "CredentialPropertiesOutput" 'PrefixI 'True) (S1 ('MetaSel ('Just "rk") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool))))

data PublicKeyCredentialDescriptor Source #

Instances

Instances details
FromJSON PublicKeyCredentialDescriptor Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

ToJSON PublicKeyCredentialDescriptor Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Generic PublicKeyCredentialDescriptor Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Associated Types

type Rep PublicKeyCredentialDescriptor :: Type -> Type #

Show PublicKeyCredentialDescriptor Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Eq PublicKeyCredentialDescriptor Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

type Rep PublicKeyCredentialDescriptor Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

type Rep PublicKeyCredentialDescriptor = D1 ('MetaData "PublicKeyCredentialDescriptor" "Crypto.WebAuthn.Encoding.Internal.WebAuthnJson" "webauthn-0.6.0.1-inplace" 'False) (C1 ('MetaCons "PublicKeyCredentialDescriptor" 'PrefixI 'True) (S1 ('MetaSel ('Just "littype") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "id") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Base64UrlString) :*: S1 ('MetaSel ('Just "transports") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [Text])))))

data AuthenticatorSelectionCriteria Source #

Instances

Instances details
FromJSON AuthenticatorSelectionCriteria Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

ToJSON AuthenticatorSelectionCriteria Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Generic AuthenticatorSelectionCriteria Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Associated Types

type Rep AuthenticatorSelectionCriteria :: Type -> Type #

Show AuthenticatorSelectionCriteria Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Eq AuthenticatorSelectionCriteria Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

type Rep AuthenticatorSelectionCriteria Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

type Rep AuthenticatorSelectionCriteria = D1 ('MetaData "AuthenticatorSelectionCriteria" "Crypto.WebAuthn.Encoding.Internal.WebAuthnJson" "webauthn-0.6.0.1-inplace" 'False) (C1 ('MetaCons "AuthenticatorSelectionCriteria" 'PrefixI 'True) ((S1 ('MetaSel ('Just "authenticatorAttachment") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "residentKey") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text))) :*: (S1 ('MetaSel ('Just "requireResidentKey") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "userVerification") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)))))

newtype Base64UrlString Source #

A base64url encoded string. Its FromJSON/ToJSON instances do the conversion

Type classes

class Encode a where Source #

A type class to indicate that some Haskell type a can be encoded to a corresponding JSON-serializable webauthn-json type JSON a using encode

Minimal complete definition

Nothing

Associated Types

type JSON a :: Type Source #

Methods

encode :: a -> JSON a Source #

Encodes a value to its webauthn-json equivalent

default encode :: Coercible a (JSON a) => a -> JSON a Source #

Instances

Instances details
Encode CoseSignAlg Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Associated Types

type JSON CoseSignAlg Source #

Encode AssertionSignature Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Associated Types

type JSON AssertionSignature Source #

Encode AttestationConveyancePreference Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Encode AuthenticationExtensionsClientInputs Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Encode AuthenticationExtensionsClientOutputs Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Encode AuthenticatorAttachment Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Associated Types

type JSON AuthenticatorAttachment Source #

Encode AuthenticatorSelectionCriteria Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Encode AuthenticatorTransport Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Associated Types

type JSON AuthenticatorTransport Source #

Encode Challenge Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Associated Types

type JSON Challenge Source #

Encode CredentialDescriptor Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Associated Types

type JSON CredentialDescriptor Source #

Encode CredentialId Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Associated Types

type JSON CredentialId Source #

Encode CredentialParameters Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Associated Types

type JSON CredentialParameters Source #

Encode CredentialPropertiesOutput Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Encode CredentialRpEntity Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Associated Types

type JSON CredentialRpEntity Source #

Encode CredentialType Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Associated Types

type JSON CredentialType Source #

Encode CredentialUserEntity Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Associated Types

type JSON CredentialUserEntity Source #

Encode RelyingPartyName Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Associated Types

type JSON RelyingPartyName Source #

Encode ResidentKeyRequirement Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Associated Types

type JSON ResidentKeyRequirement Source #

Encode RpId Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Associated Types

type JSON RpId Source #

Methods

encode :: RpId -> JSON RpId Source #

Encode Timeout Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Associated Types

type JSON Timeout Source #

Encode UserAccountDisplayName Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Associated Types

type JSON UserAccountDisplayName Source #

Encode UserAccountName Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Associated Types

type JSON UserAccountName Source #

Encode UserHandle Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Associated Types

type JSON UserHandle Source #

Encode UserVerificationRequirement Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Encode (AttestationObject 'True) Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Associated Types

type JSON (AttestationObject 'True) Source #

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 #

(Functor f, Encode a) => Encode (f a) Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Associated Types

type JSON (f a) Source #

Methods

encode :: f a -> JSON (f a) Source #

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

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

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

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

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Associated Types

type JSON (CollectedClientData c 'True) Source #

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 #

class Encode a => Decode m a where Source #

An extension of Encode to decoding. This typeclass is parametrized by a Monad m since decoding certain structures requires additional information to succeed, specifically SupportedAttestationStatementFormats, which can be provided with a MonadReader constraint

Minimal complete definition

Nothing

Methods

decode :: MonadError Text m => JSON a -> m a Source #

Decodes a webauthn-json type, potentially throwing a Text error

default decode :: (MonadError Text m, Coercible (JSON a) a) => JSON a -> m a Source #

Instances

Instances details
Decode m CoseSignAlg Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Decode m AssertionSignature Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Decode m AttestationConveyancePreference Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Decode m AuthenticationExtensionsClientInputs Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Decode m AuthenticationExtensionsClientOutputs Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Decode m AuthenticatorAttachment Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Decode m AuthenticatorSelectionCriteria Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Decode m AuthenticatorTransport Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Decode m Challenge Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Decode m CredentialDescriptor Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Decode m CredentialId Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Decode m CredentialParameters Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Decode m CredentialPropertiesOutput Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Decode m CredentialRpEntity Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Decode m CredentialType Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Decode m CredentialUserEntity Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Decode m RelyingPartyName Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Decode m ResidentKeyRequirement Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Decode m RpId Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Methods

decode :: JSON RpId -> m RpId Source #

Decode m Timeout Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Decode m UserAccountDisplayName Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Decode m UserAccountName Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Decode m UserHandle Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Decode m UserVerificationRequirement Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

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

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

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

(Traversable f, Decode m a) => Decode m (f a) Source # 
Instance details

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

Methods

decode :: JSON (f a) -> m (f a) Source #

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

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

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

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

Defined in Crypto.WebAuthn.Encoding.Internal.WebAuthnJson

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