{-# 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.MigrationHub.ListApplicationStates
-- 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 all the migration statuses for your applications. If you use the
-- optional @ApplicationIds@ parameter, only the migration statuses for
-- those applications will be returned.
--
-- This operation returns paginated results.
module Amazonka.MigrationHub.ListApplicationStates
  ( -- * Creating a Request
    ListApplicationStates (..),
    newListApplicationStates,

    -- * Request Lenses
    listApplicationStates_applicationIds,
    listApplicationStates_maxResults,
    listApplicationStates_nextToken,

    -- * Destructuring the Response
    ListApplicationStatesResponse (..),
    newListApplicationStatesResponse,

    -- * Response Lenses
    listApplicationStatesResponse_applicationStateList,
    listApplicationStatesResponse_nextToken,
    listApplicationStatesResponse_httpStatus,
  )
where

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

-- | /See:/ 'newListApplicationStates' smart constructor.
data ListApplicationStates = ListApplicationStates'
  { -- | The configurationIds from the Application Discovery Service that
    -- uniquely identifies your applications.
    ListApplicationStates -> Maybe (NonEmpty Text)
applicationIds :: Prelude.Maybe (Prelude.NonEmpty Prelude.Text),
    -- | Maximum number of results to be returned per page.
    ListApplicationStates -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | If a @NextToken@ was returned by a previous call, there are more results
    -- available. To retrieve the next page of results, make the call again
    -- using the returned token in @NextToken@.
    ListApplicationStates -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text
  }
  deriving (ListApplicationStates -> ListApplicationStates -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListApplicationStates -> ListApplicationStates -> Bool
$c/= :: ListApplicationStates -> ListApplicationStates -> Bool
== :: ListApplicationStates -> ListApplicationStates -> Bool
$c== :: ListApplicationStates -> ListApplicationStates -> Bool
Prelude.Eq, ReadPrec [ListApplicationStates]
ReadPrec ListApplicationStates
Int -> ReadS ListApplicationStates
ReadS [ListApplicationStates]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListApplicationStates]
$creadListPrec :: ReadPrec [ListApplicationStates]
readPrec :: ReadPrec ListApplicationStates
$creadPrec :: ReadPrec ListApplicationStates
readList :: ReadS [ListApplicationStates]
$creadList :: ReadS [ListApplicationStates]
readsPrec :: Int -> ReadS ListApplicationStates
$creadsPrec :: Int -> ReadS ListApplicationStates
Prelude.Read, Int -> ListApplicationStates -> ShowS
[ListApplicationStates] -> ShowS
ListApplicationStates -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListApplicationStates] -> ShowS
$cshowList :: [ListApplicationStates] -> ShowS
show :: ListApplicationStates -> String
$cshow :: ListApplicationStates -> String
showsPrec :: Int -> ListApplicationStates -> ShowS
$cshowsPrec :: Int -> ListApplicationStates -> ShowS
Prelude.Show, forall x. Rep ListApplicationStates x -> ListApplicationStates
forall x. ListApplicationStates -> Rep ListApplicationStates x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListApplicationStates x -> ListApplicationStates
$cfrom :: forall x. ListApplicationStates -> Rep ListApplicationStates x
Prelude.Generic)

-- |
-- Create a value of 'ListApplicationStates' 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:
--
-- 'applicationIds', 'listApplicationStates_applicationIds' - The configurationIds from the Application Discovery Service that
-- uniquely identifies your applications.
--
-- 'maxResults', 'listApplicationStates_maxResults' - Maximum number of results to be returned per page.
--
-- 'nextToken', 'listApplicationStates_nextToken' - If a @NextToken@ was returned by a previous call, there are more results
-- available. To retrieve the next page of results, make the call again
-- using the returned token in @NextToken@.
newListApplicationStates ::
  ListApplicationStates
newListApplicationStates :: ListApplicationStates
newListApplicationStates =
  ListApplicationStates'
    { $sel:applicationIds:ListApplicationStates' :: Maybe (NonEmpty Text)
applicationIds =
        forall a. Maybe a
Prelude.Nothing,
      $sel:maxResults:ListApplicationStates' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListApplicationStates' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing
    }

-- | The configurationIds from the Application Discovery Service that
-- uniquely identifies your applications.
listApplicationStates_applicationIds :: Lens.Lens' ListApplicationStates (Prelude.Maybe (Prelude.NonEmpty Prelude.Text))
listApplicationStates_applicationIds :: Lens' ListApplicationStates (Maybe (NonEmpty Text))
listApplicationStates_applicationIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListApplicationStates' {Maybe (NonEmpty Text)
applicationIds :: Maybe (NonEmpty Text)
$sel:applicationIds:ListApplicationStates' :: ListApplicationStates -> Maybe (NonEmpty Text)
applicationIds} -> Maybe (NonEmpty Text)
applicationIds) (\s :: ListApplicationStates
s@ListApplicationStates' {} Maybe (NonEmpty Text)
a -> ListApplicationStates
s {$sel:applicationIds:ListApplicationStates' :: Maybe (NonEmpty Text)
applicationIds = Maybe (NonEmpty Text)
a} :: ListApplicationStates) 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

-- | Maximum number of results to be returned per page.
listApplicationStates_maxResults :: Lens.Lens' ListApplicationStates (Prelude.Maybe Prelude.Natural)
listApplicationStates_maxResults :: Lens' ListApplicationStates (Maybe Natural)
listApplicationStates_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListApplicationStates' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListApplicationStates' :: ListApplicationStates -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListApplicationStates
s@ListApplicationStates' {} Maybe Natural
a -> ListApplicationStates
s {$sel:maxResults:ListApplicationStates' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListApplicationStates)

-- | If a @NextToken@ was returned by a previous call, there are more results
-- available. To retrieve the next page of results, make the call again
-- using the returned token in @NextToken@.
listApplicationStates_nextToken :: Lens.Lens' ListApplicationStates (Prelude.Maybe Prelude.Text)
listApplicationStates_nextToken :: Lens' ListApplicationStates (Maybe Text)
listApplicationStates_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListApplicationStates' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListApplicationStates' :: ListApplicationStates -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListApplicationStates
s@ListApplicationStates' {} Maybe Text
a -> ListApplicationStates
s {$sel:nextToken:ListApplicationStates' :: Maybe Text
nextToken = Maybe Text
a} :: ListApplicationStates)

instance Core.AWSPager ListApplicationStates where
  page :: ListApplicationStates
-> AWSResponse ListApplicationStates -> Maybe ListApplicationStates
page ListApplicationStates
rq AWSResponse ListApplicationStates
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListApplicationStates
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListApplicationStatesResponse (Maybe Text)
listApplicationStatesResponse_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 ListApplicationStates
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListApplicationStatesResponse (Maybe [ApplicationState])
listApplicationStatesResponse_applicationStateList
            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.$ ListApplicationStates
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListApplicationStates (Maybe Text)
listApplicationStates_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListApplicationStates
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListApplicationStatesResponse (Maybe Text)
listApplicationStatesResponse_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 ListApplicationStates where
  type
    AWSResponse ListApplicationStates =
      ListApplicationStatesResponse
  request :: (Service -> Service)
-> ListApplicationStates -> Request ListApplicationStates
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 ListApplicationStates
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListApplicationStates)))
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 [ApplicationState]
-> Maybe Text -> Int -> ListApplicationStatesResponse
ListApplicationStatesResponse'
            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
"ApplicationStateList"
                            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 ListApplicationStates where
  hashWithSalt :: Int -> ListApplicationStates -> Int
hashWithSalt Int
_salt ListApplicationStates' {Maybe Natural
Maybe (NonEmpty Text)
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
applicationIds :: Maybe (NonEmpty Text)
$sel:nextToken:ListApplicationStates' :: ListApplicationStates -> Maybe Text
$sel:maxResults:ListApplicationStates' :: ListApplicationStates -> Maybe Natural
$sel:applicationIds:ListApplicationStates' :: ListApplicationStates -> Maybe (NonEmpty Text)
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (NonEmpty Text)
applicationIds
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maxResults
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken

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

instance Data.ToHeaders ListApplicationStates where
  toHeaders :: ListApplicationStates -> 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
"AWSMigrationHub.ListApplicationStates" ::
                          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 ListApplicationStates where
  toJSON :: ListApplicationStates -> Value
toJSON ListApplicationStates' {Maybe Natural
Maybe (NonEmpty Text)
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
applicationIds :: Maybe (NonEmpty Text)
$sel:nextToken:ListApplicationStates' :: ListApplicationStates -> Maybe Text
$sel:maxResults:ListApplicationStates' :: ListApplicationStates -> Maybe Natural
$sel:applicationIds:ListApplicationStates' :: ListApplicationStates -> Maybe (NonEmpty Text)
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"ApplicationIds" 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 (NonEmpty Text)
applicationIds,
            (Key
"MaxResults" 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 Natural
maxResults,
            (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
          ]
      )

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

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

-- | /See:/ 'newListApplicationStatesResponse' smart constructor.
data ListApplicationStatesResponse = ListApplicationStatesResponse'
  { -- | A list of Applications that exist in Application Discovery Service.
    ListApplicationStatesResponse -> Maybe [ApplicationState]
applicationStateList :: Prelude.Maybe [ApplicationState],
    -- | If a @NextToken@ was returned by a previous call, there are more results
    -- available. To retrieve the next page of results, make the call again
    -- using the returned token in @NextToken@.
    ListApplicationStatesResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListApplicationStatesResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListApplicationStatesResponse
-> ListApplicationStatesResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListApplicationStatesResponse
-> ListApplicationStatesResponse -> Bool
$c/= :: ListApplicationStatesResponse
-> ListApplicationStatesResponse -> Bool
== :: ListApplicationStatesResponse
-> ListApplicationStatesResponse -> Bool
$c== :: ListApplicationStatesResponse
-> ListApplicationStatesResponse -> Bool
Prelude.Eq, ReadPrec [ListApplicationStatesResponse]
ReadPrec ListApplicationStatesResponse
Int -> ReadS ListApplicationStatesResponse
ReadS [ListApplicationStatesResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListApplicationStatesResponse]
$creadListPrec :: ReadPrec [ListApplicationStatesResponse]
readPrec :: ReadPrec ListApplicationStatesResponse
$creadPrec :: ReadPrec ListApplicationStatesResponse
readList :: ReadS [ListApplicationStatesResponse]
$creadList :: ReadS [ListApplicationStatesResponse]
readsPrec :: Int -> ReadS ListApplicationStatesResponse
$creadsPrec :: Int -> ReadS ListApplicationStatesResponse
Prelude.Read, Int -> ListApplicationStatesResponse -> ShowS
[ListApplicationStatesResponse] -> ShowS
ListApplicationStatesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListApplicationStatesResponse] -> ShowS
$cshowList :: [ListApplicationStatesResponse] -> ShowS
show :: ListApplicationStatesResponse -> String
$cshow :: ListApplicationStatesResponse -> String
showsPrec :: Int -> ListApplicationStatesResponse -> ShowS
$cshowsPrec :: Int -> ListApplicationStatesResponse -> ShowS
Prelude.Show, forall x.
Rep ListApplicationStatesResponse x
-> ListApplicationStatesResponse
forall x.
ListApplicationStatesResponse
-> Rep ListApplicationStatesResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListApplicationStatesResponse x
-> ListApplicationStatesResponse
$cfrom :: forall x.
ListApplicationStatesResponse
-> Rep ListApplicationStatesResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListApplicationStatesResponse' 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:
--
-- 'applicationStateList', 'listApplicationStatesResponse_applicationStateList' - A list of Applications that exist in Application Discovery Service.
--
-- 'nextToken', 'listApplicationStatesResponse_nextToken' - If a @NextToken@ was returned by a previous call, there are more results
-- available. To retrieve the next page of results, make the call again
-- using the returned token in @NextToken@.
--
-- 'httpStatus', 'listApplicationStatesResponse_httpStatus' - The response's http status code.
newListApplicationStatesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListApplicationStatesResponse
newListApplicationStatesResponse :: Int -> ListApplicationStatesResponse
newListApplicationStatesResponse Int
pHttpStatus_ =
  ListApplicationStatesResponse'
    { $sel:applicationStateList:ListApplicationStatesResponse' :: Maybe [ApplicationState]
applicationStateList =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListApplicationStatesResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListApplicationStatesResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A list of Applications that exist in Application Discovery Service.
listApplicationStatesResponse_applicationStateList :: Lens.Lens' ListApplicationStatesResponse (Prelude.Maybe [ApplicationState])
listApplicationStatesResponse_applicationStateList :: Lens' ListApplicationStatesResponse (Maybe [ApplicationState])
listApplicationStatesResponse_applicationStateList = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListApplicationStatesResponse' {Maybe [ApplicationState]
applicationStateList :: Maybe [ApplicationState]
$sel:applicationStateList:ListApplicationStatesResponse' :: ListApplicationStatesResponse -> Maybe [ApplicationState]
applicationStateList} -> Maybe [ApplicationState]
applicationStateList) (\s :: ListApplicationStatesResponse
s@ListApplicationStatesResponse' {} Maybe [ApplicationState]
a -> ListApplicationStatesResponse
s {$sel:applicationStateList:ListApplicationStatesResponse' :: Maybe [ApplicationState]
applicationStateList = Maybe [ApplicationState]
a} :: ListApplicationStatesResponse) 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

-- | If a @NextToken@ was returned by a previous call, there are more results
-- available. To retrieve the next page of results, make the call again
-- using the returned token in @NextToken@.
listApplicationStatesResponse_nextToken :: Lens.Lens' ListApplicationStatesResponse (Prelude.Maybe Prelude.Text)
listApplicationStatesResponse_nextToken :: Lens' ListApplicationStatesResponse (Maybe Text)
listApplicationStatesResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListApplicationStatesResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListApplicationStatesResponse' :: ListApplicationStatesResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListApplicationStatesResponse
s@ListApplicationStatesResponse' {} Maybe Text
a -> ListApplicationStatesResponse
s {$sel:nextToken:ListApplicationStatesResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListApplicationStatesResponse)

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

instance Prelude.NFData ListApplicationStatesResponse where
  rnf :: ListApplicationStatesResponse -> ()
rnf ListApplicationStatesResponse' {Int
Maybe [ApplicationState]
Maybe Text
httpStatus :: Int
nextToken :: Maybe Text
applicationStateList :: Maybe [ApplicationState]
$sel:httpStatus:ListApplicationStatesResponse' :: ListApplicationStatesResponse -> Int
$sel:nextToken:ListApplicationStatesResponse' :: ListApplicationStatesResponse -> Maybe Text
$sel:applicationStateList:ListApplicationStatesResponse' :: ListApplicationStatesResponse -> Maybe [ApplicationState]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [ApplicationState]
applicationStateList
      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