{-# 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.EC2.GetSubnetCidrReservations
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Gets information about the subnet CIDR reservations.
module Amazonka.EC2.GetSubnetCidrReservations
  ( -- * Creating a Request
    GetSubnetCidrReservations (..),
    newGetSubnetCidrReservations,

    -- * Request Lenses
    getSubnetCidrReservations_dryRun,
    getSubnetCidrReservations_filters,
    getSubnetCidrReservations_maxResults,
    getSubnetCidrReservations_nextToken,
    getSubnetCidrReservations_subnetId,

    -- * Destructuring the Response
    GetSubnetCidrReservationsResponse (..),
    newGetSubnetCidrReservationsResponse,

    -- * Response Lenses
    getSubnetCidrReservationsResponse_nextToken,
    getSubnetCidrReservationsResponse_subnetIpv4CidrReservations,
    getSubnetCidrReservationsResponse_subnetIpv6CidrReservations,
    getSubnetCidrReservationsResponse_httpStatus,
  )
where

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

-- | /See:/ 'newGetSubnetCidrReservations' smart constructor.
data GetSubnetCidrReservations = GetSubnetCidrReservations'
  { -- | Checks whether you have the required permissions for the action, without
    -- actually making the request, and provides an error response. If you have
    -- the required permissions, the error response is @DryRunOperation@.
    -- Otherwise, it is @UnauthorizedOperation@.
    GetSubnetCidrReservations -> Maybe Bool
dryRun :: Prelude.Maybe Prelude.Bool,
    -- | One or more filters.
    --
    -- -   @reservationType@ - The type of reservation (@prefix@ | @explicit@).
    --
    -- -   @subnet-id@ - The ID of the subnet.
    --
    -- -   @tag@:\<key> - The key\/value combination of a tag assigned to the
    --     resource. Use the tag key in the filter name and the tag value as
    --     the filter value. For example, to find all resources that have a tag
    --     with the key @Owner@ and the value @TeamA@, specify @tag:Owner@ for
    --     the filter name and @TeamA@ for the filter value.
    --
    -- -   @tag-key@ - The key of a tag assigned to the resource. Use this
    --     filter to find all resources assigned a tag with a specific key,
    --     regardless of the tag value.
    GetSubnetCidrReservations -> Maybe [Filter]
filters :: Prelude.Maybe [Filter],
    -- | The maximum number of results to return with a single call. To retrieve
    -- the remaining results, make another call with the returned @nextToken@
    -- value.
    GetSubnetCidrReservations -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | The token for the next page of results.
    GetSubnetCidrReservations -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The ID of the subnet.
    GetSubnetCidrReservations -> Text
subnetId :: Prelude.Text
  }
  deriving (GetSubnetCidrReservations -> GetSubnetCidrReservations -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetSubnetCidrReservations -> GetSubnetCidrReservations -> Bool
$c/= :: GetSubnetCidrReservations -> GetSubnetCidrReservations -> Bool
== :: GetSubnetCidrReservations -> GetSubnetCidrReservations -> Bool
$c== :: GetSubnetCidrReservations -> GetSubnetCidrReservations -> Bool
Prelude.Eq, ReadPrec [GetSubnetCidrReservations]
ReadPrec GetSubnetCidrReservations
Int -> ReadS GetSubnetCidrReservations
ReadS [GetSubnetCidrReservations]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetSubnetCidrReservations]
$creadListPrec :: ReadPrec [GetSubnetCidrReservations]
readPrec :: ReadPrec GetSubnetCidrReservations
$creadPrec :: ReadPrec GetSubnetCidrReservations
readList :: ReadS [GetSubnetCidrReservations]
$creadList :: ReadS [GetSubnetCidrReservations]
readsPrec :: Int -> ReadS GetSubnetCidrReservations
$creadsPrec :: Int -> ReadS GetSubnetCidrReservations
Prelude.Read, Int -> GetSubnetCidrReservations -> ShowS
[GetSubnetCidrReservations] -> ShowS
GetSubnetCidrReservations -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetSubnetCidrReservations] -> ShowS
$cshowList :: [GetSubnetCidrReservations] -> ShowS
show :: GetSubnetCidrReservations -> String
$cshow :: GetSubnetCidrReservations -> String
showsPrec :: Int -> GetSubnetCidrReservations -> ShowS
$cshowsPrec :: Int -> GetSubnetCidrReservations -> ShowS
Prelude.Show, forall x.
Rep GetSubnetCidrReservations x -> GetSubnetCidrReservations
forall x.
GetSubnetCidrReservations -> Rep GetSubnetCidrReservations x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetSubnetCidrReservations x -> GetSubnetCidrReservations
$cfrom :: forall x.
GetSubnetCidrReservations -> Rep GetSubnetCidrReservations x
Prelude.Generic)

