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

    -- * Request Lenses
    describeThingGroup_thingGroupName,

    -- * Destructuring the Response
    DescribeThingGroupResponse (..),
    newDescribeThingGroupResponse,

    -- * Response Lenses
    describeThingGroupResponse_indexName,
    describeThingGroupResponse_queryString,
    describeThingGroupResponse_queryVersion,
    describeThingGroupResponse_status,
    describeThingGroupResponse_thingGroupArn,
    describeThingGroupResponse_thingGroupId,
    describeThingGroupResponse_thingGroupMetadata,
    describeThingGroupResponse_thingGroupName,
    describeThingGroupResponse_thingGroupProperties,
    describeThingGroupResponse_version,
    describeThingGroupResponse_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

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

-- |
-- Create a value of 'DescribeThingGroup' 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:
--
-- 'thingGroupName', 'describeThingGroup_thingGroupName' - The name of the thing group.
newDescribeThingGroup ::
  -- | 'thingGroupName'
  Prelude.Text ->
  DescribeThingGroup
newDescribeThingGroup :: Text -> DescribeThingGroup
newDescribeThingGroup Text
pThingGroupName_ =
  DescribeThingGroup'
    { $sel:thingGroupName:DescribeThingGroup' :: Text
thingGroupName =
        Text
pThingGroupName_
    }

-- | The name of the thing group.
describeThingGroup_thingGroupName :: Lens.Lens' DescribeThingGroup Prelude.Text
describeThingGroup_thingGroupName :: Lens' DescribeThingGroup Text
describeThingGroup_thingGroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeThingGroup' {Text
thingGroupName :: Text
$sel:thingGroupName:DescribeThingGroup' :: DescribeThingGroup -> Text
thingGroupName} -> Text
thingGroupName) (\s :: DescribeThingGroup
s@DescribeThingGroup' {} Text
a -> DescribeThingGroup
s {$sel:thingGroupName:DescribeThingGroup' :: Text
thingGroupName = Text
a} :: DescribeThingGroup)

instance Core.AWSRequest DescribeThingGroup where
  type
    AWSResponse DescribeThingGroup =
      DescribeThingGroupResponse
  request :: (Service -> Service)
-> DescribeThingGroup -> Request DescribeThingGroup
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 DescribeThingGroup
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeThingGroup)))
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
-> Maybe DynamicGroupStatus
-> Maybe Text
-> Maybe Text
-> Maybe ThingGroupMetadata
-> Maybe Text
-> Maybe ThingGroupProperties
-> Maybe Integer
-> Int
-> DescribeThingGroupResponse
DescribeThingGroupResponse'
            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
"indexName")
            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
"queryString")
            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
"queryVersion")
            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
"status")
            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
"thingGroupArn")
            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
"thingGroupId")
            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
"thingGroupMetadata")
            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
"thingGroupName")
            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
"thingGroupProperties")
            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 DescribeThingGroup where
  hashWithSalt :: Int -> DescribeThingGroup -> Int
hashWithSalt Int
_salt DescribeThingGroup' {Text
thingGroupName :: Text
$sel:thingGroupName:DescribeThingGroup' :: DescribeThingGroup -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
thingGroupName

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

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

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

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

-- | /See:/ 'newDescribeThingGroupResponse' smart constructor.
data DescribeThingGroupResponse = DescribeThingGroupResponse'
  { -- | The dynamic thing group index name.
    DescribeThingGroupResponse -> Maybe Text
indexName :: Prelude.Maybe Prelude.Text,
    -- | The dynamic thing group search query string.
    DescribeThingGroupResponse -> Maybe Text
queryString :: Prelude.Maybe Prelude.Text,
    -- | The dynamic thing group query version.
    DescribeThingGroupResponse -> Maybe Text
queryVersion :: Prelude.Maybe Prelude.Text,
    -- | The dynamic thing group status.
    DescribeThingGroupResponse -> Maybe DynamicGroupStatus
status :: Prelude.Maybe DynamicGroupStatus,
    -- | The thing group ARN.
    DescribeThingGroupResponse -> Maybe Text
thingGroupArn :: Prelude.Maybe Prelude.Text,
    -- | The thing group ID.
    DescribeThingGroupResponse -> Maybe Text
thingGroupId :: Prelude.Maybe Prelude.Text,
    -- | Thing group metadata.
    DescribeThingGroupResponse -> Maybe ThingGroupMetadata
thingGroupMetadata :: Prelude.Maybe ThingGroupMetadata,
    -- | The name of the thing group.
    DescribeThingGroupResponse -> Maybe Text
thingGroupName :: Prelude.Maybe Prelude.Text,
    -- | The thing group properties.
    DescribeThingGroupResponse -> Maybe ThingGroupProperties
thingGroupProperties :: Prelude.Maybe ThingGroupProperties,
    -- | The version of the thing group.
    DescribeThingGroupResponse -> Maybe Integer
version :: Prelude.Maybe Prelude.Integer,
    -- | The response's http status code.
    DescribeThingGroupResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeThingGroupResponse -> DescribeThingGroupResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeThingGroupResponse -> DescribeThingGroupResponse -> Bool
$c/= :: DescribeThingGroupResponse -> DescribeThingGroupResponse -> Bool
== :: DescribeThingGroupResponse -> DescribeThingGroupResponse -> Bool
$c== :: DescribeThingGroupResponse -> DescribeThingGroupResponse -> Bool
Prelude.Eq, ReadPrec [DescribeThingGroupResponse]
ReadPrec DescribeThingGroupResponse
Int -> ReadS DescribeThingGroupResponse
ReadS [DescribeThingGroupResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeThingGroupResponse]
$creadListPrec :: ReadPrec [DescribeThingGroupResponse]
readPrec :: ReadPrec DescribeThingGroupResponse
$creadPrec :: ReadPrec DescribeThingGroupResponse
readList :: ReadS [DescribeThingGroupResponse]
$creadList :: ReadS [DescribeThingGroupResponse]
readsPrec :: Int -> ReadS DescribeThingGroupResponse
$creadsPrec :: Int -> ReadS DescribeThingGroupResponse
Prelude.Read, Int -> DescribeThingGroupResponse -> ShowS
[DescribeThingGroupResponse] -> ShowS
DescribeThingGroupResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeThingGroupResponse] -> ShowS
$cshowList :: [DescribeThingGroupResponse] -> ShowS
show :: DescribeThingGroupResponse -> String
$cshow :: DescribeThingGroupResponse -> String
showsPrec :: Int -> DescribeThingGroupResponse -> ShowS
$cshowsPrec :: Int -> DescribeThingGroupResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeThingGroupResponse x -> DescribeThingGroupResponse
forall x.
DescribeThingGroupResponse -> Rep DescribeThingGroupResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeThingGroupResponse x -> DescribeThingGroupResponse
$cfrom :: forall x.
DescribeThingGroupResponse -> Rep DescribeThingGroupResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeThingGroupResponse' 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:
--
-- 'indexName', 'describeThingGroupResponse_indexName' - The dynamic thing group index name.
--
-- 'queryString', 'describeThingGroupResponse_queryString' - The dynamic thing group search query string.
--
-- 'queryVersion', 'describeThingGroupResponse_queryVersion' - The dynamic thing group query version.
--
-- 'status', 'describeThingGroupResponse_status' - The dynamic thing group status.
--
-- 'thingGroupArn', 'describeThingGroupResponse_thingGroupArn' - The thing group ARN.
--
-- 'thingGroupId', 'describeThingGroupResponse_thingGroupId' - The thing group ID.
--
-- 'thingGroupMetadata', 'describeThingGroupResponse_thingGroupMetadata' - Thing group metadata.
--
-- 'thingGroupName', 'describeThingGroupResponse_thingGroupName' - The name of the thing group.
--
-- 'thingGroupProperties', 'describeThingGroupResponse_thingGroupProperties' - The thing group properties.
--
-- 'version', 'describeThingGroupResponse_version' - The version of the thing group.
--
-- 'httpStatus', 'describeThingGroupResponse_httpStatus' - The response's http status code.
newDescribeThingGroupResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeThingGroupResponse
newDescribeThingGroupResponse :: Int -> DescribeThingGroupResponse
newDescribeThingGroupResponse Int
pHttpStatus_ =
  DescribeThingGroupResponse'
    { $sel:indexName:DescribeThingGroupResponse' :: Maybe Text
indexName =
        forall a. Maybe a
Prelude.Nothing,
      $sel:queryString:DescribeThingGroupResponse' :: Maybe Text
queryString = forall a. Maybe a
Prelude.Nothing,
      $sel:queryVersion:DescribeThingGroupResponse' :: Maybe Text
queryVersion = forall a. Maybe a
Prelude.Nothing,
      $sel:status:DescribeThingGroupResponse' :: Maybe DynamicGroupStatus
status = forall a. Maybe a
Prelude.Nothing,
      $sel:thingGroupArn:DescribeThingGroupResponse' :: Maybe Text
thingGroupArn = forall a. Maybe a
Prelude.Nothing,
      $sel:thingGroupId:DescribeThingGroupResponse' :: Maybe Text
thingGroupId = forall a. Maybe a
Prelude.Nothing,
      $sel:thingGroupMetadata:DescribeThingGroupResponse' :: Maybe ThingGroupMetadata
thingGroupMetadata = forall a. Maybe a
Prelude.Nothing,
      $sel:thingGroupName:DescribeThingGroupResponse' :: Maybe Text
thingGroupName = forall a. Maybe a
Prelude.Nothing,
      $sel:thingGroupProperties:DescribeThingGroupResponse' :: Maybe ThingGroupProperties
thingGroupProperties = forall a. Maybe a
Prelude.Nothing,
      $sel:version:DescribeThingGroupResponse' :: Maybe Integer
version = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeThingGroupResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The dynamic thing group index name.
describeThingGroupResponse_indexName :: Lens.Lens' DescribeThingGroupResponse (Prelude.Maybe Prelude.Text)
describeThingGroupResponse_indexName :: Lens' DescribeThingGroupResponse (Maybe Text)
describeThingGroupResponse_indexName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeThingGroupResponse' {Maybe Text
indexName :: Maybe Text
$sel:indexName:DescribeThingGroupResponse' :: DescribeThingGroupResponse -> Maybe Text
indexName} -> Maybe Text
indexName) (\s :: DescribeThingGroupResponse
s@DescribeThingGroupResponse' {} Maybe Text
a -> DescribeThingGroupResponse
s {$sel:indexName:DescribeThingGroupResponse' :: Maybe Text
indexName = Maybe Text
a} :: DescribeThingGroupResponse)

-- | The dynamic thing group search query string.
describeThingGroupResponse_queryString :: Lens.Lens' DescribeThingGroupResponse (Prelude.Maybe Prelude.Text)
describeThingGroupResponse_queryString :: Lens' DescribeThingGroupResponse (Maybe Text)
describeThingGroupResponse_queryString = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeThingGroupResponse' {Maybe Text
queryString :: Maybe Text
$sel:queryString:DescribeThingGroupResponse' :: DescribeThingGroupResponse -> Maybe Text
queryString} -> Maybe Text
queryString) (\s :: DescribeThingGroupResponse
s@DescribeThingGroupResponse' {} Maybe Text
a -> DescribeThingGroupResponse
s {$sel:queryString:DescribeThingGroupResponse' :: Maybe Text
queryString = Maybe Text
a} :: DescribeThingGroupResponse)

-- | The dynamic thing group query version.
describeThingGroupResponse_queryVersion :: Lens.Lens' DescribeThingGroupResponse (Prelude.Maybe Prelude.Text)
describeThingGroupResponse_queryVersion :: Lens' DescribeThingGroupResponse (Maybe Text)
describeThingGroupResponse_queryVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeThingGroupResponse' {Maybe Text
queryVersion :: Maybe Text
$sel:queryVersion:DescribeThingGroupResponse' :: DescribeThingGroupResponse -> Maybe Text
queryVersion} -> Maybe Text
queryVersion) (\s :: DescribeThingGroupResponse
s@DescribeThingGroupResponse' {} Maybe Text
a -> DescribeThingGroupResponse
s {$sel:queryVersion:DescribeThingGroupResponse' :: Maybe Text
queryVersion = Maybe Text
a} :: DescribeThingGroupResponse)

-- | The dynamic thing group status.
describeThingGroupResponse_status :: Lens.Lens' DescribeThingGroupResponse (Prelude.Maybe DynamicGroupStatus)
describeThingGroupResponse_status :: Lens' DescribeThingGroupResponse (Maybe DynamicGroupStatus)
describeThingGroupResponse_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeThingGroupResponse' {Maybe DynamicGroupStatus
status :: Maybe DynamicGroupStatus
$sel:status:DescribeThingGroupResponse' :: DescribeThingGroupResponse -> Maybe DynamicGroupStatus
status} -> Maybe DynamicGroupStatus
status) (\s :: DescribeThingGroupResponse
s@DescribeThingGroupResponse' {} Maybe DynamicGroupStatus
a -> DescribeThingGroupResponse
s {$sel:status:DescribeThingGroupResponse' :: Maybe DynamicGroupStatus
status = Maybe DynamicGroupStatus
a} :: DescribeThingGroupResponse)

-- | The thing group ARN.
describeThingGroupResponse_thingGroupArn :: Lens.Lens' DescribeThingGroupResponse (Prelude.Maybe Prelude.Text)
describeThingGroupResponse_thingGroupArn :: Lens' DescribeThingGroupResponse (Maybe Text)
describeThingGroupResponse_thingGroupArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeThingGroupResponse' {Maybe Text
thingGroupArn :: Maybe Text
$sel:thingGroupArn:DescribeThingGroupResponse' :: DescribeThingGroupResponse -> Maybe Text
thingGroupArn} -> Maybe Text
thingGroupArn) (\s :: DescribeThingGroupResponse
s@DescribeThingGroupResponse' {} Maybe Text
a -> DescribeThingGroupResponse
s {$sel:thingGroupArn:DescribeThingGroupResponse' :: Maybe Text
thingGroupArn = Maybe Text
a} :: DescribeThingGroupResponse)

-- | The thing group ID.
describeThingGroupResponse_thingGroupId :: Lens.Lens' DescribeThingGroupResponse (Prelude.Maybe Prelude.Text)
describeThingGroupResponse_thingGroupId :: Lens' DescribeThingGroupResponse (Maybe Text)
describeThingGroupResponse_thingGroupId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeThingGroupResponse' {Maybe Text
thingGroupId :: Maybe Text
$sel:thingGroupId:DescribeThingGroupResponse' :: DescribeThingGroupResponse -> Maybe Text
thingGroupId} -> Maybe Text
thingGroupId) (\s :: DescribeThingGroupResponse
s@DescribeThingGroupResponse' {} Maybe Text
a -> DescribeThingGroupResponse
s {$sel:thingGroupId:DescribeThingGroupResponse' :: Maybe Text
thingGroupId = Maybe Text
a} :: DescribeThingGroupResponse)

-- | Thing group metadata.
describeThingGroupResponse_thingGroupMetadata :: Lens.Lens' DescribeThingGroupResponse (Prelude.Maybe ThingGroupMetadata)
describeThingGroupResponse_thingGroupMetadata :: Lens' DescribeThingGroupResponse (Maybe ThingGroupMetadata)
describeThingGroupResponse_thingGroupMetadata = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeThingGroupResponse' {Maybe ThingGroupMetadata
thingGroupMetadata :: Maybe ThingGroupMetadata
$sel:thingGroupMetadata:DescribeThingGroupResponse' :: DescribeThingGroupResponse -> Maybe ThingGroupMetadata
thingGroupMetadata} -> Maybe ThingGroupMetadata
thingGroupMetadata) (\s :: DescribeThingGroupResponse
s@DescribeThingGroupResponse' {} Maybe ThingGroupMetadata
a -> DescribeThingGroupResponse
s {$sel:thingGroupMetadata:DescribeThingGroupResponse' :: Maybe ThingGroupMetadata
thingGroupMetadata = Maybe ThingGroupMetadata
a} :: DescribeThingGroupResponse)

-- | The name of the thing group.
describeThingGroupResponse_thingGroupName :: Lens.Lens' DescribeThingGroupResponse (Prelude.Maybe Prelude.Text)
describeThingGroupResponse_thingGroupName :: Lens' DescribeThingGroupResponse (Maybe Text)
describeThingGroupResponse_thingGroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeThingGroupResponse' {Maybe Text
thingGroupName :: Maybe Text
$sel:thingGroupName:DescribeThingGroupResponse' :: DescribeThingGroupResponse -> Maybe Text
thingGroupName} -> Maybe Text
thingGroupName) (\s :: DescribeThingGroupResponse
s@DescribeThingGroupResponse' {} Maybe Text
a -> DescribeThingGroupResponse
s {$sel:thingGroupName:DescribeThingGroupResponse' :: Maybe Text
thingGroupName = Maybe Text
a} :: DescribeThingGroupResponse)

-- | The thing group properties.
describeThingGroupResponse_thingGroupProperties :: Lens.Lens' DescribeThingGroupResponse (Prelude.Maybe ThingGroupProperties)
describeThingGroupResponse_thingGroupProperties :: Lens' DescribeThingGroupResponse (Maybe ThingGroupProperties)
describeThingGroupResponse_thingGroupProperties = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeThingGroupResponse' {Maybe ThingGroupProperties
thingGroupProperties :: Maybe ThingGroupProperties
$sel:thingGroupProperties:DescribeThingGroupResponse' :: DescribeThingGroupResponse -> Maybe ThingGroupProperties
thingGroupProperties} -> Maybe ThingGroupProperties
thingGroupProperties) (\s :: DescribeThingGroupResponse
s@DescribeThingGroupResponse' {} Maybe ThingGroupProperties
a -> DescribeThingGroupResponse
s {$sel:thingGroupProperties:DescribeThingGroupResponse' :: Maybe ThingGroupProperties
thingGroupProperties = Maybe ThingGroupProperties
a} :: DescribeThingGroupResponse)

-- | The version of the thing group.
describeThingGroupResponse_version :: Lens.Lens' DescribeThingGroupResponse (Prelude.Maybe Prelude.Integer)
describeThingGroupResponse_version :: Lens' DescribeThingGroupResponse (Maybe Integer)
describeThingGroupResponse_version = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeThingGroupResponse' {Maybe Integer
version :: Maybe Integer
$sel:version:DescribeThingGroupResponse' :: DescribeThingGroupResponse -> Maybe Integer
version} -> Maybe Integer
version) (\s :: DescribeThingGroupResponse
s@DescribeThingGroupResponse' {} Maybe Integer
a -> DescribeThingGroupResponse
s {$sel:version:DescribeThingGroupResponse' :: Maybe Integer
version = Maybe Integer
a} :: DescribeThingGroupResponse)

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

instance Prelude.NFData DescribeThingGroupResponse where
  rnf :: DescribeThingGroupResponse -> ()
rnf DescribeThingGroupResponse' {Int
Maybe Integer
Maybe Text
Maybe DynamicGroupStatus
Maybe ThingGroupMetadata
Maybe ThingGroupProperties
httpStatus :: Int
version :: Maybe Integer
thingGroupProperties :: Maybe ThingGroupProperties
thingGroupName :: Maybe Text
thingGroupMetadata :: Maybe ThingGroupMetadata
thingGroupId :: Maybe Text
thingGroupArn :: Maybe Text
status :: Maybe DynamicGroupStatus
queryVersion :: Maybe Text
queryString :: Maybe Text
indexName :: Maybe Text
$sel:httpStatus:DescribeThingGroupResponse' :: DescribeThingGroupResponse -> Int
$sel:version:DescribeThingGroupResponse' :: DescribeThingGroupResponse -> Maybe Integer
$sel:thingGroupProperties:DescribeThingGroupResponse' :: DescribeThingGroupResponse -> Maybe ThingGroupProperties
$sel:thingGroupName:DescribeThingGroupResponse' :: DescribeThingGroupResponse -> Maybe Text
$sel:thingGroupMetadata:DescribeThingGroupResponse' :: DescribeThingGroupResponse -> Maybe ThingGroupMetadata
$sel:thingGroupId:DescribeThingGroupResponse' :: DescribeThingGroupResponse -> Maybe Text
$sel:thingGroupArn:DescribeThingGroupResponse' :: DescribeThingGroupResponse -> Maybe Text
$sel:status:DescribeThingGroupResponse' :: DescribeThingGroupResponse -> Maybe DynamicGroupStatus
$sel:queryVersion:DescribeThingGroupResponse' :: DescribeThingGroupResponse -> Maybe Text
$sel:queryString:DescribeThingGroupResponse' :: DescribeThingGroupResponse -> Maybe Text
$sel:indexName:DescribeThingGroupResponse' :: DescribeThingGroupResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
indexName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
queryString
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
queryVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DynamicGroupStatus
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
thingGroupArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
thingGroupId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ThingGroupMetadata
thingGroupMetadata
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
thingGroupName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ThingGroupProperties
thingGroupProperties
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
version
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus