{-# 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.Route53.ListCidrCollections
-- 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 paginated list of CIDR collections in the Amazon Web Services
-- account (metadata only).
--
-- This operation returns paginated results.
module Amazonka.Route53.ListCidrCollections
  ( -- * Creating a Request
    ListCidrCollections (..),
    newListCidrCollections,

    -- * Request Lenses
    listCidrCollections_maxResults,
    listCidrCollections_nextToken,

    -- * Destructuring the Response
    ListCidrCollectionsResponse (..),
    newListCidrCollectionsResponse,

    -- * Response Lenses
    listCidrCollectionsResponse_cidrCollections,
    listCidrCollectionsResponse_nextToken,
    listCidrCollectionsResponse_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.Route53.Types

-- | /See:/ 'newListCidrCollections' smart constructor.
data ListCidrCollections = ListCidrCollections'
  { -- | The maximum number of CIDR collections to return in the response.
    ListCidrCollections -> Maybe Text
maxResults :: Prelude.Maybe Prelude.Text,
    -- | An opaque pagination token to indicate where the service is to begin
    -- enumerating results.
    --
    -- If no value is provided, the listing of results starts from the
    -- beginning.
    ListCidrCollections -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text
  }
  deriving (ListCidrCollections -> ListCidrCollections -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListCidrCollections -> ListCidrCollections -> Bool
$c/= :: ListCidrCollections -> ListCidrCollections -> Bool
== :: ListCidrCollections -> ListCidrCollections -> Bool
$c== :: ListCidrCollections -> ListCidrCollections -> Bool
Prelude.Eq, ReadPrec [ListCidrCollections]
ReadPrec ListCidrCollections
Int -> ReadS ListCidrCollections
ReadS [ListCidrCollections]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListCidrCollections]
$creadListPrec :: ReadPrec [ListCidrCollections]
readPrec :: ReadPrec ListCidrCollections
$creadPrec :: ReadPrec ListCidrCollections
readList :: ReadS [ListCidrCollections]
$creadList :: ReadS [ListCidrCollections]
readsPrec :: Int -> ReadS ListCidrCollections
$creadsPrec :: Int -> ReadS ListCidrCollections
Prelude.Read, Int -> ListCidrCollections -> ShowS
[ListCidrCollections] -> ShowS
ListCidrCollections -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListCidrCollections] -> ShowS
$cshowList :: [ListCidrCollections] -> ShowS
show :: ListCidrCollections -> String
$cshow :: ListCidrCollections -> String
showsPrec :: Int -> ListCidrCollections -> ShowS
$cshowsPrec :: Int -> ListCidrCollections -> ShowS
Prelude.Show, forall x. Rep ListCidrCollections x -> ListCidrCollections
forall x. ListCidrCollections -> Rep ListCidrCollections x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListCidrCollections x -> ListCidrCollections
$cfrom :: forall x. ListCidrCollections -> Rep ListCidrCollections x
Prelude.Generic)

-- |
-- Create a value of 'ListCidrCollections' 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', 'listCidrCollections_maxResults' - The maximum number of CIDR collections to return in the response.
--
-- 'nextToken', 'listCidrCollections_nextToken' - An opaque pagination token to indicate where the service is to begin
-- enumerating results.
--
-- If no value is provided, the listing of results starts from the
-- beginning.
newListCidrCollections ::
  ListCidrCollections
newListCidrCollections :: ListCidrCollections
newListCidrCollections =
  ListCidrCollections'
    { $sel:maxResults:ListCidrCollections' :: Maybe Text
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListCidrCollections' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing
    }

-- | The maximum number of CIDR collections to return in the response.
listCidrCollections_maxResults :: Lens.Lens' ListCidrCollections (Prelude.Maybe Prelude.Text)
listCidrCollections_maxResults :: Lens' ListCidrCollections (Maybe Text)
listCidrCollections_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListCidrCollections' {Maybe Text
maxResults :: Maybe Text
$sel:maxResults:ListCidrCollections' :: ListCidrCollections -> Maybe Text
maxResults} -> Maybe Text
maxResults) (\s :: ListCidrCollections
s@ListCidrCollections' {} Maybe Text
a -> ListCidrCollections
s {$sel:maxResults:ListCidrCollections' :: Maybe Text
maxResults = Maybe Text
a} :: ListCidrCollections)

