{-# 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.ServerlessApplicationRepository.ListApplicationDependencies
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Retrieves the list of applications nested in the containing application.
--
-- This operation returns paginated results.
module Amazonka.ServerlessApplicationRepository.ListApplicationDependencies
  ( -- * Creating a Request
    ListApplicationDependencies (..),
    newListApplicationDependencies,

    -- * Request Lenses
    listApplicationDependencies_maxItems,
    listApplicationDependencies_nextToken,
    listApplicationDependencies_semanticVersion,
    listApplicationDependencies_applicationId,

    -- * Destructuring the Response
    ListApplicationDependenciesResponse (..),
    newListApplicationDependenciesResponse,

    -- * Response Lenses
    listApplicationDependenciesResponse_dependencies,
    listApplicationDependenciesResponse_nextToken,
    listApplicationDependenciesResponse_httpStatus,
  )
where

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
import Amazonka.ServerlessApplicationRepository.Types

-- | /See:/ 'newListApplicationDependencies' smart constructor.
data ListApplicationDependencies = ListApplicationDependencies'
  { -- | The total number of items to return.
    ListApplicationDependencies -> Maybe Natural
maxItems :: Prelude.Maybe Prelude.Natural,
    -- | A token to specify where to start paginating.
    ListApplicationDependencies -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The semantic version of the application to get.
    ListApplicationDependencies -> Maybe Text
semanticVersion :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the application.
    ListApplicationDependencies -> Text
applicationId :: Prelude.Text
  }
  deriving (ListApplicationDependencies -> ListApplicationDependencies -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListApplicationDependencies -> ListApplicationDependencies -> Bool
$c/= :: ListApplicationDependencies -> ListApplicationDependencies -> Bool
== :: ListApplicationDependencies -> ListApplicationDependencies -> Bool
$c== :: ListApplicationDependencies -> ListApplicationDependencies -> Bool
Prelude.Eq, ReadPrec [ListApplicationDependencies]
ReadPrec ListApplicationDependencies
Int -> ReadS ListApplicationDependencies
ReadS [ListApplicationDependencies]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListApplicationDependencies]
$creadListPrec :: ReadPrec [ListApplicationDependencies]
readPrec :: ReadPrec ListApplicationDependencies
$creadPrec :: ReadPrec ListApplicationDependencies
readList :: ReadS [ListApplicationDependencies]
$creadList :: ReadS [ListApplicationDependencies]
readsPrec :: Int -> ReadS ListApplicationDependencies
$creadsPrec :: Int -> ReadS ListApplicationDependencies
Prelude.Read, Int -> ListApplicationDependencies -> ShowS
[ListApplicationDependencies] -> ShowS
ListApplicationDependencies -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListApplicationDependencies] -> ShowS
$cshowList :: [ListApplicationDependencies] -> ShowS
show :: ListApplicationDependencies -> String
$cshow :: ListApplicationDependencies -> String
showsPrec :: Int -> ListApplicationDependencies -> ShowS
$cshowsPrec :: Int -> ListApplicationDependencies -> ShowS
Prelude.Show, forall x.
Rep ListApplicationDependencies x -> ListApplicationDependencies
forall x.
ListApplicationDependencies -> Rep ListApplicationDependencies x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListApplicationDependencies x -> ListApplicationDependencies
$cfrom :: forall x.
ListApplicationDependencies -> Rep ListApplicationDependencies x
Prelude.Generic)

-- |
-- Create a value of 'ListApplicationDependencies' 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:
--
-- 'maxItems', 'listApplicationDependencies_maxItems' - The total number of items to return.
--
-- 'nextToken', 'listApplicationDependencies_nextToken' - A token to specify where to start paginating.
--
-- 'semanticVersion', 'listApplicationDependencies_semanticVersion' - The semantic version of the application to get.
--
-- 'applicationId', 'listApplicationDependencies_applicationId' - The Amazon Resource Name (ARN) of the application.
newListApplicationDependencies ::
  -- | 'applicationId'
  Prelude.Text ->
  ListApplicationDependencies
newListApplicationDependencies :: Text -> ListApplicationDependencies
newListApplicationDependencies Text
pApplicationId_ =
  ListApplicationDependencies'
    { $sel:maxItems:ListApplicationDependencies' :: Maybe Natural
maxItems =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListApplicationDependencies' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:semanticVersion:ListApplicationDependencies' :: Maybe Text
semanticVersion = forall a. Maybe a
Prelude.Nothing,
      $sel:applicationId:ListApplicationDependencies' :: Text
applicationId = Text
pApplicationId_
    }

-- | The total number of items to return.
listApplicationDependencies_maxItems :: Lens.Lens' ListApplicationDependencies (Prelude.Maybe Prelude.Natural)
listApplicationDependencies_maxItems :: Lens' ListApplicationDependencies (Maybe Natural)
listApplicationDependencies_maxItems = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListApplicationDependencies' {Maybe Natural
maxItems :: Maybe Natural
$sel:maxItems:ListApplicationDependencies' :: ListApplicationDependencies -> Maybe Natural
maxItems} -> Maybe Natural
maxItems) (\s :: ListApplicationDependencies
s@ListApplicationDependencies' {} Maybe Natural
a -> ListApplicationDependencies
s {$sel:maxItems:ListApplicationDependencies' :: Maybe Natural
maxItems = Maybe Natural
a} :: ListApplicationDependencies)

-- | A token to specify where to start paginating.
listApplicationDependencies_nextToken :: Lens.Lens' ListApplicationDependencies (Prelude.Maybe Prelude.Text)
listApplicationDependencies_nextToken :: Lens' ListApplicationDependencies (Maybe Text)
listApplicationDependencies_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListApplicationDependencies' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListApplicationDependencies' :: ListApplicationDependencies -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListApplicationDependencies
s@ListApplicationDependencies' {} Maybe Text
a -> ListApplicationDependencies
s {$sel:nextToken:ListApplicationDependencies' :: Maybe Text
nextToken = Maybe Text
a} :: ListApplicationDependencies)

-- | The semantic version of the application to get.
listApplicationDependencies_semanticVersion :: Lens.Lens' ListApplicationDependencies (Prelude.Maybe Prelude.Text)
listApplicationDependencies_semanticVersion :: Lens' ListApplicationDependencies (Maybe Text)
listApplicationDependencies_semanticVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListApplicationDependencies' {Maybe Text
semanticVersion :: Maybe Text
$sel:semanticVersion:ListApplicationDependencies' :: ListApplicationDependencies -> Maybe Text
semanticVersion} -> Maybe Text
semanticVersion) (\s :: ListApplicationDependencies
s@ListApplicationDependencies' {} Maybe Text
a -> ListApplicationDependencies
s {$sel:semanticVersion:ListApplicationDependencies' :: Maybe Text
semanticVersion = Maybe Text
a} :: ListApplicationDependencies)

-- | The Amazon Resource Name (ARN) of the application.
listApplicationDependencies_applicationId :: Lens.Lens' ListApplicationDependencies Prelude.Text
listApplicationDependencies_applicationId :: Lens' ListApplicationDependencies Text
listApplicationDependencies_applicationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListApplicationDependencies' {Text
applicationId :: Text
$sel:applicationId:ListApplicationDependencies' :: ListApplicationDependencies -> Text
applicationId} -> Text
applicationId) (\s :: ListApplicationDependencies
s@ListApplicationDependencies' {} Text
a -> ListApplicationDependencies
s {$sel:applicationId:ListApplicationDependencies' :: Text
applicationId = Text
a} :: ListApplicationDependencies)

instance Core.AWSPager ListApplicationDependencies where
  page :: ListApplicationDependencies
-> AWSResponse ListApplicationDependencies
-> Maybe ListApplicationDependencies
page ListApplicationDependencies
rq AWSResponse ListApplicationDependencies
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListApplicationDependencies
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListApplicationDependenciesResponse (Maybe Text)
listApplicationDependenciesResponse_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 ListApplicationDependencies
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens'
  ListApplicationDependenciesResponse
  (Maybe [ApplicationDependencySummary])
listApplicationDependenciesResponse_dependencies
            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.$ ListApplicationDependencies
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListApplicationDependencies (Maybe Text)
listApplicationDependencies_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListApplicationDependencies
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListApplicationDependenciesResponse (Maybe Text)
listApplicationDependenciesResponse_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 ListApplicationDependencies where
  type
    AWSResponse ListApplicationDependencies =
      ListApplicationDependenciesResponse
  request :: (Service -> Service)
-> ListApplicationDependencies
-> Request ListApplicationDependencies
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 ListApplicationDependencies
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListApplicationDependencies)))
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 [ApplicationDependencySummary]
-> Maybe Text -> Int -> ListApplicationDependenciesResponse
ListApplicationDependenciesResponse'
            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
"dependencies" 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 ListApplicationDependencies where
  hashWithSalt :: Int -> ListApplicationDependencies -> Int
hashWithSalt Int
_salt ListApplicationDependencies' {Maybe Natural
Maybe Text
Text
applicationId :: Text
semanticVersion :: Maybe Text
nextToken :: Maybe Text
maxItems :: Maybe Natural
$sel:applicationId:ListApplicationDependencies' :: ListApplicationDependencies -> Text
$sel:semanticVersion:ListApplicationDependencies' :: ListApplicationDependencies -> Maybe Text
$sel:nextToken:ListApplicationDependencies' :: ListApplicationDependencies -> Maybe Text
$sel:maxItems:ListApplicationDependencies' :: ListApplicationDependencies -> Maybe Natural
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maxItems
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
semanticVersion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
applicationId

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

instance Data.ToHeaders ListApplicationDependencies where
  toHeaders :: ListApplicationDependencies -> 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 ListApplicationDependencies where
  toPath :: ListApplicationDependencies -> ByteString
toPath ListApplicationDependencies' {Maybe Natural
Maybe Text
Text
applicationId :: Text
semanticVersion :: Maybe Text
nextToken :: Maybe Text
maxItems :: Maybe Natural
$sel:applicationId:ListApplicationDependencies' :: ListApplicationDependencies -> Text
$sel:semanticVersion:ListApplicationDependencies' :: ListApplicationDependencies -> Maybe Text
$sel:nextToken:ListApplicationDependencies' :: ListApplicationDependencies -> Maybe Text
$sel:maxItems:ListApplicationDependencies' :: ListApplicationDependencies -> Maybe Natural
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/applications/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
applicationId,
        ByteString
"/dependencies"
      ]

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

-- | /See:/ 'newListApplicationDependenciesResponse' smart constructor.
data ListApplicationDependenciesResponse = ListApplicationDependenciesResponse'
  { -- | An array of application summaries nested in the application.
    ListApplicationDependenciesResponse
-> Maybe [ApplicationDependencySummary]
dependencies :: Prelude.Maybe [ApplicationDependencySummary],
    -- | The token to request the next page of results.
    ListApplicationDependenciesResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListApplicationDependenciesResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListApplicationDependenciesResponse
-> ListApplicationDependenciesResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListApplicationDependenciesResponse
-> ListApplicationDependenciesResponse -> Bool
$c/= :: ListApplicationDependenciesResponse
-> ListApplicationDependenciesResponse -> Bool
== :: ListApplicationDependenciesResponse
-> ListApplicationDependenciesResponse -> Bool
$c== :: ListApplicationDependenciesResponse
-> ListApplicationDependenciesResponse -> Bool
Prelude.Eq, ReadPrec [ListApplicationDependenciesResponse]
ReadPrec ListApplicationDependenciesResponse
Int -> ReadS ListApplicationDependenciesResponse
ReadS [ListApplicationDependenciesResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListApplicationDependenciesResponse]
$creadListPrec :: ReadPrec [ListApplicationDependenciesResponse]
readPrec :: ReadPrec ListApplicationDependenciesResponse
$creadPrec :: ReadPrec ListApplicationDependenciesResponse
readList :: ReadS [ListApplicationDependenciesResponse]
$creadList :: ReadS [ListApplicationDependenciesResponse]
readsPrec :: Int -> ReadS ListApplicationDependenciesResponse
$creadsPrec :: Int -> ReadS ListApplicationDependenciesResponse
Prelude.Read, Int -> ListApplicationDependenciesResponse -> ShowS
[ListApplicationDependenciesResponse] -> ShowS
ListApplicationDependenciesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListApplicationDependenciesResponse] -> ShowS
$cshowList :: [ListApplicationDependenciesResponse] -> ShowS
show :: ListApplicationDependenciesResponse -> String
$cshow :: ListApplicationDependenciesResponse -> String
showsPrec :: Int -> ListApplicationDependenciesResponse -> ShowS
$cshowsPrec :: Int -> ListApplicationDependenciesResponse -> ShowS
Prelude.Show, forall x.
Rep ListApplicationDependenciesResponse x
-> ListApplicationDependenciesResponse
forall x.
ListApplicationDependenciesResponse
-> Rep ListApplicationDependenciesResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListApplicationDependenciesResponse x
-> ListApplicationDependenciesResponse
$cfrom :: forall x.
ListApplicationDependenciesResponse
-> Rep ListApplicationDependenciesResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListApplicationDependenciesResponse' 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:
--
-- 'dependencies', 'listApplicationDependenciesResponse_dependencies' - An array of application summaries nested in the application.
--
-- 'nextToken', 'listApplicationDependenciesResponse_nextToken' - The token to request the next page of results.
--
-- 'httpStatus', 'listApplicationDependenciesResponse_httpStatus' - The response's http status code.
newListApplicationDependenciesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListApplicationDependenciesResponse
newListApplicationDependenciesResponse :: Int -> ListApplicationDependenciesResponse
newListApplicationDependenciesResponse Int
pHttpStatus_ =
  ListApplicationDependenciesResponse'
    { $sel:dependencies:ListApplicationDependenciesResponse' :: Maybe [ApplicationDependencySummary]
dependencies =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListApplicationDependenciesResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListApplicationDependenciesResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | An array of application summaries nested in the application.
listApplicationDependenciesResponse_dependencies :: Lens.Lens' ListApplicationDependenciesResponse (Prelude.Maybe [ApplicationDependencySummary])
listApplicationDependenciesResponse_dependencies :: Lens'
  ListApplicationDependenciesResponse
  (Maybe [ApplicationDependencySummary])
listApplicationDependenciesResponse_dependencies = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListApplicationDependenciesResponse' {Maybe [ApplicationDependencySummary]
dependencies :: Maybe [ApplicationDependencySummary]
$sel:dependencies:ListApplicationDependenciesResponse' :: ListApplicationDependenciesResponse
-> Maybe [ApplicationDependencySummary]
dependencies} -> Maybe [ApplicationDependencySummary]
dependencies) (\s :: ListApplicationDependenciesResponse
s@ListApplicationDependenciesResponse' {} Maybe [ApplicationDependencySummary]
a -> ListApplicationDependenciesResponse
s {$sel:dependencies:ListApplicationDependenciesResponse' :: Maybe [ApplicationDependencySummary]
dependencies = Maybe [ApplicationDependencySummary]
a} :: ListApplicationDependenciesResponse) 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 token to request the next page of results.
listApplicationDependenciesResponse_nextToken :: Lens.Lens' ListApplicationDependenciesResponse (Prelude.Maybe Prelude.Text)
listApplicationDependenciesResponse_nextToken :: Lens' ListApplicationDependenciesResponse (Maybe Text)
listApplicationDependenciesResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListApplicationDependenciesResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListApplicationDependenciesResponse' :: ListApplicationDependenciesResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListApplicationDependenciesResponse
s@ListApplicationDependenciesResponse' {} Maybe Text
a -> ListApplicationDependenciesResponse
s {$sel:nextToken:ListApplicationDependenciesResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListApplicationDependenciesResponse)

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

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