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

    -- * Request Lenses
    listNamedShadowsForThing_nextToken,
    listNamedShadowsForThing_pageSize,
    listNamedShadowsForThing_thingName,

    -- * Destructuring the Response
    ListNamedShadowsForThingResponse (..),
    newListNamedShadowsForThingResponse,

    -- * Response Lenses
    listNamedShadowsForThingResponse_nextToken,
    listNamedShadowsForThingResponse_results,
    listNamedShadowsForThingResponse_timestamp,
    listNamedShadowsForThingResponse_httpStatus,
  )
where

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

-- | /See:/ 'newListNamedShadowsForThing' smart constructor.
data ListNamedShadowsForThing = ListNamedShadowsForThing'
  { -- | The token to retrieve the next set of results.
    ListNamedShadowsForThing -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The result page size.
    ListNamedShadowsForThing -> Maybe Natural
pageSize :: Prelude.Maybe Prelude.Natural,
    -- | The name of the thing.
    ListNamedShadowsForThing -> Text
thingName :: Prelude.Text
  }
  deriving (ListNamedShadowsForThing -> ListNamedShadowsForThing -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListNamedShadowsForThing -> ListNamedShadowsForThing -> Bool
$c/= :: ListNamedShadowsForThing -> ListNamedShadowsForThing -> Bool
== :: ListNamedShadowsForThing -> ListNamedShadowsForThing -> Bool
$c== :: ListNamedShadowsForThing -> ListNamedShadowsForThing -> Bool
Prelude.Eq, ReadPrec [ListNamedShadowsForThing]
ReadPrec ListNamedShadowsForThing
Int -> ReadS ListNamedShadowsForThing
ReadS [ListNamedShadowsForThing]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListNamedShadowsForThing]
$creadListPrec :: ReadPrec [ListNamedShadowsForThing]
readPrec :: ReadPrec ListNamedShadowsForThing
$creadPrec :: ReadPrec ListNamedShadowsForThing
readList :: ReadS [ListNamedShadowsForThing]
$creadList :: ReadS [ListNamedShadowsForThing]
readsPrec :: Int -> ReadS ListNamedShadowsForThing
$creadsPrec :: Int -> ReadS ListNamedShadowsForThing
Prelude.Read, Int -> ListNamedShadowsForThing -> ShowS
[ListNamedShadowsForThing] -> ShowS
ListNamedShadowsForThing -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListNamedShadowsForThing] -> ShowS
$cshowList :: [ListNamedShadowsForThing] -> ShowS
show :: ListNamedShadowsForThing -> String
$cshow :: ListNamedShadowsForThing -> String
showsPrec :: Int -> ListNamedShadowsForThing -> ShowS
$cshowsPrec :: Int -> ListNamedShadowsForThing -> ShowS
Prelude.Show, forall x.
Rep ListNamedShadowsForThing x -> ListNamedShadowsForThing
forall x.
ListNamedShadowsForThing -> Rep ListNamedShadowsForThing x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListNamedShadowsForThing x -> ListNamedShadowsForThing
$cfrom :: forall x.
ListNamedShadowsForThing -> Rep ListNamedShadowsForThing x
Prelude.Generic)

-- |
-- Create a value of 'ListNamedShadowsForThing' 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:
--
-- 'nextToken', 'listNamedShadowsForThing_nextToken' - The token to retrieve the next set of results.
--
-- 'pageSize', 'listNamedShadowsForThing_pageSize' - The result page size.
--
-- 'thingName', 'listNamedShadowsForThing_thingName' - The name of the thing.
newListNamedShadowsForThing ::
  -- | 'thingName'
  Prelude.Text ->
  ListNamedShadowsForThing
newListNamedShadowsForThing :: Text -> ListNamedShadowsForThing
newListNamedShadowsForThing Text
pThingName_ =
  ListNamedShadowsForThing'
    { $sel:nextToken:ListNamedShadowsForThing' :: Maybe Text
nextToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:pageSize:ListNamedShadowsForThing' :: Maybe Natural
pageSize = forall a. Maybe a
Prelude.Nothing,
      $sel:thingName:ListNamedShadowsForThing' :: Text
thingName = Text
pThingName_
    }

-- | The token to retrieve the next set of results.
listNamedShadowsForThing_nextToken :: Lens.Lens' ListNamedShadowsForThing (Prelude.Maybe Prelude.Text)
listNamedShadowsForThing_nextToken :: Lens' ListNamedShadowsForThing (Maybe Text)
listNamedShadowsForThing_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListNamedShadowsForThing' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListNamedShadowsForThing' :: ListNamedShadowsForThing -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListNamedShadowsForThing
s@ListNamedShadowsForThing' {} Maybe Text
a -> ListNamedShadowsForThing
s {$sel:nextToken:ListNamedShadowsForThing' :: Maybe Text
nextToken = Maybe Text
a} :: ListNamedShadowsForThing)

-- | The result page size.
listNamedShadowsForThing_pageSize :: Lens.Lens' ListNamedShadowsForThing (Prelude.Maybe Prelude.Natural)
listNamedShadowsForThing_pageSize :: Lens' ListNamedShadowsForThing (Maybe Natural)
listNamedShadowsForThing_pageSize = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListNamedShadowsForThing' {Maybe Natural
pageSize :: Maybe Natural
$sel:pageSize:ListNamedShadowsForThing' :: ListNamedShadowsForThing -> Maybe Natural
pageSize} -> Maybe Natural
pageSize) (\s :: ListNamedShadowsForThing
s@ListNamedShadowsForThing' {} Maybe Natural
a -> ListNamedShadowsForThing
s {$sel:pageSize:ListNamedShadowsForThing' :: Maybe Natural
pageSize = Maybe Natural
a} :: ListNamedShadowsForThing)

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

instance Core.AWSRequest ListNamedShadowsForThing where
  type
    AWSResponse ListNamedShadowsForThing =
      ListNamedShadowsForThingResponse
  request :: (Service -> Service)
-> ListNamedShadowsForThing -> Request ListNamedShadowsForThing
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 ListNamedShadowsForThing
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListNamedShadowsForThing)))
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 Integer
-> Int
-> ListNamedShadowsForThingResponse
ListNamedShadowsForThingResponse'
            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
"nextToken")
            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
"results" 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
"timestamp")
            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 ListNamedShadowsForThing where
  hashWithSalt :: Int -> ListNamedShadowsForThing -> Int
hashWithSalt Int
_salt ListNamedShadowsForThing' {Maybe Natural
Maybe Text
Text
thingName :: Text
pageSize :: Maybe Natural
nextToken :: Maybe Text
$sel:thingName:ListNamedShadowsForThing' :: ListNamedShadowsForThing -> Text
$sel:pageSize:ListNamedShadowsForThing' :: ListNamedShadowsForThing -> Maybe Natural
$sel:nextToken:ListNamedShadowsForThing' :: ListNamedShadowsForThing -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
pageSize
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
thingName

instance Prelude.NFData ListNamedShadowsForThing where
  rnf :: ListNamedShadowsForThing -> ()
rnf ListNamedShadowsForThing' {Maybe Natural
Maybe Text
Text
thingName :: Text
pageSize :: Maybe Natural
nextToken :: Maybe Text
$sel:thingName:ListNamedShadowsForThing' :: ListNamedShadowsForThing -> Text
$sel:pageSize:ListNamedShadowsForThing' :: ListNamedShadowsForThing -> Maybe Natural
$sel:nextToken:ListNamedShadowsForThing' :: ListNamedShadowsForThing -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
pageSize
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
thingName

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

instance Data.ToPath ListNamedShadowsForThing where
  toPath :: ListNamedShadowsForThing -> ByteString
toPath ListNamedShadowsForThing' {Maybe Natural
Maybe Text
Text
thingName :: Text
pageSize :: Maybe Natural
nextToken :: Maybe Text
$sel:thingName:ListNamedShadowsForThing' :: ListNamedShadowsForThing -> Text
$sel:pageSize:ListNamedShadowsForThing' :: ListNamedShadowsForThing -> Maybe Natural
$sel:nextToken:ListNamedShadowsForThing' :: ListNamedShadowsForThing -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/api/things/shadow/ListNamedShadowsForThing/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
thingName
      ]

instance Data.ToQuery ListNamedShadowsForThing where
  toQuery :: ListNamedShadowsForThing -> QueryString
toQuery ListNamedShadowsForThing' {Maybe Natural
Maybe Text
Text
thingName :: Text
pageSize :: Maybe Natural
nextToken :: Maybe Text
$sel:thingName:ListNamedShadowsForThing' :: ListNamedShadowsForThing -> Text
$sel:pageSize:ListNamedShadowsForThing' :: ListNamedShadowsForThing -> Maybe Natural
$sel:nextToken:ListNamedShadowsForThing' :: ListNamedShadowsForThing -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"nextToken" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
nextToken,
        ByteString
"pageSize" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Natural
pageSize
      ]

-- | /See:/ 'newListNamedShadowsForThingResponse' smart constructor.
data ListNamedShadowsForThingResponse = ListNamedShadowsForThingResponse'
  { -- | The token to use to get the next set of results, or __null__ if there
    -- are no additional results.
    ListNamedShadowsForThingResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The list of shadows for the specified thing.
    ListNamedShadowsForThingResponse -> Maybe [Text]
results :: Prelude.Maybe [Prelude.Text],
    -- | The Epoch date and time the response was generated by IoT.
    ListNamedShadowsForThingResponse -> Maybe Integer
timestamp :: Prelude.Maybe Prelude.Integer,
    -- | The response's http status code.
    ListNamedShadowsForThingResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListNamedShadowsForThingResponse
-> ListNamedShadowsForThingResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListNamedShadowsForThingResponse
-> ListNamedShadowsForThingResponse -> Bool
$c/= :: ListNamedShadowsForThingResponse
-> ListNamedShadowsForThingResponse -> Bool
== :: ListNamedShadowsForThingResponse
-> ListNamedShadowsForThingResponse -> Bool
$c== :: ListNamedShadowsForThingResponse
-> ListNamedShadowsForThingResponse -> Bool
Prelude.Eq, ReadPrec [ListNamedShadowsForThingResponse]
ReadPrec ListNamedShadowsForThingResponse
Int -> ReadS ListNamedShadowsForThingResponse
ReadS [ListNamedShadowsForThingResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListNamedShadowsForThingResponse]
$creadListPrec :: ReadPrec [ListNamedShadowsForThingResponse]
readPrec :: ReadPrec ListNamedShadowsForThingResponse
$creadPrec :: ReadPrec ListNamedShadowsForThingResponse
readList :: ReadS [ListNamedShadowsForThingResponse]
$creadList :: ReadS [ListNamedShadowsForThingResponse]
readsPrec :: Int -> ReadS ListNamedShadowsForThingResponse
$creadsPrec :: Int -> ReadS ListNamedShadowsForThingResponse
Prelude.Read, Int -> ListNamedShadowsForThingResponse -> ShowS
[ListNamedShadowsForThingResponse] -> ShowS
ListNamedShadowsForThingResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListNamedShadowsForThingResponse] -> ShowS
$cshowList :: [ListNamedShadowsForThingResponse] -> ShowS
show :: ListNamedShadowsForThingResponse -> String
$cshow :: ListNamedShadowsForThingResponse -> String
showsPrec :: Int -> ListNamedShadowsForThingResponse -> ShowS
$cshowsPrec :: Int -> ListNamedShadowsForThingResponse -> ShowS
Prelude.Show, forall x.
Rep ListNamedShadowsForThingResponse x
-> ListNamedShadowsForThingResponse
forall x.
ListNamedShadowsForThingResponse
-> Rep ListNamedShadowsForThingResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListNamedShadowsForThingResponse x
-> ListNamedShadowsForThingResponse
$cfrom :: forall x.
ListNamedShadowsForThingResponse
-> Rep ListNamedShadowsForThingResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListNamedShadowsForThingResponse' 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:
--
-- 'nextToken', 'listNamedShadowsForThingResponse_nextToken' - The token to use to get the next set of results, or __null__ if there
-- are no additional results.
--
-- 'results', 'listNamedShadowsForThingResponse_results' - The list of shadows for the specified thing.
--
-- 'timestamp', 'listNamedShadowsForThingResponse_timestamp' - The Epoch date and time the response was generated by IoT.
--
-- 'httpStatus', 'listNamedShadowsForThingResponse_httpStatus' - The response's http status code.
newListNamedShadowsForThingResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListNamedShadowsForThingResponse
newListNamedShadowsForThingResponse :: Int -> ListNamedShadowsForThingResponse
newListNamedShadowsForThingResponse Int
pHttpStatus_ =
  ListNamedShadowsForThingResponse'
    { $sel:nextToken:ListNamedShadowsForThingResponse' :: Maybe Text
nextToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:results:ListNamedShadowsForThingResponse' :: Maybe [Text]
results = forall a. Maybe a
Prelude.Nothing,
      $sel:timestamp:ListNamedShadowsForThingResponse' :: Maybe Integer
timestamp = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListNamedShadowsForThingResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The token to use to get the next set of results, or __null__ if there
-- are no additional results.
listNamedShadowsForThingResponse_nextToken :: Lens.Lens' ListNamedShadowsForThingResponse (Prelude.Maybe Prelude.Text)
listNamedShadowsForThingResponse_nextToken :: Lens' ListNamedShadowsForThingResponse (Maybe Text)
listNamedShadowsForThingResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListNamedShadowsForThingResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListNamedShadowsForThingResponse' :: ListNamedShadowsForThingResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListNamedShadowsForThingResponse
s@ListNamedShadowsForThingResponse' {} Maybe Text
a -> ListNamedShadowsForThingResponse
s {$sel:nextToken:ListNamedShadowsForThingResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListNamedShadowsForThingResponse)

-- | The list of shadows for the specified thing.
listNamedShadowsForThingResponse_results :: Lens.Lens' ListNamedShadowsForThingResponse (Prelude.Maybe [Prelude.Text])
listNamedShadowsForThingResponse_results :: Lens' ListNamedShadowsForThingResponse (Maybe [Text])
listNamedShadowsForThingResponse_results = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListNamedShadowsForThingResponse' {Maybe [Text]
results :: Maybe [Text]
$sel:results:ListNamedShadowsForThingResponse' :: ListNamedShadowsForThingResponse -> Maybe [Text]
results} -> Maybe [Text]
results) (\s :: ListNamedShadowsForThingResponse
s@ListNamedShadowsForThingResponse' {} Maybe [Text]
a -> ListNamedShadowsForThingResponse
s {$sel:results:ListNamedShadowsForThingResponse' :: Maybe [Text]
results = Maybe [Text]
a} :: ListNamedShadowsForThingResponse) 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 Epoch date and time the response was generated by IoT.
listNamedShadowsForThingResponse_timestamp :: Lens.Lens' ListNamedShadowsForThingResponse (Prelude.Maybe Prelude.Integer)
listNamedShadowsForThingResponse_timestamp :: Lens' ListNamedShadowsForThingResponse (Maybe Integer)
listNamedShadowsForThingResponse_timestamp = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListNamedShadowsForThingResponse' {Maybe Integer
timestamp :: Maybe Integer
$sel:timestamp:ListNamedShadowsForThingResponse' :: ListNamedShadowsForThingResponse -> Maybe Integer
timestamp} -> Maybe Integer
timestamp) (\s :: ListNamedShadowsForThingResponse
s@ListNamedShadowsForThingResponse' {} Maybe Integer
a -> ListNamedShadowsForThingResponse
s {$sel:timestamp:ListNamedShadowsForThingResponse' :: Maybe Integer
timestamp = Maybe Integer
a} :: ListNamedShadowsForThingResponse)

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

instance
  Prelude.NFData
    ListNamedShadowsForThingResponse
  where
  rnf :: ListNamedShadowsForThingResponse -> ()
rnf ListNamedShadowsForThingResponse' {Int
Maybe Integer
Maybe [Text]
Maybe Text
httpStatus :: Int
timestamp :: Maybe Integer
results :: Maybe [Text]
nextToken :: Maybe Text
$sel:httpStatus:ListNamedShadowsForThingResponse' :: ListNamedShadowsForThingResponse -> Int
$sel:timestamp:ListNamedShadowsForThingResponse' :: ListNamedShadowsForThingResponse -> Maybe Integer
$sel:results:ListNamedShadowsForThingResponse' :: ListNamedShadowsForThingResponse -> Maybe [Text]
$sel:nextToken:ListNamedShadowsForThingResponse' :: ListNamedShadowsForThingResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
results
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
timestamp
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus