{-# 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.DeleteBotLocale
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Removes a locale from a bot.
--
-- When you delete a locale, all intents, slots, and slot types defined for
-- the locale are also deleted.
module Amazonka.LexV2Models.DeleteBotLocale
  ( -- * Creating a Request
    DeleteBotLocale (..),
    newDeleteBotLocale,

    -- * Request Lenses
    deleteBotLocale_botId,
    deleteBotLocale_botVersion,
    deleteBotLocale_localeId,

    -- * Destructuring the Response
    DeleteBotLocaleResponse (..),
    newDeleteBotLocaleResponse,

    -- * Response Lenses
    deleteBotLocaleResponse_botId,
    deleteBotLocaleResponse_botLocaleStatus,
    deleteBotLocaleResponse_botVersion,
    deleteBotLocaleResponse_localeId,
    deleteBotLocaleResponse_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:/ 'newDeleteBotLocale' smart constructor.
data DeleteBotLocale = DeleteBotLocale'
  { -- | The unique identifier of the bot that contains the locale.
    DeleteBotLocale -> Text
botId :: Prelude.Text,
    -- | The version of the bot that contains the locale.
    DeleteBotLocale -> Text
botVersion :: Prelude.Text,
    -- | The identifier of the language and locale that will be deleted. 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>.
    DeleteBotLocale -> Text
localeId :: Prelude.Text
  }
  deriving (DeleteBotLocale -> DeleteBotLocale -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteBotLocale -> DeleteBotLocale -> Bool
$c/= :: DeleteBotLocale -> DeleteBotLocale -> Bool
== :: DeleteBotLocale -> DeleteBotLocale -> Bool
$c== :: DeleteBotLocale -> DeleteBotLocale -> Bool
Prelude.Eq, ReadPrec [DeleteBotLocale]
ReadPrec DeleteBotLocale
Int -> ReadS DeleteBotLocale
ReadS [DeleteBotLocale]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteBotLocale]
$creadListPrec :: ReadPrec [DeleteBotLocale]
readPrec :: ReadPrec DeleteBotLocale
$creadPrec :: ReadPrec DeleteBotLocale
readList :: ReadS [DeleteBotLocale]
$creadList :: ReadS [DeleteBotLocale]
readsPrec :: Int -> ReadS DeleteBotLocale
$creadsPrec :: Int -> ReadS DeleteBotLocale
Prelude.Read, Int -> DeleteBotLocale -> ShowS
[DeleteBotLocale] -> ShowS
DeleteBotLocale -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteBotLocale] -> ShowS
$cshowList :: [DeleteBotLocale] -> ShowS
show :: DeleteBotLocale -> String
$cshow :: DeleteBotLocale -> String
showsPrec :: Int -> DeleteBotLocale -> ShowS
$cshowsPrec :: Int -> DeleteBotLocale -> ShowS
Prelude.Show, forall x. Rep DeleteBotLocale x -> DeleteBotLocale
forall x. DeleteBotLocale -> Rep DeleteBotLocale x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteBotLocale x -> DeleteBotLocale
$cfrom :: forall x. DeleteBotLocale -> Rep DeleteBotLocale x
Prelude.Generic)

-- |
-- Create a value of 'DeleteBotLocale' 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', 'deleteBotLocale_botId' - The unique identifier of the bot that contains the locale.
--
-- 'botVersion', 'deleteBotLocale_botVersion' - The version of the bot that contains the locale.
--
-- 'localeId', 'deleteBotLocale_localeId' - The identifier of the language and locale that will be deleted. 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>.
newDeleteBotLocale ::
  -- | 'botId'
  Prelude.Text ->
  -- | 'botVersion'
  Prelude.Text ->
  -- | 'localeId'
  Prelude.Text ->
  DeleteBotLocale
newDeleteBotLocale :: Text -> Text -> Text -> DeleteBotLocale
newDeleteBotLocale Text
pBotId_ Text
pBotVersion_ Text
pLocaleId_ =
  DeleteBotLocale'
    { $sel:botId:DeleteBotLocale' :: Text
botId = Text
pBotId_,
      $sel:botVersion:DeleteBotLocale' :: Text
botVersion = Text
pBotVersion_,
      $sel:localeId:DeleteBotLocale' :: Text
localeId = Text
pLocaleId_
    }

-- | The unique identifier of the bot that contains the locale.
deleteBotLocale_botId :: Lens.Lens' DeleteBotLocale Prelude.Text
deleteBotLocale_botId :: Lens' DeleteBotLocale Text
deleteBotLocale_botId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteBotLocale' {Text
botId :: Text
$sel:botId:DeleteBotLocale' :: DeleteBotLocale -> Text
botId} -> Text
botId) (\s :: DeleteBotLocale
s@DeleteBotLocale' {} Text
a -> DeleteBotLocale
s {$sel:botId:DeleteBotLocale' :: Text
botId = Text
a} :: DeleteBotLocale)

-- | The version of the bot that contains the locale.
deleteBotLocale_botVersion :: Lens.Lens' DeleteBotLocale Prelude.Text
deleteBotLocale_botVersion :: Lens' DeleteBotLocale Text
deleteBotLocale_botVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteBotLocale' {Text
botVersion :: Text
$sel:botVersion:DeleteBotLocale' :: DeleteBotLocale -> Text
botVersion} -> Text
botVersion) (\s :: DeleteBotLocale
s@DeleteBotLocale' {} Text
a -> DeleteBotLocale
s {$sel:botVersion:DeleteBotLocale' :: Text
botVersion = Text
a} :: DeleteBotLocale)

-- | The identifier of the language and locale that will be deleted. 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>.
deleteBotLocale_localeId :: Lens.Lens' DeleteBotLocale Prelude.Text
deleteBotLocale_localeId :: Lens' DeleteBotLocale Text
deleteBotLocale_localeId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteBotLocale' {Text
localeId :: Text
$sel:localeId:DeleteBotLocale' :: DeleteBotLocale -> Text
localeId} -> Text
localeId) (\s :: DeleteBotLocale
s@DeleteBotLocale' {} Text
a -> DeleteBotLocale
s {$sel:localeId:DeleteBotLocale' :: Text
localeId = Text
a} :: DeleteBotLocale)

instance Core.AWSRequest DeleteBotLocale where
  type
    AWSResponse DeleteBotLocale =
      DeleteBotLocaleResponse
  request :: (Service -> Service) -> DeleteBotLocale -> Request DeleteBotLocale
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.delete (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DeleteBotLocale
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DeleteBotLocale)))
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 BotLocaleStatus
-> Maybe Text
-> Maybe Text
-> Int
-> DeleteBotLocaleResponse
DeleteBotLocaleResponse'
            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
"botLocaleStatus")
            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
"localeId")
            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 DeleteBotLocale where
  hashWithSalt :: Int -> DeleteBotLocale -> Int
hashWithSalt Int
_salt DeleteBotLocale' {Text
localeId :: Text
botVersion :: Text
botId :: Text
$sel:localeId:DeleteBotLocale' :: DeleteBotLocale -> Text
$sel:botVersion:DeleteBotLocale' :: DeleteBotLocale -> Text
$sel:botId:DeleteBotLocale' :: DeleteBotLocale -> Text
..} =
    Int
_salt
      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

instance Prelude.NFData DeleteBotLocale where
  rnf :: DeleteBotLocale -> ()
rnf DeleteBotLocale' {Text
localeId :: Text
botVersion :: Text
botId :: Text
$sel:localeId:DeleteBotLocale' :: DeleteBotLocale -> Text
$sel:botVersion:DeleteBotLocale' :: DeleteBotLocale -> Text
$sel:botId:DeleteBotLocale' :: DeleteBotLocale -> Text
..} =
    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

instance Data.ToHeaders DeleteBotLocale where
  toHeaders :: DeleteBotLocale -> 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.ToPath DeleteBotLocale where
  toPath :: DeleteBotLocale -> ByteString
toPath DeleteBotLocale' {Text
localeId :: Text
botVersion :: Text
botId :: Text
$sel:localeId:DeleteBotLocale' :: DeleteBotLocale -> Text
$sel:botVersion:DeleteBotLocale' :: DeleteBotLocale -> Text
$sel:botId:DeleteBotLocale' :: DeleteBotLocale -> Text
..} =
    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
"/"
      ]

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

-- | /See:/ 'newDeleteBotLocaleResponse' smart constructor.
data DeleteBotLocaleResponse = DeleteBotLocaleResponse'
  { -- | The identifier of the bot that contained the deleted locale.
    DeleteBotLocaleResponse -> Maybe Text
botId :: Prelude.Maybe Prelude.Text,
    -- | The status of deleting the bot locale. The locale first enters the
    -- @Deleting@ status. Once the locale is deleted it no longer appears in
    -- the list of locales for the bot.
    DeleteBotLocaleResponse -> Maybe BotLocaleStatus
botLocaleStatus :: Prelude.Maybe BotLocaleStatus,
    -- | The version of the bot that contained the deleted locale.
    DeleteBotLocaleResponse -> Maybe Text
botVersion :: Prelude.Maybe Prelude.Text,
    -- | The language and locale of the deleted locale.
    DeleteBotLocaleResponse -> Maybe Text
localeId :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    DeleteBotLocaleResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DeleteBotLocaleResponse -> DeleteBotLocaleResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteBotLocaleResponse -> DeleteBotLocaleResponse -> Bool
$c/= :: DeleteBotLocaleResponse -> DeleteBotLocaleResponse -> Bool
== :: DeleteBotLocaleResponse -> DeleteBotLocaleResponse -> Bool
$c== :: DeleteBotLocaleResponse -> DeleteBotLocaleResponse -> Bool
Prelude.Eq, ReadPrec [DeleteBotLocaleResponse]
ReadPrec DeleteBotLocaleResponse
Int -> ReadS DeleteBotLocaleResponse
ReadS [DeleteBotLocaleResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteBotLocaleResponse]
$creadListPrec :: ReadPrec [DeleteBotLocaleResponse]
readPrec :: ReadPrec DeleteBotLocaleResponse
$creadPrec :: ReadPrec DeleteBotLocaleResponse
readList :: ReadS [DeleteBotLocaleResponse]
$creadList :: ReadS [DeleteBotLocaleResponse]
readsPrec :: Int -> ReadS DeleteBotLocaleResponse
$creadsPrec :: Int -> ReadS DeleteBotLocaleResponse
Prelude.Read, Int -> DeleteBotLocaleResponse -> ShowS
[DeleteBotLocaleResponse] -> ShowS
DeleteBotLocaleResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteBotLocaleResponse] -> ShowS
$cshowList :: [DeleteBotLocaleResponse] -> ShowS
show :: DeleteBotLocaleResponse -> String
$cshow :: DeleteBotLocaleResponse -> String
showsPrec :: Int -> DeleteBotLocaleResponse -> ShowS
$cshowsPrec :: Int -> DeleteBotLocaleResponse -> ShowS
Prelude.Show, forall x. Rep DeleteBotLocaleResponse x -> DeleteBotLocaleResponse
forall x. DeleteBotLocaleResponse -> Rep DeleteBotLocaleResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteBotLocaleResponse x -> DeleteBotLocaleResponse
$cfrom :: forall x. DeleteBotLocaleResponse -> Rep DeleteBotLocaleResponse x
Prelude.Generic)

-- |
-- Create a value of 'DeleteBotLocaleResponse' 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', 'deleteBotLocaleResponse_botId' - The identifier of the bot that contained the deleted locale.
--
-- 'botLocaleStatus', 'deleteBotLocaleResponse_botLocaleStatus' - The status of deleting the bot locale. The locale first enters the
-- @Deleting@ status. Once the locale is deleted it no longer appears in
-- the list of locales for the bot.
--
-- 'botVersion', 'deleteBotLocaleResponse_botVersion' - The version of the bot that contained the deleted locale.
--
-- 'localeId', 'deleteBotLocaleResponse_localeId' - The language and locale of the deleted locale.
--
-- 'httpStatus', 'deleteBotLocaleResponse_httpStatus' - The response's http status code.
newDeleteBotLocaleResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DeleteBotLocaleResponse
newDeleteBotLocaleResponse :: Int -> DeleteBotLocaleResponse
newDeleteBotLocaleResponse Int
pHttpStatus_ =
  DeleteBotLocaleResponse'
    { $sel:botId:DeleteBotLocaleResponse' :: Maybe Text
botId = forall a. Maybe a
Prelude.Nothing,
      $sel:botLocaleStatus:DeleteBotLocaleResponse' :: Maybe BotLocaleStatus
botLocaleStatus = forall a. Maybe a
Prelude.Nothing,
      $sel:botVersion:DeleteBotLocaleResponse' :: Maybe Text
botVersion = forall a. Maybe a
Prelude.Nothing,
      $sel:localeId:DeleteBotLocaleResponse' :: Maybe Text
localeId = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DeleteBotLocaleResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The identifier of the bot that contained the deleted locale.
deleteBotLocaleResponse_botId :: Lens.Lens' DeleteBotLocaleResponse (Prelude.Maybe Prelude.Text)
deleteBotLocaleResponse_botId :: Lens' DeleteBotLocaleResponse (Maybe Text)
deleteBotLocaleResponse_botId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteBotLocaleResponse' {Maybe Text
botId :: Maybe Text
$sel:botId:DeleteBotLocaleResponse' :: DeleteBotLocaleResponse -> Maybe Text
botId} -> Maybe Text
botId) (\s :: DeleteBotLocaleResponse
s@DeleteBotLocaleResponse' {} Maybe Text
a -> DeleteBotLocaleResponse
s {$sel:botId:DeleteBotLocaleResponse' :: Maybe Text
botId = Maybe Text
a} :: DeleteBotLocaleResponse)

-- | The status of deleting the bot locale. The locale first enters the
-- @Deleting@ status. Once the locale is deleted it no longer appears in
-- the list of locales for the bot.
deleteBotLocaleResponse_botLocaleStatus :: Lens.Lens' DeleteBotLocaleResponse (Prelude.Maybe BotLocaleStatus)
deleteBotLocaleResponse_botLocaleStatus :: Lens' DeleteBotLocaleResponse (Maybe BotLocaleStatus)
deleteBotLocaleResponse_botLocaleStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteBotLocaleResponse' {Maybe BotLocaleStatus
botLocaleStatus :: Maybe BotLocaleStatus
$sel:botLocaleStatus:DeleteBotLocaleResponse' :: DeleteBotLocaleResponse -> Maybe BotLocaleStatus
botLocaleStatus} -> Maybe BotLocaleStatus
botLocaleStatus) (\s :: DeleteBotLocaleResponse
s@DeleteBotLocaleResponse' {} Maybe BotLocaleStatus
a -> DeleteBotLocaleResponse
s {$sel:botLocaleStatus:DeleteBotLocaleResponse' :: Maybe BotLocaleStatus
botLocaleStatus = Maybe BotLocaleStatus
a} :: DeleteBotLocaleResponse)

-- | The version of the bot that contained the deleted locale.
deleteBotLocaleResponse_botVersion :: Lens.Lens' DeleteBotLocaleResponse (Prelude.Maybe Prelude.Text)
deleteBotLocaleResponse_botVersion :: Lens' DeleteBotLocaleResponse (Maybe Text)
deleteBotLocaleResponse_botVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteBotLocaleResponse' {Maybe Text
botVersion :: Maybe Text
$sel:botVersion:DeleteBotLocaleResponse' :: DeleteBotLocaleResponse -> Maybe Text
botVersion} -> Maybe Text
botVersion) (\s :: DeleteBotLocaleResponse
s@DeleteBotLocaleResponse' {} Maybe Text
a -> DeleteBotLocaleResponse
s {$sel:botVersion:DeleteBotLocaleResponse' :: Maybe Text
botVersion = Maybe Text
a} :: DeleteBotLocaleResponse)

-- | The language and locale of the deleted locale.
deleteBotLocaleResponse_localeId :: Lens.Lens' DeleteBotLocaleResponse (Prelude.Maybe Prelude.Text)
deleteBotLocaleResponse_localeId :: Lens' DeleteBotLocaleResponse (Maybe Text)
deleteBotLocaleResponse_localeId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteBotLocaleResponse' {Maybe Text
localeId :: Maybe Text
$sel:localeId:DeleteBotLocaleResponse' :: DeleteBotLocaleResponse -> Maybe Text
localeId} -> Maybe Text
localeId) (\s :: DeleteBotLocaleResponse
s@DeleteBotLocaleResponse' {} Maybe Text
a -> DeleteBotLocaleResponse
s {$sel:localeId:DeleteBotLocaleResponse' :: Maybe Text
localeId = Maybe Text
a} :: DeleteBotLocaleResponse)

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

instance Prelude.NFData DeleteBotLocaleResponse where
  rnf :: DeleteBotLocaleResponse -> ()
rnf DeleteBotLocaleResponse' {Int
Maybe Text
Maybe BotLocaleStatus
httpStatus :: Int
localeId :: Maybe Text
botVersion :: Maybe Text
botLocaleStatus :: Maybe BotLocaleStatus
botId :: Maybe Text
$sel:httpStatus:DeleteBotLocaleResponse' :: DeleteBotLocaleResponse -> Int
$sel:localeId:DeleteBotLocaleResponse' :: DeleteBotLocaleResponse -> Maybe Text
$sel:botVersion:DeleteBotLocaleResponse' :: DeleteBotLocaleResponse -> Maybe Text
$sel:botLocaleStatus:DeleteBotLocaleResponse' :: DeleteBotLocaleResponse -> Maybe BotLocaleStatus
$sel:botId:DeleteBotLocaleResponse' :: DeleteBotLocaleResponse -> 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 BotLocaleStatus
botLocaleStatus
      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 Text
localeId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus