{-# 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.AppStream.ListAssociatedStacks
(
ListAssociatedStacks (..),
newListAssociatedStacks,
listAssociatedStacks_nextToken,
listAssociatedStacks_fleetName,
ListAssociatedStacksResponse (..),
newListAssociatedStacksResponse,
listAssociatedStacksResponse_names,
listAssociatedStacksResponse_nextToken,
listAssociatedStacksResponse_httpStatus,
)
where
import Amazonka.AppStream.Types
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
data ListAssociatedStacks = ListAssociatedStacks'
{
ListAssociatedStacks -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
ListAssociatedStacks -> Text
fleetName :: Prelude.Text
}
deriving (ListAssociatedStacks -> ListAssociatedStacks -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListAssociatedStacks -> ListAssociatedStacks -> Bool
$c/= :: ListAssociatedStacks -> ListAssociatedStacks -> Bool
== :: ListAssociatedStacks -> ListAssociatedStacks -> Bool
$c== :: ListAssociatedStacks -> ListAssociatedStacks -> Bool
Prelude.Eq, ReadPrec [ListAssociatedStacks]
ReadPrec ListAssociatedStacks
Int -> ReadS ListAssociatedStacks
ReadS [ListAssociatedStacks]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListAssociatedStacks]
$creadListPrec :: ReadPrec [ListAssociatedStacks]
readPrec :: ReadPrec ListAssociatedStacks
$creadPrec :: ReadPrec ListAssociatedStacks
readList :: ReadS [ListAssociatedStacks]
$creadList :: ReadS [ListAssociatedStacks]
readsPrec :: Int -> ReadS ListAssociatedStacks
$creadsPrec :: Int -> ReadS ListAssociatedStacks
Prelude.Read, Int -> ListAssociatedStacks -> ShowS
[ListAssociatedStacks] -> ShowS
ListAssociatedStacks -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListAssociatedStacks] -> ShowS
$cshowList :: [ListAssociatedStacks] -> ShowS
show :: ListAssociatedStacks -> String
$cshow :: ListAssociatedStacks -> String
showsPrec :: Int -> ListAssociatedStacks -> ShowS
$cshowsPrec :: Int -> ListAssociatedStacks -> ShowS
Prelude.Show, forall x. Rep ListAssociatedStacks x -> ListAssociatedStacks
forall x. ListAssociatedStacks -> Rep ListAssociatedStacks x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListAssociatedStacks x -> ListAssociatedStacks
$cfrom :: forall x. ListAssociatedStacks -> Rep ListAssociatedStacks x
Prelude.Generic)
newListAssociatedStacks ::
Prelude.Text ->
ListAssociatedStacks
newListAssociatedStacks :: Text -> ListAssociatedStacks
newListAssociatedStacks Text
pFleetName_ =
ListAssociatedStacks'
{ $sel:nextToken:ListAssociatedStacks' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
$sel:fleetName:ListAssociatedStacks' :: Text
fleetName = Text
pFleetName_
}
listAssociatedStacks_nextToken :: Lens.Lens' ListAssociatedStacks (Prelude.Maybe Prelude.Text)
listAssociatedStacks_nextToken :: Lens' ListAssociatedStacks (Maybe Text)
listAssociatedStacks_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAssociatedStacks' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListAssociatedStacks' :: ListAssociatedStacks -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListAssociatedStacks
s@ListAssociatedStacks' {} Maybe Text
a -> ListAssociatedStacks
s {$sel:nextToken:ListAssociatedStacks' :: Maybe Text
nextToken = Maybe Text
a} :: ListAssociatedStacks)
listAssociatedStacks_fleetName :: Lens.Lens' ListAssociatedStacks Prelude.Text
listAssociatedStacks_fleetName :: Lens' ListAssociatedStacks Text
listAssociatedStacks_fleetName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAssociatedStacks' {Text
fleetName :: Text
$sel:fleetName:ListAssociatedStacks' :: ListAssociatedStacks -> Text
fleetName} -> Text
fleetName) (\s :: ListAssociatedStacks
s@ListAssociatedStacks' {} Text
a -> ListAssociatedStacks
s {$sel:fleetName:ListAssociatedStacks' :: Text
fleetName = Text
a} :: ListAssociatedStacks)
instance Core.AWSPager ListAssociatedStacks where
page :: ListAssociatedStacks
-> AWSResponse ListAssociatedStacks -> Maybe ListAssociatedStacks
page ListAssociatedStacks
rq AWSResponse ListAssociatedStacks
rs
| forall a. AWSTruncated a => a -> Bool
Core.stop
( AWSResponse ListAssociatedStacks
rs
forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListAssociatedStacksResponse (Maybe Text)
listAssociatedStacksResponse_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 ListAssociatedStacks
rs
forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListAssociatedStacksResponse (Maybe [Text])
listAssociatedStacksResponse_names
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.$ ListAssociatedStacks
rq
forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListAssociatedStacks (Maybe Text)
listAssociatedStacks_nextToken
forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListAssociatedStacks
rs
forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListAssociatedStacksResponse (Maybe Text)
listAssociatedStacksResponse_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 ListAssociatedStacks where
type
AWSResponse ListAssociatedStacks =
ListAssociatedStacksResponse
request :: (Service -> Service)
-> ListAssociatedStacks -> Request ListAssociatedStacks
request Service -> Service
overrides =
forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy ListAssociatedStacks
-> ClientResponse ClientBody
-> m (Either
Error (ClientResponse (AWSResponse ListAssociatedStacks)))
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 -> ListAssociatedStacksResponse
ListAssociatedStacksResponse'
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
"Names" 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
"NextToken")
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 ListAssociatedStacks where
hashWithSalt :: Int -> ListAssociatedStacks -> Int
hashWithSalt Int
_salt ListAssociatedStacks' {Maybe Text
Text
fleetName :: Text
nextToken :: Maybe Text
$sel:fleetName:ListAssociatedStacks' :: ListAssociatedStacks -> Text
$sel:nextToken:ListAssociatedStacks' :: ListAssociatedStacks -> 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` Text
fleetName
instance Prelude.NFData ListAssociatedStacks where
rnf :: ListAssociatedStacks -> ()
rnf ListAssociatedStacks' {Maybe Text
Text
fleetName :: Text
nextToken :: Maybe Text
$sel:fleetName:ListAssociatedStacks' :: ListAssociatedStacks -> Text
$sel:nextToken:ListAssociatedStacks' :: ListAssociatedStacks -> 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 Text
fleetName
instance Data.ToHeaders ListAssociatedStacks where
toHeaders :: ListAssociatedStacks -> ResponseHeaders
toHeaders =
forall a b. a -> b -> a
Prelude.const
( forall a. Monoid a => [a] -> a
Prelude.mconcat
[ HeaderName
"X-Amz-Target"
forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"PhotonAdminProxyService.ListAssociatedStacks" ::
Prelude.ByteString
),
HeaderName
"Content-Type"
forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
Prelude.ByteString
)
]
)
instance Data.ToJSON ListAssociatedStacks where
toJSON :: ListAssociatedStacks -> Value
toJSON ListAssociatedStacks' {Maybe Text
Text
fleetName :: Text
nextToken :: Maybe Text
$sel:fleetName:ListAssociatedStacks' :: ListAssociatedStacks -> Text
$sel:nextToken:ListAssociatedStacks' :: ListAssociatedStacks -> Maybe Text
..} =
[Pair] -> Value
Data.object
( forall a. [Maybe a] -> [a]
Prelude.catMaybes
[ (Key
"NextToken" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
nextToken,
forall a. a -> Maybe a
Prelude.Just (Key
"FleetName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
fleetName)
]
)
instance Data.ToPath ListAssociatedStacks where
toPath :: ListAssociatedStacks -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"
instance Data.ToQuery ListAssociatedStacks where
toQuery :: ListAssociatedStacks -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data ListAssociatedStacksResponse = ListAssociatedStacksResponse'
{
ListAssociatedStacksResponse -> Maybe [Text]
names :: Prelude.Maybe [Prelude.Text],
ListAssociatedStacksResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
ListAssociatedStacksResponse -> Int
httpStatus :: Prelude.Int
}
deriving (ListAssociatedStacksResponse
-> ListAssociatedStacksResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListAssociatedStacksResponse
-> ListAssociatedStacksResponse -> Bool
$c/= :: ListAssociatedStacksResponse
-> ListAssociatedStacksResponse -> Bool
== :: ListAssociatedStacksResponse
-> ListAssociatedStacksResponse -> Bool
$c== :: ListAssociatedStacksResponse
-> ListAssociatedStacksResponse -> Bool
Prelude.Eq, ReadPrec [ListAssociatedStacksResponse]
ReadPrec ListAssociatedStacksResponse
Int -> ReadS ListAssociatedStacksResponse
ReadS [ListAssociatedStacksResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListAssociatedStacksResponse]
$creadListPrec :: ReadPrec [ListAssociatedStacksResponse]
readPrec :: ReadPrec ListAssociatedStacksResponse
$creadPrec :: ReadPrec ListAssociatedStacksResponse
readList :: ReadS [ListAssociatedStacksResponse]
$creadList :: ReadS [ListAssociatedStacksResponse]
readsPrec :: Int -> ReadS ListAssociatedStacksResponse
$creadsPrec :: Int -> ReadS ListAssociatedStacksResponse
Prelude.Read, Int -> ListAssociatedStacksResponse -> ShowS
[ListAssociatedStacksResponse] -> ShowS
ListAssociatedStacksResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListAssociatedStacksResponse] -> ShowS
$cshowList :: [ListAssociatedStacksResponse] -> ShowS
show :: ListAssociatedStacksResponse -> String
$cshow :: ListAssociatedStacksResponse -> String
showsPrec :: Int -> ListAssociatedStacksResponse -> ShowS
$cshowsPrec :: Int -> ListAssociatedStacksResponse -> ShowS
Prelude.Show, forall x.
Rep ListAssociatedStacksResponse x -> ListAssociatedStacksResponse
forall x.
ListAssociatedStacksResponse -> Rep ListAssociatedStacksResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListAssociatedStacksResponse x -> ListAssociatedStacksResponse
$cfrom :: forall x.
ListAssociatedStacksResponse -> Rep ListAssociatedStacksResponse x
Prelude.Generic)
newListAssociatedStacksResponse ::
Prelude.Int ->
ListAssociatedStacksResponse
newListAssociatedStacksResponse :: Int -> ListAssociatedStacksResponse
newListAssociatedStacksResponse Int
pHttpStatus_ =
ListAssociatedStacksResponse'
{ $sel:names:ListAssociatedStacksResponse' :: Maybe [Text]
names =
forall a. Maybe a
Prelude.Nothing,
$sel:nextToken:ListAssociatedStacksResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
$sel:httpStatus:ListAssociatedStacksResponse' :: Int
httpStatus = Int
pHttpStatus_
}
listAssociatedStacksResponse_names :: Lens.Lens' ListAssociatedStacksResponse (Prelude.Maybe [Prelude.Text])
listAssociatedStacksResponse_names :: Lens' ListAssociatedStacksResponse (Maybe [Text])
listAssociatedStacksResponse_names = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAssociatedStacksResponse' {Maybe [Text]
names :: Maybe [Text]
$sel:names:ListAssociatedStacksResponse' :: ListAssociatedStacksResponse -> Maybe [Text]
names} -> Maybe [Text]
names) (\s :: ListAssociatedStacksResponse
s@ListAssociatedStacksResponse' {} Maybe [Text]
a -> ListAssociatedStacksResponse
s {$sel:names:ListAssociatedStacksResponse' :: Maybe [Text]
names = Maybe [Text]
a} :: ListAssociatedStacksResponse) 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
listAssociatedStacksResponse_nextToken :: Lens.Lens' ListAssociatedStacksResponse (Prelude.Maybe Prelude.Text)
listAssociatedStacksResponse_nextToken :: Lens' ListAssociatedStacksResponse (Maybe Text)
listAssociatedStacksResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAssociatedStacksResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListAssociatedStacksResponse' :: ListAssociatedStacksResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListAssociatedStacksResponse
s@ListAssociatedStacksResponse' {} Maybe Text
a -> ListAssociatedStacksResponse
s {$sel:nextToken:ListAssociatedStacksResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListAssociatedStacksResponse)
listAssociatedStacksResponse_httpStatus :: Lens.Lens' ListAssociatedStacksResponse Prelude.Int
listAssociatedStacksResponse_httpStatus :: Lens' ListAssociatedStacksResponse Int
listAssociatedStacksResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAssociatedStacksResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListAssociatedStacksResponse' :: ListAssociatedStacksResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListAssociatedStacksResponse
s@ListAssociatedStacksResponse' {} Int
a -> ListAssociatedStacksResponse
s {$sel:httpStatus:ListAssociatedStacksResponse' :: Int
httpStatus = Int
a} :: ListAssociatedStacksResponse)
instance Prelude.NFData ListAssociatedStacksResponse where
rnf :: ListAssociatedStacksResponse -> ()
rnf ListAssociatedStacksResponse' {Int
Maybe [Text]
Maybe Text
httpStatus :: Int
nextToken :: Maybe Text
names :: Maybe [Text]
$sel:httpStatus:ListAssociatedStacksResponse' :: ListAssociatedStacksResponse -> Int
$sel:nextToken:ListAssociatedStacksResponse' :: ListAssociatedStacksResponse -> Maybe Text
$sel:names:ListAssociatedStacksResponse' :: ListAssociatedStacksResponse -> Maybe [Text]
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
names
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 Int
httpStatus