{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TypeFamilies #-}

-- | Stability: internal
-- This module implements decoding\/encoding from\/to
-- [webauthn-json](https://github.com/github/webauthn-json) JSON values to the
-- Haskell types defined in "Crypto.WebAuthn.Model.Types".
module Crypto.WebAuthn.Encoding.Internal.WebAuthnJson
  ( -- * Top-level types
    PublicKeyCredentialCreationOptions (..),
    PublicKeyCredentialRequestOptions (..),
    PublicKeyCredential (..),

    -- * Nested types
    AuthenticatorAttestationResponse (..),
    AuthenticatorAssertionResponse (..),
    PublicKeyCredentialRpEntity (..),
    PublicKeyCredentialUserEntity (..),
    PublicKeyCredentialParameters (..),
    AuthenticationExtensionsClientInputs (..),
    AuthenticationExtensionsClientOutputs (..),
    CredentialPropertiesOutput (..),
    COSEAlgorithmIdentifier,
    PublicKeyCredentialDescriptor (..),
    AuthenticatorSelectionCriteria (..),
    Base64UrlString (..),

    -- * Type classes
    Encode (..),
    Decode (..),
  )
where

import Control.Monad.Except (MonadError, liftEither)
import Control.Monad.Reader (MonadReader (ask))
import qualified Crypto.WebAuthn.Cose.SignAlg as Cose
import qualified Crypto.WebAuthn.Encoding.Binary as B
import qualified Crypto.WebAuthn.Encoding.Strings as S
import Crypto.WebAuthn.Internal.Utils (jsonEncodingOptions)
import qualified Crypto.WebAuthn.Model.Defaults as D
import qualified Crypto.WebAuthn.Model.Kinds as K
import qualified Crypto.WebAuthn.Model.Types as T
import qualified Data.Aeson as Aeson
import qualified Data.ByteString as BS
import qualified Data.ByteString.Base64.URL as Base64Url
import Data.Coerce (Coercible, coerce)
import Data.Int (Int32)
import Data.Kind (Type)
import Data.Singletons (SingI)
import Data.Text (Text)
import qualified Data.Text.Encoding as Text
import Data.Word (Word32)
import GHC.Generics (Generic)

-- | 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'
class Encode a where
  type JSON a :: Type

  -- | Encodes a value to its webauthn-json equivalent
  encode :: a -> JSON a
  default encode :: Coercible a (JSON a) => a -> JSON a
  encode = coerce :: forall a b. Coercible a b => a -> b
coerce

-- | An extension of 'Encode' to decoding. This typeclass is parametrized by a
-- 'Monad' @m@ since decoding certain structures requires additional
-- information to succeed, specifically
-- 'M.SupportedAttestationStatementFormats', which can be provided with a
-- 'MonadReader' constraint
class Encode a => Decode m a where
  -- | Decodes a webauthn-json type, potentially throwing a 'Text' error
  decode :: MonadError Text m => JSON a -> m a
  default decode :: (MonadError Text m, Coercible (JSON a) a) => JSON a -> m a
  decode = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall b c a. (b -> c) -> (a -> b) -> a -> c
. coerce :: forall a b. Coercible a b => a -> b
coerce

-- | Decodes an optional value with a default
decodeWithDefault :: (MonadError Text m, Decode m a) => a -> Maybe (JSON a) -> m a
decodeWithDefault :: forall (m :: * -> *) a.
(MonadError Text m, Decode m a) =>
a -> Maybe (JSON a) -> m a
decodeWithDefault a
def Maybe (JSON a)
Nothing = forall (f :: * -> *) a. Applicative f => a -> f a
pure a
def
decodeWithDefault a
_ (Just JSON a
value) = forall (m :: * -> *) a.
(Decode m a, MonadError Text m) =>
JSON a -> m a
decode JSON a
value

instance (Functor f, Encode a) => Encode (f a) where
  type JSON (f a) = f (JSON a)
  encode :: f a -> JSON (f a)
encode = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Encode a => a -> JSON a
encode

instance (Traversable f, Decode m a) => Decode m (f a) where
  decode :: MonadError Text m => JSON (f a) -> m (f a)
decode = forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse forall (m :: * -> *) a.
(Decode m a, MonadError Text m) =>
JSON a -> m a
decode

-- | A base64url encoded string. Its 'Aeson.FromJSON'\/'Aeson.ToJSON' instances
-- do the conversion
newtype Base64UrlString = Base64UrlString {Base64UrlString -> ByteString
unBase64UrlString :: BS.ByteString}
  deriving (Int -> Base64UrlString -> ShowS
[Base64UrlString] -> ShowS
Base64UrlString -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Base64UrlString] -> ShowS
$cshowList :: [Base64UrlString] -> ShowS
show :: Base64UrlString -> String
$cshow :: Base64UrlString -> String
showsPrec :: Int -> Base64UrlString -> ShowS
$cshowsPrec :: Int -> Base64UrlString -> ShowS
Show, Base64UrlString -> Base64UrlString -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Base64UrlString -> Base64UrlString -> Bool
$c/= :: Base64UrlString -> Base64UrlString -> Bool
== :: Base64UrlString -> Base64UrlString -> Bool
$c== :: Base64UrlString -> Base64UrlString -> Bool
Eq)

-- | Decodes a base64url encoded JSON string into the bytes it represents
instance Aeson.FromJSON Base64UrlString where
  parseJSON :: Value -> Parser Base64UrlString
parseJSON = forall a. String -> (Text -> Parser a) -> Value -> Parser a
Aeson.withText String
"base64url" forall a b. (a -> b) -> a -> b
$ \Text
t ->
    forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either forall (m :: * -> *) a. MonadFail m => String -> m a
fail (forall (f :: * -> *) a. Applicative f => a -> f a
pure forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Base64UrlString
Base64UrlString) (ByteString -> Either String ByteString
Base64Url.decode forall a b. (a -> b) -> a -> b
$ Text -> ByteString
Text.encodeUtf8 Text
t)

-- | Encodes bytes using base64url to a JSON string
instance Aeson.ToJSON Base64UrlString where
  toJSON :: Base64UrlString -> Value
toJSON = Text -> Value
Aeson.String forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Text
Text.decodeUtf8 forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
Base64Url.encodeUnpadded forall b c a. (b -> c) -> (a -> b) -> a -> c
. Base64UrlString -> ByteString
unBase64UrlString

instance Encode T.Timeout where
  type JSON T.Timeout = Word32

instance Decode m T.Timeout

instance Encode T.RpId where
  type JSON T.RpId = Text

instance Decode m T.RpId

instance Encode T.RelyingPartyName where
  type JSON T.RelyingPartyName = Text

instance Decode m T.RelyingPartyName

instance Encode T.UserHandle where
  type JSON T.UserHandle = Base64UrlString

instance Decode m T.UserHandle

instance Encode T.UserAccountDisplayName where
  type JSON T.UserAccountDisplayName = Text

instance Decode m T.UserAccountDisplayName

instance Encode T.UserAccountName where
  type JSON T.UserAccountName = Text

instance Decode m T.UserAccountName

instance Encode T.Challenge where
  type JSON T.Challenge = Base64UrlString

instance Decode m T.Challenge

instance Encode T.CredentialId where
  type JSON T.CredentialId = Base64UrlString

instance Decode m T.CredentialId

instance Encode T.AssertionSignature where
  type JSON T.AssertionSignature = Base64UrlString

instance Decode m T.AssertionSignature

{-
Note: The spec often mentions that _client platforms_ must ignore unknown
values, but since we implement a RP, we don't need to concern ourselves with
that.

The only place where we do need to concern ourselves with it is the
[transports](https://www.w3.org/TR/webauthn-2/#dom-authenticatorattestationresponse-transports-slot)
field returned from the client, which in Level 2 of the spec mentions:

> The values SHOULD be members of
> `[AuthenticatorTransport](https://www.w3.org/TR/webauthn-2/#enumdef-authenticatortransport)`
> but [Relying Parties](https://www.w3.org/TR/webauthn-2/#relying-party) MUST
> ignore unknown values.

However that doesn't say what should happen in case of unknown values. This has
been fixed in a more recent version of the spec, see
https://github.com/w3c/webauthn/issues/1587. It will say this in the future:

> The values SHOULD be members of AuthenticatorTransport but Relying Parties
> SHOULD accept and store unknown values.
-}

instance Encode T.CredentialType where
  type JSON T.CredentialType = Text
  encode :: CredentialType -> JSON CredentialType
encode = CredentialType -> Text
S.encodeCredentialType

instance Decode m T.CredentialType where
  decode :: MonadError Text m => JSON CredentialType -> m CredentialType
decode = forall e (m :: * -> *) a. MonadError e m => Either e a -> m a
liftEither forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Either Text CredentialType
S.decodeCredentialType

instance Encode T.UserVerificationRequirement where
  type JSON T.UserVerificationRequirement = Text
  encode :: UserVerificationRequirement -> JSON UserVerificationRequirement
encode = UserVerificationRequirement -> Text
S.encodeUserVerificationRequirement

instance Decode m T.UserVerificationRequirement where
  decode :: MonadError Text m =>
JSON UserVerificationRequirement -> m UserVerificationRequirement
decode = forall e (m :: * -> *) a. MonadError e m => Either e a -> m a
liftEither forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Either Text UserVerificationRequirement
S.decodeUserVerificationRequirement

instance Encode T.AuthenticatorAttachment where
  type JSON T.AuthenticatorAttachment = Text
  encode :: AuthenticatorAttachment -> JSON AuthenticatorAttachment
encode = AuthenticatorAttachment -> Text
S.encodeAuthenticatorAttachment

instance Decode m T.AuthenticatorAttachment where
  decode :: MonadError Text m =>
JSON AuthenticatorAttachment -> m AuthenticatorAttachment
decode = forall e (m :: * -> *) a. MonadError e m => Either e a -> m a
liftEither forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Either Text AuthenticatorAttachment
S.decodeAuthenticatorAttachment

instance Encode T.ResidentKeyRequirement where
  type JSON T.ResidentKeyRequirement = Text
  encode :: ResidentKeyRequirement -> JSON ResidentKeyRequirement
encode = ResidentKeyRequirement -> Text
S.encodeResidentKeyRequirement

instance Decode m T.ResidentKeyRequirement where
  decode :: MonadError Text m =>
JSON ResidentKeyRequirement -> m ResidentKeyRequirement
decode = forall e (m :: * -> *) a. MonadError e m => Either e a -> m a
liftEither forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Either Text ResidentKeyRequirement
S.decodeResidentKeyRequirement

instance Encode T.AttestationConveyancePreference where
  type JSON T.AttestationConveyancePreference = Text
  encode :: AttestationConveyancePreference
-> JSON AttestationConveyancePreference
encode = AttestationConveyancePreference -> Text
S.encodeAttestationConveyancePreference

instance Decode m T.AttestationConveyancePreference where
  decode :: MonadError Text m =>
JSON AttestationConveyancePreference
-> m AttestationConveyancePreference
decode = forall e (m :: * -> *) a. MonadError e m => Either e a -> m a
liftEither forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Either Text AttestationConveyancePreference
S.decodeAttestationConveyancePreference

instance Encode T.AuthenticatorTransport where
  type JSON T.AuthenticatorTransport = Text
  encode :: AuthenticatorTransport -> JSON AuthenticatorTransport
encode = AuthenticatorTransport -> Text
S.encodeAuthenticatorTransport

instance Decode m T.AuthenticatorTransport where
  decode :: MonadError Text m =>
JSON AuthenticatorTransport -> m AuthenticatorTransport
decode = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> AuthenticatorTransport
S.decodeAuthenticatorTransport

instance Encode Cose.CoseSignAlg where
  type JSON Cose.CoseSignAlg = Int32
  encode :: CoseSignAlg -> JSON CoseSignAlg
encode = forall p. Num p => CoseSignAlg -> p
Cose.fromCoseSignAlg

instance Decode m Cose.CoseSignAlg where
  decode :: MonadError Text m => JSON CoseSignAlg -> m CoseSignAlg
decode = forall e (m :: * -> *) a. MonadError e m => Either e a -> m a
liftEither forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (Eq a, Num a, Show a) => a -> Either Text CoseSignAlg
Cose.toCoseSignAlg

-- | [(spec)](https://www.w3.org/TR/webauthn-2/#iface-authentication-extensions-client-inputs)
newtype AuthenticationExtensionsClientInputs = AuthenticationExtensionsClientInputs
  { -- | [(spec)](https://www.w3.org/TR/webauthn-2/#sctn-authenticator-credential-properties-extension)
    AuthenticationExtensionsClientInputs -> Maybe Bool
credProps :: Maybe Bool
  }
  deriving (AuthenticationExtensionsClientInputs
-> AuthenticationExtensionsClientInputs -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AuthenticationExtensionsClientInputs
-> AuthenticationExtensionsClientInputs -> Bool
$c/= :: AuthenticationExtensionsClientInputs
-> AuthenticationExtensionsClientInputs -> Bool
== :: AuthenticationExtensionsClientInputs
-> AuthenticationExtensionsClientInputs -> Bool
$c== :: AuthenticationExtensionsClientInputs
-> AuthenticationExtensionsClientInputs -> Bool
Eq, Int -> AuthenticationExtensionsClientInputs -> ShowS
[AuthenticationExtensionsClientInputs] -> ShowS
AuthenticationExtensionsClientInputs -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AuthenticationExtensionsClientInputs] -> ShowS
$cshowList :: [AuthenticationExtensionsClientInputs] -> ShowS
show :: AuthenticationExtensionsClientInputs -> String
$cshow :: AuthenticationExtensionsClientInputs -> String
showsPrec :: Int -> AuthenticationExtensionsClientInputs -> ShowS
$cshowsPrec :: Int -> AuthenticationExtensionsClientInputs -> ShowS
Show, forall x.
Rep AuthenticationExtensionsClientInputs x
-> AuthenticationExtensionsClientInputs
forall x.
AuthenticationExtensionsClientInputs
-> Rep AuthenticationExtensionsClientInputs x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep AuthenticationExtensionsClientInputs x
-> AuthenticationExtensionsClientInputs
$cfrom :: forall x.
AuthenticationExtensionsClientInputs
-> Rep AuthenticationExtensionsClientInputs x
Generic)

instance Aeson.FromJSON AuthenticationExtensionsClientInputs where
  parseJSON :: Value -> Parser AuthenticationExtensionsClientInputs
parseJSON = forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
Aeson.genericParseJSON Options
jsonEncodingOptions

instance Aeson.ToJSON AuthenticationExtensionsClientInputs where
  toJSON :: AuthenticationExtensionsClientInputs -> Value
toJSON = forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
Aeson.genericToJSON Options
jsonEncodingOptions

instance Encode T.AuthenticationExtensionsClientInputs where
  type JSON T.AuthenticationExtensionsClientInputs = AuthenticationExtensionsClientInputs

  -- TODO: Extensions are not implemented by this library, see the TODO in the
  -- module documentation of `Crypto.WebAuthn.Model` for more information.
  encode :: AuthenticationExtensionsClientInputs
-> JSON AuthenticationExtensionsClientInputs
encode T.AuthenticationExtensionsClientInputs {Maybe Bool
aeciCredProps :: AuthenticationExtensionsClientInputs -> Maybe Bool
aeciCredProps :: Maybe Bool
..} =
    AuthenticationExtensionsClientInputs
      { $sel:credProps:AuthenticationExtensionsClientInputs :: Maybe Bool
credProps = Maybe Bool
aeciCredProps
      }

instance Decode m T.AuthenticationExtensionsClientInputs where
  -- TODO: Extensions are not implemented by this library, see the TODO in the
  -- module documentation of `Crypto.WebAuthn.Model` for more information.
  decode :: MonadError Text m =>
JSON AuthenticationExtensionsClientInputs
-> m AuthenticationExtensionsClientInputs
decode AuthenticationExtensionsClientInputs {Maybe Bool
credProps :: Maybe Bool
$sel:credProps:AuthenticationExtensionsClientInputs :: AuthenticationExtensionsClientInputs -> Maybe Bool
..} = do
    let aeciCredProps :: Maybe Bool
aeciCredProps = Maybe Bool
credProps
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ T.AuthenticationExtensionsClientInputs {Maybe Bool
aeciCredProps :: Maybe Bool
aeciCredProps :: Maybe Bool
..}

-- | [(spec)](https://www.w3.org/TR/webauthn-2/#dictdef-credentialpropertiesoutput)
newtype CredentialPropertiesOutput = CredentialPropertiesOutput
  { -- | [(spec)](https://www.w3.org/TR/webauthn-2/#dom-credentialpropertiesoutput-rk)
    CredentialPropertiesOutput -> Maybe Bool
rk :: Maybe Bool
  }
  deriving (CredentialPropertiesOutput -> CredentialPropertiesOutput -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CredentialPropertiesOutput -> CredentialPropertiesOutput -> Bool
$c/= :: CredentialPropertiesOutput -> CredentialPropertiesOutput -> Bool
== :: CredentialPropertiesOutput -> CredentialPropertiesOutput -> Bool
$c== :: CredentialPropertiesOutput -> CredentialPropertiesOutput -> Bool
Eq, Int -> CredentialPropertiesOutput -> ShowS
[CredentialPropertiesOutput] -> ShowS
CredentialPropertiesOutput -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CredentialPropertiesOutput] -> ShowS
$cshowList :: [CredentialPropertiesOutput] -> ShowS
show :: CredentialPropertiesOutput -> String
$cshow :: CredentialPropertiesOutput -> String
showsPrec :: Int -> CredentialPropertiesOutput -> ShowS
$cshowsPrec :: Int -> CredentialPropertiesOutput -> ShowS
Show, forall x.
Rep CredentialPropertiesOutput x -> CredentialPropertiesOutput
forall x.
CredentialPropertiesOutput -> Rep CredentialPropertiesOutput x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CredentialPropertiesOutput x -> CredentialPropertiesOutput
$cfrom :: forall x.
CredentialPropertiesOutput -> Rep CredentialPropertiesOutput x
Generic)

instance Aeson.FromJSON CredentialPropertiesOutput where
  parseJSON :: Value -> Parser CredentialPropertiesOutput
parseJSON = forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
Aeson.genericParseJSON Options
jsonEncodingOptions

instance Aeson.ToJSON CredentialPropertiesOutput where
  toJSON :: CredentialPropertiesOutput -> Value
toJSON = forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
Aeson.genericToJSON Options
jsonEncodingOptions

instance Encode T.CredentialPropertiesOutput where
  type JSON T.CredentialPropertiesOutput = CredentialPropertiesOutput
  encode :: CredentialPropertiesOutput -> JSON CredentialPropertiesOutput
encode T.CredentialPropertiesOutput {Maybe Bool
cpoRk :: CredentialPropertiesOutput -> Maybe Bool
cpoRk :: Maybe Bool
..} =
    CredentialPropertiesOutput
      { $sel:rk:CredentialPropertiesOutput :: Maybe Bool
rk = Maybe Bool
cpoRk
      }

instance Decode m T.CredentialPropertiesOutput where
  decode :: MonadError Text m =>
JSON CredentialPropertiesOutput -> m CredentialPropertiesOutput
decode CredentialPropertiesOutput {Maybe Bool
rk :: Maybe Bool
$sel:rk:CredentialPropertiesOutput :: CredentialPropertiesOutput -> Maybe Bool
..} = do
    let cpoRk :: Maybe Bool
cpoRk = Maybe Bool
rk
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ T.CredentialPropertiesOutput {Maybe Bool
cpoRk :: Maybe Bool
cpoRk :: Maybe Bool
..}

-- | [(spec)](https://www.w3.org/TR/webauthn-2/#iface-authentication-extensions-client-outputs)
newtype AuthenticationExtensionsClientOutputs = AuthenticationExtensionsClientOutputs
  { -- | [(spec)](https://www.w3.org/TR/webauthn-2/#sctn-authenticator-credential-properties-extension)
    AuthenticationExtensionsClientOutputs
-> Maybe CredentialPropertiesOutput
credProps :: Maybe CredentialPropertiesOutput
  }
  deriving (AuthenticationExtensionsClientOutputs
-> AuthenticationExtensionsClientOutputs -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AuthenticationExtensionsClientOutputs
-> AuthenticationExtensionsClientOutputs -> Bool
$c/= :: AuthenticationExtensionsClientOutputs
-> AuthenticationExtensionsClientOutputs -> Bool
== :: AuthenticationExtensionsClientOutputs
-> AuthenticationExtensionsClientOutputs -> Bool
$c== :: AuthenticationExtensionsClientOutputs
-> AuthenticationExtensionsClientOutputs -> Bool
Eq, Int -> AuthenticationExtensionsClientOutputs -> ShowS
[AuthenticationExtensionsClientOutputs] -> ShowS
AuthenticationExtensionsClientOutputs -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AuthenticationExtensionsClientOutputs] -> ShowS
$cshowList :: [AuthenticationExtensionsClientOutputs] -> ShowS
show :: AuthenticationExtensionsClientOutputs -> String
$cshow :: AuthenticationExtensionsClientOutputs -> String
showsPrec :: Int -> AuthenticationExtensionsClientOutputs -> ShowS
$cshowsPrec :: Int -> AuthenticationExtensionsClientOutputs -> ShowS
Show, forall x.
Rep AuthenticationExtensionsClientOutputs x
-> AuthenticationExtensionsClientOutputs
forall x.
AuthenticationExtensionsClientOutputs
-> Rep AuthenticationExtensionsClientOutputs x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep AuthenticationExtensionsClientOutputs x
-> AuthenticationExtensionsClientOutputs
$cfrom :: forall x.
AuthenticationExtensionsClientOutputs
-> Rep AuthenticationExtensionsClientOutputs x
Generic)

instance Aeson.FromJSON AuthenticationExtensionsClientOutputs where
  parseJSON :: Value -> Parser AuthenticationExtensionsClientOutputs
parseJSON = forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
Aeson.genericParseJSON Options
jsonEncodingOptions

instance Aeson.ToJSON AuthenticationExtensionsClientOutputs where
  toJSON :: AuthenticationExtensionsClientOutputs -> Value
toJSON = forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
Aeson.genericToJSON Options
jsonEncodingOptions

instance Encode T.AuthenticationExtensionsClientOutputs where
  type JSON T.AuthenticationExtensionsClientOutputs = AuthenticationExtensionsClientOutputs

  -- TODO: Extensions are not implemented by this library, see the TODO in the
  -- module documentation of `Crypto.WebAuthn.Model` for more information.
  encode :: AuthenticationExtensionsClientOutputs
-> JSON AuthenticationExtensionsClientOutputs
encode T.AuthenticationExtensionsClientOutputs {Maybe CredentialPropertiesOutput
aecoCredProps :: AuthenticationExtensionsClientOutputs
-> Maybe CredentialPropertiesOutput
aecoCredProps :: Maybe CredentialPropertiesOutput
..} =
    AuthenticationExtensionsClientOutputs
      { $sel:credProps:AuthenticationExtensionsClientOutputs :: Maybe CredentialPropertiesOutput
credProps = forall a. Encode a => a -> JSON a
encode Maybe CredentialPropertiesOutput
aecoCredProps
      }

instance Decode m T.AuthenticationExtensionsClientOutputs where
  -- TODO: Extensions are not implemented by this library, see the TODO in the
  -- module documentation of `Crypto.WebAuthn.Model` for more information.
  decode :: MonadError Text m =>
JSON AuthenticationExtensionsClientOutputs
-> m AuthenticationExtensionsClientOutputs
decode AuthenticationExtensionsClientOutputs {Maybe CredentialPropertiesOutput
credProps :: Maybe CredentialPropertiesOutput
$sel:credProps:AuthenticationExtensionsClientOutputs :: AuthenticationExtensionsClientOutputs
-> Maybe CredentialPropertiesOutput
..} = do
    Maybe CredentialPropertiesOutput
aecoCredProps <- forall (m :: * -> *) a.
(Decode m a, MonadError Text m) =>
JSON a -> m a
decode Maybe CredentialPropertiesOutput
credProps
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ T.AuthenticationExtensionsClientOutputs {Maybe CredentialPropertiesOutput
aecoCredProps :: Maybe CredentialPropertiesOutput
aecoCredProps :: Maybe CredentialPropertiesOutput
..}

instance SingI c => Encode (T.CollectedClientData (c :: K.CeremonyKind) 'True) where
  type JSON (T.CollectedClientData c 'True) = Base64UrlString
  encode :: CollectedClientData c 'True -> JSON (CollectedClientData c 'True)
encode = ByteString -> Base64UrlString
Base64UrlString forall b c a. (b -> c) -> (a -> b) -> a -> c
. RawField 'True -> ByteString
T.unRaw forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (c :: CeremonyKind) (raw :: Bool).
CollectedClientData c raw -> RawField raw
T.ccdRawData

instance SingI c => Decode m (T.CollectedClientData (c :: K.CeremonyKind) 'True) where
  decode :: MonadError Text m =>
JSON (CollectedClientData c 'True)
-> m (CollectedClientData c 'True)
decode = forall e (m :: * -> *) a. MonadError e m => Either e a -> m a
liftEither forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (c :: CeremonyKind).
SingI c =>
ByteString -> Either Text (CollectedClientData c 'True)
B.decodeCollectedClientData forall b c a. (b -> c) -> (a -> b) -> a -> c
. Base64UrlString -> ByteString
unBase64UrlString

instance Encode (T.AttestationObject 'True) where
  type JSON (T.AttestationObject 'True) = Base64UrlString
  encode :: AttestationObject 'True -> JSON (AttestationObject 'True)
encode = ByteString -> Base64UrlString
Base64UrlString forall b c a. (b -> c) -> (a -> b) -> a -> c
. AttestationObject 'True -> ByteString
B.encodeAttestationObject

instance
  MonadReader T.SupportedAttestationStatementFormats m =>
  Decode m (T.AttestationObject 'True)
  where
  decode :: MonadError Text m =>
JSON (AttestationObject 'True) -> m (AttestationObject 'True)
decode (Base64UrlString ByteString
bytes) = do
    SupportedAttestationStatementFormats
supportedFormats <- forall r (m :: * -> *). MonadReader r m => m r
ask
    forall e (m :: * -> *) a. MonadError e m => Either e a -> m a
liftEither forall a b. (a -> b) -> a -> b
$ SupportedAttestationStatementFormats
-> ByteString -> Either Text (AttestationObject 'True)
B.decodeAttestationObject SupportedAttestationStatementFormats
supportedFormats ByteString
bytes

instance Encode (T.AuthenticatorData 'K.Authentication 'True) where
  type JSON (T.AuthenticatorData 'K.Authentication 'True) = Base64UrlString
  encode :: AuthenticatorData 'Authentication 'True
-> JSON (AuthenticatorData 'Authentication 'True)
encode = ByteString -> Base64UrlString
Base64UrlString forall b c a. (b -> c) -> (a -> b) -> a -> c
. RawField 'True -> ByteString
T.unRaw forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (c :: CeremonyKind) (raw :: Bool).
AuthenticatorData c raw -> RawField raw
T.adRawData

instance Decode m (T.AuthenticatorData 'K.Authentication 'True) where
  decode :: MonadError Text m =>
JSON (AuthenticatorData 'Authentication 'True)
-> m (AuthenticatorData 'Authentication 'True)
decode = forall e (m :: * -> *) a. MonadError e m => Either e a -> m a
liftEither forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (c :: CeremonyKind).
SingI c =>
ByteString -> Either Text (AuthenticatorData c 'True)
B.decodeAuthenticatorData forall b c a. (b -> c) -> (a -> b) -> a -> c
. Base64UrlString -> ByteString
unBase64UrlString

-- | [(spec)](https://www.w3.org/TR/webauthn-2/#dictionary-makecredentialoptions)
data PublicKeyCredentialCreationOptions = PublicKeyCredentialCreationOptions
  { -- | [(spec)](https://www.w3.org/TR/webauthn-2/#dom-publickeycredentialcreationoptions-rp)
    PublicKeyCredentialCreationOptions -> PublicKeyCredentialRpEntity
rp :: PublicKeyCredentialRpEntity,
    -- | [(spec)](https://www.w3.org/TR/webauthn-2/#dom-publickeycredentialcreationoptions-user)
    PublicKeyCredentialCreationOptions -> PublicKeyCredentialUserEntity
user :: PublicKeyCredentialUserEntity,
    -- | [(spec)](https://www.w3.org/TR/webauthn-2/#dom-publickeycredentialcreationoptions-challenge)
    PublicKeyCredentialCreationOptions -> Base64UrlString
challenge :: Base64UrlString,
    -- | [(spec)](https://www.w3.org/TR/webauthn-2/#dom-publickeycredentialcreationoptions-pubkeycredparams)
    PublicKeyCredentialCreationOptions
-> [PublicKeyCredentialParameters]
pubKeyCredParams :: [PublicKeyCredentialParameters],
    -- | [(spec)](https://www.w3.org/TR/webauthn-2/#dom-publickeycredentialcreationoptions-timeout)
    PublicKeyCredentialCreationOptions -> Maybe Word32
timeout :: Maybe Word32,
    -- | [(spec)](https://www.w3.org/TR/webauthn-2/#dom-publickeycredentialcreationoptions-excludecredentials)
    PublicKeyCredentialCreationOptions
-> Maybe [PublicKeyCredentialDescriptor]
excludeCredentials :: Maybe [PublicKeyCredentialDescriptor],
    -- | [(spec)](https://www.w3.org/TR/webauthn-2/#dom-publickeycredentialcreationoptions-authenticatorselection)
    PublicKeyCredentialCreationOptions
-> Maybe AuthenticatorSelectionCriteria
authenticatorSelection :: Maybe AuthenticatorSelectionCriteria,
    -- | [(spec)](https://www.w3.org/TR/webauthn-2/#dom-publickeycredentialcreationoptions-attestation)
    PublicKeyCredentialCreationOptions -> Maybe Text
attestation :: Maybe Text,
    -- | [(spec)](https://www.w3.org/TR/webauthn-2/#dom-publickeycredentialcreationoptions-extensions)
    PublicKeyCredentialCreationOptions
-> Maybe AuthenticationExtensionsClientInputs
extensions :: Maybe AuthenticationExtensionsClientInputs
  }
  deriving (PublicKeyCredentialCreationOptions
-> PublicKeyCredentialCreationOptions -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PublicKeyCredentialCreationOptions
-> PublicKeyCredentialCreationOptions -> Bool
$c/= :: PublicKeyCredentialCreationOptions
-> PublicKeyCredentialCreationOptions -> Bool
== :: PublicKeyCredentialCreationOptions
-> PublicKeyCredentialCreationOptions -> Bool
$c== :: PublicKeyCredentialCreationOptions
-> PublicKeyCredentialCreationOptions -> Bool
Eq, Int -> PublicKeyCredentialCreationOptions -> ShowS
[PublicKeyCredentialCreationOptions] -> ShowS
PublicKeyCredentialCreationOptions -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PublicKeyCredentialCreationOptions] -> ShowS
$cshowList :: [PublicKeyCredentialCreationOptions] -> ShowS
show :: PublicKeyCredentialCreationOptions -> String
$cshow :: PublicKeyCredentialCreationOptions -> String
showsPrec :: Int -> PublicKeyCredentialCreationOptions -> ShowS
$cshowsPrec :: Int -> PublicKeyCredentialCreationOptions -> ShowS
Show, forall x.
Rep PublicKeyCredentialCreationOptions x
-> PublicKeyCredentialCreationOptions
forall x.
PublicKeyCredentialCreationOptions
-> Rep PublicKeyCredentialCreationOptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep PublicKeyCredentialCreationOptions x
-> PublicKeyCredentialCreationOptions
$cfrom :: forall x.
PublicKeyCredentialCreationOptions
-> Rep PublicKeyCredentialCreationOptions x
Generic)

instance Aeson.FromJSON PublicKeyCredentialCreationOptions where
  parseJSON :: Value -> Parser PublicKeyCredentialCreationOptions
parseJSON = forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
Aeson.genericParseJSON Options
jsonEncodingOptions

instance Aeson.ToJSON PublicKeyCredentialCreationOptions where
  toJSON :: PublicKeyCredentialCreationOptions -> Value
toJSON = forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
Aeson.genericToJSON Options
jsonEncodingOptions

instance Encode (T.CredentialOptions 'K.Registration) where
  type JSON (T.CredentialOptions 'K.Registration) = PublicKeyCredentialCreationOptions
  encode :: CredentialOptions 'Registration
-> JSON (CredentialOptions 'Registration)
encode T.CredentialOptionsRegistration {[CredentialDescriptor]
[CredentialParameters]
Maybe AuthenticatorSelectionCriteria
Maybe AuthenticationExtensionsClientInputs
Maybe Timeout
CredentialUserEntity
CredentialRpEntity
Challenge
AttestationConveyancePreference
corExtensions :: CredentialOptions 'Registration
-> Maybe AuthenticationExtensionsClientInputs
corAttestation :: CredentialOptions 'Registration -> AttestationConveyancePreference
corAuthenticatorSelection :: CredentialOptions 'Registration
-> Maybe AuthenticatorSelectionCriteria
corExcludeCredentials :: CredentialOptions 'Registration -> [CredentialDescriptor]
corTimeout :: CredentialOptions 'Registration -> Maybe Timeout
corPubKeyCredParams :: CredentialOptions 'Registration -> [CredentialParameters]
corChallenge :: CredentialOptions 'Registration -> Challenge
corUser :: CredentialOptions 'Registration -> CredentialUserEntity
corRp :: CredentialOptions 'Registration -> CredentialRpEntity
corExtensions :: Maybe AuthenticationExtensionsClientInputs
corAttestation :: AttestationConveyancePreference
corAuthenticatorSelection :: Maybe AuthenticatorSelectionCriteria
corExcludeCredentials :: [CredentialDescriptor]
corTimeout :: Maybe Timeout
corPubKeyCredParams :: [CredentialParameters]
corChallenge :: Challenge
corUser :: CredentialUserEntity
corRp :: CredentialRpEntity
..} =
    PublicKeyCredentialCreationOptions
      { $sel:rp:PublicKeyCredentialCreationOptions :: PublicKeyCredentialRpEntity
rp = forall a. Encode a => a -> JSON a
encode CredentialRpEntity
corRp,
        $sel:user:PublicKeyCredentialCreationOptions :: PublicKeyCredentialUserEntity
user = forall a. Encode a => a -> JSON a
encode CredentialUserEntity
corUser,
        $sel:challenge:PublicKeyCredentialCreationOptions :: Base64UrlString
challenge = forall a. Encode a => a -> JSON a
encode Challenge
corChallenge,
        $sel:pubKeyCredParams:PublicKeyCredentialCreationOptions :: [PublicKeyCredentialParameters]
pubKeyCredParams = forall a. Encode a => a -> JSON a
encode [CredentialParameters]
corPubKeyCredParams,
        $sel:timeout:PublicKeyCredentialCreationOptions :: Maybe Word32
timeout = forall a. Encode a => a -> JSON a
encode Maybe Timeout
corTimeout,
        $sel:excludeCredentials:PublicKeyCredentialCreationOptions :: Maybe [PublicKeyCredentialDescriptor]
excludeCredentials = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall a. Encode a => a -> JSON a
encode [CredentialDescriptor]
corExcludeCredentials,
        $sel:authenticatorSelection:PublicKeyCredentialCreationOptions :: Maybe AuthenticatorSelectionCriteria
authenticatorSelection = forall a. Encode a => a -> JSON a
encode Maybe AuthenticatorSelectionCriteria
corAuthenticatorSelection,
        $sel:attestation:PublicKeyCredentialCreationOptions :: Maybe Text
attestation = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall a. Encode a => a -> JSON a
encode AttestationConveyancePreference
corAttestation,
        $sel:extensions:PublicKeyCredentialCreationOptions :: Maybe AuthenticationExtensionsClientInputs
extensions = forall a. Encode a => a -> JSON a
encode Maybe AuthenticationExtensionsClientInputs
corExtensions
      }

instance Decode m (T.CredentialOptions 'K.Registration) where
  decode :: MonadError Text m =>
JSON (CredentialOptions 'Registration)
-> m (CredentialOptions 'Registration)
decode PublicKeyCredentialCreationOptions {[PublicKeyCredentialParameters]
Maybe [PublicKeyCredentialDescriptor]
Maybe Word32
Maybe Text
Maybe AuthenticatorSelectionCriteria
Maybe AuthenticationExtensionsClientInputs
PublicKeyCredentialUserEntity
PublicKeyCredentialRpEntity
Base64UrlString
extensions :: Maybe AuthenticationExtensionsClientInputs
attestation :: Maybe Text
authenticatorSelection :: Maybe AuthenticatorSelectionCriteria
excludeCredentials :: Maybe [PublicKeyCredentialDescriptor]
timeout :: Maybe Word32
pubKeyCredParams :: [PublicKeyCredentialParameters]
challenge :: Base64UrlString
user :: PublicKeyCredentialUserEntity
rp :: PublicKeyCredentialRpEntity
$sel:extensions:PublicKeyCredentialCreationOptions :: PublicKeyCredentialCreationOptions
-> Maybe AuthenticationExtensionsClientInputs
$sel:attestation:PublicKeyCredentialCreationOptions :: PublicKeyCredentialCreationOptions -> Maybe Text
$sel:authenticatorSelection:PublicKeyCredentialCreationOptions :: PublicKeyCredentialCreationOptions
-> Maybe AuthenticatorSelectionCriteria
$sel:excludeCredentials:PublicKeyCredentialCreationOptions :: PublicKeyCredentialCreationOptions
-> Maybe [PublicKeyCredentialDescriptor]
$sel:timeout:PublicKeyCredentialCreationOptions :: PublicKeyCredentialCreationOptions -> Maybe Word32
$sel:pubKeyCredParams:PublicKeyCredentialCreationOptions :: PublicKeyCredentialCreationOptions
-> [PublicKeyCredentialParameters]
$sel:challenge:PublicKeyCredentialCreationOptions :: PublicKeyCredentialCreationOptions -> Base64UrlString
$sel:user:PublicKeyCredentialCreationOptions :: PublicKeyCredentialCreationOptions -> PublicKeyCredentialUserEntity
$sel:rp:PublicKeyCredentialCreationOptions :: PublicKeyCredentialCreationOptions -> PublicKeyCredentialRpEntity
..} = do
    CredentialRpEntity
corRp <- forall (m :: * -> *) a.
(Decode m a, MonadError Text m) =>
JSON a -> m a
decode PublicKeyCredentialRpEntity
rp
    CredentialUserEntity
corUser <- forall (m :: * -> *) a.
(Decode m a, MonadError Text m) =>
JSON a -> m a
decode PublicKeyCredentialUserEntity
user
    Challenge
corChallenge <- forall (m :: * -> *) a.
(Decode m a, MonadError Text m) =>
JSON a -> m a
decode Base64UrlString
challenge
    [CredentialParameters]
corPubKeyCredParams <- forall (m :: * -> *) a.
(Decode m a, MonadError Text m) =>
JSON a -> m a
decode [PublicKeyCredentialParameters]
pubKeyCredParams
    Maybe Timeout
corTimeout <- forall (m :: * -> *) a.
(Decode m a, MonadError Text m) =>
JSON a -> m a
decode Maybe Word32
timeout
    [CredentialDescriptor]
corExcludeCredentials <- forall (m :: * -> *) a.
(MonadError Text m, Decode m a) =>
a -> Maybe (JSON a) -> m a
decodeWithDefault [CredentialDescriptor]
D.corExcludeCredentialsDefault Maybe [PublicKeyCredentialDescriptor]
excludeCredentials
    Maybe AuthenticatorSelectionCriteria
corAuthenticatorSelection <- forall (m :: * -> *) a.
(Decode m a, MonadError Text m) =>
JSON a -> m a
decode Maybe AuthenticatorSelectionCriteria
authenticatorSelection
    AttestationConveyancePreference
corAttestation <- forall (m :: * -> *) a.
(MonadError Text m, Decode m a) =>
a -> Maybe (JSON a) -> m a
decodeWithDefault AttestationConveyancePreference
D.corAttestationDefault Maybe Text
attestation
    Maybe AuthenticationExtensionsClientInputs
corExtensions <- forall (m :: * -> *) a.
(Decode m a, MonadError Text m) =>
JSON a -> m a
decode Maybe AuthenticationExtensionsClientInputs
extensions
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ T.CredentialOptionsRegistration {[CredentialDescriptor]
[CredentialParameters]
Maybe AuthenticatorSelectionCriteria
Maybe AuthenticationExtensionsClientInputs
Maybe Timeout
CredentialUserEntity
CredentialRpEntity
Challenge
AttestationConveyancePreference
corExtensions :: Maybe AuthenticationExtensionsClientInputs
corAttestation :: AttestationConveyancePreference
corAuthenticatorSelection :: Maybe AuthenticatorSelectionCriteria
corExcludeCredentials :: [CredentialDescriptor]
corTimeout :: Maybe Timeout
corPubKeyCredParams :: [CredentialParameters]
corChallenge :: Challenge
corUser :: CredentialUserEntity
corRp :: CredentialRpEntity
corExtensions :: Maybe AuthenticationExtensionsClientInputs
corAttestation :: AttestationConveyancePreference
corAuthenticatorSelection :: Maybe AuthenticatorSelectionCriteria
corExcludeCredentials :: [CredentialDescriptor]
corTimeout :: Maybe Timeout
corPubKeyCredParams :: [CredentialParameters]
corChallenge :: Challenge
corUser :: CredentialUserEntity
corRp :: CredentialRpEntity
..}

-- | [(spec)](https://www.w3.org/TR/webauthn-2/#dictionary-assertion-options)
data PublicKeyCredentialRequestOptions = PublicKeyCredentialRequestOptions
  { -- | [(spec)](https://www.w3.org/TR/webauthn-2/#dom-publickeycredentialrequestoptions-challenge)
    PublicKeyCredentialRequestOptions -> Base64UrlString
challenge :: Base64UrlString,
    -- | [(spec)](https://www.w3.org/TR/webauthn-2/#dom-publickeycredentialrequestoptions-timeout)
    PublicKeyCredentialRequestOptions -> Maybe Word32
timeout :: Maybe Word32,
    -- | [(spec)](https://www.w3.org/TR/webauthn-2/#dom-publickeycredentialrequestoptions-rpid)
    PublicKeyCredentialRequestOptions -> Maybe Text
rpId :: Maybe Text,
    -- | [(spec)](https://www.w3.org/TR/webauthn-2/#dom-publickeycredentialrequestoptions-allowcredentials)
    PublicKeyCredentialRequestOptions
-> Maybe [PublicKeyCredentialDescriptor]
allowCredentials :: Maybe [PublicKeyCredentialDescriptor],
    -- | [(spec)](https://www.w3.org/TR/webauthn-2/#dom-publickeycredentialrequestoptions-userverification)
    PublicKeyCredentialRequestOptions -> Maybe Text
userVerification :: Maybe Text,
    -- | [(spec)](https://www.w3.org/TR/webauthn-2/#dom-publickeycredentialrequestoptions-extensions)
    PublicKeyCredentialRequestOptions
-> Maybe AuthenticationExtensionsClientInputs
extensions :: Maybe AuthenticationExtensionsClientInputs
  }
  deriving (PublicKeyCredentialRequestOptions
-> PublicKeyCredentialRequestOptions -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PublicKeyCredentialRequestOptions
-> PublicKeyCredentialRequestOptions -> Bool
$c/= :: PublicKeyCredentialRequestOptions
-> PublicKeyCredentialRequestOptions -> Bool
== :: PublicKeyCredentialRequestOptions
-> PublicKeyCredentialRequestOptions -> Bool
$c== :: PublicKeyCredentialRequestOptions
-> PublicKeyCredentialRequestOptions -> Bool
Eq, Int -> PublicKeyCredentialRequestOptions -> ShowS
[PublicKeyCredentialRequestOptions] -> ShowS
PublicKeyCredentialRequestOptions -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PublicKeyCredentialRequestOptions] -> ShowS
$cshowList :: [PublicKeyCredentialRequestOptions] -> ShowS
show :: PublicKeyCredentialRequestOptions -> String
$cshow :: PublicKeyCredentialRequestOptions -> String
showsPrec :: Int -> PublicKeyCredentialRequestOptions -> ShowS
$cshowsPrec :: Int -> PublicKeyCredentialRequestOptions -> ShowS
Show, forall x.
Rep PublicKeyCredentialRequestOptions x
-> PublicKeyCredentialRequestOptions
forall x.
PublicKeyCredentialRequestOptions
-> Rep PublicKeyCredentialRequestOptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep PublicKeyCredentialRequestOptions x
-> PublicKeyCredentialRequestOptions
$cfrom :: forall x.
PublicKeyCredentialRequestOptions
-> Rep PublicKeyCredentialRequestOptions x
Generic)

instance Aeson.FromJSON PublicKeyCredentialRequestOptions where
  parseJSON :: Value -> Parser PublicKeyCredentialRequestOptions
parseJSON = forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
Aeson.genericParseJSON Options
jsonEncodingOptions

instance Aeson.ToJSON PublicKeyCredentialRequestOptions where
  toJSON :: PublicKeyCredentialRequestOptions -> Value
toJSON = forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
Aeson.genericToJSON Options
jsonEncodingOptions

instance Encode (T.CredentialOptions 'K.Authentication) where
  type JSON (T.CredentialOptions 'K.Authentication) = PublicKeyCredentialRequestOptions
  encode :: CredentialOptions 'Authentication
-> JSON (CredentialOptions 'Authentication)
encode T.CredentialOptionsAuthentication {[CredentialDescriptor]
Maybe AuthenticationExtensionsClientInputs
Maybe Timeout
Maybe RpId
Challenge
UserVerificationRequirement
coaExtensions :: CredentialOptions 'Authentication
-> Maybe AuthenticationExtensionsClientInputs
coaUserVerification :: CredentialOptions 'Authentication -> UserVerificationRequirement
coaAllowCredentials :: CredentialOptions 'Authentication -> [CredentialDescriptor]
coaRpId :: CredentialOptions 'Authentication -> Maybe RpId
coaTimeout :: CredentialOptions 'Authentication -> Maybe Timeout
coaChallenge :: CredentialOptions 'Authentication -> Challenge
coaExtensions :: Maybe AuthenticationExtensionsClientInputs
coaUserVerification :: UserVerificationRequirement
coaAllowCredentials :: [CredentialDescriptor]
coaRpId :: Maybe RpId
coaTimeout :: Maybe Timeout
coaChallenge :: Challenge
..} =
    PublicKeyCredentialRequestOptions
      { $sel:challenge:PublicKeyCredentialRequestOptions :: Base64UrlString
challenge = forall a. Encode a => a -> JSON a
encode Challenge
coaChallenge,
        $sel:timeout:PublicKeyCredentialRequestOptions :: Maybe Word32
timeout = forall a. Encode a => a -> JSON a
encode Maybe Timeout
coaTimeout,
        $sel:rpId:PublicKeyCredentialRequestOptions :: Maybe Text
rpId = forall a. Encode a => a -> JSON a
encode Maybe RpId
coaRpId,
        $sel:allowCredentials:PublicKeyCredentialRequestOptions :: Maybe [PublicKeyCredentialDescriptor]
allowCredentials = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall a. Encode a => a -> JSON a
encode [CredentialDescriptor]
coaAllowCredentials,
        $sel:userVerification:PublicKeyCredentialRequestOptions :: Maybe Text
userVerification = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall a. Encode a => a -> JSON a
encode UserVerificationRequirement
coaUserVerification,
        $sel:extensions:PublicKeyCredentialRequestOptions :: Maybe AuthenticationExtensionsClientInputs
extensions = forall a. Encode a => a -> JSON a
encode Maybe AuthenticationExtensionsClientInputs
coaExtensions
      }

instance Decode m (T.CredentialOptions 'K.Authentication) where
  decode :: MonadError Text m =>
JSON (CredentialOptions 'Authentication)
-> m (CredentialOptions 'Authentication)
decode PublicKeyCredentialRequestOptions {Maybe [PublicKeyCredentialDescriptor]
Maybe Word32
Maybe Text
Maybe AuthenticationExtensionsClientInputs
Base64UrlString
extensions :: Maybe AuthenticationExtensionsClientInputs
userVerification :: Maybe Text
allowCredentials :: Maybe [PublicKeyCredentialDescriptor]
rpId :: Maybe Text
timeout :: Maybe Word32
challenge :: Base64UrlString
$sel:extensions:PublicKeyCredentialRequestOptions :: PublicKeyCredentialRequestOptions
-> Maybe AuthenticationExtensionsClientInputs
$sel:userVerification:PublicKeyCredentialRequestOptions :: PublicKeyCredentialRequestOptions -> Maybe Text
$sel:allowCredentials:PublicKeyCredentialRequestOptions :: PublicKeyCredentialRequestOptions
-> Maybe [PublicKeyCredentialDescriptor]
$sel:rpId:PublicKeyCredentialRequestOptions :: PublicKeyCredentialRequestOptions -> Maybe Text
$sel:timeout:PublicKeyCredentialRequestOptions :: PublicKeyCredentialRequestOptions -> Maybe Word32
$sel:challenge:PublicKeyCredentialRequestOptions :: PublicKeyCredentialRequestOptions -> Base64UrlString
..} = do
    Challenge
coaChallenge <- forall (m :: * -> *) a.
(Decode m a, MonadError Text m) =>
JSON a -> m a
decode Base64UrlString
challenge
    Maybe Timeout
coaTimeout <- forall (m :: * -> *) a.
(Decode m a, MonadError Text m) =>
JSON a -> m a
decode Maybe Word32
timeout
    Maybe RpId
coaRpId <- forall (m :: * -> *) a.
(Decode m a, MonadError Text m) =>
JSON a -> m a
decode Maybe Text
rpId
    [CredentialDescriptor]
coaAllowCredentials <- forall (m :: * -> *) a.
(MonadError Text m, Decode m a) =>
a -> Maybe (JSON a) -> m a
decodeWithDefault [CredentialDescriptor]
D.coaAllowCredentialsDefault Maybe [PublicKeyCredentialDescriptor]
allowCredentials
    UserVerificationRequirement
coaUserVerification <- forall (m :: * -> *) a.
(MonadError Text m, Decode m a) =>
a -> Maybe (JSON a) -> m a
decodeWithDefault UserVerificationRequirement
D.coaUserVerificationDefault Maybe Text
userVerification
    Maybe AuthenticationExtensionsClientInputs
coaExtensions <- forall (m :: * -> *) a.
(Decode m a, MonadError Text m) =>
JSON a -> m a
decode Maybe AuthenticationExtensionsClientInputs
extensions
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ T.CredentialOptionsAuthentication {[CredentialDescriptor]
Maybe AuthenticationExtensionsClientInputs
Maybe Timeout
Maybe RpId
Challenge
UserVerificationRequirement
coaExtensions :: Maybe AuthenticationExtensionsClientInputs
coaUserVerification :: UserVerificationRequirement
coaAllowCredentials :: [CredentialDescriptor]
coaRpId :: Maybe RpId
coaTimeout :: Maybe Timeout
coaChallenge :: Challenge
coaExtensions :: Maybe AuthenticationExtensionsClientInputs
coaUserVerification :: UserVerificationRequirement
coaAllowCredentials :: [CredentialDescriptor]
coaRpId :: Maybe RpId
coaTimeout :: Maybe Timeout
coaChallenge :: Challenge
..}

-- | [(spec)](https://www.w3.org/TR/webauthn-2/#dictionary-rp-credential-params)
data PublicKeyCredentialRpEntity = PublicKeyCredentialRpEntity
  { -- | [(spec)](https://www.w3.org/TR/webauthn-2/#dom-publickeycredentialrpentity-id)
    PublicKeyCredentialRpEntity -> Maybe Text
id :: Maybe Text,
    -- | [(spec)](https://www.w3.org/TR/webauthn-2/#dom-publickeycredentialentity-name)
    PublicKeyCredentialRpEntity -> Text
name :: Text
  }
  deriving (PublicKeyCredentialRpEntity -> PublicKeyCredentialRpEntity -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PublicKeyCredentialRpEntity -> PublicKeyCredentialRpEntity -> Bool
$c/= :: PublicKeyCredentialRpEntity -> PublicKeyCredentialRpEntity -> Bool
== :: PublicKeyCredentialRpEntity -> PublicKeyCredentialRpEntity -> Bool
$c== :: PublicKeyCredentialRpEntity -> PublicKeyCredentialRpEntity -> Bool
Eq, Int -> PublicKeyCredentialRpEntity -> ShowS
[PublicKeyCredentialRpEntity] -> ShowS
PublicKeyCredentialRpEntity -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PublicKeyCredentialRpEntity] -> ShowS
$cshowList :: [PublicKeyCredentialRpEntity] -> ShowS
show :: PublicKeyCredentialRpEntity -> String
$cshow :: PublicKeyCredentialRpEntity -> String
showsPrec :: Int -> PublicKeyCredentialRpEntity -> ShowS
$cshowsPrec :: Int -> PublicKeyCredentialRpEntity -> ShowS
Show, forall x.
Rep PublicKeyCredentialRpEntity x -> PublicKeyCredentialRpEntity
forall x.
PublicKeyCredentialRpEntity -> Rep PublicKeyCredentialRpEntity x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep PublicKeyCredentialRpEntity x -> PublicKeyCredentialRpEntity
$cfrom :: forall x.
PublicKeyCredentialRpEntity -> Rep PublicKeyCredentialRpEntity x
Generic)

instance Aeson.FromJSON PublicKeyCredentialRpEntity where
  parseJSON :: Value -> Parser PublicKeyCredentialRpEntity
parseJSON = forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
Aeson.genericParseJSON Options
jsonEncodingOptions

instance Aeson.ToJSON PublicKeyCredentialRpEntity where
  toJSON :: PublicKeyCredentialRpEntity -> Value
toJSON = forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
Aeson.genericToJSON Options
jsonEncodingOptions

instance Encode T.CredentialRpEntity where
  type JSON T.CredentialRpEntity = PublicKeyCredentialRpEntity
  encode :: CredentialRpEntity -> JSON CredentialRpEntity
encode T.CredentialRpEntity {Maybe RpId
RelyingPartyName
creName :: CredentialRpEntity -> RelyingPartyName
creId :: CredentialRpEntity -> Maybe RpId
creName :: RelyingPartyName
creId :: Maybe RpId
..} =
    PublicKeyCredentialRpEntity
      { $sel:id:PublicKeyCredentialRpEntity :: Maybe Text
id = forall a. Encode a => a -> JSON a
encode Maybe RpId
creId,
        $sel:name:PublicKeyCredentialRpEntity :: Text
name = forall a. Encode a => a -> JSON a
encode RelyingPartyName
creName
      }

instance Decode m T.CredentialRpEntity where
  decode :: MonadError Text m =>
JSON CredentialRpEntity -> m CredentialRpEntity
decode PublicKeyCredentialRpEntity {Maybe Text
Text
name :: Text
id :: Maybe Text
$sel:name:PublicKeyCredentialRpEntity :: PublicKeyCredentialRpEntity -> Text
$sel:id:PublicKeyCredentialRpEntity :: PublicKeyCredentialRpEntity -> Maybe Text
..} = do
    Maybe RpId
creId <- forall (m :: * -> *) a.
(Decode m a, MonadError Text m) =>
JSON a -> m a
decode Maybe Text
id
    RelyingPartyName
creName <- forall (m :: * -> *) a.
(Decode m a, MonadError Text m) =>
JSON a -> m a
decode Text
name
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ T.CredentialRpEntity {Maybe RpId
RelyingPartyName
creName :: RelyingPartyName
creId :: Maybe RpId
creName :: RelyingPartyName
creId :: Maybe RpId
..}

-- | [(spec)](https://www.w3.org/TR/webauthn-2/#dictionary-user-credential-params)
data PublicKeyCredentialUserEntity = PublicKeyCredentialUserEntity
  { -- | [(spec)](https://www.w3.org/TR/webauthn-2/#dom-publickeycredentialuserentity-id)
    PublicKeyCredentialUserEntity -> Base64UrlString
id :: Base64UrlString,
    -- | [(spec)](https://www.w3.org/TR/webauthn-2/#dom-publickeycredentialuserentity-displayname)
    PublicKeyCredentialUserEntity -> Text
displayName :: Text,
    -- | [(spec)](https://www.w3.org/TR/webauthn-2/#dom-publickeycredentialentity-name)
    PublicKeyCredentialUserEntity -> Text
name :: Text
  }
  deriving (PublicKeyCredentialUserEntity
-> PublicKeyCredentialUserEntity -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PublicKeyCredentialUserEntity
-> PublicKeyCredentialUserEntity -> Bool
$c/= :: PublicKeyCredentialUserEntity
-> PublicKeyCredentialUserEntity -> Bool
== :: PublicKeyCredentialUserEntity
-> PublicKeyCredentialUserEntity -> Bool
$c== :: PublicKeyCredentialUserEntity
-> PublicKeyCredentialUserEntity -> Bool
Eq, Int -> PublicKeyCredentialUserEntity -> ShowS
[PublicKeyCredentialUserEntity] -> ShowS
PublicKeyCredentialUserEntity -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PublicKeyCredentialUserEntity] -> ShowS
$cshowList :: [PublicKeyCredentialUserEntity] -> ShowS
show :: PublicKeyCredentialUserEntity -> String
$cshow :: PublicKeyCredentialUserEntity -> String
showsPrec :: Int -> PublicKeyCredentialUserEntity -> ShowS
$cshowsPrec :: Int -> PublicKeyCredentialUserEntity -> ShowS
Show, forall x.
Rep PublicKeyCredentialUserEntity x
-> PublicKeyCredentialUserEntity
forall x.
PublicKeyCredentialUserEntity
-> Rep PublicKeyCredentialUserEntity x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep PublicKeyCredentialUserEntity x
-> PublicKeyCredentialUserEntity
$cfrom :: forall x.
PublicKeyCredentialUserEntity
-> Rep PublicKeyCredentialUserEntity x
Generic)

instance Aeson.FromJSON PublicKeyCredentialUserEntity where
  parseJSON :: Value -> Parser PublicKeyCredentialUserEntity
parseJSON = forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
Aeson.genericParseJSON Options
jsonEncodingOptions

instance Aeson.ToJSON PublicKeyCredentialUserEntity where
  toJSON :: PublicKeyCredentialUserEntity -> Value
toJSON = forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
Aeson.genericToJSON Options
jsonEncodingOptions

instance Encode T.CredentialUserEntity where
  type JSON T.CredentialUserEntity = PublicKeyCredentialUserEntity
  encode :: CredentialUserEntity -> JSON CredentialUserEntity
encode T.CredentialUserEntity {UserAccountName
UserAccountDisplayName
UserHandle
cueName :: CredentialUserEntity -> UserAccountName
cueDisplayName :: CredentialUserEntity -> UserAccountDisplayName
cueId :: CredentialUserEntity -> UserHandle
cueName :: UserAccountName
cueDisplayName :: UserAccountDisplayName
cueId :: UserHandle
..} =
    PublicKeyCredentialUserEntity
      { $sel:id:PublicKeyCredentialUserEntity :: Base64UrlString
id = forall a. Encode a => a -> JSON a
encode UserHandle
cueId,
        $sel:displayName:PublicKeyCredentialUserEntity :: Text
displayName = forall a. Encode a => a -> JSON a
encode UserAccountDisplayName
cueDisplayName,
        $sel:name:PublicKeyCredentialUserEntity :: Text
name = forall a. Encode a => a -> JSON a
encode UserAccountName
cueName
      }

instance Decode m T.CredentialUserEntity where
  decode :: MonadError Text m =>
JSON CredentialUserEntity -> m CredentialUserEntity
decode PublicKeyCredentialUserEntity {Text
Base64UrlString
name :: Text
displayName :: Text
id :: Base64UrlString
$sel:name:PublicKeyCredentialUserEntity :: PublicKeyCredentialUserEntity -> Text
$sel:displayName:PublicKeyCredentialUserEntity :: PublicKeyCredentialUserEntity -> Text
$sel:id:PublicKeyCredentialUserEntity :: PublicKeyCredentialUserEntity -> Base64UrlString
..} = do
    UserHandle
cueId <- forall (m :: * -> *) a.
(Decode m a, MonadError Text m) =>
JSON a -> m a
decode Base64UrlString
id
    UserAccountDisplayName
cueDisplayName <- forall (m :: * -> *) a.
(Decode m a, MonadError Text m) =>
JSON a -> m a
decode Text
displayName
    UserAccountName
cueName <- forall (m :: * -> *) a.
(Decode m a, MonadError Text m) =>
JSON a -> m a
decode Text
name
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ T.CredentialUserEntity {UserAccountName
UserAccountDisplayName
UserHandle
cueName :: UserAccountName
cueDisplayName :: UserAccountDisplayName
cueId :: UserHandle
cueName :: UserAccountName
cueDisplayName :: UserAccountDisplayName
cueId :: UserHandle
..}

-- | [(spec)](https://www.w3.org/TR/webauthn-2/#dictionary-credential-params)
data PublicKeyCredentialParameters = PublicKeyCredentialParameters
  { -- | [(spec)](https://www.w3.org/TR/webauthn-2/#dom-publickeycredentialparameters-type)
    PublicKeyCredentialParameters -> Text
littype :: Text,
    -- | [(spec)](https://www.w3.org/TR/webauthn-2/#dom-publickeycredentialparameters-alg)
    PublicKeyCredentialParameters -> Int32
alg :: COSEAlgorithmIdentifier
  }
  deriving (PublicKeyCredentialParameters
-> PublicKeyCredentialParameters -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PublicKeyCredentialParameters
-> PublicKeyCredentialParameters -> Bool
$c/= :: PublicKeyCredentialParameters
-> PublicKeyCredentialParameters -> Bool
== :: PublicKeyCredentialParameters
-> PublicKeyCredentialParameters -> Bool
$c== :: PublicKeyCredentialParameters
-> PublicKeyCredentialParameters -> Bool
Eq, Int -> PublicKeyCredentialParameters -> ShowS
[PublicKeyCredentialParameters] -> ShowS
PublicKeyCredentialParameters -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PublicKeyCredentialParameters] -> ShowS
$cshowList :: [PublicKeyCredentialParameters] -> ShowS
show :: PublicKeyCredentialParameters -> String
$cshow :: PublicKeyCredentialParameters -> String
showsPrec :: Int -> PublicKeyCredentialParameters -> ShowS
$cshowsPrec :: Int -> PublicKeyCredentialParameters -> ShowS
Show, forall x.
Rep PublicKeyCredentialParameters x
-> PublicKeyCredentialParameters
forall x.
PublicKeyCredentialParameters
-> Rep PublicKeyCredentialParameters x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep PublicKeyCredentialParameters x
-> PublicKeyCredentialParameters
$cfrom :: forall x.
PublicKeyCredentialParameters
-> Rep PublicKeyCredentialParameters x
Generic)

instance Aeson.FromJSON PublicKeyCredentialParameters where
  parseJSON :: Value -> Parser PublicKeyCredentialParameters
parseJSON = forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
Aeson.genericParseJSON Options
jsonEncodingOptions

instance Aeson.ToJSON PublicKeyCredentialParameters where
  toJSON :: PublicKeyCredentialParameters -> Value
toJSON = forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
Aeson.genericToJSON Options
jsonEncodingOptions

instance Encode T.CredentialParameters where
  type JSON T.CredentialParameters = PublicKeyCredentialParameters
  encode :: CredentialParameters -> JSON CredentialParameters
encode T.CredentialParameters {CoseSignAlg
CredentialType
cpAlg :: CredentialParameters -> CoseSignAlg
cpTyp :: CredentialParameters -> CredentialType
cpAlg :: CoseSignAlg
cpTyp :: CredentialType
..} =
    PublicKeyCredentialParameters
      { $sel:littype:PublicKeyCredentialParameters :: Text
littype = forall a. Encode a => a -> JSON a
encode CredentialType
cpTyp,
        $sel:alg:PublicKeyCredentialParameters :: Int32
alg = forall a. Encode a => a -> JSON a
encode CoseSignAlg
cpAlg
      }

instance Decode m T.CredentialParameters where
  decode :: MonadError Text m =>
JSON CredentialParameters -> m CredentialParameters
decode PublicKeyCredentialParameters {Int32
Text
alg :: Int32
littype :: Text
$sel:alg:PublicKeyCredentialParameters :: PublicKeyCredentialParameters -> Int32
$sel:littype:PublicKeyCredentialParameters :: PublicKeyCredentialParameters -> Text
..} = do
    CredentialType
cpTyp <- forall (m :: * -> *) a.
(Decode m a, MonadError Text m) =>
JSON a -> m a
decode Text
littype
    CoseSignAlg
cpAlg <- forall (m :: * -> *) a.
(Decode m a, MonadError Text m) =>
JSON a -> m a
decode Int32
alg
    forall (f :: * -> *) a. Applicative f => a -> f a
pure T.CredentialParameters {CoseSignAlg
CredentialType
cpAlg :: CoseSignAlg
cpTyp :: CredentialType
cpAlg :: CoseSignAlg
cpTyp :: CredentialType
..}

-- | [(spec)](https://www.w3.org/TR/webauthn-2/#sctn-alg-identifier)
type COSEAlgorithmIdentifier = Int32

-- | [(spec)](https://www.w3.org/TR/webauthn-2/#dictdef-publickeycredentialdescriptor)
data PublicKeyCredentialDescriptor = PublicKeyCredentialDescriptor
  { -- | [(spec)](https://www.w3.org/TR/webauthn-2/#dom-publickeycredentialdescriptor-type)
    PublicKeyCredentialDescriptor -> Text
littype :: Text,
    -- | [(spec)](https://www.w3.org/TR/webauthn-2/#dom-publickeycredentialdescriptor-id)
    PublicKeyCredentialDescriptor -> Base64UrlString
id :: Base64UrlString,
    -- | [(spec)](https://www.w3.org/TR/webauthn-2/#dom-publickeycredentialdescriptor-transports)
    PublicKeyCredentialDescriptor -> Maybe [Text]
transports :: Maybe [Text]
  }
  deriving (PublicKeyCredentialDescriptor
-> PublicKeyCredentialDescriptor -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PublicKeyCredentialDescriptor
-> PublicKeyCredentialDescriptor -> Bool
$c/= :: PublicKeyCredentialDescriptor
-> PublicKeyCredentialDescriptor -> Bool
== :: PublicKeyCredentialDescriptor
-> PublicKeyCredentialDescriptor -> Bool
$c== :: PublicKeyCredentialDescriptor
-> PublicKeyCredentialDescriptor -> Bool
Eq, Int -> PublicKeyCredentialDescriptor -> ShowS
[PublicKeyCredentialDescriptor] -> ShowS
PublicKeyCredentialDescriptor -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PublicKeyCredentialDescriptor] -> ShowS
$cshowList :: [PublicKeyCredentialDescriptor] -> ShowS
show :: PublicKeyCredentialDescriptor -> String
$cshow :: PublicKeyCredentialDescriptor -> String
showsPrec :: Int -> PublicKeyCredentialDescriptor -> ShowS
$cshowsPrec :: Int -> PublicKeyCredentialDescriptor -> ShowS
Show, forall x.
Rep PublicKeyCredentialDescriptor x
-> PublicKeyCredentialDescriptor
forall x.
PublicKeyCredentialDescriptor
-> Rep PublicKeyCredentialDescriptor x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep PublicKeyCredentialDescriptor x
-> PublicKeyCredentialDescriptor
$cfrom :: forall x.
PublicKeyCredentialDescriptor
-> Rep PublicKeyCredentialDescriptor x
Generic)

instance Aeson.FromJSON PublicKeyCredentialDescriptor where
  parseJSON :: Value -> Parser PublicKeyCredentialDescriptor
parseJSON = forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
Aeson.genericParseJSON Options
jsonEncodingOptions

instance Aeson.ToJSON PublicKeyCredentialDescriptor where
  toJSON :: PublicKeyCredentialDescriptor -> Value
toJSON = forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
Aeson.genericToJSON Options
jsonEncodingOptions

instance Encode T.CredentialDescriptor where
  type JSON T.CredentialDescriptor = PublicKeyCredentialDescriptor
  encode :: CredentialDescriptor -> JSON CredentialDescriptor
encode T.CredentialDescriptor {Maybe [AuthenticatorTransport]
CredentialId
CredentialType
cdTransports :: CredentialDescriptor -> Maybe [AuthenticatorTransport]
cdId :: CredentialDescriptor -> CredentialId
cdTyp :: CredentialDescriptor -> CredentialType
cdTransports :: Maybe [AuthenticatorTransport]
cdId :: CredentialId
cdTyp :: CredentialType
..} =
    PublicKeyCredentialDescriptor
      { $sel:littype:PublicKeyCredentialDescriptor :: Text
littype = forall a. Encode a => a -> JSON a
encode CredentialType
cdTyp,
        $sel:id:PublicKeyCredentialDescriptor :: Base64UrlString
id = forall a. Encode a => a -> JSON a
encode CredentialId
cdId,
        $sel:transports:PublicKeyCredentialDescriptor :: Maybe [Text]
transports = forall a. Encode a => a -> JSON a
encode Maybe [AuthenticatorTransport]
cdTransports
      }

instance Decode m T.CredentialDescriptor where
  decode :: MonadError Text m =>
JSON CredentialDescriptor -> m CredentialDescriptor
decode PublicKeyCredentialDescriptor {Maybe [Text]
Text
Base64UrlString
transports :: Maybe [Text]
id :: Base64UrlString
littype :: Text
$sel:transports:PublicKeyCredentialDescriptor :: PublicKeyCredentialDescriptor -> Maybe [Text]
$sel:id:PublicKeyCredentialDescriptor :: PublicKeyCredentialDescriptor -> Base64UrlString
$sel:littype:PublicKeyCredentialDescriptor :: PublicKeyCredentialDescriptor -> Text
..} = do
    CredentialType
cdTyp <- forall (m :: * -> *) a.
(Decode m a, MonadError Text m) =>
JSON a -> m a
decode Text
littype
    CredentialId
cdId <- forall (m :: * -> *) a.
(Decode m a, MonadError Text m) =>
JSON a -> m a
decode Base64UrlString
id
    Maybe [AuthenticatorTransport]
cdTransports <- forall (m :: * -> *) a.
(Decode m a, MonadError Text m) =>
JSON a -> m a
decode Maybe [Text]
transports
    forall (f :: * -> *) a. Applicative f => a -> f a
pure T.CredentialDescriptor {Maybe [AuthenticatorTransport]
CredentialId
CredentialType
cdTransports :: Maybe [AuthenticatorTransport]
cdId :: CredentialId
cdTyp :: CredentialType
cdTransports :: Maybe [AuthenticatorTransport]
cdId :: CredentialId
cdTyp :: CredentialType
..}

-- | [(spec)](https://www.w3.org/TR/webauthn-2/#dictdef-authenticatorselectioncriteria)
data AuthenticatorSelectionCriteria = AuthenticatorSelectionCriteria
  { -- | [(spec)](https://www.w3.org/TR/webauthn-2/#dom-authenticatorselectioncriteria-authenticatorattachment)
    AuthenticatorSelectionCriteria -> Maybe Text
authenticatorAttachment :: Maybe Text,
    -- | [(spec)](https://www.w3.org/TR/webauthn-2/#dom-authenticatorselectioncriteria-residentkey)
    AuthenticatorSelectionCriteria -> Maybe Text
residentKey :: Maybe Text,
    -- | [(spec)](https://www.w3.org/TR/webauthn-2/#dom-authenticatorselectioncriteria-requireresidentkey)
    AuthenticatorSelectionCriteria -> Maybe Bool
requireResidentKey :: Maybe Bool,
    -- | [(spec)](https://www.w3.org/TR/webauthn-2/#dom-authenticatorselectioncriteria-userverification)
    AuthenticatorSelectionCriteria -> Maybe Text
userVerification :: Maybe Text
  }
  deriving (AuthenticatorSelectionCriteria
-> AuthenticatorSelectionCriteria -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AuthenticatorSelectionCriteria
-> AuthenticatorSelectionCriteria -> Bool
$c/= :: AuthenticatorSelectionCriteria
-> AuthenticatorSelectionCriteria -> Bool
== :: AuthenticatorSelectionCriteria
-> AuthenticatorSelectionCriteria -> Bool
$c== :: AuthenticatorSelectionCriteria
-> AuthenticatorSelectionCriteria -> Bool
Eq, Int -> AuthenticatorSelectionCriteria -> ShowS
[AuthenticatorSelectionCriteria] -> ShowS
AuthenticatorSelectionCriteria -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AuthenticatorSelectionCriteria] -> ShowS
$cshowList :: [AuthenticatorSelectionCriteria] -> ShowS
show :: AuthenticatorSelectionCriteria -> String
$cshow :: AuthenticatorSelectionCriteria -> String
showsPrec :: Int -> AuthenticatorSelectionCriteria -> ShowS
$cshowsPrec :: Int -> AuthenticatorSelectionCriteria -> ShowS
Show, forall x.
Rep AuthenticatorSelectionCriteria x
-> AuthenticatorSelectionCriteria
forall x.
AuthenticatorSelectionCriteria
-> Rep AuthenticatorSelectionCriteria x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep AuthenticatorSelectionCriteria x
-> AuthenticatorSelectionCriteria
$cfrom :: forall x.
AuthenticatorSelectionCriteria
-> Rep AuthenticatorSelectionCriteria x
Generic)

instance Aeson.FromJSON AuthenticatorSelectionCriteria where
  parseJSON :: Value -> Parser AuthenticatorSelectionCriteria
parseJSON = forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
Aeson.genericParseJSON Options
jsonEncodingOptions

instance Aeson.ToJSON AuthenticatorSelectionCriteria where
  toJSON :: AuthenticatorSelectionCriteria -> Value
toJSON = forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
Aeson.genericToJSON Options
jsonEncodingOptions

instance Encode T.AuthenticatorSelectionCriteria where
  type JSON T.AuthenticatorSelectionCriteria = AuthenticatorSelectionCriteria
  encode :: AuthenticatorSelectionCriteria
-> JSON AuthenticatorSelectionCriteria
encode T.AuthenticatorSelectionCriteria {Maybe AuthenticatorAttachment
UserVerificationRequirement
ResidentKeyRequirement
ascUserVerification :: AuthenticatorSelectionCriteria -> UserVerificationRequirement
ascResidentKey :: AuthenticatorSelectionCriteria -> ResidentKeyRequirement
ascAuthenticatorAttachment :: AuthenticatorSelectionCriteria -> Maybe AuthenticatorAttachment
ascUserVerification :: UserVerificationRequirement
ascResidentKey :: ResidentKeyRequirement
ascAuthenticatorAttachment :: Maybe AuthenticatorAttachment
..} =
    AuthenticatorSelectionCriteria
      { $sel:authenticatorAttachment:AuthenticatorSelectionCriteria :: Maybe Text
authenticatorAttachment = forall a. Encode a => a -> JSON a
encode Maybe AuthenticatorAttachment
ascAuthenticatorAttachment,
        $sel:residentKey:AuthenticatorSelectionCriteria :: Maybe Text
residentKey = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall a. Encode a => a -> JSON a
encode ResidentKeyRequirement
ascResidentKey,
        -- [(spec)](https://www.w3.org/TR/webauthn-2/#dom-authenticatorselectioncriteria-requireresidentkey)
        -- Relying Parties SHOULD set it to true if, and only if, residentKey is set to required.
        $sel:requireResidentKey:AuthenticatorSelectionCriteria :: Maybe Bool
requireResidentKey = forall a. a -> Maybe a
Just (ResidentKeyRequirement
ascResidentKey forall a. Eq a => a -> a -> Bool
== ResidentKeyRequirement
T.ResidentKeyRequirementRequired),
        $sel:userVerification:AuthenticatorSelectionCriteria :: Maybe Text
userVerification = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall a. Encode a => a -> JSON a
encode UserVerificationRequirement
ascUserVerification
      }

instance Decode m T.AuthenticatorSelectionCriteria where
  decode :: MonadError Text m =>
JSON AuthenticatorSelectionCriteria
-> m AuthenticatorSelectionCriteria
decode AuthenticatorSelectionCriteria {Maybe Bool
Maybe Text
userVerification :: Maybe Text
requireResidentKey :: Maybe Bool
residentKey :: Maybe Text
authenticatorAttachment :: Maybe Text
$sel:userVerification:AuthenticatorSelectionCriteria :: AuthenticatorSelectionCriteria -> Maybe Text
$sel:requireResidentKey:AuthenticatorSelectionCriteria :: AuthenticatorSelectionCriteria -> Maybe Bool
$sel:residentKey:AuthenticatorSelectionCriteria :: AuthenticatorSelectionCriteria -> Maybe Text
$sel:authenticatorAttachment:AuthenticatorSelectionCriteria :: AuthenticatorSelectionCriteria -> Maybe Text
..} = do
    Maybe AuthenticatorAttachment
ascAuthenticatorAttachment <- forall (m :: * -> *) a.
(Decode m a, MonadError Text m) =>
JSON a -> m a
decode Maybe Text
authenticatorAttachment
    ResidentKeyRequirement
ascResidentKey <- forall (m :: * -> *) a.
(MonadError Text m, Decode m a) =>
a -> Maybe (JSON a) -> m a
decodeWithDefault (Maybe Bool -> ResidentKeyRequirement
D.ascResidentKeyDefault Maybe Bool
requireResidentKey) Maybe Text
residentKey
    UserVerificationRequirement
ascUserVerification <- forall (m :: * -> *) a.
(MonadError Text m, Decode m a) =>
a -> Maybe (JSON a) -> m a
decodeWithDefault UserVerificationRequirement
D.ascUserVerificationDefault Maybe Text
userVerification
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ T.AuthenticatorSelectionCriteria {Maybe AuthenticatorAttachment
UserVerificationRequirement
ResidentKeyRequirement
ascUserVerification :: UserVerificationRequirement
ascResidentKey :: ResidentKeyRequirement
ascAuthenticatorAttachment :: Maybe AuthenticatorAttachment
ascUserVerification :: UserVerificationRequirement
ascResidentKey :: ResidentKeyRequirement
ascAuthenticatorAttachment :: Maybe AuthenticatorAttachment
..}

-- | [(spec)](https://www.w3.org/TR/webauthn-2/#iface-pkcredential)
data PublicKeyCredential response = PublicKeyCredential
  { -- | [(spec)](https://www.w3.org/TR/webauthn-2/#dom-publickeycredential-identifier-slot)
    forall response. PublicKeyCredential response -> Base64UrlString
rawId :: Base64UrlString,
    -- | [(spec)](https://www.w3.org/TR/webauthn-2/#dom-publickeycredential-response)
    forall response. PublicKeyCredential response -> response
response :: response,
    -- | [(spec)](https://www.w3.org/TR/webauthn-2/#dom-publickeycredential-getclientextensionresults)
    forall response.
PublicKeyCredential response
-> AuthenticationExtensionsClientOutputs
clientExtensionResults :: AuthenticationExtensionsClientOutputs
  }
  deriving (PublicKeyCredential response
-> PublicKeyCredential response -> Bool
forall response.
Eq response =>
PublicKeyCredential response
-> PublicKeyCredential response -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PublicKeyCredential response
-> PublicKeyCredential response -> Bool
$c/= :: forall response.
Eq response =>
PublicKeyCredential response
-> PublicKeyCredential response -> Bool
== :: PublicKeyCredential response
-> PublicKeyCredential response -> Bool
$c== :: forall response.
Eq response =>
PublicKeyCredential response
-> PublicKeyCredential response -> Bool
Eq, Int -> PublicKeyCredential response -> ShowS
forall response.
Show response =>
Int -> PublicKeyCredential response -> ShowS
forall response.
Show response =>
[PublicKeyCredential response] -> ShowS
forall response.
Show response =>
PublicKeyCredential response -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PublicKeyCredential response] -> ShowS
$cshowList :: forall response.
Show response =>
[PublicKeyCredential response] -> ShowS
show :: PublicKeyCredential response -> String
$cshow :: forall response.
Show response =>
PublicKeyCredential response -> String
showsPrec :: Int -> PublicKeyCredential response -> ShowS
$cshowsPrec :: forall response.
Show response =>
Int -> PublicKeyCredential response -> ShowS
Show, forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall response x.
Rep (PublicKeyCredential response) x
-> PublicKeyCredential response
forall response x.
PublicKeyCredential response
-> Rep (PublicKeyCredential response) x
$cto :: forall response x.
Rep (PublicKeyCredential response) x
-> PublicKeyCredential response
$cfrom :: forall response x.
PublicKeyCredential response
-> Rep (PublicKeyCredential response) x
Generic)

instance Aeson.FromJSON response => Aeson.FromJSON (PublicKeyCredential response) where
  parseJSON :: Value -> Parser (PublicKeyCredential response)
parseJSON = forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
Aeson.genericParseJSON Options
jsonEncodingOptions

instance Aeson.ToJSON response => Aeson.ToJSON (PublicKeyCredential response) where
  toJSON :: PublicKeyCredential response -> Value
toJSON = forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
Aeson.genericToJSON Options
jsonEncodingOptions

instance Encode (T.Credential 'K.Registration 'True) where
  type JSON (T.Credential 'K.Registration 'True) = PublicKeyCredential AuthenticatorAttestationResponse
  encode :: Credential 'Registration 'True
-> JSON (Credential 'Registration 'True)
encode T.Credential {AuthenticatorResponse 'Registration 'True
AuthenticationExtensionsClientOutputs
CredentialId
cClientExtensionResults :: forall (c :: CeremonyKind) (raw :: Bool).
Credential c raw -> AuthenticationExtensionsClientOutputs
cResponse :: forall (c :: CeremonyKind) (raw :: Bool).
Credential c raw -> AuthenticatorResponse c raw
cIdentifier :: forall (c :: CeremonyKind) (raw :: Bool).
Credential c raw -> CredentialId
cClientExtensionResults :: AuthenticationExtensionsClientOutputs
cResponse :: AuthenticatorResponse 'Registration 'True
cIdentifier :: CredentialId
..} =
    PublicKeyCredential
      { $sel:rawId:PublicKeyCredential :: Base64UrlString
rawId = forall a. Encode a => a -> JSON a
encode CredentialId
cIdentifier,
        $sel:response:PublicKeyCredential :: AuthenticatorAttestationResponse
response = forall a. Encode a => a -> JSON a
encode AuthenticatorResponse 'Registration 'True
cResponse,
        $sel:clientExtensionResults:PublicKeyCredential :: AuthenticationExtensionsClientOutputs
clientExtensionResults = forall a. Encode a => a -> JSON a
encode AuthenticationExtensionsClientOutputs
cClientExtensionResults
      }

instance
  MonadReader T.SupportedAttestationStatementFormats m =>
  Decode m (T.Credential 'K.Registration 'True)
  where
  decode :: MonadError Text m =>
JSON (Credential 'Registration 'True)
-> m (Credential 'Registration 'True)
decode PublicKeyCredential {AuthenticatorAttestationResponse
AuthenticationExtensionsClientOutputs
Base64UrlString
clientExtensionResults :: AuthenticationExtensionsClientOutputs
response :: AuthenticatorAttestationResponse
rawId :: Base64UrlString
$sel:clientExtensionResults:PublicKeyCredential :: forall response.
PublicKeyCredential response
-> AuthenticationExtensionsClientOutputs
$sel:response:PublicKeyCredential :: forall response. PublicKeyCredential response -> response
$sel:rawId:PublicKeyCredential :: forall response. PublicKeyCredential response -> Base64UrlString
..} = do
    CredentialId
cIdentifier <- forall (m :: * -> *) a.
(Decode m a, MonadError Text m) =>
JSON a -> m a
decode Base64UrlString
rawId
    AuthenticatorResponse 'Registration 'True
cResponse <- forall (m :: * -> *) a.
(Decode m a, MonadError Text m) =>
JSON a -> m a
decode AuthenticatorAttestationResponse
response
    AuthenticationExtensionsClientOutputs
cClientExtensionResults <- forall (m :: * -> *) a.
(Decode m a, MonadError Text m) =>
JSON a -> m a
decode AuthenticationExtensionsClientOutputs
clientExtensionResults
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ T.Credential {AuthenticatorResponse 'Registration 'True
AuthenticationExtensionsClientOutputs
CredentialId
cClientExtensionResults :: AuthenticationExtensionsClientOutputs
cResponse :: AuthenticatorResponse 'Registration 'True
cIdentifier :: CredentialId
cClientExtensionResults :: AuthenticationExtensionsClientOutputs
cResponse :: AuthenticatorResponse 'Registration 'True
cIdentifier :: CredentialId
..}

instance Encode (T.Credential 'K.Authentication 'True) where
  type JSON (T.Credential 'K.Authentication 'True) = PublicKeyCredential AuthenticatorAssertionResponse
  encode :: Credential 'Authentication 'True
-> JSON (Credential 'Authentication 'True)
encode T.Credential {AuthenticatorResponse 'Authentication 'True
AuthenticationExtensionsClientOutputs
CredentialId
cClientExtensionResults :: AuthenticationExtensionsClientOutputs
cResponse :: AuthenticatorResponse 'Authentication 'True
cIdentifier :: CredentialId
cClientExtensionResults :: forall (c :: CeremonyKind) (raw :: Bool).
Credential c raw -> AuthenticationExtensionsClientOutputs
cResponse :: forall (c :: CeremonyKind) (raw :: Bool).
Credential c raw -> AuthenticatorResponse c raw
cIdentifier :: forall (c :: CeremonyKind) (raw :: Bool).
Credential c raw -> CredentialId
..} =
    PublicKeyCredential
      { $sel:rawId:PublicKeyCredential :: Base64UrlString
rawId = forall a. Encode a => a -> JSON a
encode CredentialId
cIdentifier,
        $sel:response:PublicKeyCredential :: AuthenticatorAssertionResponse
response = forall a. Encode a => a -> JSON a
encode AuthenticatorResponse 'Authentication 'True
cResponse,
        $sel:clientExtensionResults:PublicKeyCredential :: AuthenticationExtensionsClientOutputs
clientExtensionResults = forall a. Encode a => a -> JSON a
encode AuthenticationExtensionsClientOutputs
cClientExtensionResults
      }

instance Decode m (T.Credential 'K.Authentication 'True) where
  decode :: MonadError Text m =>
JSON (Credential 'Authentication 'True)
-> m (Credential 'Authentication 'True)
decode PublicKeyCredential {AuthenticatorAssertionResponse
AuthenticationExtensionsClientOutputs
Base64UrlString
clientExtensionResults :: AuthenticationExtensionsClientOutputs
response :: AuthenticatorAssertionResponse
rawId :: Base64UrlString
$sel:clientExtensionResults:PublicKeyCredential :: forall response.
PublicKeyCredential response
-> AuthenticationExtensionsClientOutputs
$sel:response:PublicKeyCredential :: forall response. PublicKeyCredential response -> response
$sel:rawId:PublicKeyCredential :: forall response. PublicKeyCredential response -> Base64UrlString
..} = do
    CredentialId
cIdentifier <- forall (m :: * -> *) a.
(Decode m a, MonadError Text m) =>
JSON a -> m a
decode Base64UrlString
rawId
    AuthenticatorResponse 'Authentication 'True
cResponse <- forall (m :: * -> *) a.
(Decode m a, MonadError Text m) =>
JSON a -> m a
decode AuthenticatorAssertionResponse
response
    AuthenticationExtensionsClientOutputs
cClientExtensionResults <- forall (m :: * -> *) a.
(Decode m a, MonadError Text m) =>
JSON a -> m a
decode AuthenticationExtensionsClientOutputs
clientExtensionResults
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ T.Credential {AuthenticatorResponse 'Authentication 'True
AuthenticationExtensionsClientOutputs
CredentialId
cClientExtensionResults :: AuthenticationExtensionsClientOutputs
cResponse :: AuthenticatorResponse 'Authentication 'True
cIdentifier :: CredentialId
cClientExtensionResults :: AuthenticationExtensionsClientOutputs
cResponse :: AuthenticatorResponse 'Authentication 'True
cIdentifier :: CredentialId
..}

-- | [(spec)](https://www.w3.org/TR/webauthn-2/#iface-authenticatorattestationresponse)
data AuthenticatorAttestationResponse = AuthenticatorAttestationResponse
  { -- | [(spec)](https://www.w3.org/TR/webauthn-2/#dom-authenticatorresponse-clientdatajson)
    AuthenticatorAttestationResponse -> Base64UrlString
clientDataJSON :: Base64UrlString,
    -- | [(spec)](https://www.w3.org/TR/webauthn-2/#dom-authenticatorattestationresponse-attestationobject)
    AuthenticatorAttestationResponse -> Base64UrlString
attestationObject :: Base64UrlString,
    -- | [(spec)](https://www.w3.org/TR/webauthn-2/#dom-authenticatorattestationresponse-transports-slot)
    -- This field is only being propagated by webauthn-json [since recently](https://github.com/github/webauthn-json/pull/44),
    -- which is why we allow absence of this value
    AuthenticatorAttestationResponse -> Maybe [Text]
transports :: Maybe [Text]
  }
  deriving (AuthenticatorAttestationResponse
-> AuthenticatorAttestationResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AuthenticatorAttestationResponse
-> AuthenticatorAttestationResponse -> Bool
$c/= :: AuthenticatorAttestationResponse
-> AuthenticatorAttestationResponse -> Bool
== :: AuthenticatorAttestationResponse
-> AuthenticatorAttestationResponse -> Bool
$c== :: AuthenticatorAttestationResponse
-> AuthenticatorAttestationResponse -> Bool
Eq, Int -> AuthenticatorAttestationResponse -> ShowS
[AuthenticatorAttestationResponse] -> ShowS
AuthenticatorAttestationResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AuthenticatorAttestationResponse] -> ShowS
$cshowList :: [AuthenticatorAttestationResponse] -> ShowS
show :: AuthenticatorAttestationResponse -> String
$cshow :: AuthenticatorAttestationResponse -> String
showsPrec :: Int -> AuthenticatorAttestationResponse -> ShowS
$cshowsPrec :: Int -> AuthenticatorAttestationResponse -> ShowS
Show, forall x.
Rep AuthenticatorAttestationResponse x
-> AuthenticatorAttestationResponse
forall x.
AuthenticatorAttestationResponse
-> Rep AuthenticatorAttestationResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep AuthenticatorAttestationResponse x
-> AuthenticatorAttestationResponse
$cfrom :: forall x.
AuthenticatorAttestationResponse
-> Rep AuthenticatorAttestationResponse x
Generic)

instance Aeson.FromJSON AuthenticatorAttestationResponse where
  parseJSON :: Value -> Parser AuthenticatorAttestationResponse
parseJSON = forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
Aeson.genericParseJSON Options
jsonEncodingOptions

instance Aeson.ToJSON AuthenticatorAttestationResponse where
  toJSON :: AuthenticatorAttestationResponse -> Value
toJSON = forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
Aeson.genericToJSON Options
jsonEncodingOptions

instance Encode (T.AuthenticatorResponse 'K.Registration 'True) where
  type JSON (T.AuthenticatorResponse 'K.Registration 'True) = AuthenticatorAttestationResponse
  encode :: AuthenticatorResponse 'Registration 'True
-> JSON (AuthenticatorResponse 'Registration 'True)
encode T.AuthenticatorResponseRegistration {[AuthenticatorTransport]
AttestationObject 'True
CollectedClientData 'Registration 'True
arrTransports :: forall (raw :: Bool).
AuthenticatorResponse 'Registration raw -> [AuthenticatorTransport]
arrAttestationObject :: forall (raw :: Bool).
AuthenticatorResponse 'Registration raw -> AttestationObject raw
arrClientData :: forall (raw :: Bool).
AuthenticatorResponse 'Registration raw
-> CollectedClientData 'Registration raw
arrTransports :: [AuthenticatorTransport]
arrAttestationObject :: AttestationObject 'True
arrClientData :: CollectedClientData 'Registration 'True
..} =
    AuthenticatorAttestationResponse
      { $sel:clientDataJSON:AuthenticatorAttestationResponse :: Base64UrlString
clientDataJSON = forall a. Encode a => a -> JSON a
encode CollectedClientData 'Registration 'True
arrClientData,
        $sel:attestationObject:AuthenticatorAttestationResponse :: Base64UrlString
attestationObject = forall a. Encode a => a -> JSON a
encode AttestationObject 'True
arrAttestationObject,
        $sel:transports:AuthenticatorAttestationResponse :: Maybe [Text]
transports = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall a. Encode a => a -> JSON a
encode [AuthenticatorTransport]
arrTransports
      }

instance
  MonadReader T.SupportedAttestationStatementFormats m =>
  Decode m (T.AuthenticatorResponse 'K.Registration 'True)
  where
  decode :: MonadError Text m =>
JSON (AuthenticatorResponse 'Registration 'True)
-> m (AuthenticatorResponse 'Registration 'True)
decode AuthenticatorAttestationResponse {Maybe [Text]
Base64UrlString
transports :: Maybe [Text]
attestationObject :: Base64UrlString
clientDataJSON :: Base64UrlString
$sel:transports:AuthenticatorAttestationResponse :: AuthenticatorAttestationResponse -> Maybe [Text]
$sel:attestationObject:AuthenticatorAttestationResponse :: AuthenticatorAttestationResponse -> Base64UrlString
$sel:clientDataJSON:AuthenticatorAttestationResponse :: AuthenticatorAttestationResponse -> Base64UrlString
..} = do
    CollectedClientData 'Registration 'True
arrClientData <- forall (m :: * -> *) a.
(Decode m a, MonadError Text m) =>
JSON a -> m a
decode Base64UrlString
clientDataJSON
    AttestationObject 'True
arrAttestationObject <- forall (m :: * -> *) a.
(Decode m a, MonadError Text m) =>
JSON a -> m a
decode Base64UrlString
attestationObject
    -- Older webauthn-json versions don't add that field
    [AuthenticatorTransport]
arrTransports <- forall (m :: * -> *) a.
(MonadError Text m, Decode m a) =>
a -> Maybe (JSON a) -> m a
decodeWithDefault [] Maybe [Text]
transports
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ T.AuthenticatorResponseRegistration {[AuthenticatorTransport]
AttestationObject 'True
CollectedClientData 'Registration 'True
arrTransports :: [AuthenticatorTransport]
arrAttestationObject :: AttestationObject 'True
arrClientData :: CollectedClientData 'Registration 'True
arrTransports :: [AuthenticatorTransport]
arrAttestationObject :: AttestationObject 'True
arrClientData :: CollectedClientData 'Registration 'True
..}

-- | [(spec)](https://www.w3.org/TR/webauthn-2/#iface-authenticatorassertionresponse)
data AuthenticatorAssertionResponse = AuthenticatorAssertionResponse
  { -- | [(spec)](https://www.w3.org/TR/webauthn-2/#dom-authenticatorresponse-clientdatajson)
    AuthenticatorAssertionResponse -> Base64UrlString
clientDataJSON :: Base64UrlString,
    -- | [(spec)](https://www.w3.org/TR/webauthn-2/#dom-authenticatorassertionresponse-authenticatordata)
    AuthenticatorAssertionResponse -> Base64UrlString
authenticatorData :: Base64UrlString,
    -- | [(spec)](https://www.w3.org/TR/webauthn-2/#dom-authenticatorassertionresponse-signature)
    AuthenticatorAssertionResponse -> Base64UrlString
signature :: Base64UrlString,
    -- | [(spec)](https://www.w3.org/TR/webauthn-2/#dom-authenticatorassertionresponse-userhandle)
    AuthenticatorAssertionResponse -> Maybe Base64UrlString
userHandle :: Maybe Base64UrlString
  }
  deriving (AuthenticatorAssertionResponse
-> AuthenticatorAssertionResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AuthenticatorAssertionResponse
-> AuthenticatorAssertionResponse -> Bool
$c/= :: AuthenticatorAssertionResponse
-> AuthenticatorAssertionResponse -> Bool
== :: AuthenticatorAssertionResponse
-> AuthenticatorAssertionResponse -> Bool
$c== :: AuthenticatorAssertionResponse
-> AuthenticatorAssertionResponse -> Bool
Eq, Int -> AuthenticatorAssertionResponse -> ShowS
[AuthenticatorAssertionResponse] -> ShowS
AuthenticatorAssertionResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AuthenticatorAssertionResponse] -> ShowS
$cshowList :: [AuthenticatorAssertionResponse] -> ShowS
show :: AuthenticatorAssertionResponse -> String
$cshow :: AuthenticatorAssertionResponse -> String
showsPrec :: Int -> AuthenticatorAssertionResponse -> ShowS
$cshowsPrec :: Int -> AuthenticatorAssertionResponse -> ShowS
Show, forall x.
Rep AuthenticatorAssertionResponse x
-> AuthenticatorAssertionResponse
forall x.
AuthenticatorAssertionResponse
-> Rep AuthenticatorAssertionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep AuthenticatorAssertionResponse x
-> AuthenticatorAssertionResponse
$cfrom :: forall x.
AuthenticatorAssertionResponse
-> Rep AuthenticatorAssertionResponse x
Generic)

instance Aeson.FromJSON AuthenticatorAssertionResponse where
  parseJSON :: Value -> Parser AuthenticatorAssertionResponse
parseJSON = forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
Aeson.genericParseJSON Options
jsonEncodingOptions

instance Aeson.ToJSON AuthenticatorAssertionResponse where
  toJSON :: AuthenticatorAssertionResponse -> Value
toJSON = forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
Aeson.genericToJSON Options
jsonEncodingOptions

instance Encode (T.AuthenticatorResponse 'K.Authentication 'True) where
  type JSON (T.AuthenticatorResponse 'K.Authentication 'True) = AuthenticatorAssertionResponse
  encode :: AuthenticatorResponse 'Authentication 'True
-> JSON (AuthenticatorResponse 'Authentication 'True)
encode T.AuthenticatorResponseAuthentication {Maybe UserHandle
AuthenticatorData 'Authentication 'True
CollectedClientData 'Authentication 'True
AssertionSignature
araUserHandle :: forall (raw :: Bool).
AuthenticatorResponse 'Authentication raw -> Maybe UserHandle
araSignature :: forall (raw :: Bool).
AuthenticatorResponse 'Authentication raw -> AssertionSignature
araAuthenticatorData :: forall (raw :: Bool).
AuthenticatorResponse 'Authentication raw
-> AuthenticatorData 'Authentication raw
araClientData :: forall (raw :: Bool).
AuthenticatorResponse 'Authentication raw
-> CollectedClientData 'Authentication raw
araUserHandle :: Maybe UserHandle
araSignature :: AssertionSignature
araAuthenticatorData :: AuthenticatorData 'Authentication 'True
araClientData :: CollectedClientData 'Authentication 'True
..} =
    AuthenticatorAssertionResponse
      { $sel:clientDataJSON:AuthenticatorAssertionResponse :: Base64UrlString
clientDataJSON = forall a. Encode a => a -> JSON a
encode CollectedClientData 'Authentication 'True
araClientData,
        $sel:authenticatorData:AuthenticatorAssertionResponse :: Base64UrlString
authenticatorData = forall a. Encode a => a -> JSON a
encode AuthenticatorData 'Authentication 'True
araAuthenticatorData,
        $sel:signature:AuthenticatorAssertionResponse :: Base64UrlString
signature = forall a. Encode a => a -> JSON a
encode AssertionSignature
araSignature,
        $sel:userHandle:AuthenticatorAssertionResponse :: Maybe Base64UrlString
userHandle = forall a. Encode a => a -> JSON a
encode Maybe UserHandle
araUserHandle
      }

instance Decode m (T.AuthenticatorResponse 'K.Authentication 'True) where
  decode :: MonadError Text m =>
JSON (AuthenticatorResponse 'Authentication 'True)
-> m (AuthenticatorResponse 'Authentication 'True)
decode AuthenticatorAssertionResponse {Maybe Base64UrlString
Base64UrlString
userHandle :: Maybe Base64UrlString
signature :: Base64UrlString
authenticatorData :: Base64UrlString
clientDataJSON :: Base64UrlString
$sel:userHandle:AuthenticatorAssertionResponse :: AuthenticatorAssertionResponse -> Maybe Base64UrlString
$sel:signature:AuthenticatorAssertionResponse :: AuthenticatorAssertionResponse -> Base64UrlString
$sel:authenticatorData:AuthenticatorAssertionResponse :: AuthenticatorAssertionResponse -> Base64UrlString
$sel:clientDataJSON:AuthenticatorAssertionResponse :: AuthenticatorAssertionResponse -> Base64UrlString
..} = do
    CollectedClientData 'Authentication 'True
araClientData <- forall (m :: * -> *) a.
(Decode m a, MonadError Text m) =>
JSON a -> m a
decode Base64UrlString
clientDataJSON
    AuthenticatorData 'Authentication 'True
araAuthenticatorData <- forall (m :: * -> *) a.
(Decode m a, MonadError Text m) =>
JSON a -> m a
decode Base64UrlString
authenticatorData
    AssertionSignature
araSignature <- forall (m :: * -> *) a.
(Decode m a, MonadError Text m) =>
JSON a -> m a
decode Base64UrlString
signature
    Maybe UserHandle
araUserHandle <- forall (m :: * -> *) a.
(Decode m a, MonadError Text m) =>
JSON a -> m a
decode Maybe Base64UrlString
userHandle
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ T.AuthenticatorResponseAuthentication {Maybe UserHandle
AuthenticatorData 'Authentication 'True
CollectedClientData 'Authentication 'True
AssertionSignature
araUserHandle :: Maybe UserHandle
araSignature :: AssertionSignature
araAuthenticatorData :: AuthenticatorData 'Authentication 'True
araClientData :: CollectedClientData 'Authentication 'True
araUserHandle :: Maybe UserHandle
araSignature :: AssertionSignature
araAuthenticatorData :: AuthenticatorData 'Authentication 'True
araClientData :: CollectedClientData 'Authentication 'True
..}