{-# 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.DescribeSlot
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Gets metadata information about a slot.
module Amazonka.LexV2Models.DescribeSlot
  ( -- * Creating a Request
    DescribeSlot (..),
    newDescribeSlot,

    -- * Request Lenses
    describeSlot_slotId,
    describeSlot_botId,
    describeSlot_botVersion,
    describeSlot_localeId,
    describeSlot_intentId,

    -- * Destructuring the Response
    DescribeSlotResponse (..),
    newDescribeSlotResponse,

    -- * Response Lenses
    describeSlotResponse_botId,
    describeSlotResponse_botVersion,
    describeSlotResponse_creationDateTime,
    describeSlotResponse_description,
    describeSlotResponse_intentId,
    describeSlotResponse_lastUpdatedDateTime,
    describeSlotResponse_localeId,
    describeSlotResponse_multipleValuesSetting,
    describeSlotResponse_obfuscationSetting,
    describeSlotResponse_slotId,
    describeSlotResponse_slotName,
    describeSlotResponse_slotTypeId,
    describeSlotResponse_subSlotSetting,
    describeSlotResponse_valueElicitationSetting,
    describeSlotResponse_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:/ 'newDescribeSlot' smart constructor.
data DescribeSlot = DescribeSlot'
  { -- | The unique identifier for the slot.
    DescribeSlot -> Text
slotId :: Prelude.Text,
    -- | The identifier of the bot associated with the slot.
    DescribeSlot -> Text
botId :: Prelude.Text,
    -- | The version of the bot associated with the slot.
    DescribeSlot -> Text
botVersion :: Prelude.Text,
    -- | The identifier of the language and locale of the slot to describe. 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>.
    DescribeSlot -> Text
localeId :: Prelude.Text,
    -- | The identifier of the intent that contains the slot.
    DescribeSlot -> Text
intentId :: Prelude.Text
  }
  deriving (DescribeSlot -> DescribeSlot -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeSlot -> DescribeSlot -> Bool
$c/= :: DescribeSlot -> DescribeSlot -> Bool
== :: DescribeSlot -> DescribeSlot -> Bool
$c== :: DescribeSlot -> DescribeSlot -> Bool
Prelude.Eq, ReadPrec [DescribeSlot]
ReadPrec DescribeSlot
Int -> ReadS DescribeSlot
ReadS [DescribeSlot]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeSlot]
$creadListPrec :: ReadPrec [DescribeSlot]
readPrec :: ReadPrec DescribeSlot
$creadPrec :: ReadPrec DescribeSlot
readList :: ReadS [DescribeSlot]
$creadList :: ReadS [DescribeSlot]
readsPrec :: Int -> ReadS DescribeSlot
$creadsPrec :: Int -> ReadS DescribeSlot
Prelude.Read, Int -> DescribeSlot -> ShowS
[DescribeSlot] -> ShowS
DescribeSlot -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeSlot] -> ShowS
$cshowList :: [DescribeSlot] -> ShowS
show :: DescribeSlot -> String
$cshow :: DescribeSlot -> String
showsPrec :: Int -> DescribeSlot -> ShowS
$cshowsPrec :: Int -> DescribeSlot -> ShowS
Prelude.Show, forall x. Rep DescribeSlot x -> DescribeSlot
forall x. DescribeSlot -> Rep DescribeSlot x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeSlot x -> DescribeSlot
$cfrom :: forall x. DescribeSlot -> Rep DescribeSlot x
Prelude.Generic)

-- |
-- Create a value of 'DescribeSlot' 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:
--
-- 'slotId', 'describeSlot_slotId' - The unique identifier for the slot.
--
-- 'botId', 'describeSlot_botId' - The identifier of the bot associated with the slot.
--
-- 'botVersion', 'describeSlot_botVersion' - The version of the bot associated with the slot.
--
-- 'localeId', 'describeSlot_localeId' - The identifier of the language and locale of the slot to describe. 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>.
--
-- 'intentId', 'describeSlot_intentId' - The identifier of the intent that contains the slot.
newDescribeSlot ::
  -- | 'slotId'
  Prelude.Text ->
  -- | 'botId'
  Prelude.Text ->
  -- | 'botVersion'
  Prelude.Text ->
  -- | 'localeId'
  Prelude.Text ->
  -- | 'intentId'
  Prelude.Text ->
  DescribeSlot
newDescribeSlot :: Text -> Text -> Text -> Text -> Text -> DescribeSlot
newDescribeSlot
  Text
pSlotId_
  Text
pBotId_
  Text
pBotVersion_
  Text
pLocaleId_
  Text
pIntentId_ =
    DescribeSlot'
      { $sel:slotId:DescribeSlot' :: Text
slotId = Text
pSlotId_,
        $sel:botId:DescribeSlot' :: Text
botId = Text
pBotId_,
        $sel:botVersion:DescribeSlot' :: Text
botVersion = Text
pBotVersion_,
        $sel:localeId:DescribeSlot' :: Text
localeId = Text
pLocaleId_,
        $sel:intentId:DescribeSlot' :: Text
intentId = Text
pIntentId_
      }

-- | The unique identifier for the slot.
describeSlot_slotId :: Lens.Lens' DescribeSlot Prelude.Text
describeSlot_slotId :: Lens' DescribeSlot Text
describeSlot_slotId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSlot' {Text
slotId :: Text
$sel:slotId:DescribeSlot' :: DescribeSlot -> Text
slotId} -> Text
slotId) (\s :: DescribeSlot
s@DescribeSlot' {} Text
a -> DescribeSlot
s {$sel:slotId:DescribeSlot' :: Text
slotId = Text
a} :: DescribeSlot)

-- | The identifier of the bot associated with the slot.
describeSlot_botId :: Lens.Lens' DescribeSlot Prelude.Text
describeSlot_botId :: Lens' DescribeSlot Text
describeSlot_botId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSlot' {Text
botId :: Text
$sel:botId:DescribeSlot' :: DescribeSlot -> Text
botId} -> Text
botId) (\s :: DescribeSlot
s@DescribeSlot' {} Text
a -> DescribeSlot
s {$sel:botId:DescribeSlot' :: Text
botId = Text
a} :: DescribeSlot)

-- | The version of the bot associated with the slot.
describeSlot_botVersion :: Lens.Lens' DescribeSlot Prelude.Text
describeSlot_botVersion :: Lens' DescribeSlot Text
describeSlot_botVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSlot' {Text
botVersion :: Text
$sel:botVersion:DescribeSlot' :: DescribeSlot -> Text
botVersion} -> Text
botVersion) (\s :: DescribeSlot
s@DescribeSlot' {} Text
a -> DescribeSlot
s {$sel:botVersion:DescribeSlot' :: Text
botVersion = Text
a} :: DescribeSlot)

-- | The identifier of the language and locale of the slot to describe. 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>.
describeSlot_localeId :: Lens.Lens' DescribeSlot Prelude.Text
describeSlot_localeId :: Lens' DescribeSlot Text
describeSlot_localeId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSlot' {Text
localeId :: Text
$sel:localeId:DescribeSlot' :: DescribeSlot -> Text
localeId} -> Text
localeId) (\s :: DescribeSlot
s@DescribeSlot' {} Text
a -> DescribeSlot
s {$sel:localeId:DescribeSlot' :: Text
localeId = Text
a} :: DescribeSlot)

-- | The identifier of the intent that contains the slot.
describeSlot_intentId :: Lens.Lens' DescribeSlot Prelude.Text
describeSlot_intentId :: Lens' DescribeSlot Text
describeSlot_intentId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSlot' {Text
intentId :: Text
$sel:intentId:DescribeSlot' :: DescribeSlot -> Text
intentId} -> Text
intentId) (\s :: DescribeSlot
s@DescribeSlot' {} Text
a -> DescribeSlot
s {$sel:intentId:DescribeSlot' :: Text
intentId = Text
a} :: DescribeSlot)

instance Core.AWSRequest DescribeSlot where
  type AWSResponse DescribeSlot = DescribeSlotResponse
  request :: (Service -> Service) -> DescribeSlot -> Request DescribeSlot
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.get (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DescribeSlot
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DescribeSlot)))
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 POSIX
-> Maybe Text
-> Maybe Text
-> Maybe POSIX
-> Maybe Text
-> Maybe MultipleValuesSetting
-> Maybe ObfuscationSetting
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe SubSlotSetting
-> Maybe SlotValueElicitationSetting
-> Int
-> DescribeSlotResponse
DescribeSlotResponse'
            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
"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
"description")
            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
"intentId")
            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
"lastUpdatedDateTime")
            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
"multipleValuesSetting")
            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
"obfuscationSetting")
            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
"slotId")
            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
"slotName")
            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
"slotTypeId")
            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
"subSlotSetting")
            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
"valueElicitationSetting")
            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 DescribeSlot where
  hashWithSalt :: Int -> DescribeSlot -> Int
hashWithSalt Int
_salt DescribeSlot' {Text
intentId :: Text
localeId :: Text
botVersion :: Text
botId :: Text
slotId :: Text
$sel:intentId:DescribeSlot' :: DescribeSlot -> Text
$sel:localeId:DescribeSlot' :: DescribeSlot -> Text
$sel:botVersion:DescribeSlot' :: DescribeSlot -> Text
$sel:botId:DescribeSlot' :: DescribeSlot -> Text
$sel:slotId:DescribeSlot' :: DescribeSlot -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
slotId
      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` Text
intentId

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

instance Data.ToHeaders DescribeSlot where
  toHeaders :: DescribeSlot -> 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 DescribeSlot where
  toPath :: DescribeSlot -> ByteString
toPath DescribeSlot' {Text
intentId :: Text
localeId :: Text
botVersion :: Text
botId :: Text
slotId :: Text
$sel:intentId:DescribeSlot' :: DescribeSlot -> Text
$sel:localeId:DescribeSlot' :: DescribeSlot -> Text
$sel:botVersion:DescribeSlot' :: DescribeSlot -> Text
$sel:botId:DescribeSlot' :: DescribeSlot -> Text
$sel:slotId:DescribeSlot' :: DescribeSlot -> 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
"/intents/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
intentId,
        ByteString
"/slots/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
slotId,
        ByteString
"/"
      ]

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

-- | /See:/ 'newDescribeSlotResponse' smart constructor.
data DescribeSlotResponse = DescribeSlotResponse'
  { -- | The identifier of the bot associated with the slot.
    DescribeSlotResponse -> Maybe Text
botId :: Prelude.Maybe Prelude.Text,
    -- | The version of the bot associated with the slot.
    DescribeSlotResponse -> Maybe Text
botVersion :: Prelude.Maybe Prelude.Text,
    -- | A timestamp of the date and time that the slot was created.
    DescribeSlotResponse -> Maybe POSIX
creationDateTime :: Prelude.Maybe Data.POSIX,
    -- | The description specified for the slot.
    DescribeSlotResponse -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | The identifier of the intent associated with the slot.
    DescribeSlotResponse -> Maybe Text
intentId :: Prelude.Maybe Prelude.Text,
    -- | A timestamp of the date and time that the slot was last updated.
    DescribeSlotResponse -> Maybe POSIX
lastUpdatedDateTime :: Prelude.Maybe Data.POSIX,
    -- | The language and locale specified for the slot.
    DescribeSlotResponse -> Maybe Text
localeId :: Prelude.Maybe Prelude.Text,
    -- | Indicates whether the slot accepts multiple values in a single
    -- utterance.
    --
    -- If the @multipleValuesSetting@ is not set, the default value is @false@.
    DescribeSlotResponse -> Maybe MultipleValuesSetting
multipleValuesSetting :: Prelude.Maybe MultipleValuesSetting,
    -- | Whether slot values are shown in Amazon CloudWatch logs. If the value is
    -- @None@, the actual value of the slot is shown in logs.
    DescribeSlotResponse -> Maybe ObfuscationSetting
obfuscationSetting :: Prelude.Maybe ObfuscationSetting,
    -- | The unique identifier generated for the slot.
    DescribeSlotResponse -> Maybe Text
slotId :: Prelude.Maybe Prelude.Text,
    -- | The name specified for the slot.
    DescribeSlotResponse -> Maybe Text
slotName :: Prelude.Maybe Prelude.Text,
    -- | The identifier of the slot type that determines the values entered into
    -- the slot.
    DescribeSlotResponse -> Maybe Text
slotTypeId :: Prelude.Maybe Prelude.Text,
    -- | Specifications for the constituent sub slots and the expression for the
    -- composite slot.
    DescribeSlotResponse -> Maybe SubSlotSetting
subSlotSetting :: Prelude.Maybe SubSlotSetting,
    -- | Prompts that Amazon Lex uses to elicit a value for the slot.
    DescribeSlotResponse -> Maybe SlotValueElicitationSetting
valueElicitationSetting :: Prelude.Maybe SlotValueElicitationSetting,
    -- | The response's http status code.
    DescribeSlotResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeSlotResponse -> DescribeSlotResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeSlotResponse -> DescribeSlotResponse -> Bool
$c/= :: DescribeSlotResponse -> DescribeSlotResponse -> Bool
== :: DescribeSlotResponse -> DescribeSlotResponse -> Bool
$c== :: DescribeSlotResponse -> DescribeSlotResponse -> Bool
Prelude.Eq, ReadPrec [DescribeSlotResponse]
ReadPrec DescribeSlotResponse
Int -> ReadS DescribeSlotResponse
ReadS [DescribeSlotResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeSlotResponse]
$creadListPrec :: ReadPrec [DescribeSlotResponse]
readPrec :: ReadPrec DescribeSlotResponse
$creadPrec :: ReadPrec DescribeSlotResponse
readList :: ReadS [DescribeSlotResponse]
$creadList :: ReadS [DescribeSlotResponse]
readsPrec :: Int -> ReadS DescribeSlotResponse
$creadsPrec :: Int -> ReadS DescribeSlotResponse
Prelude.Read, Int -> DescribeSlotResponse -> ShowS
[DescribeSlotResponse] -> ShowS
DescribeSlotResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeSlotResponse] -> ShowS
$cshowList :: [DescribeSlotResponse] -> ShowS
show :: DescribeSlotResponse -> String
$cshow :: DescribeSlotResponse -> String
showsPrec :: Int -> DescribeSlotResponse -> ShowS
$cshowsPrec :: Int -> DescribeSlotResponse -> ShowS
Prelude.Show, forall x. Rep DescribeSlotResponse x -> DescribeSlotResponse
forall x. DescribeSlotResponse -> Rep DescribeSlotResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeSlotResponse x -> DescribeSlotResponse
$cfrom :: forall x. DescribeSlotResponse -> Rep DescribeSlotResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeSlotResponse' 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', 'describeSlotResponse_botId' - The identifier of the bot associated with the slot.
--
-- 'botVersion', 'describeSlotResponse_botVersion' - The version of the bot associated with the slot.
--
-- 'creationDateTime', 'describeSlotResponse_creationDateTime' - A timestamp of the date and time that the slot was created.
--
-- 'description', 'describeSlotResponse_description' - The description specified for the slot.
--
-- 'intentId', 'describeSlotResponse_intentId' - The identifier of the intent associated with the slot.
--
-- 'lastUpdatedDateTime', 'describeSlotResponse_lastUpdatedDateTime' - A timestamp of the date and time that the slot was last updated.
--
-- 'localeId', 'describeSlotResponse_localeId' - The language and locale specified for the slot.
--
-- 'multipleValuesSetting', 'describeSlotResponse_multipleValuesSetting' - Indicates whether the slot accepts multiple values in a single
-- utterance.
--
-- If the @multipleValuesSetting@ is not set, the default value is @false@.
--
-- 'obfuscationSetting', 'describeSlotResponse_obfuscationSetting' - Whether slot values are shown in Amazon CloudWatch logs. If the value is
-- @None@, the actual value of the slot is shown in logs.
--
-- 'slotId', 'describeSlotResponse_slotId' - The unique identifier generated for the slot.
--
-- 'slotName', 'describeSlotResponse_slotName' - The name specified for the slot.
--
-- 'slotTypeId', 'describeSlotResponse_slotTypeId' - The identifier of the slot type that determines the values entered into
-- the slot.
--
-- 'subSlotSetting', 'describeSlotResponse_subSlotSetting' - Specifications for the constituent sub slots and the expression for the
-- composite slot.
--
-- 'valueElicitationSetting', 'describeSlotResponse_valueElicitationSetting' - Prompts that Amazon Lex uses to elicit a value for the slot.
--
-- 'httpStatus', 'describeSlotResponse_httpStatus' - The response's http status code.
newDescribeSlotResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeSlotResponse
newDescribeSlotResponse :: Int -> DescribeSlotResponse
newDescribeSlotResponse Int
pHttpStatus_ =
  DescribeSlotResponse'
    { $sel:botId:DescribeSlotResponse' :: Maybe Text
botId = forall a. Maybe a
Prelude.Nothing,
      $sel:botVersion:DescribeSlotResponse' :: Maybe Text
botVersion = forall a. Maybe a
Prelude.Nothing,
      $sel:creationDateTime:DescribeSlotResponse' :: Maybe POSIX
creationDateTime = forall a. Maybe a
Prelude.Nothing,
      $sel:description:DescribeSlotResponse' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:intentId:DescribeSlotResponse' :: Maybe Text
intentId = forall a. Maybe a
Prelude.Nothing,
      $sel:lastUpdatedDateTime:DescribeSlotResponse' :: Maybe POSIX
lastUpdatedDateTime = forall a. Maybe a
Prelude.Nothing,
      $sel:localeId:DescribeSlotResponse' :: Maybe Text
localeId = forall a. Maybe a
Prelude.Nothing,
      $sel:multipleValuesSetting:DescribeSlotResponse' :: Maybe MultipleValuesSetting
multipleValuesSetting = forall a. Maybe a
Prelude.Nothing,
      $sel:obfuscationSetting:DescribeSlotResponse' :: Maybe ObfuscationSetting
obfuscationSetting = forall a. Maybe a
Prelude.Nothing,
      $sel:slotId:DescribeSlotResponse' :: Maybe Text
slotId = forall a. Maybe a
Prelude.Nothing,
      $sel:slotName:DescribeSlotResponse' :: Maybe Text
slotName = forall a. Maybe a
Prelude.Nothing,
      $sel:slotTypeId:DescribeSlotResponse' :: Maybe Text
slotTypeId = forall a. Maybe a
Prelude.Nothing,
      $sel:subSlotSetting:DescribeSlotResponse' :: Maybe SubSlotSetting
subSlotSetting = forall a. Maybe a
Prelude.Nothing,
      $sel:valueElicitationSetting:DescribeSlotResponse' :: Maybe SlotValueElicitationSetting
valueElicitationSetting = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeSlotResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The identifier of the bot associated with the slot.
describeSlotResponse_botId :: Lens.Lens' DescribeSlotResponse (Prelude.Maybe Prelude.Text)
describeSlotResponse_botId :: Lens' DescribeSlotResponse (Maybe Text)
describeSlotResponse_botId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSlotResponse' {Maybe Text
botId :: Maybe Text
$sel:botId:DescribeSlotResponse' :: DescribeSlotResponse -> Maybe Text
botId} -> Maybe Text
botId) (\s :: DescribeSlotResponse
s@DescribeSlotResponse' {} Maybe Text
a -> DescribeSlotResponse
s {$sel:botId:DescribeSlotResponse' :: Maybe Text
botId = Maybe Text
a} :: DescribeSlotResponse)

-- | The version of the bot associated with the slot.
describeSlotResponse_botVersion :: Lens.Lens' DescribeSlotResponse (Prelude.Maybe Prelude.Text)
describeSlotResponse_botVersion :: Lens' DescribeSlotResponse (Maybe Text)
describeSlotResponse_botVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSlotResponse' {Maybe Text
botVersion :: Maybe Text
$sel:botVersion:DescribeSlotResponse' :: DescribeSlotResponse -> Maybe Text
botVersion} -> Maybe Text
botVersion) (\s :: DescribeSlotResponse
s@DescribeSlotResponse' {} Maybe Text
a -> DescribeSlotResponse
s {$sel:botVersion:DescribeSlotResponse' :: Maybe Text
botVersion = Maybe Text
a} :: DescribeSlotResponse)

-- | A timestamp of the date and time that the slot was created.
describeSlotResponse_creationDateTime :: Lens.Lens' DescribeSlotResponse (Prelude.Maybe Prelude.UTCTime)
describeSlotResponse_creationDateTime :: Lens' DescribeSlotResponse (Maybe UTCTime)
describeSlotResponse_creationDateTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSlotResponse' {Maybe POSIX
creationDateTime :: Maybe POSIX
$sel:creationDateTime:DescribeSlotResponse' :: DescribeSlotResponse -> Maybe POSIX
creationDateTime} -> Maybe POSIX
creationDateTime) (\s :: DescribeSlotResponse
s@DescribeSlotResponse' {} Maybe POSIX
a -> DescribeSlotResponse
s {$sel:creationDateTime:DescribeSlotResponse' :: Maybe POSIX
creationDateTime = Maybe POSIX
a} :: DescribeSlotResponse) 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 description specified for the slot.
describeSlotResponse_description :: Lens.Lens' DescribeSlotResponse (Prelude.Maybe Prelude.Text)
describeSlotResponse_description :: Lens' DescribeSlotResponse (Maybe Text)
describeSlotResponse_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSlotResponse' {Maybe Text
description :: Maybe Text
$sel:description:DescribeSlotResponse' :: DescribeSlotResponse -> Maybe Text
description} -> Maybe Text
description) (\s :: DescribeSlotResponse
s@DescribeSlotResponse' {} Maybe Text
a -> DescribeSlotResponse
s {$sel:description:DescribeSlotResponse' :: Maybe Text
description = Maybe Text
a} :: DescribeSlotResponse)

-- | The identifier of the intent associated with the slot.
describeSlotResponse_intentId :: Lens.Lens' DescribeSlotResponse (Prelude.Maybe Prelude.Text)
describeSlotResponse_intentId :: Lens' DescribeSlotResponse (Maybe Text)
describeSlotResponse_intentId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSlotResponse' {Maybe Text
intentId :: Maybe Text
$sel:intentId:DescribeSlotResponse' :: DescribeSlotResponse -> Maybe Text
intentId} -> Maybe Text
intentId) (\s :: DescribeSlotResponse
s@DescribeSlotResponse' {} Maybe Text
a -> DescribeSlotResponse
s {$sel:intentId:DescribeSlotResponse' :: Maybe Text
intentId = Maybe Text
a} :: DescribeSlotResponse)

-- | A timestamp of the date and time that the slot was last updated.
describeSlotResponse_lastUpdatedDateTime :: Lens.Lens' DescribeSlotResponse (Prelude.Maybe Prelude.UTCTime)
describeSlotResponse_lastUpdatedDateTime :: Lens' DescribeSlotResponse (Maybe UTCTime)
describeSlotResponse_lastUpdatedDateTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSlotResponse' {Maybe POSIX
lastUpdatedDateTime :: Maybe POSIX
$sel:lastUpdatedDateTime:DescribeSlotResponse' :: DescribeSlotResponse -> Maybe POSIX
lastUpdatedDateTime} -> Maybe POSIX
lastUpdatedDateTime) (\s :: DescribeSlotResponse
s@DescribeSlotResponse' {} Maybe POSIX
a -> DescribeSlotResponse
s {$sel:lastUpdatedDateTime:DescribeSlotResponse' :: Maybe POSIX
lastUpdatedDateTime = Maybe POSIX
a} :: DescribeSlotResponse) 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 language and locale specified for the slot.
describeSlotResponse_localeId :: Lens.Lens' DescribeSlotResponse (Prelude.Maybe Prelude.Text)
describeSlotResponse_localeId :: Lens' DescribeSlotResponse (Maybe Text)
describeSlotResponse_localeId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSlotResponse' {Maybe Text
localeId :: Maybe Text
$sel:localeId:DescribeSlotResponse' :: DescribeSlotResponse -> Maybe Text
localeId} -> Maybe Text
localeId) (\s :: DescribeSlotResponse
s@DescribeSlotResponse' {} Maybe Text
a -> DescribeSlotResponse
s {$sel:localeId:DescribeSlotResponse' :: Maybe Text
localeId = Maybe Text
a} :: DescribeSlotResponse)

-- | Indicates whether the slot accepts multiple values in a single
-- utterance.
--
-- If the @multipleValuesSetting@ is not set, the default value is @false@.
describeSlotResponse_multipleValuesSetting :: Lens.Lens' DescribeSlotResponse (Prelude.Maybe MultipleValuesSetting)
describeSlotResponse_multipleValuesSetting :: Lens' DescribeSlotResponse (Maybe MultipleValuesSetting)
describeSlotResponse_multipleValuesSetting = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSlotResponse' {Maybe MultipleValuesSetting
multipleValuesSetting :: Maybe MultipleValuesSetting
$sel:multipleValuesSetting:DescribeSlotResponse' :: DescribeSlotResponse -> Maybe MultipleValuesSetting
multipleValuesSetting} -> Maybe MultipleValuesSetting
multipleValuesSetting) (\s :: DescribeSlotResponse
s@DescribeSlotResponse' {} Maybe MultipleValuesSetting
a -> DescribeSlotResponse
s {$sel:multipleValuesSetting:DescribeSlotResponse' :: Maybe MultipleValuesSetting
multipleValuesSetting = Maybe MultipleValuesSetting
a} :: DescribeSlotResponse)

-- | Whether slot values are shown in Amazon CloudWatch logs. If the value is
-- @None@, the actual value of the slot is shown in logs.
describeSlotResponse_obfuscationSetting :: Lens.Lens' DescribeSlotResponse (Prelude.Maybe ObfuscationSetting)
describeSlotResponse_obfuscationSetting :: Lens' DescribeSlotResponse (Maybe ObfuscationSetting)
describeSlotResponse_obfuscationSetting = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSlotResponse' {Maybe ObfuscationSetting
obfuscationSetting :: Maybe ObfuscationSetting
$sel:obfuscationSetting:DescribeSlotResponse' :: DescribeSlotResponse -> Maybe ObfuscationSetting
obfuscationSetting} -> Maybe ObfuscationSetting
obfuscationSetting) (\s :: DescribeSlotResponse
s@DescribeSlotResponse' {} Maybe ObfuscationSetting
a -> DescribeSlotResponse
s {$sel:obfuscationSetting:DescribeSlotResponse' :: Maybe ObfuscationSetting
obfuscationSetting = Maybe ObfuscationSetting
a} :: DescribeSlotResponse)

-- | The unique identifier generated for the slot.
describeSlotResponse_slotId :: Lens.Lens' DescribeSlotResponse (Prelude.Maybe Prelude.Text)
describeSlotResponse_slotId :: Lens' DescribeSlotResponse (Maybe Text)
describeSlotResponse_slotId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSlotResponse' {Maybe Text
slotId :: Maybe Text
$sel:slotId:DescribeSlotResponse' :: DescribeSlotResponse -> Maybe Text
slotId} -> Maybe Text
slotId) (\s :: DescribeSlotResponse
s@DescribeSlotResponse' {} Maybe Text
a -> DescribeSlotResponse
s {$sel:slotId:DescribeSlotResponse' :: Maybe Text
slotId = Maybe Text
a} :: DescribeSlotResponse)

-- | The name specified for the slot.
describeSlotResponse_slotName :: Lens.Lens' DescribeSlotResponse (Prelude.Maybe Prelude.Text)
describeSlotResponse_slotName :: Lens' DescribeSlotResponse (Maybe Text)
describeSlotResponse_slotName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSlotResponse' {Maybe Text
slotName :: Maybe Text
$sel:slotName:DescribeSlotResponse' :: DescribeSlotResponse -> Maybe Text
slotName} -> Maybe Text
slotName) (\s :: DescribeSlotResponse
s@DescribeSlotResponse' {} Maybe Text
a -> DescribeSlotResponse
s {$sel:slotName:DescribeSlotResponse' :: Maybe Text
slotName = Maybe Text
a} :: DescribeSlotResponse)

-- | The identifier of the slot type that determines the values entered into
-- the slot.
describeSlotResponse_slotTypeId :: Lens.Lens' DescribeSlotResponse (Prelude.Maybe Prelude.Text)
describeSlotResponse_slotTypeId :: Lens' DescribeSlotResponse (Maybe Text)
describeSlotResponse_slotTypeId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSlotResponse' {Maybe Text
slotTypeId :: Maybe Text
$sel:slotTypeId:DescribeSlotResponse' :: DescribeSlotResponse -> Maybe Text
slotTypeId} -> Maybe Text
slotTypeId) (\s :: DescribeSlotResponse
s@DescribeSlotResponse' {} Maybe Text
a -> DescribeSlotResponse
s {$sel:slotTypeId:DescribeSlotResponse' :: Maybe Text
slotTypeId = Maybe Text
a} :: DescribeSlotResponse)

-- | Specifications for the constituent sub slots and the expression for the
-- composite slot.
describeSlotResponse_subSlotSetting :: Lens.Lens' DescribeSlotResponse (Prelude.Maybe SubSlotSetting)
describeSlotResponse_subSlotSetting :: Lens' DescribeSlotResponse (Maybe SubSlotSetting)
describeSlotResponse_subSlotSetting = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSlotResponse' {Maybe SubSlotSetting
subSlotSetting :: Maybe SubSlotSetting
$sel:subSlotSetting:DescribeSlotResponse' :: DescribeSlotResponse -> Maybe SubSlotSetting
subSlotSetting} -> Maybe SubSlotSetting
subSlotSetting) (\s :: DescribeSlotResponse
s@DescribeSlotResponse' {} Maybe SubSlotSetting
a -> DescribeSlotResponse
s {$sel:subSlotSetting:DescribeSlotResponse' :: Maybe SubSlotSetting
subSlotSetting = Maybe SubSlotSetting
a} :: DescribeSlotResponse)

-- | Prompts that Amazon Lex uses to elicit a value for the slot.
describeSlotResponse_valueElicitationSetting :: Lens.Lens' DescribeSlotResponse (Prelude.Maybe SlotValueElicitationSetting)
describeSlotResponse_valueElicitationSetting :: Lens' DescribeSlotResponse (Maybe SlotValueElicitationSetting)
describeSlotResponse_valueElicitationSetting = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSlotResponse' {Maybe SlotValueElicitationSetting
valueElicitationSetting :: Maybe SlotValueElicitationSetting
$sel:valueElicitationSetting:DescribeSlotResponse' :: DescribeSlotResponse -> Maybe SlotValueElicitationSetting
valueElicitationSetting} -> Maybe SlotValueElicitationSetting
valueElicitationSetting) (\s :: DescribeSlotResponse
s@DescribeSlotResponse' {} Maybe SlotValueElicitationSetting
a -> DescribeSlotResponse
s {$sel:valueElicitationSetting:DescribeSlotResponse' :: Maybe SlotValueElicitationSetting
valueElicitationSetting = Maybe SlotValueElicitationSetting
a} :: DescribeSlotResponse)

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

instance Prelude.NFData DescribeSlotResponse where
  rnf :: DescribeSlotResponse -> ()
rnf DescribeSlotResponse' {Int
Maybe Text
Maybe POSIX
Maybe MultipleValuesSetting
Maybe ObfuscationSetting
Maybe SubSlotSetting
Maybe SlotValueElicitationSetting
httpStatus :: Int
valueElicitationSetting :: Maybe SlotValueElicitationSetting
subSlotSetting :: Maybe SubSlotSetting
slotTypeId :: Maybe Text
slotName :: Maybe Text
slotId :: Maybe Text
obfuscationSetting :: Maybe ObfuscationSetting
multipleValuesSetting :: Maybe MultipleValuesSetting
localeId :: Maybe Text
lastUpdatedDateTime :: Maybe POSIX
intentId :: Maybe Text
description :: Maybe Text
creationDateTime :: Maybe POSIX
botVersion :: Maybe Text
botId :: Maybe Text
$sel:httpStatus:DescribeSlotResponse' :: DescribeSlotResponse -> Int
$sel:valueElicitationSetting:DescribeSlotResponse' :: DescribeSlotResponse -> Maybe SlotValueElicitationSetting
$sel:subSlotSetting:DescribeSlotResponse' :: DescribeSlotResponse -> Maybe SubSlotSetting
$sel:slotTypeId:DescribeSlotResponse' :: DescribeSlotResponse -> Maybe Text
$sel:slotName:DescribeSlotResponse' :: DescribeSlotResponse -> Maybe Text
$sel:slotId:DescribeSlotResponse' :: DescribeSlotResponse -> Maybe Text
$sel:obfuscationSetting:DescribeSlotResponse' :: DescribeSlotResponse -> Maybe ObfuscationSetting
$sel:multipleValuesSetting:DescribeSlotResponse' :: DescribeSlotResponse -> Maybe MultipleValuesSetting
$sel:localeId:DescribeSlotResponse' :: DescribeSlotResponse -> Maybe Text
$sel:lastUpdatedDateTime:DescribeSlotResponse' :: DescribeSlotResponse -> Maybe POSIX
$sel:intentId:DescribeSlotResponse' :: DescribeSlotResponse -> Maybe Text
$sel:description:DescribeSlotResponse' :: DescribeSlotResponse -> Maybe Text
$sel:creationDateTime:DescribeSlotResponse' :: DescribeSlotResponse -> Maybe POSIX
$sel:botVersion:DescribeSlotResponse' :: DescribeSlotResponse -> Maybe Text
$sel:botId:DescribeSlotResponse' :: DescribeSlotResponse -> 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
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 Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
intentId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
lastUpdatedDateTime
      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 MultipleValuesSetting
multipleValuesSetting
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ObfuscationSetting
obfuscationSetting
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
slotId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
slotName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
slotTypeId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe SubSlotSetting
subSlotSetting
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe SlotValueElicitationSetting
valueElicitationSetting
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus