{-# LANGUAGE DataKinds #-}

-- | Stability: experimental
-- This module contains functions and types for encoding 'T.CredentialOptions'
-- and decoding 'T.Credential's, based on intermediate types that implement the
-- 'ToJSON' and 'FromJSON' types respectively, matching the serialization used
-- by [webauthn-json](https://github.com/github/webauthn-json).
module Crypto.WebAuthn.Encoding.WebAuthnJson
  ( -- * Registration
    wjEncodeCredentialOptionsRegistration,
    WJCredentialOptionsRegistration (..),
    WJCredentialRegistration (..),
    wjDecodeCredentialRegistration',
    wjDecodeCredentialRegistration,

    -- * Authentication
    wjEncodeCredentialOptionsAuthentication,
    WJCredentialOptionsAuthentication (..),
    WJCredentialAuthentication (..),
    wjDecodeCredentialAuthentication,
  )
where

import Control.Monad.Except (runExceptT)
import Control.Monad.Identity (runIdentity)
import Control.Monad.Reader (runReaderT)
import Crypto.WebAuthn.AttestationStatementFormat (allSupportedFormats)
import qualified Crypto.WebAuthn.Encoding.Internal.WebAuthnJson as WJ
import qualified Crypto.WebAuthn.Model.Kinds as K
import qualified Crypto.WebAuthn.Model.Types as T
import Data.Aeson (FromJSON, ToJSON)
import Data.Text (Text)

-- | Encodes a @'T.CredentialOptions' 'K.Registration'@, which is needed for the
-- [registration ceremony](https://www.w3.org/TR/webauthn-2/#registration). The
-- resulting type from this function can be encoded using 'Data.Aeson.toJSON',
-- sent as a response, received by the Relying Party script, passed directly as the [@publicKey@](https://www.w3.org/TR/webauthn-2/#dom-credentialcreationoptions-publickey)
-- field in the argument to [webauthn-json](https://github.com/github/webauthn-json)'s [@create()@](https://github.com/github/webauthn-json#api) (or equivalent) function. The result of that function can then be decoded using 'wjDecodeCredentialRegistration'.
wjEncodeCredentialOptionsRegistration ::
  T.CredentialOptions 'K.Registration ->
  WJCredentialOptionsRegistration
wjEncodeCredentialOptionsRegistration :: CredentialOptions 'Registration -> WJCredentialOptionsRegistration
wjEncodeCredentialOptionsRegistration = PublicKeyCredentialCreationOptions
-> WJCredentialOptionsRegistration
WJCredentialOptionsRegistration forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Encode a => a -> JSON a
WJ.encode

-- | The intermediate type returned by 'wjEncodeCredentialOptionsRegistration',
-- equivalent to the [@PublicKeyCredentialCreationOptions@](https://www.w3.org/TR/webauthn-2/#dictdef-publickeycredentialcreationoptions) dictionary
newtype WJCredentialOptionsRegistration = WJCredentialOptionsRegistration
  { WJCredentialOptionsRegistration
-> PublicKeyCredentialCreationOptions
_unWJCredentialOptionsRegistration :: WJ.PublicKeyCredentialCreationOptions
  }
  deriving newtype (Int -> WJCredentialOptionsRegistration -> ShowS
[WJCredentialOptionsRegistration] -> ShowS
WJCredentialOptionsRegistration -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WJCredentialOptionsRegistration] -> ShowS
$cshowList :: [WJCredentialOptionsRegistration] -> ShowS
show :: WJCredentialOptionsRegistration -> String
$cshow :: WJCredentialOptionsRegistration -> String
showsPrec :: Int -> WJCredentialOptionsRegistration -> ShowS
$cshowsPrec :: Int -> WJCredentialOptionsRegistration -> ShowS
Show, WJCredentialOptionsRegistration
-> WJCredentialOptionsRegistration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WJCredentialOptionsRegistration
-> WJCredentialOptionsRegistration -> Bool
$c/= :: WJCredentialOptionsRegistration
-> WJCredentialOptionsRegistration -> Bool
== :: WJCredentialOptionsRegistration
-> WJCredentialOptionsRegistration -> Bool
$c== :: WJCredentialOptionsRegistration
-> WJCredentialOptionsRegistration -> Bool
Eq, Value -> Parser [WJCredentialOptionsRegistration]
Value -> Parser WJCredentialOptionsRegistration
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [WJCredentialOptionsRegistration]
$cparseJSONList :: Value -> Parser [WJCredentialOptionsRegistration]
parseJSON :: Value -> Parser WJCredentialOptionsRegistration
$cparseJSON :: Value -> Parser WJCredentialOptionsRegistration
FromJSON, [WJCredentialOptionsRegistration] -> Encoding
[WJCredentialOptionsRegistration] -> Value
WJCredentialOptionsRegistration -> Encoding
WJCredentialOptionsRegistration -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [WJCredentialOptionsRegistration] -> Encoding
$ctoEncodingList :: [WJCredentialOptionsRegistration] -> Encoding
toJSONList :: [WJCredentialOptionsRegistration] -> Value
$ctoJSONList :: [WJCredentialOptionsRegistration] -> Value
toEncoding :: WJCredentialOptionsRegistration -> Encoding
$ctoEncoding :: WJCredentialOptionsRegistration -> Encoding
toJSON :: WJCredentialOptionsRegistration -> Value
$ctoJSON :: WJCredentialOptionsRegistration -> Value
ToJSON)

-- | The intermediate type as an input to 'wjDecodeCredentialRegistration',
-- equivalent to the [PublicKeyCredential](https://www.w3.org/TR/webauthn-2/#iface-pkcredential)
-- interface with the response being an
-- [AuthenticatorAttestationResponse](https://www.w3.org/TR/webauthn-2/#authenticatorattestationresponse).
newtype WJCredentialRegistration = WJCredentialRegistration
  { WJCredentialRegistration
-> PublicKeyCredential AuthenticatorAttestationResponse
unWJCredentialRegistration :: WJ.PublicKeyCredential WJ.AuthenticatorAttestationResponse
  }
  deriving newtype (Int -> WJCredentialRegistration -> ShowS
[WJCredentialRegistration] -> ShowS
WJCredentialRegistration -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WJCredentialRegistration] -> ShowS
$cshowList :: [WJCredentialRegistration] -> ShowS
show :: WJCredentialRegistration -> String
$cshow :: WJCredentialRegistration -> String
showsPrec :: Int -> WJCredentialRegistration -> ShowS
$cshowsPrec :: Int -> WJCredentialRegistration -> ShowS
Show, WJCredentialRegistration -> WJCredentialRegistration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WJCredentialRegistration -> WJCredentialRegistration -> Bool
$c/= :: WJCredentialRegistration -> WJCredentialRegistration -> Bool
== :: WJCredentialRegistration -> WJCredentialRegistration -> Bool
$c== :: WJCredentialRegistration -> WJCredentialRegistration -> Bool
Eq, Value -> Parser [WJCredentialRegistration]
Value -> Parser WJCredentialRegistration
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [WJCredentialRegistration]
$cparseJSONList :: Value -> Parser [WJCredentialRegistration]
parseJSON :: Value -> Parser WJCredentialRegistration
$cparseJSON :: Value -> Parser WJCredentialRegistration
FromJSON, [WJCredentialRegistration] -> Encoding
[WJCredentialRegistration] -> Value
WJCredentialRegistration -> Encoding
WJCredentialRegistration -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [WJCredentialRegistration] -> Encoding
$ctoEncodingList :: [WJCredentialRegistration] -> Encoding
toJSONList :: [WJCredentialRegistration] -> Value
$ctoJSONList :: [WJCredentialRegistration] -> Value
toEncoding :: WJCredentialRegistration -> Encoding
$ctoEncoding :: WJCredentialRegistration -> Encoding
toJSON :: WJCredentialRegistration -> Value
$ctoJSON :: WJCredentialRegistration -> Value
ToJSON)

-- | Decodes the intermediate 'WJCredentialRegistration' type which can be
-- parsed with 'Data.Aeson.fromJSON' from the result of
-- [webauthn-json](https://github.com/github/webauthn-json)'s
-- [@create()@](https://github.com/github/webauthn-json#api) (or equivalent)
-- function, to a @'T.Credential' 'K.Registration'@. This is the continuation
-- of 'wjEncodeCredentialOptionsRegistration'.
wjDecodeCredentialRegistration' ::
  -- | The [attestation statement formats](https://www.w3.org/TR/webauthn-2/#sctn-attestation-formats)
  -- that should be supported. The value of 'Crypto.WebAuthn.allSupportedFormats'
  -- can be passed here, but additional or custom formats may also be used if needed
  T.SupportedAttestationStatementFormats ->
  WJCredentialRegistration ->
  Either Text (T.Credential 'K.Registration 'True)
wjDecodeCredentialRegistration' :: SupportedAttestationStatementFormats
-> WJCredentialRegistration
-> Either Text (Credential 'Registration 'True)
wjDecodeCredentialRegistration' SupportedAttestationStatementFormats
supportedFormats =
  forall a. Identity a -> a
runIdentity forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
`runReaderT` SupportedAttestationStatementFormats
supportedFormats) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a.
(Decode m a, MonadError Text m) =>
JSON a -> m a
WJ.decode forall b c a. (b -> c) -> (a -> b) -> a -> c
. WJCredentialRegistration
-> PublicKeyCredential AuthenticatorAttestationResponse
unWJCredentialRegistration

-- | A version of 'wjDecodeCredentialRegistration'' with 'allSupportedFormats' passed as the supported formats
wjDecodeCredentialRegistration ::
  WJCredentialRegistration ->
  Either Text (T.Credential 'K.Registration 'True)
wjDecodeCredentialRegistration :: WJCredentialRegistration
-> Either Text (Credential 'Registration 'True)
wjDecodeCredentialRegistration = SupportedAttestationStatementFormats
-> WJCredentialRegistration
-> Either Text (Credential 'Registration 'True)
wjDecodeCredentialRegistration' SupportedAttestationStatementFormats
allSupportedFormats

-- | Encodes a @'T.CredentialOptions' 'K.Authentication'@, which is needed for the
-- [authentication ceremony](https://www.w3.org/TR/webauthn-2/#authentication). The
-- resulting type from this function can be encoded using 'Data.Aeson.toJSON',
-- sent as a response, received by the Relying Party script, parsed as JSON,
-- and passed directly as the [@publicKey@](https://www.w3.org/TR/webauthn-2/#dom-credentialrequestoptions-publickey)
-- field in the argument to the [@navigator.credentials.get()@](https://w3c.github.io/webappsec-credential-management/#dom-credentialscontainer-get)
-- function.
wjEncodeCredentialOptionsAuthentication ::
  T.CredentialOptions 'K.Authentication ->
  WJCredentialOptionsAuthentication
wjEncodeCredentialOptionsAuthentication :: CredentialOptions 'Authentication
-> WJCredentialOptionsAuthentication
wjEncodeCredentialOptionsAuthentication = PublicKeyCredentialRequestOptions
-> WJCredentialOptionsAuthentication
WJCredentialOptionsAuthentication forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Encode a => a -> JSON a
WJ.encode

-- | The intermediate type returned by 'wjEncodeCredentialOptionsAuthentication',
-- equivalent to the [@PublicKeyCredentialRequestOptions@](https://www.w3.org/TR/webauthn-2/#dictdef-publickeycredentialrequestoptions) dictionary
newtype WJCredentialOptionsAuthentication = WJCredentialOptionsAuthentication
  { WJCredentialOptionsAuthentication
-> PublicKeyCredentialRequestOptions
_unWJCredentialOptionsAuthentication :: WJ.PublicKeyCredentialRequestOptions
  }
  deriving newtype (Int -> WJCredentialOptionsAuthentication -> ShowS
[WJCredentialOptionsAuthentication] -> ShowS
WJCredentialOptionsAuthentication -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WJCredentialOptionsAuthentication] -> ShowS
$cshowList :: [WJCredentialOptionsAuthentication] -> ShowS
show :: WJCredentialOptionsAuthentication -> String
$cshow :: WJCredentialOptionsAuthentication -> String
showsPrec :: Int -> WJCredentialOptionsAuthentication -> ShowS
$cshowsPrec :: Int -> WJCredentialOptionsAuthentication -> ShowS
Show, WJCredentialOptionsAuthentication
-> WJCredentialOptionsAuthentication -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WJCredentialOptionsAuthentication
-> WJCredentialOptionsAuthentication -> Bool
$c/= :: WJCredentialOptionsAuthentication
-> WJCredentialOptionsAuthentication -> Bool
== :: WJCredentialOptionsAuthentication
-> WJCredentialOptionsAuthentication -> Bool
$c== :: WJCredentialOptionsAuthentication
-> WJCredentialOptionsAuthentication -> Bool
Eq, Value -> Parser [WJCredentialOptionsAuthentication]
Value -> Parser WJCredentialOptionsAuthentication
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [WJCredentialOptionsAuthentication]
$cparseJSONList :: Value -> Parser [WJCredentialOptionsAuthentication]
parseJSON :: Value -> Parser WJCredentialOptionsAuthentication
$cparseJSON :: Value -> Parser WJCredentialOptionsAuthentication
FromJSON, [WJCredentialOptionsAuthentication] -> Encoding
[WJCredentialOptionsAuthentication] -> Value
WJCredentialOptionsAuthentication -> Encoding
WJCredentialOptionsAuthentication -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [WJCredentialOptionsAuthentication] -> Encoding
$ctoEncodingList :: [WJCredentialOptionsAuthentication] -> Encoding
toJSONList :: [WJCredentialOptionsAuthentication] -> Value
$ctoJSONList :: [WJCredentialOptionsAuthentication] -> Value
toEncoding :: WJCredentialOptionsAuthentication -> Encoding
$ctoEncoding :: WJCredentialOptionsAuthentication -> Encoding
toJSON :: WJCredentialOptionsAuthentication -> Value
$ctoJSON :: WJCredentialOptionsAuthentication -> Value
ToJSON)

-- | The intermediate type as an input to 'wjDecodeCredentialAuthentication',
-- equivalent to the [PublicKeyCredential](https://www.w3.org/TR/webauthn-2/#iface-pkcredential)
-- interface with the response being an
-- [AuthenticatorAssertionResponse](https://www.w3.org/TR/webauthn-2/#authenticatorassertionresponse).
newtype WJCredentialAuthentication = WJCredentialAuthentication
  { WJCredentialAuthentication
-> PublicKeyCredential AuthenticatorAssertionResponse
unWJCredentialAuthentication :: WJ.PublicKeyCredential WJ.AuthenticatorAssertionResponse
  }
  deriving newtype (Int -> WJCredentialAuthentication -> ShowS
[WJCredentialAuthentication] -> ShowS
WJCredentialAuthentication -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WJCredentialAuthentication] -> ShowS
$cshowList :: [WJCredentialAuthentication] -> ShowS
show :: WJCredentialAuthentication -> String
$cshow :: WJCredentialAuthentication -> String
showsPrec :: Int -> WJCredentialAuthentication -> ShowS
$cshowsPrec :: Int -> WJCredentialAuthentication -> ShowS
Show, WJCredentialAuthentication -> WJCredentialAuthentication -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WJCredentialAuthentication -> WJCredentialAuthentication -> Bool
$c/= :: WJCredentialAuthentication -> WJCredentialAuthentication -> Bool
== :: WJCredentialAuthentication -> WJCredentialAuthentication -> Bool
$c== :: WJCredentialAuthentication -> WJCredentialAuthentication -> Bool
Eq, Value -> Parser [WJCredentialAuthentication]
Value -> Parser WJCredentialAuthentication
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [WJCredentialAuthentication]
$cparseJSONList :: Value -> Parser [WJCredentialAuthentication]
parseJSON :: Value -> Parser WJCredentialAuthentication
$cparseJSON :: Value -> Parser WJCredentialAuthentication
FromJSON, [WJCredentialAuthentication] -> Encoding
[WJCredentialAuthentication] -> Value
WJCredentialAuthentication -> Encoding
WJCredentialAuthentication -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [WJCredentialAuthentication] -> Encoding
$ctoEncodingList :: [WJCredentialAuthentication] -> Encoding
toJSONList :: [WJCredentialAuthentication] -> Value
$ctoJSONList :: [WJCredentialAuthentication] -> Value
toEncoding :: WJCredentialAuthentication -> Encoding
$ctoEncoding :: WJCredentialAuthentication -> Encoding
toJSON :: WJCredentialAuthentication -> Value
$ctoJSON :: WJCredentialAuthentication -> Value
ToJSON)

-- | Decodes a 'WJ.RequestedPublicKeyCredential' result, corresponding to the
-- [@PublicKeyCredential@ interface](https://www.w3.org/TR/webauthn-2/#iface-pkcredential)
-- as returned by the [get()](https://w3c.github.io/webappsec-credential-management/#dom-credentialscontainer-get)
-- method while [Verifying an Authentication Assertion](https://www.w3.org/TR/webauthn-2/#sctn-verifying-assertion)
--
-- | Decodes the intermediate 'WJCredentialAuthentication' type which can be
-- parsed with 'Data.Aeson.fromJSON' from the result of
-- [webauthn-json](https://github.com/github/webauthn-json)'s
-- [@get()@](https://github.com/github/webauthn-json#api) (or equivalent)
-- function, to a @'T.Credential' 'K.Authentication' True@. This is the continuation
-- of 'wjEncodeCredentialOptionsAuthentication'
wjDecodeCredentialAuthentication ::
  WJCredentialAuthentication ->
  Either Text (T.Credential 'K.Authentication 'True)
wjDecodeCredentialAuthentication :: WJCredentialAuthentication
-> Either Text (Credential 'Authentication 'True)
wjDecodeCredentialAuthentication =
  forall a. Identity a -> a
runIdentity forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a.
(Decode m a, MonadError Text m) =>
JSON a -> m a
WJ.decode forall b c a. (b -> c) -> (a -> b) -> a -> c
. WJCredentialAuthentication
-> PublicKeyCredential AuthenticatorAssertionResponse
unWJCredentialAuthentication