-- | An opaque pagination token to indicate where the service is to begin
-- enumerating results.
--
-- If no value is provided, the listing of results starts from the
-- beginning.
listCidrCollections_nextToken :: Lens.Lens' ListCidrCollections (Prelude.Maybe Prelude.Text)
listCidrCollections_nextToken :: Lens' ListCidrCollections (Maybe Text)
listCidrCollections_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListCidrCollections' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListCidrCollections' :: ListCidrCollections -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListCidrCollections
s@ListCidrCollections' {} Maybe Text
a -> ListCidrCollections
s {$sel:nextToken:ListCidrCollections' :: Maybe Text
nextToken = Maybe Text
a} :: ListCidrCollections)

instance Core.AWSPager ListCidrCollections where
  page :: ListCidrCollections
-> AWSResponse ListCidrCollections -> Maybe ListCidrCollections
page ListCidrCollections
rq AWSResponse ListCidrCollections
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListCidrCollections
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListCidrCollectionsResponse (Maybe Text)
listCidrCollectionsResponse_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 ListCidrCollections
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListCidrCollectionsResponse (Maybe [CollectionSummary])
listCidrCollectionsResponse_cidrCollections
            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.$ ListCidrCollections
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListCidrCollections (Maybe Text)
listCidrCollections_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListCidrCollections
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListCidrCollectionsResponse (Maybe Text)
listCidrCollectionsResponse_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 ListCidrCollections where
  type
    AWSResponse ListCidrCollections =
      ListCidrCollectionsResponse
  request :: (Service -> Service)
-> ListCidrCollections -> Request ListCidrCollections
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 ListCidrCollections
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListCidrCollections)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXML
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe [CollectionSummary]
-> Maybe Text -> Int -> ListCidrCollectionsResponse
ListCidrCollectionsResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ( [Node]
x
                            forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"CidrCollections"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                            forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"member")
                        )
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"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 ListCidrCollections where
  hashWithSalt :: Int -> ListCidrCollections -> Int
hashWithSalt Int
_salt ListCidrCollections' {Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Text
$sel:nextToken:ListCidrCollections' :: ListCidrCollections -> Maybe Text
$sel:maxResults:ListCidrCollections' :: ListCidrCollections -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
maxResults
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken

instance Prelude.NFData ListCidrCollections where
  rnf :: ListCidrCollections -> ()
rnf ListCidrCollections' {Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Text
$sel:nextToken:ListCidrCollections' :: ListCidrCollections -> Maybe Text
$sel:maxResults:ListCidrCollections' :: ListCidrCollections -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
maxResults
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken

instance Data.ToHeaders ListCidrCollections where
  toHeaders :: ListCidrCollections -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

instance Data.ToPath ListCidrCollections where
  toPath :: ListCidrCollections -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/2013-04-01/cidrcollection"

instance Data.ToQuery ListCidrCollections where
  toQuery :: ListCidrCollections -> QueryString
toQuery ListCidrCollections' {Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Text
$sel:nextToken:ListCidrCollections' :: ListCidrCollections -> Maybe Text
$sel:maxResults:ListCidrCollections' :: ListCidrCollections -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"maxresults" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
maxResults,
        ByteString
"nexttoken" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
nextToken
      ]

-- | /See:/ 'newListCidrCollectionsResponse' smart constructor.
data ListCidrCollectionsResponse = ListCidrCollectionsResponse'
  { -- | A complex type with information about the CIDR collection.
    ListCidrCollectionsResponse -> Maybe [CollectionSummary]
cidrCollections :: Prelude.Maybe [CollectionSummary],
    -- | An opaque pagination token to indicate where the service is to begin
    -- enumerating results.
    --
    -- If no value is provided, the listing of results starts from the
    -- beginning.
    ListCidrCollectionsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListCidrCollectionsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListCidrCollectionsResponse -> ListCidrCollectionsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListCidrCollectionsResponse -> ListCidrCollectionsResponse -> Bool
$c/= :: ListCidrCollectionsResponse -> ListCidrCollectionsResponse -> Bool
== :: ListCidrCollectionsResponse -> ListCidrCollectionsResponse -> Bool
$c== :: ListCidrCollectionsResponse -> ListCidrCollectionsResponse -> Bool
Prelude.Eq, ReadPrec [ListCidrCollectionsResponse]
ReadPrec ListCidrCollectionsResponse
Int -> ReadS ListCidrCollectionsResponse
ReadS [ListCidrCollectionsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListCidrCollectionsResponse]
$creadListPrec :: ReadPrec [ListCidrCollectionsResponse]
readPrec :: ReadPrec ListCidrCollectionsResponse
$creadPrec :: ReadPrec ListCidrCollectionsResponse
readList :: ReadS [ListCidrCollectionsResponse]
$creadList :: ReadS [ListCidrCollectionsResponse]
readsPrec :: Int -> ReadS ListCidrCollectionsResponse
$creadsPrec :: Int -> ReadS ListCidrCollectionsResponse
Prelude.Read, Int -> ListCidrCollectionsResponse -> ShowS
[ListCidrCollectionsResponse] -> ShowS
ListCidrCollectionsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListCidrCollectionsResponse] -> ShowS
$cshowList :: [ListCidrCollectionsResponse] -> ShowS
show :: ListCidrCollectionsResponse -> String
$cshow :: ListCidrCollectionsResponse -> String
showsPrec :: Int -> ListCidrCollectionsResponse -> ShowS
$cshowsPrec :: Int -> ListCidrCollectionsResponse -> ShowS
Prelude.Show, forall x.
Rep ListCidrCollectionsResponse x -> ListCidrCollectionsResponse
forall x.
ListCidrCollectionsResponse -> Rep ListCidrCollectionsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListCidrCollectionsResponse x -> ListCidrCollectionsResponse
$cfrom :: forall x.
ListCidrCollectionsResponse -> Rep ListCidrCollectionsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListCidrCollectionsResponse' 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:
--
-- 'cidrCollections', 'listCidrCollectionsResponse_cidrCollections' - A complex type with information about the CIDR collection.
--
-- 'nextToken', 'listCidrCollectionsResponse_nextToken' - An opaque pagination token to indicate where the service is to begin
-- enumerating results.
--
-- If no value is provided, the listing of results starts from the
-- beginning.
--
-- 'httpStatus', 'listCidrCollectionsResponse_httpStatus' - The response's http status code.
newListCidrCollectionsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListCidrCollectionsResponse
newListCidrCollectionsResponse :: Int -> ListCidrCollectionsResponse
newListCidrCollectionsResponse Int
pHttpStatus_ =
  ListCidrCollectionsResponse'
    { $sel:cidrCollections:ListCidrCollectionsResponse' :: Maybe [CollectionSummary]
cidrCollections =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListCidrCollectionsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListCidrCollectionsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A complex type with information about the CIDR collection.
listCidrCollectionsResponse_cidrCollections :: Lens.Lens' ListCidrCollectionsResponse (Prelude.Maybe [CollectionSummary])
listCidrCollectionsResponse_cidrCollections :: Lens' ListCidrCollectionsResponse (Maybe [CollectionSummary])
listCidrCollectionsResponse_cidrCollections = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListCidrCollectionsResponse' {Maybe [CollectionSummary]
cidrCollections :: Maybe [CollectionSummary]
$sel:cidrCollections:ListCidrCollectionsResponse' :: ListCidrCollectionsResponse -> Maybe [CollectionSummary]
cidrCollections} -> Maybe [CollectionSummary]
cidrCollections) (\s :: ListCidrCollectionsResponse
s@ListCidrCollectionsResponse' {} Maybe [CollectionSummary]
a -> ListCidrCollectionsResponse
s {$sel:cidrCollections:ListCidrCollectionsResponse' :: Maybe [CollectionSummary]
cidrCollections = Maybe [CollectionSummary]
a} :: ListCidrCollectionsResponse) 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

-- | An opaque pagination token to indicate where the service is to begin
-- enumerating results.
--
-- If no value is provided, the listing of results starts from the
-- beginning.
listCidrCollectionsResponse_nextToken :: Lens.Lens' ListCidrCollectionsResponse (Prelude.Maybe Prelude.Text)
listCidrCollectionsResponse_nextToken :: Lens' ListCidrCollectionsResponse (Maybe Text)
listCidrCollectionsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListCidrCollectionsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListCidrCollectionsResponse' :: ListCidrCollectionsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListCidrCollectionsResponse
s@ListCidrCollectionsResponse' {} Maybe Text
a -> ListCidrCollectionsResponse
s {$sel:nextToken:ListCidrCollectionsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListCidrCollectionsResponse)

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

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