{-# 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 #-}
module Amazonka.IoT.ListPrincipalThings
(
ListPrincipalThings (..),
newListPrincipalThings,
listPrincipalThings_maxResults,
listPrincipalThings_nextToken,
listPrincipalThings_principal,
ListPrincipalThingsResponse (..),
newListPrincipalThingsResponse,
listPrincipalThingsResponse_nextToken,
listPrincipalThingsResponse_things,
listPrincipalThingsResponse_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
data ListPrincipalThings = ListPrincipalThings'
{
ListPrincipalThings -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
ListPrincipalThings -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
ListPrincipalThings -> Text
principal :: Prelude.Text
}
deriving (ListPrincipalThings -> ListPrincipalThings -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListPrincipalThings -> ListPrincipalThings -> Bool
$c/= :: ListPrincipalThings -> ListPrincipalThings -> Bool
== :: ListPrincipalThings -> ListPrincipalThings -> Bool
$c== :: ListPrincipalThings -> ListPrincipalThings -> Bool
Prelude.Eq, ReadPrec [ListPrincipalThings]
ReadPrec ListPrincipalThings
Int -> ReadS ListPrincipalThings
ReadS [ListPrincipalThings]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListPrincipalThings]
$creadListPrec :: ReadPrec [ListPrincipalThings]
readPrec :: ReadPrec ListPrincipalThings
$creadPrec :: ReadPrec ListPrincipalThings
readList :: ReadS [ListPrincipalThings]
$creadList :: ReadS [ListPrincipalThings]
readsPrec :: Int -> ReadS ListPrincipalThings
$creadsPrec :: Int -> ReadS ListPrincipalThings
Prelude.Read, Int -> ListPrincipalThings -> ShowS
[ListPrincipalThings] -> ShowS
ListPrincipalThings -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListPrincipalThings] -> ShowS
$cshowList :: [ListPrincipalThings] -> ShowS
show :: ListPrincipalThings -> String
$cshow :: ListPrincipalThings -> String
showsPrec :: Int -> ListPrincipalThings -> ShowS
$cshowsPrec :: Int -> ListPrincipalThings -> ShowS
Prelude.Show, forall x. Rep ListPrincipalThings x -> ListPrincipalThings
forall x. ListPrincipalThings -> Rep ListPrincipalThings x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListPrincipalThings x -> ListPrincipalThings
$cfrom :: forall x. ListPrincipalThings -> Rep ListPrincipalThings x
Prelude.Generic)
newListPrincipalThings ::
Prelude.Text ->
ListPrincipalThings
newListPrincipalThings :: Text -> ListPrincipalThings
newListPrincipalThings Text
pPrincipal_ =
ListPrincipalThings'
{ $sel:maxResults:ListPrincipalThings' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
$sel:nextToken:ListPrincipalThings' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
$sel:principal:ListPrincipalThings' :: Text
principal = Text
pPrincipal_
}
listPrincipalThings_maxResults :: Lens.Lens' ListPrincipalThings (Prelude.Maybe Prelude.Natural)
listPrincipalThings_maxResults :: Lens' ListPrincipalThings (Maybe Natural)
listPrincipalThings_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPrincipalThings' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListPrincipalThings' :: ListPrincipalThings -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListPrincipalThings
s@ListPrincipalThings' {} Maybe Natural
a -> ListPrincipalThings
s {$sel:maxResults:ListPrincipalThings' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListPrincipalThings)
listPrincipalThings_nextToken :: Lens.Lens' ListPrincipalThings (Prelude.Maybe Prelude.Text)
listPrincipalThings_nextToken :: Lens' ListPrincipalThings (Maybe Text)
listPrincipalThings_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPrincipalThings' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListPrincipalThings' :: ListPrincipalThings -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListPrincipalThings
s@ListPrincipalThings' {} Maybe Text
a -> ListPrincipalThings
s {$sel:nextToken:ListPrincipalThings' :: Maybe Text
nextToken = Maybe Text
a} :: ListPrincipalThings)
listPrincipalThings_principal :: Lens.Lens' ListPrincipalThings Prelude.Text
listPrincipalThings_principal :: Lens' ListPrincipalThings Text
listPrincipalThings_principal = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPrincipalThings' {Text
principal :: Text
$sel:principal:ListPrincipalThings' :: ListPrincipalThings -> Text
principal} -> Text
principal) (\s :: ListPrincipalThings
s@ListPrincipalThings' {} Text
a -> ListPrincipalThings
s {$sel:principal:ListPrincipalThings' :: Text
principal = Text
a} :: ListPrincipalThings)
instance Core.AWSPager ListPrincipalThings where
page :: ListPrincipalThings
-> AWSResponse ListPrincipalThings -> Maybe ListPrincipalThings
page ListPrincipalThings
rq AWSResponse ListPrincipalThings
rs
| forall a. AWSTruncated a => a -> Bool
Core.stop
( AWSResponse ListPrincipalThings
rs
forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListPrincipalThingsResponse (Maybe Text)
listPrincipalThingsResponse_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 ListPrincipalThings
rs
forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListPrincipalThingsResponse (Maybe [Text])
listPrincipalThingsResponse_things
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.$ ListPrincipalThings
rq
forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListPrincipalThings (Maybe Text)
listPrincipalThings_nextToken
forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListPrincipalThings
rs
forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListPrincipalThingsResponse (Maybe Text)
listPrincipalThingsResponse_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 ListPrincipalThings where
type
AWSResponse ListPrincipalThings =
ListPrincipalThingsResponse
request :: (Service -> Service)
-> ListPrincipalThings -> Request ListPrincipalThings
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 ListPrincipalThings
-> ClientResponse ClientBody
-> m (Either
Error (ClientResponse (AWSResponse ListPrincipalThings)))
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] -> Int -> ListPrincipalThingsResponse
ListPrincipalThingsResponse'
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
"things" 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 ListPrincipalThings where
hashWithSalt :: Int -> ListPrincipalThings -> Int
hashWithSalt Int
_salt ListPrincipalThings' {Maybe Natural
Maybe Text
Text
principal :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:principal:ListPrincipalThings' :: ListPrincipalThings -> Text
$sel:nextToken:ListPrincipalThings' :: ListPrincipalThings -> Maybe Text
$sel:maxResults:ListPrincipalThings' :: ListPrincipalThings -> 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` Text
principal
instance Prelude.NFData ListPrincipalThings where
rnf :: ListPrincipalThings -> ()
rnf ListPrincipalThings' {Maybe Natural
Maybe Text
Text
principal :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:principal:ListPrincipalThings' :: ListPrincipalThings -> Text
$sel:nextToken:ListPrincipalThings' :: ListPrincipalThings -> Maybe Text
$sel:maxResults:ListPrincipalThings' :: ListPrincipalThings -> 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 Text
principal
instance Data.ToHeaders ListPrincipalThings where
toHeaders :: ListPrincipalThings -> ResponseHeaders
toHeaders ListPrincipalThings' {Maybe Natural
Maybe Text
Text
principal :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:principal:ListPrincipalThings' :: ListPrincipalThings -> Text
$sel:nextToken:ListPrincipalThings' :: ListPrincipalThings -> Maybe Text
$sel:maxResults:ListPrincipalThings' :: ListPrincipalThings -> Maybe Natural
..} =
forall a. Monoid a => [a] -> a
Prelude.mconcat
[HeaderName
"x-amzn-principal" forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Text
principal]
instance Data.ToPath ListPrincipalThings where
toPath :: ListPrincipalThings -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/principals/things"
instance Data.ToQuery ListPrincipalThings where
toQuery :: ListPrincipalThings -> QueryString
toQuery ListPrincipalThings' {Maybe Natural
Maybe Text
Text
principal :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:principal:ListPrincipalThings' :: ListPrincipalThings -> Text
$sel:nextToken:ListPrincipalThings' :: ListPrincipalThings -> Maybe Text
$sel:maxResults:ListPrincipalThings' :: ListPrincipalThings -> 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
]
data ListPrincipalThingsResponse = ListPrincipalThingsResponse'
{
ListPrincipalThingsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
ListPrincipalThingsResponse -> Maybe [Text]
things :: Prelude.Maybe [Prelude.Text],
ListPrincipalThingsResponse -> Int
httpStatus :: Prelude.Int
}
deriving (ListPrincipalThingsResponse -> ListPrincipalThingsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListPrincipalThingsResponse -> ListPrincipalThingsResponse -> Bool
$c/= :: ListPrincipalThingsResponse -> ListPrincipalThingsResponse -> Bool
== :: ListPrincipalThingsResponse -> ListPrincipalThingsResponse -> Bool
$c== :: ListPrincipalThingsResponse -> ListPrincipalThingsResponse -> Bool
Prelude.Eq, ReadPrec [ListPrincipalThingsResponse]
ReadPrec ListPrincipalThingsResponse
Int -> ReadS ListPrincipalThingsResponse
ReadS [ListPrincipalThingsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListPrincipalThingsResponse]
$creadListPrec :: ReadPrec [ListPrincipalThingsResponse]
readPrec :: ReadPrec ListPrincipalThingsResponse
$creadPrec :: ReadPrec ListPrincipalThingsResponse
readList :: ReadS [ListPrincipalThingsResponse]
$creadList :: ReadS [ListPrincipalThingsResponse]
readsPrec :: Int -> ReadS ListPrincipalThingsResponse
$creadsPrec :: Int -> ReadS ListPrincipalThingsResponse
Prelude.Read, Int -> ListPrincipalThingsResponse -> ShowS
[ListPrincipalThingsResponse] -> ShowS
ListPrincipalThingsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListPrincipalThingsResponse] -> ShowS
$cshowList :: [ListPrincipalThingsResponse] -> ShowS
show :: ListPrincipalThingsResponse -> String
$cshow :: ListPrincipalThingsResponse -> String
showsPrec :: Int -> ListPrincipalThingsResponse -> ShowS
$cshowsPrec :: Int -> ListPrincipalThingsResponse -> ShowS
Prelude.Show, forall x.
Rep ListPrincipalThingsResponse x -> ListPrincipalThingsResponse
forall x.
ListPrincipalThingsResponse -> Rep ListPrincipalThingsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListPrincipalThingsResponse x -> ListPrincipalThingsResponse
$cfrom :: forall x.
ListPrincipalThingsResponse -> Rep ListPrincipalThingsResponse x
Prelude.Generic)
newListPrincipalThingsResponse ::
Prelude.Int ->
ListPrincipalThingsResponse
newListPrincipalThingsResponse :: Int -> ListPrincipalThingsResponse
newListPrincipalThingsResponse Int
pHttpStatus_ =
ListPrincipalThingsResponse'
{ $sel:nextToken:ListPrincipalThingsResponse' :: Maybe Text
nextToken =
forall a. Maybe a
Prelude.Nothing,
$sel:things:ListPrincipalThingsResponse' :: Maybe [Text]
things = forall a. Maybe a
Prelude.Nothing,
$sel:httpStatus:ListPrincipalThingsResponse' :: Int
httpStatus = Int
pHttpStatus_
}
listPrincipalThingsResponse_nextToken :: Lens.Lens' ListPrincipalThingsResponse (Prelude.Maybe Prelude.Text)
listPrincipalThingsResponse_nextToken :: Lens' ListPrincipalThingsResponse (Maybe Text)
listPrincipalThingsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPrincipalThingsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListPrincipalThingsResponse' :: ListPrincipalThingsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListPrincipalThingsResponse
s@ListPrincipalThingsResponse' {} Maybe Text
a -> ListPrincipalThingsResponse
s {$sel:nextToken:ListPrincipalThingsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListPrincipalThingsResponse)
listPrincipalThingsResponse_things :: Lens.Lens' ListPrincipalThingsResponse (Prelude.Maybe [Prelude.Text])
listPrincipalThingsResponse_things :: Lens' ListPrincipalThingsResponse (Maybe [Text])
listPrincipalThingsResponse_things = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPrincipalThingsResponse' {Maybe [Text]
things :: Maybe [Text]
$sel:things:ListPrincipalThingsResponse' :: ListPrincipalThingsResponse -> Maybe [Text]
things} -> Maybe [Text]
things) (\s :: ListPrincipalThingsResponse
s@ListPrincipalThingsResponse' {} Maybe [Text]
a -> ListPrincipalThingsResponse
s {$sel:things:ListPrincipalThingsResponse' :: Maybe [Text]
things = Maybe [Text]
a} :: ListPrincipalThingsResponse) 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
listPrincipalThingsResponse_httpStatus :: Lens.Lens' ListPrincipalThingsResponse Prelude.Int
listPrincipalThingsResponse_httpStatus :: Lens' ListPrincipalThingsResponse Int
listPrincipalThingsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPrincipalThingsResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListPrincipalThingsResponse' :: ListPrincipalThingsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListPrincipalThingsResponse
s@ListPrincipalThingsResponse' {} Int
a -> ListPrincipalThingsResponse
s {$sel:httpStatus:ListPrincipalThingsResponse' :: Int
httpStatus = Int
a} :: ListPrincipalThingsResponse)
instance Prelude.NFData ListPrincipalThingsResponse where
rnf :: ListPrincipalThingsResponse -> ()
rnf ListPrincipalThingsResponse' {Int
Maybe [Text]
Maybe Text
httpStatus :: Int
things :: Maybe [Text]
nextToken :: Maybe Text
$sel:httpStatus:ListPrincipalThingsResponse' :: ListPrincipalThingsResponse -> Int
$sel:things:ListPrincipalThingsResponse' :: ListPrincipalThingsResponse -> Maybe [Text]
$sel:nextToken:ListPrincipalThingsResponse' :: ListPrincipalThingsResponse -> 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]
things
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus