{-# 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.LexModels.GetSlotType
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Returns information about a specific version of a slot type. In addition
-- to specifying the slot type name, you must specify the slot type
-- version.
--
-- This operation requires permissions for the @lex:GetSlotType@ action.
module Amazonka.LexModels.GetSlotType
  ( -- * Creating a Request
    GetSlotType (..),
    newGetSlotType,

    -- * Request Lenses
    getSlotType_name,
    getSlotType_version,

    -- * Destructuring the Response
    GetSlotTypeResponse (..),
    newGetSlotTypeResponse,

    -- * Response Lenses
    getSlotTypeResponse_checksum,
    getSlotTypeResponse_createdDate,
    getSlotTypeResponse_description,
    getSlotTypeResponse_enumerationValues,
    getSlotTypeResponse_lastUpdatedDate,
    getSlotTypeResponse_name,
    getSlotTypeResponse_parentSlotTypeSignature,
    getSlotTypeResponse_slotTypeConfigurations,
    getSlotTypeResponse_valueSelectionStrategy,
    getSlotTypeResponse_version,
    getSlotTypeResponse_httpStatus,
  )
where

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

-- | /See:/ 'newGetSlotType' smart constructor.
data GetSlotType = GetSlotType'
  { -- | The name of the slot type. The name is case sensitive.
    GetSlotType -> Text
name :: Prelude.Text,
    -- | The version of the slot type.
    GetSlotType -> Text
version :: Prelude.Text
  }
  deriving (GetSlotType -> GetSlotType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetSlotType -> GetSlotType -> Bool
$c/= :: GetSlotType -> GetSlotType -> Bool
== :: GetSlotType -> GetSlotType -> Bool
$c== :: GetSlotType -> GetSlotType -> Bool
Prelude.Eq, ReadPrec [GetSlotType]
ReadPrec GetSlotType
Int -> ReadS GetSlotType
ReadS [GetSlotType]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetSlotType]
$creadListPrec :: ReadPrec [GetSlotType]
readPrec :: ReadPrec GetSlotType
$creadPrec :: ReadPrec GetSlotType
readList :: ReadS [GetSlotType]
$creadList :: ReadS [GetSlotType]
readsPrec :: Int -> ReadS GetSlotType
$creadsPrec :: Int -> ReadS GetSlotType
Prelude.Read, Int -> GetSlotType -> ShowS
[GetSlotType] -> ShowS
GetSlotType -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetSlotType] -> ShowS
$cshowList :: [GetSlotType] -> ShowS
show :: GetSlotType -> String
$cshow :: GetSlotType -> String
showsPrec :: Int -> GetSlotType -> ShowS
$cshowsPrec :: Int -> GetSlotType -> ShowS
Prelude.Show, forall x. Rep GetSlotType x -> GetSlotType
forall x. GetSlotType -> Rep GetSlotType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetSlotType x -> GetSlotType
$cfrom :: forall x. GetSlotType -> Rep GetSlotType x
Prelude.Generic)

-- |
-- Create a value of 'GetSlotType' 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:
--
-- 'name', 'getSlotType_name' - The name of the slot type. The name is case sensitive.
--
-- 'version', 'getSlotType_version' - The version of the slot type.
newGetSlotType ::
  -- | 'name'
  Prelude.Text ->
  -- | 'version'
  Prelude.Text ->
  GetSlotType
newGetSlotType :: Text -> Text -> GetSlotType
newGetSlotType Text
pName_ Text
pVersion_ =
  GetSlotType' {$sel:name:GetSlotType' :: Text
name = Text
pName_, $sel:version:GetSlotType' :: Text
version = Text
pVersion_}

-- | The name of the slot type. The name is case sensitive.
getSlotType_name :: Lens.Lens' GetSlotType Prelude.Text
getSlotType_name :: Lens' GetSlotType Text
getSlotType_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSlotType' {Text
name :: Text
$sel:name:GetSlotType' :: GetSlotType -> Text
name} -> Text
name) (\s :: GetSlotType
s@GetSlotType' {} Text
a -> GetSlotType
s {$sel:name:GetSlotType' :: Text
name = Text
a} :: GetSlotType)

-- | The version of the slot type.
getSlotType_version :: Lens.Lens' GetSlotType Prelude.Text
getSlotType_version :: Lens' GetSlotType Text
getSlotType_version = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSlotType' {Text
version :: Text
$sel:version:GetSlotType' :: GetSlotType -> Text
version} -> Text
version) (\s :: GetSlotType
s@GetSlotType' {} Text
a -> GetSlotType
s {$sel:version:GetSlotType' :: Text
version = Text
a} :: GetSlotType)

instance Core.AWSRequest GetSlotType where
  type AWSResponse GetSlotType = GetSlotTypeResponse
  request :: (Service -> Service) -> GetSlotType -> Request GetSlotType
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 GetSlotType
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetSlotType)))
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 POSIX
-> Maybe Text
-> Maybe [EnumerationValue]
-> Maybe POSIX
-> Maybe Text
-> Maybe Text
-> Maybe [SlotTypeConfiguration]
-> Maybe SlotValueSelectionStrategy
-> Maybe Text
-> Int
-> GetSlotTypeResponse
GetSlotTypeResponse'
            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
"checksum")
            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
"createdDate")
            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
"enumerationValues"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                        )
            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
"lastUpdatedDate")
            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
"name")
            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
"parentSlotTypeSignature")
            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
"slotTypeConfigurations"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                        )
            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
"valueSelectionStrategy")
            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
"version")
            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 GetSlotType where
  hashWithSalt :: Int -> GetSlotType -> Int
hashWithSalt Int
_salt GetSlotType' {Text
version :: Text
name :: Text
$sel:version:GetSlotType' :: GetSlotType -> Text
$sel:name:GetSlotType' :: GetSlotType -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
version

instance Prelude.NFData GetSlotType where
  rnf :: GetSlotType -> ()
rnf GetSlotType' {Text
version :: Text
name :: Text
$sel:version:GetSlotType' :: GetSlotType -> Text
$sel:name:GetSlotType' :: GetSlotType -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
name seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
version

instance Data.ToHeaders GetSlotType where
  toHeaders :: GetSlotType -> 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 GetSlotType where
  toPath :: GetSlotType -> ByteString
toPath GetSlotType' {Text
version :: Text
name :: Text
$sel:version:GetSlotType' :: GetSlotType -> Text
$sel:name:GetSlotType' :: GetSlotType -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/slottypes/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
name,
        ByteString
"/versions/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
version
      ]

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

-- | /See:/ 'newGetSlotTypeResponse' smart constructor.
data GetSlotTypeResponse = GetSlotTypeResponse'
  { -- | Checksum of the @$LATEST@ version of the slot type.
    GetSlotTypeResponse -> Maybe Text
checksum :: Prelude.Maybe Prelude.Text,
    -- | The date that the slot type was created.
    GetSlotTypeResponse -> Maybe POSIX
createdDate :: Prelude.Maybe Data.POSIX,
    -- | A description of the slot type.
    GetSlotTypeResponse -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | A list of @EnumerationValue@ objects that defines the values that the
    -- slot type can take.
    GetSlotTypeResponse -> Maybe [EnumerationValue]
enumerationValues :: Prelude.Maybe [EnumerationValue],
    -- | The date that the slot type was updated. When you create a resource, the
    -- creation date and last update date are the same.
    GetSlotTypeResponse -> Maybe POSIX
lastUpdatedDate :: Prelude.Maybe Data.POSIX,
    -- | The name of the slot type.
    GetSlotTypeResponse -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | The built-in slot type used as a parent for the slot type.
    GetSlotTypeResponse -> Maybe Text
parentSlotTypeSignature :: Prelude.Maybe Prelude.Text,
    -- | Configuration information that extends the parent built-in slot type.
    GetSlotTypeResponse -> Maybe [SlotTypeConfiguration]
slotTypeConfigurations :: Prelude.Maybe [SlotTypeConfiguration],
    -- | The strategy that Amazon Lex uses to determine the value of the slot.
    -- For more information, see PutSlotType.
    GetSlotTypeResponse -> Maybe SlotValueSelectionStrategy
valueSelectionStrategy :: Prelude.Maybe SlotValueSelectionStrategy,
    -- | The version of the slot type.
    GetSlotTypeResponse -> Maybe Text
version :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    GetSlotTypeResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetSlotTypeResponse -> GetSlotTypeResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetSlotTypeResponse -> GetSlotTypeResponse -> Bool
$c/= :: GetSlotTypeResponse -> GetSlotTypeResponse -> Bool
== :: GetSlotTypeResponse -> GetSlotTypeResponse -> Bool
$c== :: GetSlotTypeResponse -> GetSlotTypeResponse -> Bool
Prelude.Eq, ReadPrec [GetSlotTypeResponse]
ReadPrec GetSlotTypeResponse
Int -> ReadS GetSlotTypeResponse
ReadS [GetSlotTypeResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetSlotTypeResponse]
$creadListPrec :: ReadPrec [GetSlotTypeResponse]
readPrec :: ReadPrec GetSlotTypeResponse
$creadPrec :: ReadPrec GetSlotTypeResponse
readList :: ReadS [GetSlotTypeResponse]
$creadList :: ReadS [GetSlotTypeResponse]
readsPrec :: Int -> ReadS GetSlotTypeResponse
$creadsPrec :: Int -> ReadS GetSlotTypeResponse
Prelude.Read, Int -> GetSlotTypeResponse -> ShowS
[GetSlotTypeResponse] -> ShowS
GetSlotTypeResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetSlotTypeResponse] -> ShowS
$cshowList :: [GetSlotTypeResponse] -> ShowS
show :: GetSlotTypeResponse -> String
$cshow :: GetSlotTypeResponse -> String
showsPrec :: Int -> GetSlotTypeResponse -> ShowS
$cshowsPrec :: Int -> GetSlotTypeResponse -> ShowS
Prelude.Show, forall x. Rep GetSlotTypeResponse x -> GetSlotTypeResponse
forall x. GetSlotTypeResponse -> Rep GetSlotTypeResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetSlotTypeResponse x -> GetSlotTypeResponse
$cfrom :: forall x. GetSlotTypeResponse -> Rep GetSlotTypeResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetSlotTypeResponse' 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:
--
-- 'checksum', 'getSlotTypeResponse_checksum' - Checksum of the @$LATEST@ version of the slot type.
--
-- 'createdDate', 'getSlotTypeResponse_createdDate' - The date that the slot type was created.
--
-- 'description', 'getSlotTypeResponse_description' - A description of the slot type.
--
-- 'enumerationValues', 'getSlotTypeResponse_enumerationValues' - A list of @EnumerationValue@ objects that defines the values that the
-- slot type can take.
--
-- 'lastUpdatedDate', 'getSlotTypeResponse_lastUpdatedDate' - The date that the slot type was updated. When you create a resource, the
-- creation date and last update date are the same.
--
-- 'name', 'getSlotTypeResponse_name' - The name of the slot type.
--
-- 'parentSlotTypeSignature', 'getSlotTypeResponse_parentSlotTypeSignature' - The built-in slot type used as a parent for the slot type.
--
-- 'slotTypeConfigurations', 'getSlotTypeResponse_slotTypeConfigurations' - Configuration information that extends the parent built-in slot type.
--
-- 'valueSelectionStrategy', 'getSlotTypeResponse_valueSelectionStrategy' - The strategy that Amazon Lex uses to determine the value of the slot.
-- For more information, see PutSlotType.
--
-- 'version', 'getSlotTypeResponse_version' - The version of the slot type.
--
-- 'httpStatus', 'getSlotTypeResponse_httpStatus' - The response's http status code.
newGetSlotTypeResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetSlotTypeResponse
newGetSlotTypeResponse :: Int -> GetSlotTypeResponse
newGetSlotTypeResponse Int
pHttpStatus_ =
  GetSlotTypeResponse'
    { $sel:checksum:GetSlotTypeResponse' :: Maybe Text
checksum = forall a. Maybe a
Prelude.Nothing,
      $sel:createdDate:GetSlotTypeResponse' :: Maybe POSIX
createdDate = forall a. Maybe a
Prelude.Nothing,
      $sel:description:GetSlotTypeResponse' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:enumerationValues:GetSlotTypeResponse' :: Maybe [EnumerationValue]
enumerationValues = forall a. Maybe a
Prelude.Nothing,
      $sel:lastUpdatedDate:GetSlotTypeResponse' :: Maybe POSIX
lastUpdatedDate = forall a. Maybe a
Prelude.Nothing,
      $sel:name:GetSlotTypeResponse' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:parentSlotTypeSignature:GetSlotTypeResponse' :: Maybe Text
parentSlotTypeSignature = forall a. Maybe a
Prelude.Nothing,
      $sel:slotTypeConfigurations:GetSlotTypeResponse' :: Maybe [SlotTypeConfiguration]
slotTypeConfigurations = forall a. Maybe a
Prelude.Nothing,
      $sel:valueSelectionStrategy:GetSlotTypeResponse' :: Maybe SlotValueSelectionStrategy
valueSelectionStrategy = forall a. Maybe a
Prelude.Nothing,
      $sel:version:GetSlotTypeResponse' :: Maybe Text
version = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetSlotTypeResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Checksum of the @$LATEST@ version of the slot type.
getSlotTypeResponse_checksum :: Lens.Lens' GetSlotTypeResponse (Prelude.Maybe Prelude.Text)
getSlotTypeResponse_checksum :: Lens' GetSlotTypeResponse (Maybe Text)
getSlotTypeResponse_checksum = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSlotTypeResponse' {Maybe Text
checksum :: Maybe Text
$sel:checksum:GetSlotTypeResponse' :: GetSlotTypeResponse -> Maybe Text
checksum} -> Maybe Text
checksum) (\s :: GetSlotTypeResponse
s@GetSlotTypeResponse' {} Maybe Text
a -> GetSlotTypeResponse
s {$sel:checksum:GetSlotTypeResponse' :: Maybe Text
checksum = Maybe Text
a} :: GetSlotTypeResponse)

-- | The date that the slot type was created.
getSlotTypeResponse_createdDate :: Lens.Lens' GetSlotTypeResponse (Prelude.Maybe Prelude.UTCTime)
getSlotTypeResponse_createdDate :: Lens' GetSlotTypeResponse (Maybe UTCTime)
getSlotTypeResponse_createdDate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSlotTypeResponse' {Maybe POSIX
createdDate :: Maybe POSIX
$sel:createdDate:GetSlotTypeResponse' :: GetSlotTypeResponse -> Maybe POSIX
createdDate} -> Maybe POSIX
createdDate) (\s :: GetSlotTypeResponse
s@GetSlotTypeResponse' {} Maybe POSIX
a -> GetSlotTypeResponse
s {$sel:createdDate:GetSlotTypeResponse' :: Maybe POSIX
createdDate = Maybe POSIX
a} :: GetSlotTypeResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | A description of the slot type.
getSlotTypeResponse_description :: Lens.Lens' GetSlotTypeResponse (Prelude.Maybe Prelude.Text)
getSlotTypeResponse_description :: Lens' GetSlotTypeResponse (Maybe Text)
getSlotTypeResponse_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSlotTypeResponse' {Maybe Text
description :: Maybe Text
$sel:description:GetSlotTypeResponse' :: GetSlotTypeResponse -> Maybe Text
description} -> Maybe Text
description) (\s :: GetSlotTypeResponse
s@GetSlotTypeResponse' {} Maybe Text
a -> GetSlotTypeResponse
s {$sel:description:GetSlotTypeResponse' :: Maybe Text
description = Maybe Text
a} :: GetSlotTypeResponse)

-- | A list of @EnumerationValue@ objects that defines the values that the
-- slot type can take.
getSlotTypeResponse_enumerationValues :: Lens.Lens' GetSlotTypeResponse (Prelude.Maybe [EnumerationValue])
getSlotTypeResponse_enumerationValues :: Lens' GetSlotTypeResponse (Maybe [EnumerationValue])
getSlotTypeResponse_enumerationValues = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSlotTypeResponse' {Maybe [EnumerationValue]
enumerationValues :: Maybe [EnumerationValue]
$sel:enumerationValues:GetSlotTypeResponse' :: GetSlotTypeResponse -> Maybe [EnumerationValue]
enumerationValues} -> Maybe [EnumerationValue]
enumerationValues) (\s :: GetSlotTypeResponse
s@GetSlotTypeResponse' {} Maybe [EnumerationValue]
a -> GetSlotTypeResponse
s {$sel:enumerationValues:GetSlotTypeResponse' :: Maybe [EnumerationValue]
enumerationValues = Maybe [EnumerationValue]
a} :: GetSlotTypeResponse) 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 s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The date that the slot type was updated. When you create a resource, the
-- creation date and last update date are the same.
getSlotTypeResponse_lastUpdatedDate :: Lens.Lens' GetSlotTypeResponse (Prelude.Maybe Prelude.UTCTime)
getSlotTypeResponse_lastUpdatedDate :: Lens' GetSlotTypeResponse (Maybe UTCTime)
getSlotTypeResponse_lastUpdatedDate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSlotTypeResponse' {Maybe POSIX
lastUpdatedDate :: Maybe POSIX
$sel:lastUpdatedDate:GetSlotTypeResponse' :: GetSlotTypeResponse -> Maybe POSIX
lastUpdatedDate} -> Maybe POSIX
lastUpdatedDate) (\s :: GetSlotTypeResponse
s@GetSlotTypeResponse' {} Maybe POSIX
a -> GetSlotTypeResponse
s {$sel:lastUpdatedDate:GetSlotTypeResponse' :: Maybe POSIX
lastUpdatedDate = Maybe POSIX
a} :: GetSlotTypeResponse) 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 name of the slot type.
getSlotTypeResponse_name :: Lens.Lens' GetSlotTypeResponse (Prelude.Maybe Prelude.Text)
getSlotTypeResponse_name :: Lens' GetSlotTypeResponse (Maybe Text)
getSlotTypeResponse_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSlotTypeResponse' {Maybe Text
name :: Maybe Text
$sel:name:GetSlotTypeResponse' :: GetSlotTypeResponse -> Maybe Text
name} -> Maybe Text
name) (\s :: GetSlotTypeResponse
s@GetSlotTypeResponse' {} Maybe Text
a -> GetSlotTypeResponse
s {$sel:name:GetSlotTypeResponse' :: Maybe Text
name = Maybe Text
a} :: GetSlotTypeResponse)

-- | The built-in slot type used as a parent for the slot type.
getSlotTypeResponse_parentSlotTypeSignature :: Lens.Lens' GetSlotTypeResponse (Prelude.Maybe Prelude.Text)
getSlotTypeResponse_parentSlotTypeSignature :: Lens' GetSlotTypeResponse (Maybe Text)
getSlotTypeResponse_parentSlotTypeSignature = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSlotTypeResponse' {Maybe Text
parentSlotTypeSignature :: Maybe Text
$sel:parentSlotTypeSignature:GetSlotTypeResponse' :: GetSlotTypeResponse -> Maybe Text
parentSlotTypeSignature} -> Maybe Text
parentSlotTypeSignature) (\s :: GetSlotTypeResponse
s@GetSlotTypeResponse' {} Maybe Text
a -> GetSlotTypeResponse
s {$sel:parentSlotTypeSignature:GetSlotTypeResponse' :: Maybe Text
parentSlotTypeSignature = Maybe Text
a} :: GetSlotTypeResponse)

-- | Configuration information that extends the parent built-in slot type.
getSlotTypeResponse_slotTypeConfigurations :: Lens.Lens' GetSlotTypeResponse (Prelude.Maybe [SlotTypeConfiguration])
getSlotTypeResponse_slotTypeConfigurations :: Lens' GetSlotTypeResponse (Maybe [SlotTypeConfiguration])
getSlotTypeResponse_slotTypeConfigurations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSlotTypeResponse' {Maybe [SlotTypeConfiguration]
slotTypeConfigurations :: Maybe [SlotTypeConfiguration]
$sel:slotTypeConfigurations:GetSlotTypeResponse' :: GetSlotTypeResponse -> Maybe [SlotTypeConfiguration]
slotTypeConfigurations} -> Maybe [SlotTypeConfiguration]
slotTypeConfigurations) (\s :: GetSlotTypeResponse
s@GetSlotTypeResponse' {} Maybe [SlotTypeConfiguration]
a -> GetSlotTypeResponse
s {$sel:slotTypeConfigurations:GetSlotTypeResponse' :: Maybe [SlotTypeConfiguration]
slotTypeConfigurations = Maybe [SlotTypeConfiguration]
a} :: GetSlotTypeResponse) 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 s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The strategy that Amazon Lex uses to determine the value of the slot.
-- For more information, see PutSlotType.
getSlotTypeResponse_valueSelectionStrategy :: Lens.Lens' GetSlotTypeResponse (Prelude.Maybe SlotValueSelectionStrategy)
getSlotTypeResponse_valueSelectionStrategy :: Lens' GetSlotTypeResponse (Maybe SlotValueSelectionStrategy)
getSlotTypeResponse_valueSelectionStrategy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSlotTypeResponse' {Maybe SlotValueSelectionStrategy
valueSelectionStrategy :: Maybe SlotValueSelectionStrategy
$sel:valueSelectionStrategy:GetSlotTypeResponse' :: GetSlotTypeResponse -> Maybe SlotValueSelectionStrategy
valueSelectionStrategy} -> Maybe SlotValueSelectionStrategy
valueSelectionStrategy) (\s :: GetSlotTypeResponse
s@GetSlotTypeResponse' {} Maybe SlotValueSelectionStrategy
a -> GetSlotTypeResponse
s {$sel:valueSelectionStrategy:GetSlotTypeResponse' :: Maybe SlotValueSelectionStrategy
valueSelectionStrategy = Maybe SlotValueSelectionStrategy
a} :: GetSlotTypeResponse)

-- | The version of the slot type.
getSlotTypeResponse_version :: Lens.Lens' GetSlotTypeResponse (Prelude.Maybe Prelude.Text)
getSlotTypeResponse_version :: Lens' GetSlotTypeResponse (Maybe Text)
getSlotTypeResponse_version = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSlotTypeResponse' {Maybe Text
version :: Maybe Text
$sel:version:GetSlotTypeResponse' :: GetSlotTypeResponse -> Maybe Text
version} -> Maybe Text
version) (\s :: GetSlotTypeResponse
s@GetSlotTypeResponse' {} Maybe Text
a -> GetSlotTypeResponse
s {$sel:version:GetSlotTypeResponse' :: Maybe Text
version = Maybe Text
a} :: GetSlotTypeResponse)

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

instance Prelude.NFData GetSlotTypeResponse where
  rnf :: GetSlotTypeResponse -> ()
rnf GetSlotTypeResponse' {Int
Maybe [EnumerationValue]
Maybe [SlotTypeConfiguration]
Maybe Text
Maybe POSIX
Maybe SlotValueSelectionStrategy
httpStatus :: Int
version :: Maybe Text
valueSelectionStrategy :: Maybe SlotValueSelectionStrategy
slotTypeConfigurations :: Maybe [SlotTypeConfiguration]
parentSlotTypeSignature :: Maybe Text
name :: Maybe Text
lastUpdatedDate :: Maybe POSIX
enumerationValues :: Maybe [EnumerationValue]
description :: Maybe Text
createdDate :: Maybe POSIX
checksum :: Maybe Text
$sel:httpStatus:GetSlotTypeResponse' :: GetSlotTypeResponse -> Int
$sel:version:GetSlotTypeResponse' :: GetSlotTypeResponse -> Maybe Text
$sel:valueSelectionStrategy:GetSlotTypeResponse' :: GetSlotTypeResponse -> Maybe SlotValueSelectionStrategy
$sel:slotTypeConfigurations:GetSlotTypeResponse' :: GetSlotTypeResponse -> Maybe [SlotTypeConfiguration]
$sel:parentSlotTypeSignature:GetSlotTypeResponse' :: GetSlotTypeResponse -> Maybe Text
$sel:name:GetSlotTypeResponse' :: GetSlotTypeResponse -> Maybe Text
$sel:lastUpdatedDate:GetSlotTypeResponse' :: GetSlotTypeResponse -> Maybe POSIX
$sel:enumerationValues:GetSlotTypeResponse' :: GetSlotTypeResponse -> Maybe [EnumerationValue]
$sel:description:GetSlotTypeResponse' :: GetSlotTypeResponse -> Maybe Text
$sel:createdDate:GetSlotTypeResponse' :: GetSlotTypeResponse -> Maybe POSIX
$sel:checksum:GetSlotTypeResponse' :: GetSlotTypeResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
checksum
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
createdDate
      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 [EnumerationValue]
enumerationValues
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
lastUpdatedDate
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
parentSlotTypeSignature
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [SlotTypeConfiguration]
slotTypeConfigurations
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe SlotValueSelectionStrategy
valueSelectionStrategy
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
version
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus