{-# 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.IoT.CreateThingType
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Creates a new thing type.
--
-- Requires permission to access the
-- <https://docs.aws.amazon.com/service-authorization/latest/reference/list_awsiot.html#awsiot-actions-as-permissions CreateThingType>
-- action.
module Amazonka.IoT.CreateThingType
  ( -- * Creating a Request
    CreateThingType (..),
    newCreateThingType,

    -- * Request Lenses
    createThingType_tags,
    createThingType_thingTypeProperties,
    createThingType_thingTypeName,

    -- * Destructuring the Response
    CreateThingTypeResponse (..),
    newCreateThingTypeResponse,

    -- * Response Lenses
    createThingTypeResponse_thingTypeArn,
    createThingTypeResponse_thingTypeId,
    createThingTypeResponse_thingTypeName,
    createThingTypeResponse_httpStatus,
  )
where

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

-- | The input for the CreateThingType operation.
--
-- /See:/ 'newCreateThingType' smart constructor.
data CreateThingType = CreateThingType'
  { -- | Metadata which can be used to manage the thing type.
    CreateThingType -> Maybe [Tag]
tags :: Prelude.Maybe [Tag],
    -- | The ThingTypeProperties for the thing type to create. It contains
    -- information about the new thing type including a description, and a list
    -- of searchable thing attribute names.
    CreateThingType -> Maybe ThingTypeProperties
thingTypeProperties :: Prelude.Maybe ThingTypeProperties,
    -- | The name of the thing type.
    CreateThingType -> Text
thingTypeName :: Prelude.Text
  }
  deriving (CreateThingType -> CreateThingType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateThingType -> CreateThingType -> Bool
$c/= :: CreateThingType -> CreateThingType -> Bool
== :: CreateThingType -> CreateThingType -> Bool
$c== :: CreateThingType -> CreateThingType -> Bool
Prelude.Eq, ReadPrec [CreateThingType]
ReadPrec CreateThingType
Int -> ReadS CreateThingType
ReadS [CreateThingType]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateThingType]
$creadListPrec :: ReadPrec [CreateThingType]
readPrec :: ReadPrec CreateThingType
$creadPrec :: ReadPrec CreateThingType
readList :: ReadS [CreateThingType]
$creadList :: ReadS [CreateThingType]
readsPrec :: Int -> ReadS CreateThingType
$creadsPrec :: Int -> ReadS CreateThingType
Prelude.Read, Int -> CreateThingType -> ShowS
[CreateThingType] -> ShowS
CreateThingType -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateThingType] -> ShowS
$cshowList :: [CreateThingType] -> ShowS
show :: CreateThingType -> String
$cshow :: CreateThingType -> String
showsPrec :: Int -> CreateThingType -> ShowS
$cshowsPrec :: Int -> CreateThingType -> ShowS
Prelude.Show, forall x. Rep CreateThingType x -> CreateThingType
forall x. CreateThingType -> Rep CreateThingType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateThingType x -> CreateThingType
$cfrom :: forall x. CreateThingType -> Rep CreateThingType x
Prelude.Generic)

-- |
-- Create a value of 'CreateThingType' 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:
--
-- 'tags', 'createThingType_tags' - Metadata which can be used to manage the thing type.
--
-- 'thingTypeProperties', 'createThingType_thingTypeProperties' - The ThingTypeProperties for the thing type to create. It contains
-- information about the new thing type including a description, and a list
-- of searchable thing attribute names.
--
-- 'thingTypeName', 'createThingType_thingTypeName' - The name of the thing type.
newCreateThingType ::
  -- | 'thingTypeName'
  Prelude.Text ->
  CreateThingType
newCreateThingType :: Text -> CreateThingType
newCreateThingType Text
pThingTypeName_ =
  CreateThingType'
    { $sel:tags:CreateThingType' :: Maybe [Tag]
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:thingTypeProperties:CreateThingType' :: Maybe ThingTypeProperties
thingTypeProperties = forall a. Maybe a
Prelude.Nothing,
      $sel:thingTypeName:CreateThingType' :: Text
thingTypeName = Text
pThingTypeName_
    }

-- | Metadata which can be used to manage the thing type.
createThingType_tags :: Lens.Lens' CreateThingType (Prelude.Maybe [Tag])
createThingType_tags :: Lens' CreateThingType (Maybe [Tag])
createThingType_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateThingType' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:CreateThingType' :: CreateThingType -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: CreateThingType
s@CreateThingType' {} Maybe [Tag]
a -> CreateThingType
s {$sel:tags:CreateThingType' :: Maybe [Tag]
tags = Maybe [Tag]
a} :: CreateThingType) 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 ThingTypeProperties for the thing type to create. It contains
-- information about the new thing type including a description, and a list
-- of searchable thing attribute names.
createThingType_thingTypeProperties :: Lens.Lens' CreateThingType (Prelude.Maybe ThingTypeProperties)
createThingType_thingTypeProperties :: Lens' CreateThingType (Maybe ThingTypeProperties)
createThingType_thingTypeProperties = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateThingType' {Maybe ThingTypeProperties
thingTypeProperties :: Maybe ThingTypeProperties
$sel:thingTypeProperties:CreateThingType' :: CreateThingType -> Maybe ThingTypeProperties
thingTypeProperties} -> Maybe ThingTypeProperties
thingTypeProperties) (\s :: CreateThingType
s@CreateThingType' {} Maybe ThingTypeProperties
a -> CreateThingType
s {$sel:thingTypeProperties:CreateThingType' :: Maybe ThingTypeProperties
thingTypeProperties = Maybe ThingTypeProperties
a} :: CreateThingType)

-- | The name of the thing type.
createThingType_thingTypeName :: Lens.Lens' CreateThingType Prelude.Text
createThingType_thingTypeName :: Lens' CreateThingType Text
createThingType_thingTypeName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateThingType' {Text
thingTypeName :: Text
$sel:thingTypeName:CreateThingType' :: CreateThingType -> Text
thingTypeName} -> Text
thingTypeName) (\s :: CreateThingType
s@CreateThingType' {} Text
a -> CreateThingType
s {$sel:thingTypeName:CreateThingType' :: Text
thingTypeName = Text
a} :: CreateThingType)

instance Core.AWSRequest CreateThingType where
  type
    AWSResponse CreateThingType =
      CreateThingTypeResponse
  request :: (Service -> Service) -> CreateThingType -> Request CreateThingType
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy CreateThingType
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse CreateThingType)))
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 Text -> Int -> CreateThingTypeResponse
CreateThingTypeResponse'
            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
"thingTypeArn")
            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
"thingTypeId")
            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
"thingTypeName")
            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 CreateThingType where
  hashWithSalt :: Int -> CreateThingType -> Int
hashWithSalt Int
_salt CreateThingType' {Maybe [Tag]
Maybe ThingTypeProperties
Text
thingTypeName :: Text
thingTypeProperties :: Maybe ThingTypeProperties
tags :: Maybe [Tag]
$sel:thingTypeName:CreateThingType' :: CreateThingType -> Text
$sel:thingTypeProperties:CreateThingType' :: CreateThingType -> Maybe ThingTypeProperties
$sel:tags:CreateThingType' :: CreateThingType -> Maybe [Tag]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Tag]
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ThingTypeProperties
thingTypeProperties
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
thingTypeName

instance Prelude.NFData CreateThingType where
  rnf :: CreateThingType -> ()
rnf CreateThingType' {Maybe [Tag]
Maybe ThingTypeProperties
Text
thingTypeName :: Text
thingTypeProperties :: Maybe ThingTypeProperties
tags :: Maybe [Tag]
$sel:thingTypeName:CreateThingType' :: CreateThingType -> Text
$sel:thingTypeProperties:CreateThingType' :: CreateThingType -> Maybe ThingTypeProperties
$sel:tags:CreateThingType' :: CreateThingType -> Maybe [Tag]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Tag]
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ThingTypeProperties
thingTypeProperties
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
thingTypeName

instance Data.ToHeaders CreateThingType where
  toHeaders :: CreateThingType -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

instance Data.ToJSON CreateThingType where
  toJSON :: CreateThingType -> Value
toJSON CreateThingType' {Maybe [Tag]
Maybe ThingTypeProperties
Text
thingTypeName :: Text
thingTypeProperties :: Maybe ThingTypeProperties
tags :: Maybe [Tag]
$sel:thingTypeName:CreateThingType' :: CreateThingType -> Text
$sel:thingTypeProperties:CreateThingType' :: CreateThingType -> Maybe ThingTypeProperties
$sel:tags:CreateThingType' :: CreateThingType -> Maybe [Tag]
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"tags" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Tag]
tags,
            (Key
"thingTypeProperties" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ThingTypeProperties
thingTypeProperties
          ]
      )

instance Data.ToPath CreateThingType where
  toPath :: CreateThingType -> ByteString
toPath CreateThingType' {Maybe [Tag]
Maybe ThingTypeProperties
Text
thingTypeName :: Text
thingTypeProperties :: Maybe ThingTypeProperties
tags :: Maybe [Tag]
$sel:thingTypeName:CreateThingType' :: CreateThingType -> Text
$sel:thingTypeProperties:CreateThingType' :: CreateThingType -> Maybe ThingTypeProperties
$sel:tags:CreateThingType' :: CreateThingType -> Maybe [Tag]
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/thing-types/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
thingTypeName]

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

-- | The output of the CreateThingType operation.
--
-- /See:/ 'newCreateThingTypeResponse' smart constructor.
data CreateThingTypeResponse = CreateThingTypeResponse'
  { -- | The Amazon Resource Name (ARN) of the thing type.
    CreateThingTypeResponse -> Maybe Text
thingTypeArn :: Prelude.Maybe Prelude.Text,
    -- | The thing type ID.
    CreateThingTypeResponse -> Maybe Text
thingTypeId :: Prelude.Maybe Prelude.Text,
    -- | The name of the thing type.
    CreateThingTypeResponse -> Maybe Text
thingTypeName :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    CreateThingTypeResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateThingTypeResponse -> CreateThingTypeResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateThingTypeResponse -> CreateThingTypeResponse -> Bool
$c/= :: CreateThingTypeResponse -> CreateThingTypeResponse -> Bool
== :: CreateThingTypeResponse -> CreateThingTypeResponse -> Bool
$c== :: CreateThingTypeResponse -> CreateThingTypeResponse -> Bool
Prelude.Eq, ReadPrec [CreateThingTypeResponse]
ReadPrec CreateThingTypeResponse
Int -> ReadS CreateThingTypeResponse
ReadS [CreateThingTypeResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateThingTypeResponse]
$creadListPrec :: ReadPrec [CreateThingTypeResponse]
readPrec :: ReadPrec CreateThingTypeResponse
$creadPrec :: ReadPrec CreateThingTypeResponse
readList :: ReadS [CreateThingTypeResponse]
$creadList :: ReadS [CreateThingTypeResponse]
readsPrec :: Int -> ReadS CreateThingTypeResponse
$creadsPrec :: Int -> ReadS CreateThingTypeResponse
Prelude.Read, Int -> CreateThingTypeResponse -> ShowS
[CreateThingTypeResponse] -> ShowS
CreateThingTypeResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateThingTypeResponse] -> ShowS
$cshowList :: [CreateThingTypeResponse] -> ShowS
show :: CreateThingTypeResponse -> String
$cshow :: CreateThingTypeResponse -> String
showsPrec :: Int -> CreateThingTypeResponse -> ShowS
$cshowsPrec :: Int -> CreateThingTypeResponse -> ShowS
Prelude.Show, forall x. Rep CreateThingTypeResponse x -> CreateThingTypeResponse
forall x. CreateThingTypeResponse -> Rep CreateThingTypeResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateThingTypeResponse x -> CreateThingTypeResponse
$cfrom :: forall x. CreateThingTypeResponse -> Rep CreateThingTypeResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateThingTypeResponse' 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:
--
-- 'thingTypeArn', 'createThingTypeResponse_thingTypeArn' - The Amazon Resource Name (ARN) of the thing type.
--
-- 'thingTypeId', 'createThingTypeResponse_thingTypeId' - The thing type ID.
--
-- 'thingTypeName', 'createThingTypeResponse_thingTypeName' - The name of the thing type.
--
-- 'httpStatus', 'createThingTypeResponse_httpStatus' - The response's http status code.
newCreateThingTypeResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateThingTypeResponse
newCreateThingTypeResponse :: Int -> CreateThingTypeResponse
newCreateThingTypeResponse Int
pHttpStatus_ =
  CreateThingTypeResponse'
    { $sel:thingTypeArn:CreateThingTypeResponse' :: Maybe Text
thingTypeArn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:thingTypeId:CreateThingTypeResponse' :: Maybe Text
thingTypeId = forall a. Maybe a
Prelude.Nothing,
      $sel:thingTypeName:CreateThingTypeResponse' :: Maybe Text
thingTypeName = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateThingTypeResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The Amazon Resource Name (ARN) of the thing type.
createThingTypeResponse_thingTypeArn :: Lens.Lens' CreateThingTypeResponse (Prelude.Maybe Prelude.Text)
createThingTypeResponse_thingTypeArn :: Lens' CreateThingTypeResponse (Maybe Text)
createThingTypeResponse_thingTypeArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateThingTypeResponse' {Maybe Text
thingTypeArn :: Maybe Text
$sel:thingTypeArn:CreateThingTypeResponse' :: CreateThingTypeResponse -> Maybe Text
thingTypeArn} -> Maybe Text
thingTypeArn) (\s :: CreateThingTypeResponse
s@CreateThingTypeResponse' {} Maybe Text
a -> CreateThingTypeResponse
s {$sel:thingTypeArn:CreateThingTypeResponse' :: Maybe Text
thingTypeArn = Maybe Text
a} :: CreateThingTypeResponse)

-- | The thing type ID.
createThingTypeResponse_thingTypeId :: Lens.Lens' CreateThingTypeResponse (Prelude.Maybe Prelude.Text)
createThingTypeResponse_thingTypeId :: Lens' CreateThingTypeResponse (Maybe Text)
createThingTypeResponse_thingTypeId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateThingTypeResponse' {Maybe Text
thingTypeId :: Maybe Text
$sel:thingTypeId:CreateThingTypeResponse' :: CreateThingTypeResponse -> Maybe Text
thingTypeId} -> Maybe Text
thingTypeId) (\s :: CreateThingTypeResponse
s@CreateThingTypeResponse' {} Maybe Text
a -> CreateThingTypeResponse
s {$sel:thingTypeId:CreateThingTypeResponse' :: Maybe Text
thingTypeId = Maybe Text
a} :: CreateThingTypeResponse)

-- | The name of the thing type.
createThingTypeResponse_thingTypeName :: Lens.Lens' CreateThingTypeResponse (Prelude.Maybe Prelude.Text)
createThingTypeResponse_thingTypeName :: Lens' CreateThingTypeResponse (Maybe Text)
createThingTypeResponse_thingTypeName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateThingTypeResponse' {Maybe Text
thingTypeName :: Maybe Text
$sel:thingTypeName:CreateThingTypeResponse' :: CreateThingTypeResponse -> Maybe Text
thingTypeName} -> Maybe Text
thingTypeName) (\s :: CreateThingTypeResponse
s@CreateThingTypeResponse' {} Maybe Text
a -> CreateThingTypeResponse
s {$sel:thingTypeName:CreateThingTypeResponse' :: Maybe Text
thingTypeName = Maybe Text
a} :: CreateThingTypeResponse)

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

instance Prelude.NFData CreateThingTypeResponse where
  rnf :: CreateThingTypeResponse -> ()
rnf CreateThingTypeResponse' {Int
Maybe Text
httpStatus :: Int
thingTypeName :: Maybe Text
thingTypeId :: Maybe Text
thingTypeArn :: Maybe Text
$sel:httpStatus:CreateThingTypeResponse' :: CreateThingTypeResponse -> Int
$sel:thingTypeName:CreateThingTypeResponse' :: CreateThingTypeResponse -> Maybe Text
$sel:thingTypeId:CreateThingTypeResponse' :: CreateThingTypeResponse -> Maybe Text
$sel:thingTypeArn:CreateThingTypeResponse' :: CreateThingTypeResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
thingTypeArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
thingTypeId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
thingTypeName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus