{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.VoiceId.Types.AuthenticationResult
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.VoiceId.Types.AuthenticationResult where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude
import Amazonka.VoiceId.Types.AuthenticationConfiguration
import Amazonka.VoiceId.Types.AuthenticationDecision

-- | The authentication result produced by Voice ID, processed against the
-- current session state and streamed audio of the speaker.
--
-- /See:/ 'newAuthenticationResult' smart constructor.
data AuthenticationResult = AuthenticationResult'
  { -- | A timestamp indicating when audio aggregation ended for this
    -- authentication result.
    AuthenticationResult -> Maybe POSIX
audioAggregationEndedAt :: Prelude.Maybe Data.POSIX,
    -- | A timestamp indicating when audio aggregation started for this
    -- authentication result.
    AuthenticationResult -> Maybe POSIX
audioAggregationStartedAt :: Prelude.Maybe Data.POSIX,
    -- | The unique identifier for this authentication result. Because there can
    -- be multiple authentications for a given session, this field helps to
    -- identify if the returned result is from a previous streaming activity or
    -- a new result. Note that in absence of any new streaming activity,
    -- @AcceptanceThreshold@ changes, or @SpeakerId@ changes, Voice ID always
    -- returns cached Authentication Result for this API.
    AuthenticationResult -> Maybe Text
authenticationResultId :: Prelude.Maybe Prelude.Text,
    -- | The @AuthenticationConfiguration@ used to generate this authentication
    -- result.
    AuthenticationResult -> Maybe AuthenticationConfiguration
configuration :: Prelude.Maybe AuthenticationConfiguration,
    -- | The client-provided identifier for the speaker whose authentication
    -- result is produced. Only present if a @SpeakerId@ is provided for the
    -- session.
    AuthenticationResult -> Maybe (Sensitive Text)
customerSpeakerId :: Prelude.Maybe (Data.Sensitive Prelude.Text),
    -- | The authentication decision produced by Voice ID, processed against the
    -- current session state and streamed audio of the speaker.
    AuthenticationResult -> Maybe AuthenticationDecision
decision :: Prelude.Maybe AuthenticationDecision,
    -- | The service-generated identifier for the speaker whose authentication
    -- result is produced.
    AuthenticationResult -> Maybe Text
generatedSpeakerId :: Prelude.Maybe Prelude.Text,
    -- | The authentication score for the speaker whose authentication result is
    -- produced. This value is only present if the authentication decision is
    -- either @ACCEPT@ or @REJECT@.
    AuthenticationResult -> Maybe Natural
score :: Prelude.Maybe Prelude.Natural
  }
  deriving (AuthenticationResult -> AuthenticationResult -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AuthenticationResult -> AuthenticationResult -> Bool
$c/= :: AuthenticationResult -> AuthenticationResult -> Bool
== :: AuthenticationResult -> AuthenticationResult -> Bool
$c== :: AuthenticationResult -> AuthenticationResult -> Bool
Prelude.Eq, Int -> AuthenticationResult -> ShowS
[AuthenticationResult] -> ShowS
AuthenticationResult -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AuthenticationResult] -> ShowS
$cshowList :: [AuthenticationResult] -> ShowS
show :: AuthenticationResult -> String
$cshow :: AuthenticationResult -> String
showsPrec :: Int -> AuthenticationResult -> ShowS
$cshowsPrec :: Int -> AuthenticationResult -> ShowS
Prelude.Show, forall x. Rep AuthenticationResult x -> AuthenticationResult
forall x. AuthenticationResult -> Rep AuthenticationResult x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AuthenticationResult x -> AuthenticationResult
$cfrom :: forall x. AuthenticationResult -> Rep AuthenticationResult x
Prelude.Generic)

-- |
-- Create a value of 'AuthenticationResult' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'audioAggregationEndedAt', 'authenticationResult_audioAggregationEndedAt' - A timestamp indicating when audio aggregation ended for this
-- authentication result.
--
-- 'audioAggregationStartedAt', 'authenticationResult_audioAggregationStartedAt' - A timestamp indicating when audio aggregation started for this
-- authentication result.
--
-- 'authenticationResultId', 'authenticationResult_authenticationResultId' - The unique identifier for this authentication result. Because there can
-- be multiple authentications for a given session, this field helps to
-- identify if the returned result is from a previous streaming activity or
-- a new result. Note that in absence of any new streaming activity,
-- @AcceptanceThreshold@ changes, or @SpeakerId@ changes, Voice ID always
-- returns cached Authentication Result for this API.
--
-- 'configuration', 'authenticationResult_configuration' - The @AuthenticationConfiguration@ used to generate this authentication
-- result.
--
-- 'customerSpeakerId', 'authenticationResult_customerSpeakerId' - The client-provided identifier for the speaker whose authentication
-- result is produced. Only present if a @SpeakerId@ is provided for the
-- session.
--
-- 'decision', 'authenticationResult_decision' - The authentication decision produced by Voice ID, processed against the
-- current session state and streamed audio of the speaker.
--
-- 'generatedSpeakerId', 'authenticationResult_generatedSpeakerId' - The service-generated identifier for the speaker whose authentication
-- result is produced.
--
-- 'score', 'authenticationResult_score' - The authentication score for the speaker whose authentication result is
-- produced. This value is only present if the authentication decision is
-- either @ACCEPT@ or @REJECT@.
newAuthenticationResult ::
  AuthenticationResult
newAuthenticationResult :: AuthenticationResult
newAuthenticationResult =
  AuthenticationResult'
    { $sel:audioAggregationEndedAt:AuthenticationResult' :: Maybe POSIX
audioAggregationEndedAt =
        forall a. Maybe a
Prelude.Nothing,
      $sel:audioAggregationStartedAt:AuthenticationResult' :: Maybe POSIX
audioAggregationStartedAt = forall a. Maybe a
Prelude.Nothing,
      $sel:authenticationResultId:AuthenticationResult' :: Maybe Text
authenticationResultId = forall a. Maybe a
Prelude.Nothing,
      $sel:configuration:AuthenticationResult' :: Maybe AuthenticationConfiguration
configuration = forall a. Maybe a
Prelude.Nothing,
      $sel:customerSpeakerId:AuthenticationResult' :: Maybe (Sensitive Text)
customerSpeakerId = forall a. Maybe a
Prelude.Nothing,
      $sel:decision:AuthenticationResult' :: Maybe AuthenticationDecision
decision = forall a. Maybe a
Prelude.Nothing,
      $sel:generatedSpeakerId:AuthenticationResult' :: Maybe Text
generatedSpeakerId = forall a. Maybe a
Prelude.Nothing,
      $sel:score:AuthenticationResult' :: Maybe Natural
score = forall a. Maybe a
Prelude.Nothing
    }

-- | A timestamp indicating when audio aggregation ended for this
-- authentication result.
authenticationResult_audioAggregationEndedAt :: Lens.Lens' AuthenticationResult (Prelude.Maybe Prelude.UTCTime)
authenticationResult_audioAggregationEndedAt :: Lens' AuthenticationResult (Maybe UTCTime)
authenticationResult_audioAggregationEndedAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AuthenticationResult' {Maybe POSIX
audioAggregationEndedAt :: Maybe POSIX
$sel:audioAggregationEndedAt:AuthenticationResult' :: AuthenticationResult -> Maybe POSIX
audioAggregationEndedAt} -> Maybe POSIX
audioAggregationEndedAt) (\s :: AuthenticationResult
s@AuthenticationResult' {} Maybe POSIX
a -> AuthenticationResult
s {$sel:audioAggregationEndedAt:AuthenticationResult' :: Maybe POSIX
audioAggregationEndedAt = Maybe POSIX
a} :: AuthenticationResult) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | A timestamp indicating when audio aggregation started for this
-- authentication result.
authenticationResult_audioAggregationStartedAt :: Lens.Lens' AuthenticationResult (Prelude.Maybe Prelude.UTCTime)
authenticationResult_audioAggregationStartedAt :: Lens' AuthenticationResult (Maybe UTCTime)
authenticationResult_audioAggregationStartedAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AuthenticationResult' {Maybe POSIX
audioAggregationStartedAt :: Maybe POSIX
$sel:audioAggregationStartedAt:AuthenticationResult' :: AuthenticationResult -> Maybe POSIX
audioAggregationStartedAt} -> Maybe POSIX
audioAggregationStartedAt) (\s :: AuthenticationResult
s@AuthenticationResult' {} Maybe POSIX
a -> AuthenticationResult
s {$sel:audioAggregationStartedAt:AuthenticationResult' :: Maybe POSIX
audioAggregationStartedAt = Maybe POSIX
a} :: AuthenticationResult) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The unique identifier for this authentication result. Because there can
-- be multiple authentications for a given session, this field helps to
-- identify if the returned result is from a previous streaming activity or
-- a new result. Note that in absence of any new streaming activity,
-- @AcceptanceThreshold@ changes, or @SpeakerId@ changes, Voice ID always
-- returns cached Authentication Result for this API.
authenticationResult_authenticationResultId :: Lens.Lens' AuthenticationResult (Prelude.Maybe Prelude.Text)
authenticationResult_authenticationResultId :: Lens' AuthenticationResult (Maybe Text)
authenticationResult_authenticationResultId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AuthenticationResult' {Maybe Text
authenticationResultId :: Maybe Text
$sel:authenticationResultId:AuthenticationResult' :: AuthenticationResult -> Maybe Text
authenticationResultId} -> Maybe Text
authenticationResultId) (\s :: AuthenticationResult
s@AuthenticationResult' {} Maybe Text
a -> AuthenticationResult
s {$sel:authenticationResultId:AuthenticationResult' :: Maybe Text
authenticationResultId = Maybe Text
a} :: AuthenticationResult)

-- | The @AuthenticationConfiguration@ used to generate this authentication
-- result.
authenticationResult_configuration :: Lens.Lens' AuthenticationResult (Prelude.Maybe AuthenticationConfiguration)
authenticationResult_configuration :: Lens' AuthenticationResult (Maybe AuthenticationConfiguration)
authenticationResult_configuration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AuthenticationResult' {Maybe AuthenticationConfiguration
configuration :: Maybe AuthenticationConfiguration
$sel:configuration:AuthenticationResult' :: AuthenticationResult -> Maybe AuthenticationConfiguration
configuration} -> Maybe AuthenticationConfiguration
configuration) (\s :: AuthenticationResult
s@AuthenticationResult' {} Maybe AuthenticationConfiguration
a -> AuthenticationResult
s {$sel:configuration:AuthenticationResult' :: Maybe AuthenticationConfiguration
configuration = Maybe AuthenticationConfiguration
a} :: AuthenticationResult)

-- | The client-provided identifier for the speaker whose authentication
-- result is produced. Only present if a @SpeakerId@ is provided for the
-- session.
authenticationResult_customerSpeakerId :: Lens.Lens' AuthenticationResult (Prelude.Maybe Prelude.Text)
authenticationResult_customerSpeakerId :: Lens' AuthenticationResult (Maybe Text)
authenticationResult_customerSpeakerId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AuthenticationResult' {Maybe (Sensitive Text)
customerSpeakerId :: Maybe (Sensitive Text)
$sel:customerSpeakerId:AuthenticationResult' :: AuthenticationResult -> Maybe (Sensitive Text)
customerSpeakerId} -> Maybe (Sensitive Text)
customerSpeakerId) (\s :: AuthenticationResult
s@AuthenticationResult' {} Maybe (Sensitive Text)
a -> AuthenticationResult
s {$sel:customerSpeakerId:AuthenticationResult' :: Maybe (Sensitive Text)
customerSpeakerId = Maybe (Sensitive Text)
a} :: AuthenticationResult) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall a. Iso' (Sensitive a) a
Data._Sensitive

-- | The authentication decision produced by Voice ID, processed against the
-- current session state and streamed audio of the speaker.
authenticationResult_decision :: Lens.Lens' AuthenticationResult (Prelude.Maybe AuthenticationDecision)
authenticationResult_decision :: Lens' AuthenticationResult (Maybe AuthenticationDecision)
authenticationResult_decision = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AuthenticationResult' {Maybe AuthenticationDecision
decision :: Maybe AuthenticationDecision
$sel:decision:AuthenticationResult' :: AuthenticationResult -> Maybe AuthenticationDecision
decision} -> Maybe AuthenticationDecision
decision) (\s :: AuthenticationResult
s@AuthenticationResult' {} Maybe AuthenticationDecision
a -> AuthenticationResult
s {$sel:decision:AuthenticationResult' :: Maybe AuthenticationDecision
decision = Maybe AuthenticationDecision
a} :: AuthenticationResult)

-- | The service-generated identifier for the speaker whose authentication
-- result is produced.
authenticationResult_generatedSpeakerId :: Lens.Lens' AuthenticationResult (Prelude.Maybe Prelude.Text)
authenticationResult_generatedSpeakerId :: Lens' AuthenticationResult (Maybe Text)
authenticationResult_generatedSpeakerId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AuthenticationResult' {Maybe Text
generatedSpeakerId :: Maybe Text
$sel:generatedSpeakerId:AuthenticationResult' :: AuthenticationResult -> Maybe Text
generatedSpeakerId} -> Maybe Text
generatedSpeakerId) (\s :: AuthenticationResult
s@AuthenticationResult' {} Maybe Text
a -> AuthenticationResult
s {$sel:generatedSpeakerId:AuthenticationResult' :: Maybe Text
generatedSpeakerId = Maybe Text
a} :: AuthenticationResult)

-- | The authentication score for the speaker whose authentication result is
-- produced. This value is only present if the authentication decision is
-- either @ACCEPT@ or @REJECT@.
authenticationResult_score :: Lens.Lens' AuthenticationResult (Prelude.Maybe Prelude.Natural)
authenticationResult_score :: Lens' AuthenticationResult (Maybe Natural)
authenticationResult_score = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AuthenticationResult' {Maybe Natural
score :: Maybe Natural
$sel:score:AuthenticationResult' :: AuthenticationResult -> Maybe Natural
score} -> Maybe Natural
score) (\s :: AuthenticationResult
s@AuthenticationResult' {} Maybe Natural
a -> AuthenticationResult
s {$sel:score:AuthenticationResult' :: Maybe Natural
score = Maybe Natural
a} :: AuthenticationResult)

instance Data.FromJSON AuthenticationResult where
  parseJSON :: Value -> Parser AuthenticationResult
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"AuthenticationResult"
      ( \Object
x ->
          Maybe POSIX
-> Maybe POSIX
-> Maybe Text
-> Maybe AuthenticationConfiguration
-> Maybe (Sensitive Text)
-> Maybe AuthenticationDecision
-> Maybe Text
-> Maybe Natural
-> AuthenticationResult
AuthenticationResult'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"AudioAggregationEndedAt")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"AudioAggregationStartedAt")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"AuthenticationResultId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"Configuration")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"CustomerSpeakerId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"Decision")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"GeneratedSpeakerId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"Score")
      )

instance Prelude.Hashable AuthenticationResult where
  hashWithSalt :: Int -> AuthenticationResult -> Int
hashWithSalt Int
_salt AuthenticationResult' {Maybe Natural
Maybe Text
Maybe (Sensitive Text)
Maybe POSIX
Maybe AuthenticationConfiguration
Maybe AuthenticationDecision
score :: Maybe Natural
generatedSpeakerId :: Maybe Text
decision :: Maybe AuthenticationDecision
customerSpeakerId :: Maybe (Sensitive Text)
configuration :: Maybe AuthenticationConfiguration
authenticationResultId :: Maybe Text
audioAggregationStartedAt :: Maybe POSIX
audioAggregationEndedAt :: Maybe POSIX
$sel:score:AuthenticationResult' :: AuthenticationResult -> Maybe Natural
$sel:generatedSpeakerId:AuthenticationResult' :: AuthenticationResult -> Maybe Text
$sel:decision:AuthenticationResult' :: AuthenticationResult -> Maybe AuthenticationDecision
$sel:customerSpeakerId:AuthenticationResult' :: AuthenticationResult -> Maybe (Sensitive Text)
$sel:configuration:AuthenticationResult' :: AuthenticationResult -> Maybe AuthenticationConfiguration
$sel:authenticationResultId:AuthenticationResult' :: AuthenticationResult -> Maybe Text
$sel:audioAggregationStartedAt:AuthenticationResult' :: AuthenticationResult -> Maybe POSIX
$sel:audioAggregationEndedAt:AuthenticationResult' :: AuthenticationResult -> Maybe POSIX
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
audioAggregationEndedAt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
audioAggregationStartedAt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
authenticationResultId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AuthenticationConfiguration
configuration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (Sensitive Text)
customerSpeakerId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AuthenticationDecision
decision
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
generatedSpeakerId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
score

instance Prelude.NFData AuthenticationResult where
  rnf :: AuthenticationResult -> ()
rnf AuthenticationResult' {Maybe Natural
Maybe Text
Maybe (Sensitive Text)
Maybe POSIX
Maybe AuthenticationConfiguration
Maybe AuthenticationDecision
score :: Maybe Natural
generatedSpeakerId :: Maybe Text
decision :: Maybe AuthenticationDecision
customerSpeakerId :: Maybe (Sensitive Text)
configuration :: Maybe AuthenticationConfiguration
authenticationResultId :: Maybe Text
audioAggregationStartedAt :: Maybe POSIX
audioAggregationEndedAt :: Maybe POSIX
$sel:score:AuthenticationResult' :: AuthenticationResult -> Maybe Natural
$sel:generatedSpeakerId:AuthenticationResult' :: AuthenticationResult -> Maybe Text
$sel:decision:AuthenticationResult' :: AuthenticationResult -> Maybe AuthenticationDecision
$sel:customerSpeakerId:AuthenticationResult' :: AuthenticationResult -> Maybe (Sensitive Text)
$sel:configuration:AuthenticationResult' :: AuthenticationResult -> Maybe AuthenticationConfiguration
$sel:authenticationResultId:AuthenticationResult' :: AuthenticationResult -> Maybe Text
$sel:audioAggregationStartedAt:AuthenticationResult' :: AuthenticationResult -> Maybe POSIX
$sel:audioAggregationEndedAt:AuthenticationResult' :: AuthenticationResult -> Maybe POSIX
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
audioAggregationEndedAt
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
audioAggregationStartedAt
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
authenticationResultId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe AuthenticationConfiguration
configuration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (Sensitive Text)
customerSpeakerId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe AuthenticationDecision
decision
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
generatedSpeakerId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
score