{-# 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.ListThingTypes
-- 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 existing thing types.
--
-- Requires permission to access the
-- <https://docs.aws.amazon.com/service-authorization/latest/reference/list_awsiot.html#awsiot-actions-as-permissions ListThingTypes>
-- action.
--
-- This operation returns paginated results.
module Amazonka.IoT.ListThingTypes
  ( -- * Creating a Request
    ListThingTypes (..),
    newListThingTypes,

    -- * Request Lenses
    listThingTypes_maxResults,
    listThingTypes_nextToken,
    listThingTypes_thingTypeName,

    -- * Destructuring the Response
    ListThingTypesResponse (..),
    newListThingTypesResponse,

    -- * Response Lenses
    listThingTypesResponse_nextToken,
    listThingTypesResponse_thingTypes,
    listThingTypesResponse_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 ListThingTypes operation.
--
-- /See:/ 'newListThingTypes' smart constructor.
data ListThingTypes = ListThingTypes'
  { -- | The maximum number of results to return in this operation.
    ListThingTypes -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | To retrieve the next set of results, the @nextToken@ value from a
    -- previous response; otherwise __null__ to receive the first set of
    -- results.
    ListThingTypes -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The name of the thing type.
    ListThingTypes -> Maybe Text
thingTypeName :: Prelude.Maybe Prelude.Text
  }
  deriving (ListThingTypes -> ListThingTypes -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListThingTypes -> ListThingTypes -> Bool
$c/= :: ListThingTypes -> ListThingTypes -> Bool
== :: ListThingTypes -> ListThingTypes -> Bool
$c== :: ListThingTypes -> ListThingTypes -> Bool
Prelude.Eq, ReadPrec [ListThingTypes]
ReadPrec ListThingTypes
Int -> ReadS ListThingTypes
ReadS [ListThingTypes]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListThingTypes]
$creadListPrec :: ReadPrec [ListThingTypes]
readPrec :: ReadPrec ListThingTypes
$creadPrec :: ReadPrec ListThingTypes
readList :: ReadS [ListThingTypes]
$creadList :: ReadS [ListThingTypes]
readsPrec :: Int -> ReadS ListThingTypes
$creadsPrec :: Int -> ReadS ListThingTypes
Prelude.Read, Int -> ListThingTypes -> ShowS
[ListThingTypes] -> ShowS
ListThingTypes -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListThingTypes] -> ShowS
$cshowList :: [ListThingTypes] -> ShowS
show :: ListThingTypes -> String
$cshow :: ListThingTypes -> String
showsPrec :: Int -> ListThingTypes -> ShowS
$cshowsPrec :: Int -> ListThingTypes -> ShowS
Prelude.Show, forall x. Rep ListThingTypes x -> ListThingTypes
forall x. ListThingTypes -> Rep ListThingTypes x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListThingTypes x -> ListThingTypes
$cfrom :: forall x. ListThingTypes -> Rep ListThingTypes x
Prelude.Generic)

-- |
-- Create a value of 'ListThingTypes' 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:
--
-- 'maxResults', 'listThingTypes_maxResults' - The maximum number of results to return in this operation.
--
-- 'nextToken', 'listThingTypes_nextToken' - To retrieve the next set of results, the @nextToken@ value from a
-- previous response; otherwise __null__ to receive the first set of
-- results.
--
-- 'thingTypeName', 'listThingTypes_thingTypeName' - The name of the thing type.
newListThingTypes ::
  ListThingTypes
newListThingTypes :: ListThingTypes
newListThingTypes =
  ListThingTypes'
    { $sel:maxResults:ListThingTypes' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListThingTypes' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:thingTypeName:ListThingTypes' :: Maybe Text
thingTypeName = forall a. Maybe a
Prelude.Nothing
    }

-- | The maximum number of results to return in this operation.
listThingTypes_maxResults :: Lens.Lens' ListThingTypes (Prelude.Maybe Prelude.Natural)
listThingTypes_maxResults :: Lens' ListThingTypes (Maybe Natural)
listThingTypes_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListThingTypes' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListThingTypes' :: ListThingTypes -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListThingTypes
s@ListThingTypes' {} Maybe Natural
a -> ListThingTypes
s {$sel:maxResults:ListThingTypes' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListThingTypes)

-- | To retrieve the next set of results, the @nextToken@ value from a
-- previous response; otherwise __null__ to receive the first set of
-- results.
listThingTypes_nextToken :: Lens.Lens' ListThingTypes (Prelude.Maybe Prelude.Text)
listThingTypes_nextToken :: Lens' ListThingTypes (Maybe Text)
listThingTypes_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListThingTypes' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListThingTypes' :: ListThingTypes -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListThingTypes
s@ListThingTypes' {} Maybe Text
a -> ListThingTypes
s {$sel:nextToken:ListThingTypes' :: Maybe Text
nextToken = Maybe Text
a} :: ListThingTypes)

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

instance Core.AWSPager ListThingTypes where
  page :: ListThingTypes
-> AWSResponse ListThingTypes -> Maybe ListThingTypes
page ListThingTypes
rq AWSResponse ListThingTypes
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListThingTypes
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListThingTypesResponse (Maybe Text)
listThingTypesResponse_nextToken
            forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
        ) =
        forall a. Maybe a
Prelude.Nothing
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListThingTypes
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListThingTypesResponse (Maybe [ThingTypeDefinition])
listThingTypesResponse_thingTypes
            forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
        ) =
        forall a. Maybe a
Prelude.Nothing
    | Bool
Prelude.otherwise =
        forall a. a -> Maybe a
Prelude.Just
          forall a b. (a -> b) -> a -> b
Prelude.$ ListThingTypes
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListThingTypes (Maybe Text)
listThingTypes_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListThingTypes
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListThingTypesResponse (Maybe Text)
listThingTypesResponse_nextToken
          forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just

instance Core.AWSRequest ListThingTypes where
  type
    AWSResponse ListThingTypes =
      ListThingTypesResponse
  request :: (Service -> Service) -> ListThingTypes -> Request ListThingTypes
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 ListThingTypes
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListThingTypes)))
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 [ThingTypeDefinition] -> Int -> ListThingTypesResponse
ListThingTypesResponse'
            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
"thingTypes" 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.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable ListThingTypes where
  hashWithSalt :: Int -> ListThingTypes -> Int
hashWithSalt Int
_salt ListThingTypes' {Maybe Natural
Maybe Text
thingTypeName :: Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:thingTypeName:ListThingTypes' :: ListThingTypes -> Maybe Text
$sel:nextToken:ListThingTypes' :: ListThingTypes -> Maybe Text
$sel:maxResults:ListThingTypes' :: ListThingTypes -> Maybe Natural
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maxResults
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
thingTypeName

instance Prelude.NFData ListThingTypes where
  rnf :: ListThingTypes -> ()
rnf ListThingTypes' {Maybe Natural
Maybe Text
thingTypeName :: Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:thingTypeName:ListThingTypes' :: ListThingTypes -> Maybe Text
$sel:nextToken:ListThingTypes' :: ListThingTypes -> Maybe Text
$sel:maxResults:ListThingTypes' :: ListThingTypes -> Maybe Natural
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
maxResults
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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
thingTypeName

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

instance Data.ToPath ListThingTypes where
  toPath :: ListThingTypes -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/thing-types"

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

-- | The output for the ListThingTypes operation.
--
-- /See:/ 'newListThingTypesResponse' smart constructor.
data ListThingTypesResponse = ListThingTypesResponse'
  { -- | The token for the next set of results. Will not be returned if operation
    -- has returned all results.
    ListThingTypesResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The thing types.
    ListThingTypesResponse -> Maybe [ThingTypeDefinition]
thingTypes :: Prelude.Maybe [ThingTypeDefinition],
    -- | The response's http status code.
    ListThingTypesResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListThingTypesResponse -> ListThingTypesResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListThingTypesResponse -> ListThingTypesResponse -> Bool
$c/= :: ListThingTypesResponse -> ListThingTypesResponse -> Bool
== :: ListThingTypesResponse -> ListThingTypesResponse -> Bool
$c== :: ListThingTypesResponse -> ListThingTypesResponse -> Bool
Prelude.Eq, ReadPrec [ListThingTypesResponse]
ReadPrec ListThingTypesResponse
Int -> ReadS ListThingTypesResponse
ReadS [ListThingTypesResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListThingTypesResponse]
$creadListPrec :: ReadPrec [ListThingTypesResponse]
readPrec :: ReadPrec ListThingTypesResponse
$creadPrec :: ReadPrec ListThingTypesResponse
readList :: ReadS [ListThingTypesResponse]
$creadList :: ReadS [ListThingTypesResponse]
readsPrec :: Int -> ReadS ListThingTypesResponse
$creadsPrec :: Int -> ReadS ListThingTypesResponse
Prelude.Read, Int -> ListThingTypesResponse -> ShowS
[ListThingTypesResponse] -> ShowS
ListThingTypesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListThingTypesResponse] -> ShowS
$cshowList :: [ListThingTypesResponse] -> ShowS
show :: ListThingTypesResponse -> String
$cshow :: ListThingTypesResponse -> String
showsPrec :: Int -> ListThingTypesResponse -> ShowS
$cshowsPrec :: Int -> ListThingTypesResponse -> ShowS
Prelude.Show, forall x. Rep ListThingTypesResponse x -> ListThingTypesResponse
forall x. ListThingTypesResponse -> Rep ListThingTypesResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListThingTypesResponse x -> ListThingTypesResponse
$cfrom :: forall x. ListThingTypesResponse -> Rep ListThingTypesResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListThingTypesResponse' 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', 'listThingTypesResponse_nextToken' - The token for the next set of results. Will not be returned if operation
-- has returned all results.
--
-- 'thingTypes', 'listThingTypesResponse_thingTypes' - The thing types.
--
-- 'httpStatus', 'listThingTypesResponse_httpStatus' - The response's http status code.
newListThingTypesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListThingTypesResponse
newListThingTypesResponse :: Int -> ListThingTypesResponse
newListThingTypesResponse Int
pHttpStatus_ =
  ListThingTypesResponse'
    { $sel:nextToken:ListThingTypesResponse' :: Maybe Text
nextToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:thingTypes:ListThingTypesResponse' :: Maybe [ThingTypeDefinition]
thingTypes = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListThingTypesResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The token for the next set of results. Will not be returned if operation
-- has returned all results.
listThingTypesResponse_nextToken :: Lens.Lens' ListThingTypesResponse (Prelude.Maybe Prelude.Text)
listThingTypesResponse_nextToken :: Lens' ListThingTypesResponse (Maybe Text)
listThingTypesResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListThingTypesResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListThingTypesResponse' :: ListThingTypesResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListThingTypesResponse
s@ListThingTypesResponse' {} Maybe Text
a -> ListThingTypesResponse
s {$sel:nextToken:ListThingTypesResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListThingTypesResponse)

-- | The thing types.
listThingTypesResponse_thingTypes :: Lens.Lens' ListThingTypesResponse (Prelude.Maybe [ThingTypeDefinition])
listThingTypesResponse_thingTypes :: Lens' ListThingTypesResponse (Maybe [ThingTypeDefinition])
listThingTypesResponse_thingTypes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListThingTypesResponse' {Maybe [ThingTypeDefinition]
thingTypes :: Maybe [ThingTypeDefinition]
$sel:thingTypes:ListThingTypesResponse' :: ListThingTypesResponse -> Maybe [ThingTypeDefinition]
thingTypes} -> Maybe [ThingTypeDefinition]
thingTypes) (\s :: ListThingTypesResponse
s@ListThingTypesResponse' {} Maybe [ThingTypeDefinition]
a -> ListThingTypesResponse
s {$sel:thingTypes:ListThingTypesResponse' :: Maybe [ThingTypeDefinition]
thingTypes = Maybe [ThingTypeDefinition]
a} :: ListThingTypesResponse) 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 response's http status code.
listThingTypesResponse_httpStatus :: Lens.Lens' ListThingTypesResponse Prelude.Int
listThingTypesResponse_httpStatus :: Lens' ListThingTypesResponse Int
listThingTypesResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListThingTypesResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListThingTypesResponse' :: ListThingTypesResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListThingTypesResponse
s@ListThingTypesResponse' {} Int
a -> ListThingTypesResponse
s {$sel:httpStatus:ListThingTypesResponse' :: Int
httpStatus = Int
a} :: ListThingTypesResponse)

instance Prelude.NFData ListThingTypesResponse where
  rnf :: ListThingTypesResponse -> ()
rnf ListThingTypesResponse' {Int
Maybe [ThingTypeDefinition]
Maybe Text
httpStatus :: Int
thingTypes :: Maybe [ThingTypeDefinition]
nextToken :: Maybe Text
$sel:httpStatus:ListThingTypesResponse' :: ListThingTypesResponse -> Int
$sel:thingTypes:ListThingTypesResponse' :: ListThingTypesResponse -> Maybe [ThingTypeDefinition]
$sel:nextToken:ListThingTypesResponse' :: ListThingTypesResponse -> 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 [ThingTypeDefinition]
thingTypes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus