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

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

-- |
-- Module      : Amazonka.LexV2Models.StartBotRecommendation
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Use this to provide your transcript data, and to start the bot
-- recommendation process.
module Amazonka.LexV2Models.StartBotRecommendation
  ( -- * Creating a Request
    StartBotRecommendation (..),
    newStartBotRecommendation,

    -- * Request Lenses
    startBotRecommendation_encryptionSetting,
    startBotRecommendation_botId,
    startBotRecommendation_botVersion,
    startBotRecommendation_localeId,
    startBotRecommendation_transcriptSourceSetting,

    -- * Destructuring the Response
    StartBotRecommendationResponse (..),
    newStartBotRecommendationResponse,

    -- * Response Lenses
    startBotRecommendationResponse_botId,
    startBotRecommendationResponse_botRecommendationId,
    startBotRecommendationResponse_botRecommendationStatus,
    startBotRecommendationResponse_botVersion,
    startBotRecommendationResponse_creationDateTime,
    startBotRecommendationResponse_encryptionSetting,
    startBotRecommendationResponse_localeId,
    startBotRecommendationResponse_transcriptSourceSetting,
    startBotRecommendationResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.LexV2Models.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newStartBotRecommendation' smart constructor.
data StartBotRecommendation = StartBotRecommendation'
  { -- | The object representing the passwords that will be used to encrypt the
    -- data related to the bot recommendation results, as well as the KMS key
    -- ARN used to encrypt the associated metadata.
    StartBotRecommendation -> Maybe EncryptionSetting
encryptionSetting :: Prelude.Maybe EncryptionSetting,
    -- | The unique identifier of the bot containing the bot recommendation.
    StartBotRecommendation -> Text
botId :: Prelude.Text,
    -- | The version of the bot containing the bot recommendation.
    StartBotRecommendation -> Text
botVersion :: Prelude.Text,
    -- | The identifier of the language and locale of the bot recommendation to
    -- start. The string must match one of the supported locales. For more
    -- information, see
    -- <https://docs.aws.amazon.com/lexv2/latest/dg/how-languages.html Supported languages>
    StartBotRecommendation -> Text
localeId :: Prelude.Text,
    -- | The object representing the Amazon S3 bucket containing the transcript,
    -- as well as the associated metadata.
    StartBotRecommendation -> TranscriptSourceSetting
transcriptSourceSetting :: TranscriptSourceSetting
  }
  deriving (StartBotRecommendation -> StartBotRecommendation -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StartBotRecommendation -> StartBotRecommendation -> Bool
$c/= :: StartBotRecommendation -> StartBotRecommendation -> Bool
== :: StartBotRecommendation -> StartBotRecommendation -> Bool
$c== :: StartBotRecommendation -> StartBotRecommendation -> Bool
Prelude.Eq, Int -> StartBotRecommendation -> ShowS
[StartBotRecommendation] -> ShowS
StartBotRecommendation -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StartBotRecommendation] -> ShowS
$cshowList :: [StartBotRecommendation] -> ShowS
show :: StartBotRecommendation -> String
$cshow :: StartBotRecommendation -> String
showsPrec :: Int -> StartBotRecommendation -> ShowS
$cshowsPrec :: Int -> StartBotRecommendation -> ShowS
Prelude.Show, forall x. Rep StartBotRecommendation x -> StartBotRecommendation
forall x. StartBotRecommendation -> Rep StartBotRecommendation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StartBotRecommendation x -> StartBotRecommendation
$cfrom :: forall x. StartBotRecommendation -> Rep StartBotRecommendation x
Prelude.Generic)

-- |
-- Create a value of 'StartBotRecommendation' 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:
--
-- 'encryptionSetting', 'startBotRecommendation_encryptionSetting' - The object representing the passwords that will be used to encrypt the
-- data related to the bot recommendation results, as well as the KMS key
-- ARN used to encrypt the associated metadata.
--
-- 'botId', 'startBotRecommendation_botId' - The unique identifier of the bot containing the bot recommendation.
--
-- 'botVersion', 'startBotRecommendation_botVersion' - The version of the bot containing the bot recommendation.
--
-- 'localeId', 'startBotRecommendation_localeId' - The identifier of the language and locale of the bot recommendation to
-- start. The string must match one of the supported locales. For more
-- information, see
-- <https://docs.aws.amazon.com/lexv2/latest/dg/how-languages.html Supported languages>
--
-- 'transcriptSourceSetting', 'startBotRecommendation_transcriptSourceSetting' - The object representing the Amazon S3 bucket containing the transcript,
-- as well as the associated metadata.
newStartBotRecommendation ::
  -- | 'botId'
  Prelude.Text ->
  -- | 'botVersion'
  Prelude.Text ->
  -- | 'localeId'
  Prelude.Text ->
  -- | 'transcriptSourceSetting'
  TranscriptSourceSetting ->
  StartBotRecommendation
newStartBotRecommendation :: Text
-> Text
-> Text
-> TranscriptSourceSetting
-> StartBotRecommendation
newStartBotRecommendation
  Text
pBotId_
  Text
pBotVersion_
  Text
pLocaleId_
  TranscriptSourceSetting
pTranscriptSourceSetting_ =
    StartBotRecommendation'
      { $sel:encryptionSetting:StartBotRecommendation' :: Maybe EncryptionSetting
encryptionSetting =
          forall a. Maybe a
Prelude.Nothing,
        $sel:botId:StartBotRecommendation' :: Text
botId = Text
pBotId_,
        $sel:botVersion:StartBotRecommendation' :: Text
botVersion = Text
pBotVersion_,
        $sel:localeId:StartBotRecommendation' :: Text
localeId = Text
pLocaleId_,
        $sel:transcriptSourceSetting:StartBotRecommendation' :: TranscriptSourceSetting
transcriptSourceSetting = TranscriptSourceSetting
pTranscriptSourceSetting_
      }

-- | The object representing the passwords that will be used to encrypt the
-- data related to the bot recommendation results, as well as the KMS key
-- ARN used to encrypt the associated metadata.
startBotRecommendation_encryptionSetting :: Lens.Lens' StartBotRecommendation (Prelude.Maybe EncryptionSetting)
startBotRecommendation_encryptionSetting :: Lens' StartBotRecommendation (Maybe EncryptionSetting)
startBotRecommendation_encryptionSetting = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartBotRecommendation' {Maybe EncryptionSetting
encryptionSetting :: Maybe EncryptionSetting
$sel:encryptionSetting:StartBotRecommendation' :: StartBotRecommendation -> Maybe EncryptionSetting
encryptionSetting} -> Maybe EncryptionSetting
encryptionSetting) (\s :: StartBotRecommendation
s@StartBotRecommendation' {} Maybe EncryptionSetting
a -> StartBotRecommendation
s {$sel:encryptionSetting:StartBotRecommendation' :: Maybe EncryptionSetting
encryptionSetting = Maybe EncryptionSetting
a} :: StartBotRecommendation)

-- | The unique identifier of the bot containing the bot recommendation.
startBotRecommendation_botId :: Lens.Lens' StartBotRecommendation Prelude.Text
startBotRecommendation_botId :: Lens' StartBotRecommendation Text
startBotRecommendation_botId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartBotRecommendation' {Text
botId :: Text
$sel:botId:StartBotRecommendation' :: StartBotRecommendation -> Text
botId} -> Text
botId) (\s :: StartBotRecommendation
s@StartBotRecommendation' {} Text
a -> StartBotRecommendation
s {$sel:botId:StartBotRecommendation' :: Text
botId = Text
a} :: StartBotRecommendation)

-- | The version of the bot containing the bot recommendation.
startBotRecommendation_botVersion :: Lens.Lens' StartBotRecommendation Prelude.Text
startBotRecommendation_botVersion :: Lens' StartBotRecommendation Text
startBotRecommendation_botVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartBotRecommendation' {Text
botVersion :: Text
$sel:botVersion:StartBotRecommendation' :: StartBotRecommendation -> Text
botVersion} -> Text
botVersion) (\s :: StartBotRecommendation
s@StartBotRecommendation' {} Text
a -> StartBotRecommendation
s {$sel:botVersion:StartBotRecommendation' :: Text
botVersion = Text
a} :: StartBotRecommendation)

-- | The identifier of the language and locale of the bot recommendation to
-- start. The string must match one of the supported locales. For more
-- information, see
-- <https://docs.aws.amazon.com/lexv2/latest/dg/how-languages.html Supported languages>
startBotRecommendation_localeId :: Lens.Lens' StartBotRecommendation Prelude.Text
startBotRecommendation_localeId :: Lens' StartBotRecommendation Text
startBotRecommendation_localeId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartBotRecommendation' {Text
localeId :: Text
$sel:localeId:StartBotRecommendation' :: StartBotRecommendation -> Text
localeId} -> Text
localeId) (\s :: StartBotRecommendation
s@StartBotRecommendation' {} Text
a -> StartBotRecommendation
s {$sel:localeId:StartBotRecommendation' :: Text
localeId = Text
a} :: StartBotRecommendation)

-- | The object representing the Amazon S3 bucket containing the transcript,
-- as well as the associated metadata.
startBotRecommendation_transcriptSourceSetting :: Lens.Lens' StartBotRecommendation TranscriptSourceSetting
startBotRecommendation_transcriptSourceSetting :: Lens' StartBotRecommendation TranscriptSourceSetting
startBotRecommendation_transcriptSourceSetting = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartBotRecommendation' {TranscriptSourceSetting
transcriptSourceSetting :: TranscriptSourceSetting
$sel:transcriptSourceSetting:StartBotRecommendation' :: StartBotRecommendation -> TranscriptSourceSetting
transcriptSourceSetting} -> TranscriptSourceSetting
transcriptSourceSetting) (\s :: StartBotRecommendation
s@StartBotRecommendation' {} TranscriptSourceSetting
a -> StartBotRecommendation
s {$sel:transcriptSourceSetting:StartBotRecommendation' :: TranscriptSourceSetting
transcriptSourceSetting = TranscriptSourceSetting
a} :: StartBotRecommendation)

instance Core.AWSRequest StartBotRecommendation where
  type
    AWSResponse StartBotRecommendation =
      StartBotRecommendationResponse
  request :: (Service -> Service)
-> StartBotRecommendation -> Request StartBotRecommendation
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.putJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy StartBotRecommendation
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse StartBotRecommendation)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe Text
-> Maybe Text
-> Maybe BotRecommendationStatus
-> Maybe Text
-> Maybe POSIX
-> Maybe EncryptionSetting
-> Maybe Text
-> Maybe TranscriptSourceSetting
-> Int
-> StartBotRecommendationResponse
StartBotRecommendationResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"botId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"botRecommendationId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"botRecommendationStatus")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"botVersion")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"creationDateTime")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"encryptionSetting")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"localeId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"transcriptSourceSetting")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable StartBotRecommendation where
  hashWithSalt :: Int -> StartBotRecommendation -> Int
hashWithSalt Int
_salt StartBotRecommendation' {Maybe EncryptionSetting
Text
TranscriptSourceSetting
transcriptSourceSetting :: TranscriptSourceSetting
localeId :: Text
botVersion :: Text
botId :: Text
encryptionSetting :: Maybe EncryptionSetting
$sel:transcriptSourceSetting:StartBotRecommendation' :: StartBotRecommendation -> TranscriptSourceSetting
$sel:localeId:StartBotRecommendation' :: StartBotRecommendation -> Text
$sel:botVersion:StartBotRecommendation' :: StartBotRecommendation -> Text
$sel:botId:StartBotRecommendation' :: StartBotRecommendation -> Text
$sel:encryptionSetting:StartBotRecommendation' :: StartBotRecommendation -> Maybe EncryptionSetting
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe EncryptionSetting
encryptionSetting
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
botId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
botVersion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
localeId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` TranscriptSourceSetting
transcriptSourceSetting

instance Prelude.NFData StartBotRecommendation where
  rnf :: StartBotRecommendation -> ()
rnf StartBotRecommendation' {Maybe EncryptionSetting
Text
TranscriptSourceSetting
transcriptSourceSetting :: TranscriptSourceSetting
localeId :: Text
botVersion :: Text
botId :: Text
encryptionSetting :: Maybe EncryptionSetting
$sel:transcriptSourceSetting:StartBotRecommendation' :: StartBotRecommendation -> TranscriptSourceSetting
$sel:localeId:StartBotRecommendation' :: StartBotRecommendation -> Text
$sel:botVersion:StartBotRecommendation' :: StartBotRecommendation -> Text
$sel:botId:StartBotRecommendation' :: StartBotRecommendation -> Text
$sel:encryptionSetting:StartBotRecommendation' :: StartBotRecommendation -> Maybe EncryptionSetting
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe EncryptionSetting
encryptionSetting
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
botId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
botVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
localeId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf TranscriptSourceSetting
transcriptSourceSetting

instance Data.ToHeaders StartBotRecommendation where
  toHeaders :: StartBotRecommendation -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON StartBotRecommendation where
  toJSON :: StartBotRecommendation -> Value
toJSON StartBotRecommendation' {Maybe EncryptionSetting
Text
TranscriptSourceSetting
transcriptSourceSetting :: TranscriptSourceSetting
localeId :: Text
botVersion :: Text
botId :: Text
encryptionSetting :: Maybe EncryptionSetting
$sel:transcriptSourceSetting:StartBotRecommendation' :: StartBotRecommendation -> TranscriptSourceSetting
$sel:localeId:StartBotRecommendation' :: StartBotRecommendation -> Text
$sel:botVersion:StartBotRecommendation' :: StartBotRecommendation -> Text
$sel:botId:StartBotRecommendation' :: StartBotRecommendation -> Text
$sel:encryptionSetting:StartBotRecommendation' :: StartBotRecommendation -> Maybe EncryptionSetting
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"encryptionSetting" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe EncryptionSetting
encryptionSetting,
            forall a. a -> Maybe a
Prelude.Just
              ( Key
"transcriptSourceSetting"
                  forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= TranscriptSourceSetting
transcriptSourceSetting
              )
          ]
      )

instance Data.ToPath StartBotRecommendation where
  toPath :: StartBotRecommendation -> ByteString
toPath StartBotRecommendation' {Maybe EncryptionSetting
Text
TranscriptSourceSetting
transcriptSourceSetting :: TranscriptSourceSetting
localeId :: Text
botVersion :: Text
botId :: Text
encryptionSetting :: Maybe EncryptionSetting
$sel:transcriptSourceSetting:StartBotRecommendation' :: StartBotRecommendation -> TranscriptSourceSetting
$sel:localeId:StartBotRecommendation' :: StartBotRecommendation -> Text
$sel:botVersion:StartBotRecommendation' :: StartBotRecommendation -> Text
$sel:botId:StartBotRecommendation' :: StartBotRecommendation -> Text
$sel:encryptionSetting:StartBotRecommendation' :: StartBotRecommendation -> Maybe EncryptionSetting
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/bots/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
botId,
        ByteString
"/botversions/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
botVersion,
        ByteString
"/botlocales/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
localeId,
        ByteString
"/botrecommendations/"
      ]

instance Data.ToQuery StartBotRecommendation where
  toQuery :: StartBotRecommendation -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | /See:/ 'newStartBotRecommendationResponse' smart constructor.
data StartBotRecommendationResponse = StartBotRecommendationResponse'
  { -- | The unique identifier of the bot containing the bot recommendation.
    StartBotRecommendationResponse -> Maybe Text
botId :: Prelude.Maybe Prelude.Text,
    -- | The identifier of the bot recommendation that you have created.
    StartBotRecommendationResponse -> Maybe Text
botRecommendationId :: Prelude.Maybe Prelude.Text,
    -- | The status of the bot recommendation.
    --
    -- If the status is Failed, then the reasons for the failure are listed in
    -- the failureReasons field.
    StartBotRecommendationResponse -> Maybe BotRecommendationStatus
botRecommendationStatus :: Prelude.Maybe BotRecommendationStatus,
    -- | The version of the bot containing the bot recommendation.
    StartBotRecommendationResponse -> Maybe Text
botVersion :: Prelude.Maybe Prelude.Text,
    -- | A timestamp of the date and time that the bot recommendation was
    -- created.
    StartBotRecommendationResponse -> Maybe POSIX
creationDateTime :: Prelude.Maybe Data.POSIX,
    -- | The object representing the passwords that were used to encrypt the data
    -- related to the bot recommendation results, as well as the KMS key ARN
    -- used to encrypt the associated metadata.
    StartBotRecommendationResponse -> Maybe EncryptionSetting
encryptionSetting :: Prelude.Maybe EncryptionSetting,
    -- | The identifier of the language and locale of the bot recommendation to
    -- start. The string must match one of the supported locales. For more
    -- information, see
    -- <https://docs.aws.amazon.com/lexv2/latest/dg/how-languages.html Supported languages>
    StartBotRecommendationResponse -> Maybe Text
localeId :: Prelude.Maybe Prelude.Text,
    -- | The object representing the Amazon S3 bucket containing the transcript,
    -- as well as the associated metadata.
    StartBotRecommendationResponse -> Maybe TranscriptSourceSetting
transcriptSourceSetting :: Prelude.Maybe TranscriptSourceSetting,
    -- | The response's http status code.
    StartBotRecommendationResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (StartBotRecommendationResponse
-> StartBotRecommendationResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StartBotRecommendationResponse
-> StartBotRecommendationResponse -> Bool
$c/= :: StartBotRecommendationResponse
-> StartBotRecommendationResponse -> Bool
== :: StartBotRecommendationResponse
-> StartBotRecommendationResponse -> Bool
$c== :: StartBotRecommendationResponse
-> StartBotRecommendationResponse -> Bool
Prelude.Eq, Int -> StartBotRecommendationResponse -> ShowS
[StartBotRecommendationResponse] -> ShowS
StartBotRecommendationResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StartBotRecommendationResponse] -> ShowS
$cshowList :: [StartBotRecommendationResponse] -> ShowS
show :: StartBotRecommendationResponse -> String
$cshow :: StartBotRecommendationResponse -> String
showsPrec :: Int -> StartBotRecommendationResponse -> ShowS
$cshowsPrec :: Int -> StartBotRecommendationResponse -> ShowS
Prelude.Show, forall x.
Rep StartBotRecommendationResponse x
-> StartBotRecommendationResponse
forall x.
StartBotRecommendationResponse
-> Rep StartBotRecommendationResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep StartBotRecommendationResponse x
-> StartBotRecommendationResponse
$cfrom :: forall x.
StartBotRecommendationResponse
-> Rep StartBotRecommendationResponse x
Prelude.Generic)

-- |
-- Create a value of 'StartBotRecommendationResponse' 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:
--
-- 'botId', 'startBotRecommendationResponse_botId' - The unique identifier of the bot containing the bot recommendation.
--
-- 'botRecommendationId', 'startBotRecommendationResponse_botRecommendationId' - The identifier of the bot recommendation that you have created.
--
-- 'botRecommendationStatus', 'startBotRecommendationResponse_botRecommendationStatus' - The status of the bot recommendation.
--
-- If the status is Failed, then the reasons for the failure are listed in
-- the failureReasons field.
--
-- 'botVersion', 'startBotRecommendationResponse_botVersion' - The version of the bot containing the bot recommendation.
--
-- 'creationDateTime', 'startBotRecommendationResponse_creationDateTime' - A timestamp of the date and time that the bot recommendation was
-- created.
--
-- 'encryptionSetting', 'startBotRecommendationResponse_encryptionSetting' - The object representing the passwords that were used to encrypt the data
-- related to the bot recommendation results, as well as the KMS key ARN
-- used to encrypt the associated metadata.
--
-- 'localeId', 'startBotRecommendationResponse_localeId' - The identifier of the language and locale of the bot recommendation to
-- start. The string must match one of the supported locales. For more
-- information, see
-- <https://docs.aws.amazon.com/lexv2/latest/dg/how-languages.html Supported languages>
--
-- 'transcriptSourceSetting', 'startBotRecommendationResponse_transcriptSourceSetting' - The object representing the Amazon S3 bucket containing the transcript,
-- as well as the associated metadata.
--
-- 'httpStatus', 'startBotRecommendationResponse_httpStatus' - The response's http status code.
newStartBotRecommendationResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  StartBotRecommendationResponse
newStartBotRecommendationResponse :: Int -> StartBotRecommendationResponse
newStartBotRecommendationResponse Int
pHttpStatus_ =
  StartBotRecommendationResponse'
    { $sel:botId:StartBotRecommendationResponse' :: Maybe Text
botId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:botRecommendationId:StartBotRecommendationResponse' :: Maybe Text
botRecommendationId = forall a. Maybe a
Prelude.Nothing,
      $sel:botRecommendationStatus:StartBotRecommendationResponse' :: Maybe BotRecommendationStatus
botRecommendationStatus = forall a. Maybe a
Prelude.Nothing,
      $sel:botVersion:StartBotRecommendationResponse' :: Maybe Text
botVersion = forall a. Maybe a
Prelude.Nothing,
      $sel:creationDateTime:StartBotRecommendationResponse' :: Maybe POSIX
creationDateTime = forall a. Maybe a
Prelude.Nothing,
      $sel:encryptionSetting:StartBotRecommendationResponse' :: Maybe EncryptionSetting
encryptionSetting = forall a. Maybe a
Prelude.Nothing,
      $sel:localeId:StartBotRecommendationResponse' :: Maybe Text
localeId = forall a. Maybe a
Prelude.Nothing,
      $sel:transcriptSourceSetting:StartBotRecommendationResponse' :: Maybe TranscriptSourceSetting
transcriptSourceSetting = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:StartBotRecommendationResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The unique identifier of the bot containing the bot recommendation.
startBotRecommendationResponse_botId :: Lens.Lens' StartBotRecommendationResponse (Prelude.Maybe Prelude.Text)
startBotRecommendationResponse_botId :: Lens' StartBotRecommendationResponse (Maybe Text)
startBotRecommendationResponse_botId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartBotRecommendationResponse' {Maybe Text
botId :: Maybe Text
$sel:botId:StartBotRecommendationResponse' :: StartBotRecommendationResponse -> Maybe Text
botId} -> Maybe Text
botId) (\s :: StartBotRecommendationResponse
s@StartBotRecommendationResponse' {} Maybe Text
a -> StartBotRecommendationResponse
s {$sel:botId:StartBotRecommendationResponse' :: Maybe Text
botId = Maybe Text
a} :: StartBotRecommendationResponse)

-- | The identifier of the bot recommendation that you have created.
startBotRecommendationResponse_botRecommendationId :: Lens.Lens' StartBotRecommendationResponse (Prelude.Maybe Prelude.Text)
startBotRecommendationResponse_botRecommendationId :: Lens' StartBotRecommendationResponse (Maybe Text)
startBotRecommendationResponse_botRecommendationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartBotRecommendationResponse' {Maybe Text
botRecommendationId :: Maybe Text
$sel:botRecommendationId:StartBotRecommendationResponse' :: StartBotRecommendationResponse -> Maybe Text
botRecommendationId} -> Maybe Text
botRecommendationId) (\s :: StartBotRecommendationResponse
s@StartBotRecommendationResponse' {} Maybe Text
a -> StartBotRecommendationResponse
s {$sel:botRecommendationId:StartBotRecommendationResponse' :: Maybe Text
botRecommendationId = Maybe Text
a} :: StartBotRecommendationResponse)

-- | The status of the bot recommendation.
--
-- If the status is Failed, then the reasons for the failure are listed in
-- the failureReasons field.
startBotRecommendationResponse_botRecommendationStatus :: Lens.Lens' StartBotRecommendationResponse (Prelude.Maybe BotRecommendationStatus)
startBotRecommendationResponse_botRecommendationStatus :: Lens'
  StartBotRecommendationResponse (Maybe BotRecommendationStatus)
startBotRecommendationResponse_botRecommendationStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartBotRecommendationResponse' {Maybe BotRecommendationStatus
botRecommendationStatus :: Maybe BotRecommendationStatus
$sel:botRecommendationStatus:StartBotRecommendationResponse' :: StartBotRecommendationResponse -> Maybe BotRecommendationStatus
botRecommendationStatus} -> Maybe BotRecommendationStatus
botRecommendationStatus) (\s :: StartBotRecommendationResponse
s@StartBotRecommendationResponse' {} Maybe BotRecommendationStatus
a -> StartBotRecommendationResponse
s {$sel:botRecommendationStatus:StartBotRecommendationResponse' :: Maybe BotRecommendationStatus
botRecommendationStatus = Maybe BotRecommendationStatus
a} :: StartBotRecommendationResponse)

-- | The version of the bot containing the bot recommendation.
startBotRecommendationResponse_botVersion :: Lens.Lens' StartBotRecommendationResponse (Prelude.Maybe Prelude.Text)
startBotRecommendationResponse_botVersion :: Lens' StartBotRecommendationResponse (Maybe Text)
startBotRecommendationResponse_botVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartBotRecommendationResponse' {Maybe Text
botVersion :: Maybe Text
$sel:botVersion:StartBotRecommendationResponse' :: StartBotRecommendationResponse -> Maybe Text
botVersion} -> Maybe Text
botVersion) (\s :: StartBotRecommendationResponse
s@StartBotRecommendationResponse' {} Maybe Text
a -> StartBotRecommendationResponse
s {$sel:botVersion:StartBotRecommendationResponse' :: Maybe Text
botVersion = Maybe Text
a} :: StartBotRecommendationResponse)

-- | A timestamp of the date and time that the bot recommendation was
-- created.
startBotRecommendationResponse_creationDateTime :: Lens.Lens' StartBotRecommendationResponse (Prelude.Maybe Prelude.UTCTime)
startBotRecommendationResponse_creationDateTime :: Lens' StartBotRecommendationResponse (Maybe UTCTime)
startBotRecommendationResponse_creationDateTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartBotRecommendationResponse' {Maybe POSIX
creationDateTime :: Maybe POSIX
$sel:creationDateTime:StartBotRecommendationResponse' :: StartBotRecommendationResponse -> Maybe POSIX
creationDateTime} -> Maybe POSIX
creationDateTime) (\s :: StartBotRecommendationResponse
s@StartBotRecommendationResponse' {} Maybe POSIX
a -> StartBotRecommendationResponse
s {$sel:creationDateTime:StartBotRecommendationResponse' :: Maybe POSIX
creationDateTime = Maybe POSIX
a} :: StartBotRecommendationResponse) 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 object representing the passwords that were used to encrypt the data
-- related to the bot recommendation results, as well as the KMS key ARN
-- used to encrypt the associated metadata.
startBotRecommendationResponse_encryptionSetting :: Lens.Lens' StartBotRecommendationResponse (Prelude.Maybe EncryptionSetting)
startBotRecommendationResponse_encryptionSetting :: Lens' StartBotRecommendationResponse (Maybe EncryptionSetting)
startBotRecommendationResponse_encryptionSetting = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartBotRecommendationResponse' {Maybe EncryptionSetting
encryptionSetting :: Maybe EncryptionSetting
$sel:encryptionSetting:StartBotRecommendationResponse' :: StartBotRecommendationResponse -> Maybe EncryptionSetting
encryptionSetting} -> Maybe EncryptionSetting
encryptionSetting) (\s :: StartBotRecommendationResponse
s@StartBotRecommendationResponse' {} Maybe EncryptionSetting
a -> StartBotRecommendationResponse
s {$sel:encryptionSetting:StartBotRecommendationResponse' :: Maybe EncryptionSetting
encryptionSetting = Maybe EncryptionSetting
a} :: StartBotRecommendationResponse)

-- | The identifier of the language and locale of the bot recommendation to
-- start. The string must match one of the supported locales. For more
-- information, see
-- <https://docs.aws.amazon.com/lexv2/latest/dg/how-languages.html Supported languages>
startBotRecommendationResponse_localeId :: Lens.Lens' StartBotRecommendationResponse (Prelude.Maybe Prelude.Text)
startBotRecommendationResponse_localeId :: Lens' StartBotRecommendationResponse (Maybe Text)
startBotRecommendationResponse_localeId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartBotRecommendationResponse' {Maybe Text
localeId :: Maybe Text
$sel:localeId:StartBotRecommendationResponse' :: StartBotRecommendationResponse -> Maybe Text
localeId} -> Maybe Text
localeId) (\s :: StartBotRecommendationResponse
s@StartBotRecommendationResponse' {} Maybe Text
a -> StartBotRecommendationResponse
s {$sel:localeId:StartBotRecommendationResponse' :: Maybe Text
localeId = Maybe Text
a} :: StartBotRecommendationResponse)

-- | The object representing the Amazon S3 bucket containing the transcript,
-- as well as the associated metadata.
startBotRecommendationResponse_transcriptSourceSetting :: Lens.Lens' StartBotRecommendationResponse (Prelude.Maybe TranscriptSourceSetting)
startBotRecommendationResponse_transcriptSourceSetting :: Lens'
  StartBotRecommendationResponse (Maybe TranscriptSourceSetting)
startBotRecommendationResponse_transcriptSourceSetting = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartBotRecommendationResponse' {Maybe TranscriptSourceSetting
transcriptSourceSetting :: Maybe TranscriptSourceSetting
$sel:transcriptSourceSetting:StartBotRecommendationResponse' :: StartBotRecommendationResponse -> Maybe TranscriptSourceSetting
transcriptSourceSetting} -> Maybe TranscriptSourceSetting
transcriptSourceSetting) (\s :: StartBotRecommendationResponse
s@StartBotRecommendationResponse' {} Maybe TranscriptSourceSetting
a -> StartBotRecommendationResponse
s {$sel:transcriptSourceSetting:StartBotRecommendationResponse' :: Maybe TranscriptSourceSetting
transcriptSourceSetting = Maybe TranscriptSourceSetting
a} :: StartBotRecommendationResponse)

-- | The response's http status code.
startBotRecommendationResponse_httpStatus :: Lens.Lens' StartBotRecommendationResponse Prelude.Int
startBotRecommendationResponse_httpStatus :: Lens' StartBotRecommendationResponse Int
startBotRecommendationResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartBotRecommendationResponse' {Int
httpStatus :: Int
$sel:httpStatus:StartBotRecommendationResponse' :: StartBotRecommendationResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: StartBotRecommendationResponse
s@StartBotRecommendationResponse' {} Int
a -> StartBotRecommendationResponse
s {$sel:httpStatus:StartBotRecommendationResponse' :: Int
httpStatus = Int
a} :: StartBotRecommendationResponse)

instance
  Prelude.NFData
    StartBotRecommendationResponse
  where
  rnf :: StartBotRecommendationResponse -> ()
rnf StartBotRecommendationResponse' {Int
Maybe Text
Maybe POSIX
Maybe BotRecommendationStatus
Maybe EncryptionSetting
Maybe TranscriptSourceSetting
httpStatus :: Int
transcriptSourceSetting :: Maybe TranscriptSourceSetting
localeId :: Maybe Text
encryptionSetting :: Maybe EncryptionSetting
creationDateTime :: Maybe POSIX
botVersion :: Maybe Text
botRecommendationStatus :: Maybe BotRecommendationStatus
botRecommendationId :: Maybe Text
botId :: Maybe Text
$sel:httpStatus:StartBotRecommendationResponse' :: StartBotRecommendationResponse -> Int
$sel:transcriptSourceSetting:StartBotRecommendationResponse' :: StartBotRecommendationResponse -> Maybe TranscriptSourceSetting
$sel:localeId:StartBotRecommendationResponse' :: StartBotRecommendationResponse -> Maybe Text
$sel:encryptionSetting:StartBotRecommendationResponse' :: StartBotRecommendationResponse -> Maybe EncryptionSetting
$sel:creationDateTime:StartBotRecommendationResponse' :: StartBotRecommendationResponse -> Maybe POSIX
$sel:botVersion:StartBotRecommendationResponse' :: StartBotRecommendationResponse -> Maybe Text
$sel:botRecommendationStatus:StartBotRecommendationResponse' :: StartBotRecommendationResponse -> Maybe BotRecommendationStatus
$sel:botRecommendationId:StartBotRecommendationResponse' :: StartBotRecommendationResponse -> Maybe Text
$sel:botId:StartBotRecommendationResponse' :: StartBotRecommendationResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
botId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
botRecommendationId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe BotRecommendationStatus
botRecommendationStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
botVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
creationDateTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe EncryptionSetting
encryptionSetting
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
localeId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe TranscriptSourceSetting
transcriptSourceSetting
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus