{-# 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.CodeArtifact.ListPackages
-- 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
-- <https://docs.aws.amazon.com/codeartifact/latest/APIReference/API_PackageSummary.html PackageSummary>
-- objects for packages in a repository that match the request parameters.
--
-- This operation returns paginated results.
module Amazonka.CodeArtifact.ListPackages
  ( -- * Creating a Request
    ListPackages (..),
    newListPackages,

    -- * Request Lenses
    listPackages_domainOwner,
    listPackages_format,
    listPackages_maxResults,
    listPackages_namespace,
    listPackages_nextToken,
    listPackages_packagePrefix,
    listPackages_publish,
    listPackages_upstream,
    listPackages_domain,
    listPackages_repository,

    -- * Destructuring the Response
    ListPackagesResponse (..),
    newListPackagesResponse,

    -- * Response Lenses
    listPackagesResponse_nextToken,
    listPackagesResponse_packages,
    listPackagesResponse_httpStatus,
  )
where

import Amazonka.CodeArtifact.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

-- | /See:/ 'newListPackages' smart constructor.
data ListPackages = ListPackages'
  { -- | The 12-digit account number of the Amazon Web Services account that owns
    -- the domain. It does not include dashes or spaces.
    ListPackages -> Maybe Text
domainOwner :: Prelude.Maybe Prelude.Text,
    -- | The format used to filter requested packages. Only packages from the
    -- provided format will be returned.
    ListPackages -> Maybe PackageFormat
format :: Prelude.Maybe PackageFormat,
    -- | The maximum number of results to return per page.
    ListPackages -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | The namespace used to filter requested packages. Only packages with the
    -- provided namespace will be returned. The package component that
    -- specifies its namespace depends on its type. For example:
    --
    -- -   The namespace of a Maven package is its @groupId@.
    --
    -- -   The namespace of an npm package is its @scope@.
    --
    -- -   Python and NuGet packages do not contain a corresponding component,
    --     packages of those formats do not have a namespace.
    ListPackages -> Maybe Text
namespace :: Prelude.Maybe Prelude.Text,
    -- | The token for the next set of results. Use the value returned in the
    -- previous response in the next request to retrieve the next set of
    -- results.
    ListPackages -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | A prefix used to filter requested packages. Only packages with names
    -- that start with @packagePrefix@ are returned.
    ListPackages -> Maybe Text
packagePrefix :: Prelude.Maybe Prelude.Text,
    -- | The value of the @Publish@ package origin control restriction used to
    -- filter requested packages. Only packages with the provided restriction
    -- are returned. For more information, see
    -- <https://docs.aws.amazon.com/codeartifact/latest/APIReference/API_PackageOriginRestrictions.html PackageOriginRestrictions>.
    ListPackages -> Maybe AllowPublish
publish :: Prelude.Maybe AllowPublish,
    -- | The value of the @Upstream@ package origin control restriction used to
    -- filter requested packages. Only packages with the provided restriction
    -- are returned. For more information, see
    -- <https://docs.aws.amazon.com/codeartifact/latest/APIReference/API_PackageOriginRestrictions.html PackageOriginRestrictions>.
    ListPackages -> Maybe AllowUpstream
upstream :: Prelude.Maybe AllowUpstream,
    -- | The name of the domain that contains the repository that contains the
    -- requested packages.
    ListPackages -> Text
domain :: Prelude.Text,
    -- | The name of the repository that contains the requested packages.
    ListPackages -> Text
repository :: Prelude.Text
  }
  deriving (ListPackages -> ListPackages -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListPackages -> ListPackages -> Bool
$c/= :: ListPackages -> ListPackages -> Bool
== :: ListPackages -> ListPackages -> Bool
$c== :: ListPackages -> ListPackages -> Bool
Prelude.Eq, ReadPrec [ListPackages]
ReadPrec ListPackages
Int -> ReadS ListPackages
ReadS [ListPackages]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListPackages]
$creadListPrec :: ReadPrec [ListPackages]
readPrec :: ReadPrec ListPackages
$creadPrec :: ReadPrec ListPackages
readList :: ReadS [ListPackages]
$creadList :: ReadS [ListPackages]
readsPrec :: Int -> ReadS ListPackages
$creadsPrec :: Int -> ReadS ListPackages
Prelude.Read, Int -> ListPackages -> ShowS
[ListPackages] -> ShowS
ListPackages -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListPackages] -> ShowS
$cshowList :: [ListPackages] -> ShowS
show :: ListPackages -> String
$cshow :: ListPackages -> String
showsPrec :: Int -> ListPackages -> ShowS
$cshowsPrec :: Int -> ListPackages -> ShowS
Prelude.Show, forall x. Rep ListPackages x -> ListPackages
forall x. ListPackages -> Rep ListPackages x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListPackages x -> ListPackages
$cfrom :: forall x. ListPackages -> Rep ListPackages x
Prelude.Generic)

-- |
-- Create a value of 'ListPackages' 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:
--
-- 'domainOwner', 'listPackages_domainOwner' - The 12-digit account number of the Amazon Web Services account that owns
-- the domain. It does not include dashes or spaces.
--
-- 'format', 'listPackages_format' - The format used to filter requested packages. Only packages from the
-- provided format will be returned.
--
-- 'maxResults', 'listPackages_maxResults' - The maximum number of results to return per page.
--
-- 'namespace', 'listPackages_namespace' - The namespace used to filter requested packages. Only packages with the
-- provided namespace will be returned. The package component that
-- specifies its namespace depends on its type. For example:
--
-- -   The namespace of a Maven package is its @groupId@.
--
-- -   The namespace of an npm package is its @scope@.
--
-- -   Python and NuGet packages do not contain a corresponding component,
--     packages of those formats do not have a namespace.
--
-- 'nextToken', 'listPackages_nextToken' - The token for the next set of results. Use the value returned in the
-- previous response in the next request to retrieve the next set of
-- results.
--
-- 'packagePrefix', 'listPackages_packagePrefix' - A prefix used to filter requested packages. Only packages with names
-- that start with @packagePrefix@ are returned.
--
-- 'publish', 'listPackages_publish' - The value of the @Publish@ package origin control restriction used to
-- filter requested packages. Only packages with the provided restriction
-- are returned. For more information, see
-- <https://docs.aws.amazon.com/codeartifact/latest/APIReference/API_PackageOriginRestrictions.html PackageOriginRestrictions>.
--
-- 'upstream', 'listPackages_upstream' - The value of the @Upstream@ package origin control restriction used to
-- filter requested packages. Only packages with the provided restriction
-- are returned. For more information, see
-- <https://docs.aws.amazon.com/codeartifact/latest/APIReference/API_PackageOriginRestrictions.html PackageOriginRestrictions>.
--
-- 'domain', 'listPackages_domain' - The name of the domain that contains the repository that contains the
-- requested packages.
--
-- 'repository', 'listPackages_repository' - The name of the repository that contains the requested packages.
newListPackages ::
  -- | 'domain'
  Prelude.Text ->
  -- | 'repository'
  Prelude.Text ->
  ListPackages
newListPackages :: Text -> Text -> ListPackages
newListPackages Text
pDomain_ Text
pRepository_ =
  ListPackages'
    { $sel:domainOwner:ListPackages' :: Maybe Text
domainOwner = forall a. Maybe a
Prelude.Nothing,
      $sel:format:ListPackages' :: Maybe PackageFormat
format = forall a. Maybe a
Prelude.Nothing,
      $sel:maxResults:ListPackages' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:namespace:ListPackages' :: Maybe Text
namespace = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListPackages' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:packagePrefix:ListPackages' :: Maybe Text
packagePrefix = forall a. Maybe a
Prelude.Nothing,
      $sel:publish:ListPackages' :: Maybe AllowPublish
publish = forall a. Maybe a
Prelude.Nothing,
      $sel:upstream:ListPackages' :: Maybe AllowUpstream
upstream = forall a. Maybe a
Prelude.Nothing,
      $sel:domain:ListPackages' :: Text
domain = Text
pDomain_,
      $sel:repository:ListPackages' :: Text
repository = Text
pRepository_
    }

-- | The 12-digit account number of the Amazon Web Services account that owns
-- the domain. It does not include dashes or spaces.
listPackages_domainOwner :: Lens.Lens' ListPackages (Prelude.Maybe Prelude.Text)
listPackages_domainOwner :: Lens' ListPackages (Maybe Text)
listPackages_domainOwner = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPackages' {Maybe Text
domainOwner :: Maybe Text
$sel:domainOwner:ListPackages' :: ListPackages -> Maybe Text
domainOwner} -> Maybe Text
domainOwner) (\s :: ListPackages
s@ListPackages' {} Maybe Text
a -> ListPackages
s {$sel:domainOwner:ListPackages' :: Maybe Text
domainOwner = Maybe Text
a} :: ListPackages)

-- | The format used to filter requested packages. Only packages from the
-- provided format will be returned.
listPackages_format :: Lens.Lens' ListPackages (Prelude.Maybe PackageFormat)
listPackages_format :: Lens' ListPackages (Maybe PackageFormat)
listPackages_format = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPackages' {Maybe PackageFormat
format :: Maybe PackageFormat
$sel:format:ListPackages' :: ListPackages -> Maybe PackageFormat
format} -> Maybe PackageFormat
format) (\s :: ListPackages
s@ListPackages' {} Maybe PackageFormat
a -> ListPackages
s {$sel:format:ListPackages' :: Maybe PackageFormat
format = Maybe PackageFormat
a} :: ListPackages)

-- | The maximum number of results to return per page.
listPackages_maxResults :: Lens.Lens' ListPackages (Prelude.Maybe Prelude.Natural)
listPackages_maxResults :: Lens' ListPackages (Maybe Natural)
listPackages_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPackages' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListPackages' :: ListPackages -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListPackages
s@ListPackages' {} Maybe Natural
a -> ListPackages
s {$sel:maxResults:ListPackages' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListPackages)

-- | The namespace used to filter requested packages. Only packages with the
-- provided namespace will be returned. The package component that
-- specifies its namespace depends on its type. For example:
--
-- -   The namespace of a Maven package is its @groupId@.
--
-- -   The namespace of an npm package is its @scope@.
--
-- -   Python and NuGet packages do not contain a corresponding component,
--     packages of those formats do not have a namespace.
listPackages_namespace :: Lens.Lens' ListPackages (Prelude.Maybe Prelude.Text)
listPackages_namespace :: Lens' ListPackages (Maybe Text)
listPackages_namespace = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPackages' {Maybe Text
namespace :: Maybe Text
$sel:namespace:ListPackages' :: ListPackages -> Maybe Text
namespace} -> Maybe Text
namespace) (\s :: ListPackages
s@ListPackages' {} Maybe Text
a -> ListPackages
s {$sel:namespace:ListPackages' :: Maybe Text
namespace = Maybe Text
a} :: ListPackages)

-- | The token for the next set of results. Use the value returned in the
-- previous response in the next request to retrieve the next set of
-- results.
listPackages_nextToken :: Lens.Lens' ListPackages (Prelude.Maybe Prelude.Text)
listPackages_nextToken :: Lens' ListPackages (Maybe Text)
listPackages_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPackages' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListPackages' :: ListPackages -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListPackages
s@ListPackages' {} Maybe Text
a -> ListPackages
s {$sel:nextToken:ListPackages' :: Maybe Text
nextToken = Maybe Text
a} :: ListPackages)

-- | A prefix used to filter requested packages. Only packages with names
-- that start with @packagePrefix@ are returned.
listPackages_packagePrefix :: Lens.Lens' ListPackages (Prelude.Maybe Prelude.Text)
listPackages_packagePrefix :: Lens' ListPackages (Maybe Text)
listPackages_packagePrefix = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPackages' {Maybe Text
packagePrefix :: Maybe Text
$sel:packagePrefix:ListPackages' :: ListPackages -> Maybe Text
packagePrefix} -> Maybe Text
packagePrefix) (\s :: ListPackages
s@ListPackages' {} Maybe Text
a -> ListPackages
s {$sel:packagePrefix:ListPackages' :: Maybe Text
packagePrefix = Maybe Text
a} :: ListPackages)

-- | The value of the @Publish@ package origin control restriction used to
-- filter requested packages. Only packages with the provided restriction
-- are returned. For more information, see
-- <https://docs.aws.amazon.com/codeartifact/latest/APIReference/API_PackageOriginRestrictions.html PackageOriginRestrictions>.
listPackages_publish :: Lens.Lens' ListPackages (Prelude.Maybe AllowPublish)
listPackages_publish :: Lens' ListPackages (Maybe AllowPublish)
listPackages_publish = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPackages' {Maybe AllowPublish
publish :: Maybe AllowPublish
$sel:publish:ListPackages' :: ListPackages -> Maybe AllowPublish
publish} -> Maybe AllowPublish
publish) (\s :: ListPackages
s@ListPackages' {} Maybe AllowPublish
a -> ListPackages
s {$sel:publish:ListPackages' :: Maybe AllowPublish
publish = Maybe AllowPublish
a} :: ListPackages)

-- | The value of the @Upstream@ package origin control restriction used to
-- filter requested packages. Only packages with the provided restriction
-- are returned. For more information, see
-- <https://docs.aws.amazon.com/codeartifact/latest/APIReference/API_PackageOriginRestrictions.html PackageOriginRestrictions>.
listPackages_upstream :: Lens.Lens' ListPackages (Prelude.Maybe AllowUpstream)
listPackages_upstream :: Lens' ListPackages (Maybe AllowUpstream)
listPackages_upstream = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPackages' {Maybe AllowUpstream
upstream :: Maybe AllowUpstream
$sel:upstream:ListPackages' :: ListPackages -> Maybe AllowUpstream
upstream} -> Maybe AllowUpstream
upstream) (\s :: ListPackages
s@ListPackages' {} Maybe AllowUpstream
a -> ListPackages
s {$sel:upstream:ListPackages' :: Maybe AllowUpstream
upstream = Maybe AllowUpstream
a} :: ListPackages)

-- | The name of the domain that contains the repository that contains the
-- requested packages.
listPackages_domain :: Lens.Lens' ListPackages Prelude.Text
listPackages_domain :: Lens' ListPackages Text
listPackages_domain = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPackages' {Text
domain :: Text
$sel:domain:ListPackages' :: ListPackages -> Text
domain} -> Text
domain) (\s :: ListPackages
s@ListPackages' {} Text
a -> ListPackages
s {$sel:domain:ListPackages' :: Text
domain = Text
a} :: ListPackages)

-- | The name of the repository that contains the requested packages.
listPackages_repository :: Lens.Lens' ListPackages Prelude.Text
listPackages_repository :: Lens' ListPackages Text
listPackages_repository = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPackages' {Text
repository :: Text
$sel:repository:ListPackages' :: ListPackages -> Text
repository} -> Text
repository) (\s :: ListPackages
s@ListPackages' {} Text
a -> ListPackages
s {$sel:repository:ListPackages' :: Text
repository = Text
a} :: ListPackages)

instance Core.AWSPager ListPackages where
  page :: ListPackages -> AWSResponse ListPackages -> Maybe ListPackages
page ListPackages
rq AWSResponse ListPackages
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListPackages
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListPackagesResponse (Maybe Text)
listPackagesResponse_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 ListPackages
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListPackagesResponse (Maybe [PackageSummary])
listPackagesResponse_packages
            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.$ ListPackages
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListPackages (Maybe Text)
listPackages_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListPackages
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListPackagesResponse (Maybe Text)
listPackagesResponse_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 ListPackages where
  type AWSResponse ListPackages = ListPackagesResponse
  request :: (Service -> Service) -> ListPackages -> Request ListPackages
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 ListPackages
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListPackages)))
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 [PackageSummary] -> Int -> ListPackagesResponse
ListPackagesResponse'
            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
"packages" 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 ListPackages where
  hashWithSalt :: Int -> ListPackages -> Int
hashWithSalt Int
_salt ListPackages' {Maybe Natural
Maybe Text
Maybe AllowPublish
Maybe AllowUpstream
Maybe PackageFormat
Text
repository :: Text
domain :: Text
upstream :: Maybe AllowUpstream
publish :: Maybe AllowPublish
packagePrefix :: Maybe Text
nextToken :: Maybe Text
namespace :: Maybe Text
maxResults :: Maybe Natural
format :: Maybe PackageFormat
domainOwner :: Maybe Text
$sel:repository:ListPackages' :: ListPackages -> Text
$sel:domain:ListPackages' :: ListPackages -> Text
$sel:upstream:ListPackages' :: ListPackages -> Maybe AllowUpstream
$sel:publish:ListPackages' :: ListPackages -> Maybe AllowPublish
$sel:packagePrefix:ListPackages' :: ListPackages -> Maybe Text
$sel:nextToken:ListPackages' :: ListPackages -> Maybe Text
$sel:namespace:ListPackages' :: ListPackages -> Maybe Text
$sel:maxResults:ListPackages' :: ListPackages -> Maybe Natural
$sel:format:ListPackages' :: ListPackages -> Maybe PackageFormat
$sel:domainOwner:ListPackages' :: ListPackages -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
domainOwner
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe PackageFormat
format
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maxResults
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
namespace
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
packagePrefix
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AllowPublish
publish
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AllowUpstream
upstream
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
domain
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
repository

instance Prelude.NFData ListPackages where
  rnf :: ListPackages -> ()
rnf ListPackages' {Maybe Natural
Maybe Text
Maybe AllowPublish
Maybe AllowUpstream
Maybe PackageFormat
Text
repository :: Text
domain :: Text
upstream :: Maybe AllowUpstream
publish :: Maybe AllowPublish
packagePrefix :: Maybe Text
nextToken :: Maybe Text
namespace :: Maybe Text
maxResults :: Maybe Natural
format :: Maybe PackageFormat
domainOwner :: Maybe Text
$sel:repository:ListPackages' :: ListPackages -> Text
$sel:domain:ListPackages' :: ListPackages -> Text
$sel:upstream:ListPackages' :: ListPackages -> Maybe AllowUpstream
$sel:publish:ListPackages' :: ListPackages -> Maybe AllowPublish
$sel:packagePrefix:ListPackages' :: ListPackages -> Maybe Text
$sel:nextToken:ListPackages' :: ListPackages -> Maybe Text
$sel:namespace:ListPackages' :: ListPackages -> Maybe Text
$sel:maxResults:ListPackages' :: ListPackages -> Maybe Natural
$sel:format:ListPackages' :: ListPackages -> Maybe PackageFormat
$sel:domainOwner:ListPackages' :: ListPackages -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
domainOwner
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe PackageFormat
format
      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
namespace
      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
packagePrefix
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe AllowPublish
publish
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe AllowUpstream
upstream
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
domain
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
repository

instance Data.ToHeaders ListPackages where
  toHeaders :: ListPackages -> 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.ToJSON ListPackages where
  toJSON :: ListPackages -> Value
toJSON = forall a b. a -> b -> a
Prelude.const (Object -> Value
Data.Object forall a. Monoid a => a
Prelude.mempty)

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

instance Data.ToQuery ListPackages where
  toQuery :: ListPackages -> QueryString
toQuery ListPackages' {Maybe Natural
Maybe Text
Maybe AllowPublish
Maybe AllowUpstream
Maybe PackageFormat
Text
repository :: Text
domain :: Text
upstream :: Maybe AllowUpstream
publish :: Maybe AllowPublish
packagePrefix :: Maybe Text
nextToken :: Maybe Text
namespace :: Maybe Text
maxResults :: Maybe Natural
format :: Maybe PackageFormat
domainOwner :: Maybe Text
$sel:repository:ListPackages' :: ListPackages -> Text
$sel:domain:ListPackages' :: ListPackages -> Text
$sel:upstream:ListPackages' :: ListPackages -> Maybe AllowUpstream
$sel:publish:ListPackages' :: ListPackages -> Maybe AllowPublish
$sel:packagePrefix:ListPackages' :: ListPackages -> Maybe Text
$sel:nextToken:ListPackages' :: ListPackages -> Maybe Text
$sel:namespace:ListPackages' :: ListPackages -> Maybe Text
$sel:maxResults:ListPackages' :: ListPackages -> Maybe Natural
$sel:format:ListPackages' :: ListPackages -> Maybe PackageFormat
$sel:domainOwner:ListPackages' :: ListPackages -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"domain-owner" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
domainOwner,
        ByteString
"format" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe PackageFormat
format,
        ByteString
"max-results" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Natural
maxResults,
        ByteString
"namespace" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
namespace,
        ByteString
"next-token" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
nextToken,
        ByteString
"package-prefix" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
packagePrefix,
        ByteString
"publish" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe AllowPublish
publish,
        ByteString
"upstream" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe AllowUpstream
upstream,
        ByteString
"domain" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
domain,
        ByteString
"repository" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
repository
      ]

-- | /See:/ 'newListPackagesResponse' smart constructor.
data ListPackagesResponse = ListPackagesResponse'
  { -- | If there are additional results, this is the token for the next set of
    -- results.
    ListPackagesResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The list of returned
    -- <https://docs.aws.amazon.com/codeartifact/latest/APIReference/API_PackageSummary.html PackageSummary>
    -- objects.
    ListPackagesResponse -> Maybe [PackageSummary]
packages :: Prelude.Maybe [PackageSummary],
    -- | The response's http status code.
    ListPackagesResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListPackagesResponse -> ListPackagesResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListPackagesResponse -> ListPackagesResponse -> Bool
$c/= :: ListPackagesResponse -> ListPackagesResponse -> Bool
== :: ListPackagesResponse -> ListPackagesResponse -> Bool
$c== :: ListPackagesResponse -> ListPackagesResponse -> Bool
Prelude.Eq, ReadPrec [ListPackagesResponse]
ReadPrec ListPackagesResponse
Int -> ReadS ListPackagesResponse
ReadS [ListPackagesResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListPackagesResponse]
$creadListPrec :: ReadPrec [ListPackagesResponse]
readPrec :: ReadPrec ListPackagesResponse
$creadPrec :: ReadPrec ListPackagesResponse
readList :: ReadS [ListPackagesResponse]
$creadList :: ReadS [ListPackagesResponse]
readsPrec :: Int -> ReadS ListPackagesResponse
$creadsPrec :: Int -> ReadS ListPackagesResponse
Prelude.Read, Int -> ListPackagesResponse -> ShowS
[ListPackagesResponse] -> ShowS
ListPackagesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListPackagesResponse] -> ShowS
$cshowList :: [ListPackagesResponse] -> ShowS
show :: ListPackagesResponse -> String
$cshow :: ListPackagesResponse -> String
showsPrec :: Int -> ListPackagesResponse -> ShowS
$cshowsPrec :: Int -> ListPackagesResponse -> ShowS
Prelude.Show, forall x. Rep ListPackagesResponse x -> ListPackagesResponse
forall x. ListPackagesResponse -> Rep ListPackagesResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListPackagesResponse x -> ListPackagesResponse
$cfrom :: forall x. ListPackagesResponse -> Rep ListPackagesResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListPackagesResponse' 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', 'listPackagesResponse_nextToken' - If there are additional results, this is the token for the next set of
-- results.
--
-- 'packages', 'listPackagesResponse_packages' - The list of returned
-- <https://docs.aws.amazon.com/codeartifact/latest/APIReference/API_PackageSummary.html PackageSummary>
-- objects.
--
-- 'httpStatus', 'listPackagesResponse_httpStatus' - The response's http status code.
newListPackagesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListPackagesResponse
newListPackagesResponse :: Int -> ListPackagesResponse
newListPackagesResponse Int
pHttpStatus_ =
  ListPackagesResponse'
    { $sel:nextToken:ListPackagesResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:packages:ListPackagesResponse' :: Maybe [PackageSummary]
packages = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListPackagesResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | If there are additional results, this is the token for the next set of
-- results.
listPackagesResponse_nextToken :: Lens.Lens' ListPackagesResponse (Prelude.Maybe Prelude.Text)
listPackagesResponse_nextToken :: Lens' ListPackagesResponse (Maybe Text)
listPackagesResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPackagesResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListPackagesResponse' :: ListPackagesResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListPackagesResponse
s@ListPackagesResponse' {} Maybe Text
a -> ListPackagesResponse
s {$sel:nextToken:ListPackagesResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListPackagesResponse)

-- | The list of returned
-- <https://docs.aws.amazon.com/codeartifact/latest/APIReference/API_PackageSummary.html PackageSummary>
-- objects.
listPackagesResponse_packages :: Lens.Lens' ListPackagesResponse (Prelude.Maybe [PackageSummary])
listPackagesResponse_packages :: Lens' ListPackagesResponse (Maybe [PackageSummary])
listPackagesResponse_packages = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPackagesResponse' {Maybe [PackageSummary]
packages :: Maybe [PackageSummary]
$sel:packages:ListPackagesResponse' :: ListPackagesResponse -> Maybe [PackageSummary]
packages} -> Maybe [PackageSummary]
packages) (\s :: ListPackagesResponse
s@ListPackagesResponse' {} Maybe [PackageSummary]
a -> ListPackagesResponse
s {$sel:packages:ListPackagesResponse' :: Maybe [PackageSummary]
packages = Maybe [PackageSummary]
a} :: ListPackagesResponse) 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.
listPackagesResponse_httpStatus :: Lens.Lens' ListPackagesResponse Prelude.Int
listPackagesResponse_httpStatus :: Lens' ListPackagesResponse Int
listPackagesResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListPackagesResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListPackagesResponse' :: ListPackagesResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListPackagesResponse
s@ListPackagesResponse' {} Int
a -> ListPackagesResponse
s {$sel:httpStatus:ListPackagesResponse' :: Int
httpStatus = Int
a} :: ListPackagesResponse)

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