-- |
-- Create a value of 'GetSubnetCidrReservations' 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:
--
-- 'dryRun', 'getSubnetCidrReservations_dryRun' - Checks whether you have the required permissions for the action, without
-- actually making the request, and provides an error response. If you have
-- the required permissions, the error response is @DryRunOperation@.
-- Otherwise, it is @UnauthorizedOperation@.
--
-- 'filters', 'getSubnetCidrReservations_filters' - One or more filters.
--
-- -   @reservationType@ - The type of reservation (@prefix@ | @explicit@).
--
-- -   @subnet-id@ - The ID of the subnet.
--
-- -   @tag@:\<key> - The key\/value combination of a tag assigned to the
--     resource. Use the tag key in the filter name and the tag value as
--     the filter value. For example, to find all resources that have a tag
--     with the key @Owner@ and the value @TeamA@, specify @tag:Owner@ for
--     the filter name and @TeamA@ for the filter value.
--
-- -   @tag-key@ - The key of a tag assigned to the resource. Use this
--     filter to find all resources assigned a tag with a specific key,
--     regardless of the tag value.
--
-- 'maxResults', 'getSubnetCidrReservations_maxResults' - The maximum number of results to return with a single call. To retrieve
-- the remaining results, make another call with the returned @nextToken@
-- value.
--
-- 'nextToken', 'getSubnetCidrReservations_nextToken' - The token for the next page of results.
--
-- 'subnetId', 'getSubnetCidrReservations_subnetId' - The ID of the subnet.
newGetSubnetCidrReservations ::
  -- | 'subnetId'
  Prelude.Text ->
  GetSubnetCidrReservations
newGetSubnetCidrReservations :: Text -> GetSubnetCidrReservations
newGetSubnetCidrReservations Text
pSubnetId_ =
  GetSubnetCidrReservations'
    { $sel:dryRun:GetSubnetCidrReservations' :: Maybe Bool
dryRun =
        forall a. Maybe a
Prelude.Nothing,
      $sel:filters:GetSubnetCidrReservations' :: Maybe [Filter]
filters = forall a. Maybe a
Prelude.Nothing,
      $sel:maxResults:GetSubnetCidrReservations' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:GetSubnetCidrReservations' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:subnetId:GetSubnetCidrReservations' :: Text
subnetId = Text
pSubnetId_
    }

-- | Checks whether you have the required permissions for the action, without
-- actually making the request, and provides an error response. If you have
-- the required permissions, the error response is @DryRunOperation@.
-- Otherwise, it is @UnauthorizedOperation@.
getSubnetCidrReservations_dryRun :: Lens.Lens' GetSubnetCidrReservations (Prelude.Maybe Prelude.Bool)
getSubnetCidrReservations_dryRun :: Lens' GetSubnetCidrReservations (Maybe Bool)
getSubnetCidrReservations_dryRun = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSubnetCidrReservations' {Maybe Bool
dryRun :: Maybe Bool
$sel:dryRun:GetSubnetCidrReservations' :: GetSubnetCidrReservations -> Maybe Bool
dryRun} -> Maybe Bool
dryRun) (\s :: GetSubnetCidrReservations
s@GetSubnetCidrReservations' {} Maybe Bool
a -> GetSubnetCidrReservations
s {$sel:dryRun:GetSubnetCidrReservations' :: Maybe Bool
dryRun = Maybe Bool
a} :: GetSubnetCidrReservations)

-- | One or more filters.
--
-- -   @reservationType@ - The type of reservation (@prefix@ | @explicit@).
--
-- -   @subnet-id@ - The ID of the subnet.
--
-- -   @tag@:\<key> - The key\/value combination of a tag assigned to the
--     resource. Use the tag key in the filter name and the tag value as
--     the filter value. For example, to find all resources that have a tag
--     with the key @Owner@ and the value @TeamA@, specify @tag:Owner@ for
--     the filter name and @TeamA@ for the filter value.
--
-- -   @tag-key@ - The key of a tag assigned to the resource. Use this
--     filter to find all resources assigned a tag with a specific key,
--     regardless of the tag value.
getSubnetCidrReservations_filters :: Lens.Lens' GetSubnetCidrReservations (Prelude.Maybe [Filter])
getSubnetCidrReservations_filters :: Lens' GetSubnetCidrReservations (Maybe [Filter])
getSubnetCidrReservations_filters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSubnetCidrReservations' {Maybe [Filter]
filters :: Maybe [Filter]
$sel:filters:GetSubnetCidrReservations' :: GetSubnetCidrReservations -> Maybe [Filter]
filters} -> Maybe [Filter]
filters) (\s :: GetSubnetCidrReservations
s@GetSubnetCidrReservations' {} Maybe [Filter]
a -> GetSubnetCidrReservations
s {$sel:filters:GetSubnetCidrReservations' :: Maybe [Filter]
filters = Maybe [Filter]
a} :: GetSubnetCidrReservations) 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 maximum number of results to return with a single call. To retrieve
-- the remaining results, make another call with the returned @nextToken@
-- value.
getSubnetCidrReservations_maxResults :: Lens.Lens' GetSubnetCidrReservations (Prelude.Maybe Prelude.Natural)
getSubnetCidrReservations_maxResults :: Lens' GetSubnetCidrReservations (Maybe Natural)
getSubnetCidrReservations_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSubnetCidrReservations' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:GetSubnetCidrReservations' :: GetSubnetCidrReservations -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: GetSubnetCidrReservations
s@GetSubnetCidrReservations' {} Maybe Natural
a -> GetSubnetCidrReservations
s {$sel:maxResults:GetSubnetCidrReservations' :: Maybe Natural
maxResults = Maybe Natural
a} :: GetSubnetCidrReservations)

-- | The token for the next page of results.
getSubnetCidrReservations_nextToken :: Lens.Lens' GetSubnetCidrReservations (Prelude.Maybe Prelude.Text)
getSubnetCidrReservations_nextToken :: Lens' GetSubnetCidrReservations (Maybe Text)
getSubnetCidrReservations_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSubnetCidrReservations' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:GetSubnetCidrReservations' :: GetSubnetCidrReservations -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: GetSubnetCidrReservations
s@GetSubnetCidrReservations' {} Maybe Text
a -> GetSubnetCidrReservations
s {$sel:nextToken:GetSubnetCidrReservations' :: Maybe Text
nextToken = Maybe Text
a} :: GetSubnetCidrReservations)

-- | The ID of the subnet.
getSubnetCidrReservations_subnetId :: Lens.Lens' GetSubnetCidrReservations Prelude.Text
getSubnetCidrReservations_subnetId :: Lens' GetSubnetCidrReservations Text
getSubnetCidrReservations_subnetId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSubnetCidrReservations' {Text
subnetId :: Text
$sel:subnetId:GetSubnetCidrReservations' :: GetSubnetCidrReservations -> Text
subnetId} -> Text
subnetId) (\s :: GetSubnetCidrReservations
s@GetSubnetCidrReservations' {} Text
a -> GetSubnetCidrReservations
s {$sel:subnetId:GetSubnetCidrReservations' :: Text
subnetId = Text
a} :: GetSubnetCidrReservations)

instance Core.AWSRequest GetSubnetCidrReservations where
  type
    AWSResponse GetSubnetCidrReservations =
      GetSubnetCidrReservationsResponse
  request :: (Service -> Service)
-> GetSubnetCidrReservations -> Request GetSubnetCidrReservations
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.postQuery (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy GetSubnetCidrReservations
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetSubnetCidrReservations)))
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 Text
-> Maybe [SubnetCidrReservation]
-> Maybe [SubnetCidrReservation]
-> Int
-> GetSubnetCidrReservationsResponse
GetSubnetCidrReservationsResponse'
            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
"nextToken")
            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
"subnetIpv4CidrReservationSet"
                            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
"item")
                        )
            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
"subnetIpv6CidrReservationSet"
                            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
"item")
                        )
            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 GetSubnetCidrReservations where
  hashWithSalt :: Int -> GetSubnetCidrReservations -> Int
hashWithSalt Int
_salt GetSubnetCidrReservations' {Maybe Bool
Maybe Natural
Maybe [Filter]
Maybe Text
Text
subnetId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
filters :: Maybe [Filter]
dryRun :: Maybe Bool
$sel:subnetId:GetSubnetCidrReservations' :: GetSubnetCidrReservations -> Text
$sel:nextToken:GetSubnetCidrReservations' :: GetSubnetCidrReservations -> Maybe Text
$sel:maxResults:GetSubnetCidrReservations' :: GetSubnetCidrReservations -> Maybe Natural
$sel:filters:GetSubnetCidrReservations' :: GetSubnetCidrReservations -> Maybe [Filter]
$sel:dryRun:GetSubnetCidrReservations' :: GetSubnetCidrReservations -> Maybe Bool
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
dryRun
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Filter]
filters
      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
subnetId

instance Prelude.NFData GetSubnetCidrReservations where
  rnf :: GetSubnetCidrReservations -> ()
rnf GetSubnetCidrReservations' {Maybe Bool
Maybe Natural
Maybe [Filter]
Maybe Text
Text
subnetId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
filters :: Maybe [Filter]
dryRun :: Maybe Bool
$sel:subnetId:GetSubnetCidrReservations' :: GetSubnetCidrReservations -> Text
$sel:nextToken:GetSubnetCidrReservations' :: GetSubnetCidrReservations -> Maybe Text
$sel:maxResults:GetSubnetCidrReservations' :: GetSubnetCidrReservations -> Maybe Natural
$sel:filters:GetSubnetCidrReservations' :: GetSubnetCidrReservations -> Maybe [Filter]
$sel:dryRun:GetSubnetCidrReservations' :: GetSubnetCidrReservations -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
dryRun
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Filter]
filters
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
maxResults
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
subnetId

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

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

instance Data.ToQuery GetSubnetCidrReservations where
  toQuery :: GetSubnetCidrReservations -> QueryString
toQuery GetSubnetCidrReservations' {Maybe Bool
Maybe Natural
Maybe [Filter]
Maybe Text
Text
subnetId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
filters :: Maybe [Filter]
dryRun :: Maybe Bool
$sel:subnetId:GetSubnetCidrReservations' :: GetSubnetCidrReservations -> Text
$sel:nextToken:GetSubnetCidrReservations' :: GetSubnetCidrReservations -> Maybe Text
$sel:maxResults:GetSubnetCidrReservations' :: GetSubnetCidrReservations -> Maybe Natural
$sel:filters:GetSubnetCidrReservations' :: GetSubnetCidrReservations -> Maybe [Filter]
$sel:dryRun:GetSubnetCidrReservations' :: GetSubnetCidrReservations -> Maybe Bool
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"GetSubnetCidrReservations" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2016-11-15" :: Prelude.ByteString),
        ByteString
"DryRun" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
dryRun,
        forall a. ToQuery a => a -> QueryString
Data.toQuery
          (forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"Filter" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Filter]
filters),
        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,
        ByteString
"SubnetId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
subnetId
      ]

-- | /See:/ 'newGetSubnetCidrReservationsResponse' smart constructor.
data GetSubnetCidrReservationsResponse = GetSubnetCidrReservationsResponse'
  { -- | The token to use to retrieve the next page of results. This value is
    -- @null@ when there are no more results to return.
    GetSubnetCidrReservationsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | Information about the IPv4 subnet CIDR reservations.
    GetSubnetCidrReservationsResponse -> Maybe [SubnetCidrReservation]
subnetIpv4CidrReservations :: Prelude.Maybe [SubnetCidrReservation],
    -- | Information about the IPv6 subnet CIDR reservations.
    GetSubnetCidrReservationsResponse -> Maybe [SubnetCidrReservation]
subnetIpv6CidrReservations :: Prelude.Maybe [SubnetCidrReservation],
    -- | The response's http status code.
    GetSubnetCidrReservationsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetSubnetCidrReservationsResponse
-> GetSubnetCidrReservationsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetSubnetCidrReservationsResponse
-> GetSubnetCidrReservationsResponse -> Bool
$c/= :: GetSubnetCidrReservationsResponse
-> GetSubnetCidrReservationsResponse -> Bool
== :: GetSubnetCidrReservationsResponse
-> GetSubnetCidrReservationsResponse -> Bool
$c== :: GetSubnetCidrReservationsResponse
-> GetSubnetCidrReservationsResponse -> Bool
Prelude.Eq, ReadPrec [GetSubnetCidrReservationsResponse]
ReadPrec GetSubnetCidrReservationsResponse
Int -> ReadS GetSubnetCidrReservationsResponse
ReadS [GetSubnetCidrReservationsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetSubnetCidrReservationsResponse]
$creadListPrec :: ReadPrec [GetSubnetCidrReservationsResponse]
readPrec :: ReadPrec GetSubnetCidrReservationsResponse
$creadPrec :: ReadPrec GetSubnetCidrReservationsResponse
readList :: ReadS [GetSubnetCidrReservationsResponse]
$creadList :: ReadS [GetSubnetCidrReservationsResponse]
readsPrec :: Int -> ReadS GetSubnetCidrReservationsResponse
$creadsPrec :: Int -> ReadS GetSubnetCidrReservationsResponse
Prelude.Read, Int -> GetSubnetCidrReservationsResponse -> ShowS
[GetSubnetCidrReservationsResponse] -> ShowS
GetSubnetCidrReservationsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetSubnetCidrReservationsResponse] -> ShowS
$cshowList :: [GetSubnetCidrReservationsResponse] -> ShowS
show :: GetSubnetCidrReservationsResponse -> String
$cshow :: GetSubnetCidrReservationsResponse -> String
showsPrec :: Int -> GetSubnetCidrReservationsResponse -> ShowS
$cshowsPrec :: Int -> GetSubnetCidrReservationsResponse -> ShowS
Prelude.Show, forall x.
Rep GetSubnetCidrReservationsResponse x
-> GetSubnetCidrReservationsResponse
forall x.
GetSubnetCidrReservationsResponse
-> Rep GetSubnetCidrReservationsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetSubnetCidrReservationsResponse x
-> GetSubnetCidrReservationsResponse
$cfrom :: forall x.
GetSubnetCidrReservationsResponse
-> Rep GetSubnetCidrReservationsResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetSubnetCidrReservationsResponse' 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', 'getSubnetCidrReservationsResponse_nextToken' - The token to use to retrieve the next page of results. This value is
-- @null@ when there are no more results to return.
--
-- 'subnetIpv4CidrReservations', 'getSubnetCidrReservationsResponse_subnetIpv4CidrReservations' - Information about the IPv4 subnet CIDR reservations.
--
-- 'subnetIpv6CidrReservations', 'getSubnetCidrReservationsResponse_subnetIpv6CidrReservations' - Information about the IPv6 subnet CIDR reservations.
--
-- 'httpStatus', 'getSubnetCidrReservationsResponse_httpStatus' - The response's http status code.
newGetSubnetCidrReservationsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetSubnetCidrReservationsResponse
newGetSubnetCidrReservationsResponse :: Int -> GetSubnetCidrReservationsResponse
newGetSubnetCidrReservationsResponse Int
pHttpStatus_ =
  GetSubnetCidrReservationsResponse'
    { $sel:nextToken:GetSubnetCidrReservationsResponse' :: Maybe Text
nextToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:subnetIpv4CidrReservations:GetSubnetCidrReservationsResponse' :: Maybe [SubnetCidrReservation]
subnetIpv4CidrReservations =
        forall a. Maybe a
Prelude.Nothing,
      $sel:subnetIpv6CidrReservations:GetSubnetCidrReservationsResponse' :: Maybe [SubnetCidrReservation]
subnetIpv6CidrReservations =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetSubnetCidrReservationsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The token to use to retrieve the next page of results. This value is
-- @null@ when there are no more results to return.
getSubnetCidrReservationsResponse_nextToken :: Lens.Lens' GetSubnetCidrReservationsResponse (Prelude.Maybe Prelude.Text)
getSubnetCidrReservationsResponse_nextToken :: Lens' GetSubnetCidrReservationsResponse (Maybe Text)
getSubnetCidrReservationsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSubnetCidrReservationsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:GetSubnetCidrReservationsResponse' :: GetSubnetCidrReservationsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: GetSubnetCidrReservationsResponse
s@GetSubnetCidrReservationsResponse' {} Maybe Text
a -> GetSubnetCidrReservationsResponse
s {$sel:nextToken:GetSubnetCidrReservationsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: GetSubnetCidrReservationsResponse)

-- | Information about the IPv4 subnet CIDR reservations.
getSubnetCidrReservationsResponse_subnetIpv4CidrReservations :: Lens.Lens' GetSubnetCidrReservationsResponse (Prelude.Maybe [SubnetCidrReservation])
getSubnetCidrReservationsResponse_subnetIpv4CidrReservations :: Lens'
  GetSubnetCidrReservationsResponse (Maybe [SubnetCidrReservation])
getSubnetCidrReservationsResponse_subnetIpv4CidrReservations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSubnetCidrReservationsResponse' {Maybe [SubnetCidrReservation]
subnetIpv4CidrReservations :: Maybe [SubnetCidrReservation]
$sel:subnetIpv4CidrReservations:GetSubnetCidrReservationsResponse' :: GetSubnetCidrReservationsResponse -> Maybe [SubnetCidrReservation]
subnetIpv4CidrReservations} -> Maybe [SubnetCidrReservation]
subnetIpv4CidrReservations) (\s :: GetSubnetCidrReservationsResponse
s@GetSubnetCidrReservationsResponse' {} Maybe [SubnetCidrReservation]
a -> GetSubnetCidrReservationsResponse
s {$sel:subnetIpv4CidrReservations:GetSubnetCidrReservationsResponse' :: Maybe [SubnetCidrReservation]
subnetIpv4CidrReservations = Maybe [SubnetCidrReservation]
a} :: GetSubnetCidrReservationsResponse) 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

-- | Information about the IPv6 subnet CIDR reservations.
getSubnetCidrReservationsResponse_subnetIpv6CidrReservations :: Lens.Lens' GetSubnetCidrReservationsResponse (Prelude.Maybe [SubnetCidrReservation])
getSubnetCidrReservationsResponse_subnetIpv6CidrReservations :: Lens'
  GetSubnetCidrReservationsResponse (Maybe [SubnetCidrReservation])
getSubnetCidrReservationsResponse_subnetIpv6CidrReservations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSubnetCidrReservationsResponse' {Maybe [SubnetCidrReservation]
subnetIpv6CidrReservations :: Maybe [SubnetCidrReservation]
$sel:subnetIpv6CidrReservations:GetSubnetCidrReservationsResponse' :: GetSubnetCidrReservationsResponse -> Maybe [SubnetCidrReservation]
subnetIpv6CidrReservations} -> Maybe [SubnetCidrReservation]
subnetIpv6CidrReservations) (\s :: GetSubnetCidrReservationsResponse
s@GetSubnetCidrReservationsResponse' {} Maybe [SubnetCidrReservation]
a -> GetSubnetCidrReservationsResponse
s {$sel:subnetIpv6CidrReservations:GetSubnetCidrReservationsResponse' :: Maybe [SubnetCidrReservation]
subnetIpv6CidrReservations = Maybe [SubnetCidrReservation]
a} :: GetSubnetCidrReservationsResponse) 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.
getSubnetCidrReservationsResponse_httpStatus :: Lens.Lens' GetSubnetCidrReservationsResponse Prelude.Int
getSubnetCidrReservationsResponse_httpStatus :: Lens' GetSubnetCidrReservationsResponse Int
getSubnetCidrReservationsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSubnetCidrReservationsResponse' {Int
httpStatus :: Int
$sel:httpStatus:GetSubnetCidrReservationsResponse' :: GetSubnetCidrReservationsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: GetSubnetCidrReservationsResponse
s@GetSubnetCidrReservationsResponse' {} Int
a -> GetSubnetCidrReservationsResponse
s {$sel:httpStatus:GetSubnetCidrReservationsResponse' :: Int
httpStatus = Int
a} :: GetSubnetCidrReservationsResponse)

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