{-# 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.DescribeThingType
-- 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 information about the specified thing type.
--
-- Requires permission to access the
-- <https://docs.aws.amazon.com/service-authorization/latest/reference/list_awsiot.html#awsiot-actions-as-permissions DescribeThingType>
-- action.
module Amazonka.IoT.DescribeThingType
  ( -- * Creating a Request
    DescribeThingType (..),
    newDescribeThingType,

    -- * Request Lenses
    describeThingType_thingTypeName,

    -- * Destructuring the Response
    DescribeThingTypeResponse (..),
    newDescribeThingTypeResponse,

    -- * Response Lenses
    describeThingTypeResponse_thingTypeArn,
    describeThingTypeResponse_thingTypeId,
    describeThingTypeResponse_thingTypeMetadata,
    describeThingTypeResponse_thingTypeName,
    describeThingTypeResponse_thingTypeProperties,
    describeThingTypeResponse_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 DescribeThingType operation.
--
-- /See:/ 'newDescribeThingType' smart constructor.
data DescribeThingType = DescribeThingType'
  { -- | The name of the thing type.
    DescribeThingType -> Text
thingTypeName :: Prelude.Text
  }
  deriving (DescribeThingType -> DescribeThingType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeThingType -> DescribeThingType -> Bool
$c/= :: DescribeThingType -> DescribeThingType -> Bool
== :: DescribeThingType -> DescribeThingType -> Bool
$c== :: DescribeThingType -> DescribeThingType -> Bool
Prelude.Eq, ReadPrec [DescribeThingType]
ReadPrec DescribeThingType
Int -> ReadS DescribeThingType
ReadS [DescribeThingType]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeThingType]
$creadListPrec :: ReadPrec [DescribeThingType]
readPrec :: ReadPrec DescribeThingType
$creadPrec :: ReadPrec DescribeThingType
readList :: ReadS [DescribeThingType]
$creadList :: ReadS [DescribeThingType]
readsPrec :: Int -> ReadS DescribeThingType
$creadsPrec :: Int -> ReadS DescribeThingType
Prelude.Read, Int -> DescribeThingType -> ShowS
[DescribeThingType] -> ShowS
DescribeThingType -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeThingType] -> ShowS
$cshowList :: [DescribeThingType] -> ShowS
show :: DescribeThingType -> String
$cshow :: DescribeThingType -> String
showsPrec :: Int -> DescribeThingType -> ShowS
$cshowsPrec :: Int -> DescribeThingType -> ShowS
Prelude.Show, forall x. Rep DescribeThingType x -> DescribeThingType
forall x. DescribeThingType -> Rep DescribeThingType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeThingType x -> DescribeThingType
$cfrom :: forall x. DescribeThingType -> Rep DescribeThingType x
Prelude.Generic)

-- |
-- Create a value of 'DescribeThingType' 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:
--
-- 'thingTypeName', 'describeThingType_thingTypeName' - The name of the thing type.
newDescribeThingType ::
  -- | 'thingTypeName'
  Prelude.Text ->
  DescribeThingType
newDescribeThingType :: Text -> DescribeThingType
newDescribeThingType Text
pThingTypeName_ =
  DescribeThingType' {$sel:thingTypeName:DescribeThingType' :: Text
thingTypeName = Text
pThingTypeName_}

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

instance Core.AWSRequest DescribeThingType where
  type
    AWSResponse DescribeThingType =
      DescribeThingTypeResponse
  request :: (Service -> Service)
-> DescribeThingType -> Request DescribeThingType
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 DescribeThingType
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeThingType)))
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 ThingTypeMetadata
-> Maybe Text
-> Maybe ThingTypeProperties
-> Int
-> DescribeThingTypeResponse
DescribeThingTypeResponse'
            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
"thingTypeMetadata")
            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.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"thingTypeProperties")
            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 DescribeThingType where
  hashWithSalt :: Int -> DescribeThingType -> Int
hashWithSalt Int
_salt DescribeThingType' {Text
thingTypeName :: Text
$sel:thingTypeName:DescribeThingType' :: DescribeThingType -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
thingTypeName

instance Prelude.NFData DescribeThingType where
  rnf :: DescribeThingType -> ()
rnf DescribeThingType' {Text
thingTypeName :: Text
$sel:thingTypeName:DescribeThingType' :: DescribeThingType -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
thingTypeName

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

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

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

-- | The output for the DescribeThingType operation.
--
-- /See:/ 'newDescribeThingTypeResponse' smart constructor.
data DescribeThingTypeResponse = DescribeThingTypeResponse'
  { -- | The thing type ARN.
    DescribeThingTypeResponse -> Maybe Text
thingTypeArn :: Prelude.Maybe Prelude.Text,
    -- | The thing type ID.
    DescribeThingTypeResponse -> Maybe Text
thingTypeId :: Prelude.Maybe Prelude.Text,
    -- | The ThingTypeMetadata contains additional information about the thing
    -- type including: creation date and time, a value indicating whether the
    -- thing type is deprecated, and a date and time when it was deprecated.
    DescribeThingTypeResponse -> Maybe ThingTypeMetadata
thingTypeMetadata :: Prelude.Maybe ThingTypeMetadata,
    -- | The name of the thing type.
    DescribeThingTypeResponse -> Maybe Text
thingTypeName :: Prelude.Maybe Prelude.Text,
    -- | The ThingTypeProperties contains information about the thing type
    -- including description, and a list of searchable thing attribute names.
    DescribeThingTypeResponse -> Maybe ThingTypeProperties
thingTypeProperties :: Prelude.Maybe ThingTypeProperties,
    -- | The response's http status code.
    DescribeThingTypeResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeThingTypeResponse -> DescribeThingTypeResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeThingTypeResponse -> DescribeThingTypeResponse -> Bool
$c/= :: DescribeThingTypeResponse -> DescribeThingTypeResponse -> Bool
== :: DescribeThingTypeResponse -> DescribeThingTypeResponse -> Bool
$c== :: DescribeThingTypeResponse -> DescribeThingTypeResponse -> Bool
Prelude.Eq, ReadPrec [DescribeThingTypeResponse]
ReadPrec DescribeThingTypeResponse
Int -> ReadS DescribeThingTypeResponse
ReadS [DescribeThingTypeResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeThingTypeResponse]
$creadListPrec :: ReadPrec [DescribeThingTypeResponse]
readPrec :: ReadPrec DescribeThingTypeResponse
$creadPrec :: ReadPrec DescribeThingTypeResponse
readList :: ReadS [DescribeThingTypeResponse]
$creadList :: ReadS [DescribeThingTypeResponse]
readsPrec :: Int -> ReadS DescribeThingTypeResponse
$creadsPrec :: Int -> ReadS DescribeThingTypeResponse
Prelude.Read, Int -> DescribeThingTypeResponse -> ShowS
[DescribeThingTypeResponse] -> ShowS
DescribeThingTypeResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeThingTypeResponse] -> ShowS
$cshowList :: [DescribeThingTypeResponse] -> ShowS
show :: DescribeThingTypeResponse -> String
$cshow :: DescribeThingTypeResponse -> String
showsPrec :: Int -> DescribeThingTypeResponse -> ShowS
$cshowsPrec :: Int -> DescribeThingTypeResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeThingTypeResponse x -> DescribeThingTypeResponse
forall x.
DescribeThingTypeResponse -> Rep DescribeThingTypeResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeThingTypeResponse x -> DescribeThingTypeResponse
$cfrom :: forall x.
DescribeThingTypeResponse -> Rep DescribeThingTypeResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeThingTypeResponse' 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', 'describeThingTypeResponse_thingTypeArn' - The thing type ARN.
--
-- 'thingTypeId', 'describeThingTypeResponse_thingTypeId' - The thing type ID.
--
-- 'thingTypeMetadata', 'describeThingTypeResponse_thingTypeMetadata' - The ThingTypeMetadata contains additional information about the thing
-- type including: creation date and time, a value indicating whether the
-- thing type is deprecated, and a date and time when it was deprecated.
--
-- 'thingTypeName', 'describeThingTypeResponse_thingTypeName' - The name of the thing type.
--
-- 'thingTypeProperties', 'describeThingTypeResponse_thingTypeProperties' - The ThingTypeProperties contains information about the thing type
-- including description, and a list of searchable thing attribute names.
--
-- 'httpStatus', 'describeThingTypeResponse_httpStatus' - The response's http status code.
newDescribeThingTypeResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeThingTypeResponse
newDescribeThingTypeResponse :: Int -> DescribeThingTypeResponse
newDescribeThingTypeResponse Int
pHttpStatus_ =
  DescribeThingTypeResponse'
    { $sel:thingTypeArn:DescribeThingTypeResponse' :: Maybe Text
thingTypeArn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:thingTypeId:DescribeThingTypeResponse' :: Maybe Text
thingTypeId = forall a. Maybe a
Prelude.Nothing,
      $sel:thingTypeMetadata:DescribeThingTypeResponse' :: Maybe ThingTypeMetadata
thingTypeMetadata = forall a. Maybe a
Prelude.Nothing,
      $sel:thingTypeName:DescribeThingTypeResponse' :: Maybe Text
thingTypeName = forall a. Maybe a
Prelude.Nothing,
      $sel:thingTypeProperties:DescribeThingTypeResponse' :: Maybe ThingTypeProperties
thingTypeProperties = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeThingTypeResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The thing type ARN.
describeThingTypeResponse_thingTypeArn :: Lens.Lens' DescribeThingTypeResponse (Prelude.Maybe Prelude.Text)
describeThingTypeResponse_thingTypeArn :: Lens' DescribeThingTypeResponse (Maybe Text)
describeThingTypeResponse_thingTypeArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeThingTypeResponse' {Maybe Text
thingTypeArn :: Maybe Text
$sel:thingTypeArn:DescribeThingTypeResponse' :: DescribeThingTypeResponse -> Maybe Text
thingTypeArn} -> Maybe Text
thingTypeArn) (\s :: DescribeThingTypeResponse
s@DescribeThingTypeResponse' {} Maybe Text
a -> DescribeThingTypeResponse
s {$sel:thingTypeArn:DescribeThingTypeResponse' :: Maybe Text
thingTypeArn = Maybe Text
a} :: DescribeThingTypeResponse)

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

-- | The ThingTypeMetadata contains additional information about the thing
-- type including: creation date and time, a value indicating whether the
-- thing type is deprecated, and a date and time when it was deprecated.
describeThingTypeResponse_thingTypeMetadata :: Lens.Lens' DescribeThingTypeResponse (Prelude.Maybe ThingTypeMetadata)
describeThingTypeResponse_thingTypeMetadata :: Lens' DescribeThingTypeResponse (Maybe ThingTypeMetadata)
describeThingTypeResponse_thingTypeMetadata = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeThingTypeResponse' {Maybe ThingTypeMetadata
thingTypeMetadata :: Maybe ThingTypeMetadata
$sel:thingTypeMetadata:DescribeThingTypeResponse' :: DescribeThingTypeResponse -> Maybe ThingTypeMetadata
thingTypeMetadata} -> Maybe ThingTypeMetadata
thingTypeMetadata) (\s :: DescribeThingTypeResponse
s@DescribeThingTypeResponse' {} Maybe ThingTypeMetadata
a -> DescribeThingTypeResponse
s {$sel:thingTypeMetadata:DescribeThingTypeResponse' :: Maybe ThingTypeMetadata
thingTypeMetadata = Maybe ThingTypeMetadata
a} :: DescribeThingTypeResponse)

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

-- | The ThingTypeProperties contains information about the thing type
-- including description, and a list of searchable thing attribute names.
describeThingTypeResponse_thingTypeProperties :: Lens.Lens' DescribeThingTypeResponse (Prelude.Maybe ThingTypeProperties)
describeThingTypeResponse_thingTypeProperties :: Lens' DescribeThingTypeResponse (Maybe ThingTypeProperties)
describeThingTypeResponse_thingTypeProperties = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeThingTypeResponse' {Maybe ThingTypeProperties
thingTypeProperties :: Maybe ThingTypeProperties
$sel:thingTypeProperties:DescribeThingTypeResponse' :: DescribeThingTypeResponse -> Maybe ThingTypeProperties
thingTypeProperties} -> Maybe ThingTypeProperties
thingTypeProperties) (\s :: DescribeThingTypeResponse
s@DescribeThingTypeResponse' {} Maybe ThingTypeProperties
a -> DescribeThingTypeResponse
s {$sel:thingTypeProperties:DescribeThingTypeResponse' :: Maybe ThingTypeProperties
thingTypeProperties = Maybe ThingTypeProperties
a} :: DescribeThingTypeResponse)

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

instance Prelude.NFData DescribeThingTypeResponse where
  rnf :: DescribeThingTypeResponse -> ()
rnf DescribeThingTypeResponse' {Int
Maybe Text
Maybe ThingTypeMetadata
Maybe ThingTypeProperties
httpStatus :: Int
thingTypeProperties :: Maybe ThingTypeProperties
thingTypeName :: Maybe Text
thingTypeMetadata :: Maybe ThingTypeMetadata
thingTypeId :: Maybe Text
thingTypeArn :: Maybe Text
$sel:httpStatus:DescribeThingTypeResponse' :: DescribeThingTypeResponse -> Int
$sel:thingTypeProperties:DescribeThingTypeResponse' :: DescribeThingTypeResponse -> Maybe ThingTypeProperties
$sel:thingTypeName:DescribeThingTypeResponse' :: DescribeThingTypeResponse -> Maybe Text
$sel:thingTypeMetadata:DescribeThingTypeResponse' :: DescribeThingTypeResponse -> Maybe ThingTypeMetadata
$sel:thingTypeId:DescribeThingTypeResponse' :: DescribeThingTypeResponse -> Maybe Text
$sel:thingTypeArn:DescribeThingTypeResponse' :: DescribeThingTypeResponse -> 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 ThingTypeMetadata
thingTypeMetadata
      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 Maybe ThingTypeProperties
thingTypeProperties
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus