{-# 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.Panorama.ListApplicationInstanceDependencies
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Returns a list of application instance dependencies.
module Amazonka.Panorama.ListApplicationInstanceDependencies
  ( -- * Creating a Request
    ListApplicationInstanceDependencies (..),
    newListApplicationInstanceDependencies,

    -- * Request Lenses
    listApplicationInstanceDependencies_maxResults,
    listApplicationInstanceDependencies_nextToken,
    listApplicationInstanceDependencies_applicationInstanceId,

    -- * Destructuring the Response
    ListApplicationInstanceDependenciesResponse (..),
    newListApplicationInstanceDependenciesResponse,

    -- * Response Lenses
    listApplicationInstanceDependenciesResponse_nextToken,
    listApplicationInstanceDependenciesResponse_packageObjects,
    listApplicationInstanceDependenciesResponse_httpStatus,
  )
where

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

-- | /See:/ 'newListApplicationInstanceDependencies' smart constructor.
data ListApplicationInstanceDependencies = ListApplicationInstanceDependencies'
  { -- | The maximum number of application instance dependencies to return in one
    -- page of results.
    ListApplicationInstanceDependencies -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | Specify the pagination token from a previous request to retrieve the
    -- next page of results.
    ListApplicationInstanceDependencies -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The application instance\'s ID.
    ListApplicationInstanceDependencies -> Text
applicationInstanceId :: Prelude.Text
  }
  deriving (ListApplicationInstanceDependencies
-> ListApplicationInstanceDependencies -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListApplicationInstanceDependencies
-> ListApplicationInstanceDependencies -> Bool
$c/= :: ListApplicationInstanceDependencies
-> ListApplicationInstanceDependencies -> Bool
== :: ListApplicationInstanceDependencies
-> ListApplicationInstanceDependencies -> Bool
$c== :: ListApplicationInstanceDependencies
-> ListApplicationInstanceDependencies -> Bool
Prelude.Eq, ReadPrec [ListApplicationInstanceDependencies]
ReadPrec ListApplicationInstanceDependencies
Int -> ReadS ListApplicationInstanceDependencies
ReadS [ListApplicationInstanceDependencies]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListApplicationInstanceDependencies]
$creadListPrec :: ReadPrec [ListApplicationInstanceDependencies]
readPrec :: ReadPrec ListApplicationInstanceDependencies
$creadPrec :: ReadPrec ListApplicationInstanceDependencies
readList :: ReadS [ListApplicationInstanceDependencies]
$creadList :: ReadS [ListApplicationInstanceDependencies]
readsPrec :: Int -> ReadS ListApplicationInstanceDependencies
$creadsPrec :: Int -> ReadS ListApplicationInstanceDependencies
Prelude.Read, Int -> ListApplicationInstanceDependencies -> ShowS
[ListApplicationInstanceDependencies] -> ShowS
ListApplicationInstanceDependencies -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListApplicationInstanceDependencies] -> ShowS
$cshowList :: [ListApplicationInstanceDependencies] -> ShowS
show :: ListApplicationInstanceDependencies -> String
$cshow :: ListApplicationInstanceDependencies -> String
showsPrec :: Int -> ListApplicationInstanceDependencies -> ShowS
$cshowsPrec :: Int -> ListApplicationInstanceDependencies -> ShowS
Prelude.Show, forall x.
Rep ListApplicationInstanceDependencies x
-> ListApplicationInstanceDependencies
forall x.
ListApplicationInstanceDependencies
-> Rep ListApplicationInstanceDependencies x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListApplicationInstanceDependencies x
-> ListApplicationInstanceDependencies
$cfrom :: forall x.
ListApplicationInstanceDependencies
-> Rep ListApplicationInstanceDependencies x
Prelude.Generic)

-- |
-- Create a value of 'ListApplicationInstanceDependencies' 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', 'listApplicationInstanceDependencies_maxResults' - The maximum number of application instance dependencies to return in one
-- page of results.
--
-- 'nextToken', 'listApplicationInstanceDependencies_nextToken' - Specify the pagination token from a previous request to retrieve the
-- next page of results.
--
-- 'applicationInstanceId', 'listApplicationInstanceDependencies_applicationInstanceId' - The application instance\'s ID.
newListApplicationInstanceDependencies ::
  -- | 'applicationInstanceId'
  Prelude.Text ->
  ListApplicationInstanceDependencies
newListApplicationInstanceDependencies :: Text -> ListApplicationInstanceDependencies
newListApplicationInstanceDependencies
  Text
pApplicationInstanceId_ =
    ListApplicationInstanceDependencies'
      { $sel:maxResults:ListApplicationInstanceDependencies' :: Maybe Natural
maxResults =
          forall a. Maybe a
Prelude.Nothing,
        $sel:nextToken:ListApplicationInstanceDependencies' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
        $sel:applicationInstanceId:ListApplicationInstanceDependencies' :: Text
applicationInstanceId =
          Text
pApplicationInstanceId_
      }

-- | The maximum number of application instance dependencies to return in one
-- page of results.
listApplicationInstanceDependencies_maxResults :: Lens.Lens' ListApplicationInstanceDependencies (Prelude.Maybe Prelude.Natural)
listApplicationInstanceDependencies_maxResults :: Lens' ListApplicationInstanceDependencies (Maybe Natural)
listApplicationInstanceDependencies_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListApplicationInstanceDependencies' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListApplicationInstanceDependencies' :: ListApplicationInstanceDependencies -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListApplicationInstanceDependencies
s@ListApplicationInstanceDependencies' {} Maybe Natural
a -> ListApplicationInstanceDependencies
s {$sel:maxResults:ListApplicationInstanceDependencies' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListApplicationInstanceDependencies)

-- | Specify the pagination token from a previous request to retrieve the
-- next page of results.
listApplicationInstanceDependencies_nextToken :: Lens.Lens' ListApplicationInstanceDependencies (Prelude.Maybe Prelude.Text)
listApplicationInstanceDependencies_nextToken :: Lens' ListApplicationInstanceDependencies (Maybe Text)
listApplicationInstanceDependencies_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListApplicationInstanceDependencies' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListApplicationInstanceDependencies' :: ListApplicationInstanceDependencies -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListApplicationInstanceDependencies
s@ListApplicationInstanceDependencies' {} Maybe Text
a -> ListApplicationInstanceDependencies
s {$sel:nextToken:ListApplicationInstanceDependencies' :: Maybe Text
nextToken = Maybe Text
a} :: ListApplicationInstanceDependencies)

-- | The application instance\'s ID.
listApplicationInstanceDependencies_applicationInstanceId :: Lens.Lens' ListApplicationInstanceDependencies Prelude.Text
listApplicationInstanceDependencies_applicationInstanceId :: Lens' ListApplicationInstanceDependencies Text
listApplicationInstanceDependencies_applicationInstanceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListApplicationInstanceDependencies' {Text
applicationInstanceId :: Text
$sel:applicationInstanceId:ListApplicationInstanceDependencies' :: ListApplicationInstanceDependencies -> Text
applicationInstanceId} -> Text
applicationInstanceId) (\s :: ListApplicationInstanceDependencies
s@ListApplicationInstanceDependencies' {} Text
a -> ListApplicationInstanceDependencies
s {$sel:applicationInstanceId:ListApplicationInstanceDependencies' :: Text
applicationInstanceId = Text
a} :: ListApplicationInstanceDependencies)

instance
  Core.AWSRequest
    ListApplicationInstanceDependencies
  where
  type
    AWSResponse ListApplicationInstanceDependencies =
      ListApplicationInstanceDependenciesResponse
  request :: (Service -> Service)
-> ListApplicationInstanceDependencies
-> Request ListApplicationInstanceDependencies
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 ListApplicationInstanceDependencies
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse (AWSResponse ListApplicationInstanceDependencies)))
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 [PackageObject]
-> Int
-> ListApplicationInstanceDependenciesResponse
ListApplicationInstanceDependenciesResponse'
            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
"PackageObjects" 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
    ListApplicationInstanceDependencies
  where
  hashWithSalt :: Int -> ListApplicationInstanceDependencies -> Int
hashWithSalt
    Int
_salt
    ListApplicationInstanceDependencies' {Maybe Natural
Maybe Text
Text
applicationInstanceId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:applicationInstanceId:ListApplicationInstanceDependencies' :: ListApplicationInstanceDependencies -> Text
$sel:nextToken:ListApplicationInstanceDependencies' :: ListApplicationInstanceDependencies -> Maybe Text
$sel:maxResults:ListApplicationInstanceDependencies' :: ListApplicationInstanceDependencies -> 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
applicationInstanceId

instance
  Prelude.NFData
    ListApplicationInstanceDependencies
  where
  rnf :: ListApplicationInstanceDependencies -> ()
rnf ListApplicationInstanceDependencies' {Maybe Natural
Maybe Text
Text
applicationInstanceId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:applicationInstanceId:ListApplicationInstanceDependencies' :: ListApplicationInstanceDependencies -> Text
$sel:nextToken:ListApplicationInstanceDependencies' :: ListApplicationInstanceDependencies -> Maybe Text
$sel:maxResults:ListApplicationInstanceDependencies' :: ListApplicationInstanceDependencies -> 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
applicationInstanceId

instance
  Data.ToHeaders
    ListApplicationInstanceDependencies
  where
  toHeaders :: ListApplicationInstanceDependencies -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance
  Data.ToPath
    ListApplicationInstanceDependencies
  where
  toPath :: ListApplicationInstanceDependencies -> ByteString
toPath ListApplicationInstanceDependencies' {Maybe Natural
Maybe Text
Text
applicationInstanceId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:applicationInstanceId:ListApplicationInstanceDependencies' :: ListApplicationInstanceDependencies -> Text
$sel:nextToken:ListApplicationInstanceDependencies' :: ListApplicationInstanceDependencies -> Maybe Text
$sel:maxResults:ListApplicationInstanceDependencies' :: ListApplicationInstanceDependencies -> Maybe Natural
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/application-instances/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
applicationInstanceId,
        ByteString
"/package-dependencies"
      ]

instance
  Data.ToQuery
    ListApplicationInstanceDependencies
  where
  toQuery :: ListApplicationInstanceDependencies -> QueryString
toQuery ListApplicationInstanceDependencies' {Maybe Natural
Maybe Text
Text
applicationInstanceId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:applicationInstanceId:ListApplicationInstanceDependencies' :: ListApplicationInstanceDependencies -> Text
$sel:nextToken:ListApplicationInstanceDependencies' :: ListApplicationInstanceDependencies -> Maybe Text
$sel:maxResults:ListApplicationInstanceDependencies' :: ListApplicationInstanceDependencies -> 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
      ]

-- | /See:/ 'newListApplicationInstanceDependenciesResponse' smart constructor.
data ListApplicationInstanceDependenciesResponse = ListApplicationInstanceDependenciesResponse'
  { -- | A pagination token that\'s included if more results are available.
    ListApplicationInstanceDependenciesResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | A list of package objects.
    ListApplicationInstanceDependenciesResponse
-> Maybe [PackageObject]
packageObjects :: Prelude.Maybe [PackageObject],
    -- | The response's http status code.
    ListApplicationInstanceDependenciesResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListApplicationInstanceDependenciesResponse
-> ListApplicationInstanceDependenciesResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListApplicationInstanceDependenciesResponse
-> ListApplicationInstanceDependenciesResponse -> Bool
$c/= :: ListApplicationInstanceDependenciesResponse
-> ListApplicationInstanceDependenciesResponse -> Bool
== :: ListApplicationInstanceDependenciesResponse
-> ListApplicationInstanceDependenciesResponse -> Bool
$c== :: ListApplicationInstanceDependenciesResponse
-> ListApplicationInstanceDependenciesResponse -> Bool
Prelude.Eq, ReadPrec [ListApplicationInstanceDependenciesResponse]
ReadPrec ListApplicationInstanceDependenciesResponse
Int -> ReadS ListApplicationInstanceDependenciesResponse
ReadS [ListApplicationInstanceDependenciesResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListApplicationInstanceDependenciesResponse]
$creadListPrec :: ReadPrec [ListApplicationInstanceDependenciesResponse]
readPrec :: ReadPrec ListApplicationInstanceDependenciesResponse
$creadPrec :: ReadPrec ListApplicationInstanceDependenciesResponse
readList :: ReadS [ListApplicationInstanceDependenciesResponse]
$creadList :: ReadS [ListApplicationInstanceDependenciesResponse]
readsPrec :: Int -> ReadS ListApplicationInstanceDependenciesResponse
$creadsPrec :: Int -> ReadS ListApplicationInstanceDependenciesResponse
Prelude.Read, Int -> ListApplicationInstanceDependenciesResponse -> ShowS
[ListApplicationInstanceDependenciesResponse] -> ShowS
ListApplicationInstanceDependenciesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListApplicationInstanceDependenciesResponse] -> ShowS
$cshowList :: [ListApplicationInstanceDependenciesResponse] -> ShowS
show :: ListApplicationInstanceDependenciesResponse -> String
$cshow :: ListApplicationInstanceDependenciesResponse -> String
showsPrec :: Int -> ListApplicationInstanceDependenciesResponse -> ShowS
$cshowsPrec :: Int -> ListApplicationInstanceDependenciesResponse -> ShowS
Prelude.Show, forall x.
Rep ListApplicationInstanceDependenciesResponse x
-> ListApplicationInstanceDependenciesResponse
forall x.
ListApplicationInstanceDependenciesResponse
-> Rep ListApplicationInstanceDependenciesResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListApplicationInstanceDependenciesResponse x
-> ListApplicationInstanceDependenciesResponse
$cfrom :: forall x.
ListApplicationInstanceDependenciesResponse
-> Rep ListApplicationInstanceDependenciesResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListApplicationInstanceDependenciesResponse' 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', 'listApplicationInstanceDependenciesResponse_nextToken' - A pagination token that\'s included if more results are available.
--
-- 'packageObjects', 'listApplicationInstanceDependenciesResponse_packageObjects' - A list of package objects.
--
-- 'httpStatus', 'listApplicationInstanceDependenciesResponse_httpStatus' - The response's http status code.
newListApplicationInstanceDependenciesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListApplicationInstanceDependenciesResponse
newListApplicationInstanceDependenciesResponse :: Int -> ListApplicationInstanceDependenciesResponse
newListApplicationInstanceDependenciesResponse
  Int
pHttpStatus_ =
    ListApplicationInstanceDependenciesResponse'
      { $sel:nextToken:ListApplicationInstanceDependenciesResponse' :: Maybe Text
nextToken =
          forall a. Maybe a
Prelude.Nothing,
        $sel:packageObjects:ListApplicationInstanceDependenciesResponse' :: Maybe [PackageObject]
packageObjects =
          forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:ListApplicationInstanceDependenciesResponse' :: Int
httpStatus = Int
pHttpStatus_
      }

-- | A pagination token that\'s included if more results are available.
listApplicationInstanceDependenciesResponse_nextToken :: Lens.Lens' ListApplicationInstanceDependenciesResponse (Prelude.Maybe Prelude.Text)
listApplicationInstanceDependenciesResponse_nextToken :: Lens' ListApplicationInstanceDependenciesResponse (Maybe Text)
listApplicationInstanceDependenciesResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListApplicationInstanceDependenciesResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListApplicationInstanceDependenciesResponse' :: ListApplicationInstanceDependenciesResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListApplicationInstanceDependenciesResponse
s@ListApplicationInstanceDependenciesResponse' {} Maybe Text
a -> ListApplicationInstanceDependenciesResponse
s {$sel:nextToken:ListApplicationInstanceDependenciesResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListApplicationInstanceDependenciesResponse)

-- | A list of package objects.
listApplicationInstanceDependenciesResponse_packageObjects :: Lens.Lens' ListApplicationInstanceDependenciesResponse (Prelude.Maybe [PackageObject])
listApplicationInstanceDependenciesResponse_packageObjects :: Lens'
  ListApplicationInstanceDependenciesResponse (Maybe [PackageObject])
listApplicationInstanceDependenciesResponse_packageObjects = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListApplicationInstanceDependenciesResponse' {Maybe [PackageObject]
packageObjects :: Maybe [PackageObject]
$sel:packageObjects:ListApplicationInstanceDependenciesResponse' :: ListApplicationInstanceDependenciesResponse
-> Maybe [PackageObject]
packageObjects} -> Maybe [PackageObject]
packageObjects) (\s :: ListApplicationInstanceDependenciesResponse
s@ListApplicationInstanceDependenciesResponse' {} Maybe [PackageObject]
a -> ListApplicationInstanceDependenciesResponse
s {$sel:packageObjects:ListApplicationInstanceDependenciesResponse' :: Maybe [PackageObject]
packageObjects = Maybe [PackageObject]
a} :: ListApplicationInstanceDependenciesResponse) 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.
listApplicationInstanceDependenciesResponse_httpStatus :: Lens.Lens' ListApplicationInstanceDependenciesResponse Prelude.Int
listApplicationInstanceDependenciesResponse_httpStatus :: Lens' ListApplicationInstanceDependenciesResponse Int
listApplicationInstanceDependenciesResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListApplicationInstanceDependenciesResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListApplicationInstanceDependenciesResponse' :: ListApplicationInstanceDependenciesResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListApplicationInstanceDependenciesResponse
s@ListApplicationInstanceDependenciesResponse' {} Int
a -> ListApplicationInstanceDependenciesResponse
s {$sel:httpStatus:ListApplicationInstanceDependenciesResponse' :: Int
httpStatus = Int
a} :: ListApplicationInstanceDependenciesResponse)

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