{-# 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.GetIpamAddressHistory
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Retrieve historical information about a CIDR within an IPAM scope. For
-- more information, see
-- <https://docs.aws.amazon.com/vpc/latest/ipam/view-history-cidr-ipam.html View the history of IP addresses>
-- in the /Amazon VPC IPAM User Guide/.
--
-- This operation returns paginated results.
module Amazonka.EC2.GetIpamAddressHistory
  ( -- * Creating a Request
    GetIpamAddressHistory (..),
    newGetIpamAddressHistory,

    -- * Request Lenses
    getIpamAddressHistory_dryRun,
    getIpamAddressHistory_endTime,
    getIpamAddressHistory_maxResults,
    getIpamAddressHistory_nextToken,
    getIpamAddressHistory_startTime,
    getIpamAddressHistory_vpcId,
    getIpamAddressHistory_cidr,
    getIpamAddressHistory_ipamScopeId,

    -- * Destructuring the Response
    GetIpamAddressHistoryResponse (..),
    newGetIpamAddressHistoryResponse,

    -- * Response Lenses
    getIpamAddressHistoryResponse_historyRecords,
    getIpamAddressHistoryResponse_nextToken,
    getIpamAddressHistoryResponse_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:/ 'newGetIpamAddressHistory' smart constructor.
data GetIpamAddressHistory = GetIpamAddressHistory'
  { -- | A check for 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@.
    GetIpamAddressHistory -> Maybe Bool
dryRun :: Prelude.Maybe Prelude.Bool,
    -- | The end of the time period for which you are looking for history. If you
    -- omit this option, it will default to the current time.
    GetIpamAddressHistory -> Maybe ISO8601
endTime :: Prelude.Maybe Data.ISO8601,
    -- | The maximum number of historical results you would like returned per
    -- page. Defaults to 100.
    GetIpamAddressHistory -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | The token for the next page of results.
    GetIpamAddressHistory -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The start of the time period for which you are looking for history. If
    -- you omit this option, it will default to the value of EndTime.
    GetIpamAddressHistory -> Maybe ISO8601
startTime :: Prelude.Maybe Data.ISO8601,
    -- | The ID of the VPC you want your history records filtered by.
    GetIpamAddressHistory -> Maybe Text
vpcId :: Prelude.Maybe Prelude.Text,
    -- | The CIDR you want the history of. The CIDR can be an IPv4 or IPv6 IP
    -- address range. If you enter a \/16 IPv4 CIDR, you will get records that
    -- match it exactly. You will not get records for any subnets within the
    -- \/16 CIDR.
    GetIpamAddressHistory -> Text
cidr :: Prelude.Text,
    -- | The ID of the IPAM scope that the CIDR is in.
    GetIpamAddressHistory -> Text
ipamScopeId :: Prelude.Text
  }
  deriving (GetIpamAddressHistory -> GetIpamAddressHistory -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetIpamAddressHistory -> GetIpamAddressHistory -> Bool
$c/= :: GetIpamAddressHistory -> GetIpamAddressHistory -> Bool
== :: GetIpamAddressHistory -> GetIpamAddressHistory -> Bool
$c== :: GetIpamAddressHistory -> GetIpamAddressHistory -> Bool
Prelude.Eq, ReadPrec [GetIpamAddressHistory]
ReadPrec GetIpamAddressHistory
Int -> ReadS GetIpamAddressHistory
ReadS [GetIpamAddressHistory]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetIpamAddressHistory]
$creadListPrec :: ReadPrec [GetIpamAddressHistory]
readPrec :: ReadPrec GetIpamAddressHistory
$creadPrec :: ReadPrec GetIpamAddressHistory
readList :: ReadS [GetIpamAddressHistory]
$creadList :: ReadS [GetIpamAddressHistory]
readsPrec :: Int -> ReadS GetIpamAddressHistory
$creadsPrec :: Int -> ReadS GetIpamAddressHistory
Prelude.Read, Int -> GetIpamAddressHistory -> ShowS
[GetIpamAddressHistory] -> ShowS
GetIpamAddressHistory -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetIpamAddressHistory] -> ShowS
$cshowList :: [GetIpamAddressHistory] -> ShowS
show :: GetIpamAddressHistory -> String
$cshow :: GetIpamAddressHistory -> String
showsPrec :: Int -> GetIpamAddressHistory -> ShowS
$cshowsPrec :: Int -> GetIpamAddressHistory -> ShowS
Prelude.Show, forall x. Rep GetIpamAddressHistory x -> GetIpamAddressHistory
forall x. GetIpamAddressHistory -> Rep GetIpamAddressHistory x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetIpamAddressHistory x -> GetIpamAddressHistory
$cfrom :: forall x. GetIpamAddressHistory -> Rep GetIpamAddressHistory x
Prelude.Generic)

-- |
-- Create a value of 'GetIpamAddressHistory' 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', 'getIpamAddressHistory_dryRun' - A check for 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@.
--
-- 'endTime', 'getIpamAddressHistory_endTime' - The end of the time period for which you are looking for history. If you
-- omit this option, it will default to the current time.
--
-- 'maxResults', 'getIpamAddressHistory_maxResults' - The maximum number of historical results you would like returned per
-- page. Defaults to 100.
--
-- 'nextToken', 'getIpamAddressHistory_nextToken' - The token for the next page of results.
--
-- 'startTime', 'getIpamAddressHistory_startTime' - The start of the time period for which you are looking for history. If
-- you omit this option, it will default to the value of EndTime.
--
-- 'vpcId', 'getIpamAddressHistory_vpcId' - The ID of the VPC you want your history records filtered by.
--
-- 'cidr', 'getIpamAddressHistory_cidr' - The CIDR you want the history of. The CIDR can be an IPv4 or IPv6 IP
-- address range. If you enter a \/16 IPv4 CIDR, you will get records that
-- match it exactly. You will not get records for any subnets within the
-- \/16 CIDR.
--
-- 'ipamScopeId', 'getIpamAddressHistory_ipamScopeId' - The ID of the IPAM scope that the CIDR is in.
newGetIpamAddressHistory ::
  -- | 'cidr'
  Prelude.Text ->
  -- | 'ipamScopeId'
  Prelude.Text ->
  GetIpamAddressHistory
newGetIpamAddressHistory :: Text -> Text -> GetIpamAddressHistory
newGetIpamAddressHistory Text
pCidr_ Text
pIpamScopeId_ =
  GetIpamAddressHistory'
    { $sel:dryRun:GetIpamAddressHistory' :: Maybe Bool
dryRun = forall a. Maybe a
Prelude.Nothing,
      $sel:endTime:GetIpamAddressHistory' :: Maybe ISO8601
endTime = forall a. Maybe a
Prelude.Nothing,
      $sel:maxResults:GetIpamAddressHistory' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:GetIpamAddressHistory' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:startTime:GetIpamAddressHistory' :: Maybe ISO8601
startTime = forall a. Maybe a
Prelude.Nothing,
      $sel:vpcId:GetIpamAddressHistory' :: Maybe Text
vpcId = forall a. Maybe a
Prelude.Nothing,
      $sel:cidr:GetIpamAddressHistory' :: Text
cidr = Text
pCidr_,
      $sel:ipamScopeId:GetIpamAddressHistory' :: Text
ipamScopeId = Text
pIpamScopeId_
    }

-- | A check for 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@.
getIpamAddressHistory_dryRun :: Lens.Lens' GetIpamAddressHistory (Prelude.Maybe Prelude.Bool)
getIpamAddressHistory_dryRun :: Lens' GetIpamAddressHistory (Maybe Bool)
getIpamAddressHistory_dryRun = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetIpamAddressHistory' {Maybe Bool
dryRun :: Maybe Bool
$sel:dryRun:GetIpamAddressHistory' :: GetIpamAddressHistory -> Maybe Bool
dryRun} -> Maybe Bool
dryRun) (\s :: GetIpamAddressHistory
s@GetIpamAddressHistory' {} Maybe Bool
a -> GetIpamAddressHistory
s {$sel:dryRun:GetIpamAddressHistory' :: Maybe Bool
dryRun = Maybe Bool
a} :: GetIpamAddressHistory)

-- | The end of the time period for which you are looking for history. If you
-- omit this option, it will default to the current time.
getIpamAddressHistory_endTime :: Lens.Lens' GetIpamAddressHistory (Prelude.Maybe Prelude.UTCTime)
getIpamAddressHistory_endTime :: Lens' GetIpamAddressHistory (Maybe UTCTime)
getIpamAddressHistory_endTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetIpamAddressHistory' {Maybe ISO8601
endTime :: Maybe ISO8601
$sel:endTime:GetIpamAddressHistory' :: GetIpamAddressHistory -> Maybe ISO8601
endTime} -> Maybe ISO8601
endTime) (\s :: GetIpamAddressHistory
s@GetIpamAddressHistory' {} Maybe ISO8601
a -> GetIpamAddressHistory
s {$sel:endTime:GetIpamAddressHistory' :: Maybe ISO8601
endTime = Maybe ISO8601
a} :: GetIpamAddressHistory) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The maximum number of historical results you would like returned per
-- page. Defaults to 100.
getIpamAddressHistory_maxResults :: Lens.Lens' GetIpamAddressHistory (Prelude.Maybe Prelude.Natural)
getIpamAddressHistory_maxResults :: Lens' GetIpamAddressHistory (Maybe Natural)
getIpamAddressHistory_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetIpamAddressHistory' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:GetIpamAddressHistory' :: GetIpamAddressHistory -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: GetIpamAddressHistory
s@GetIpamAddressHistory' {} Maybe Natural
a -> GetIpamAddressHistory
s {$sel:maxResults:GetIpamAddressHistory' :: Maybe Natural
maxResults = Maybe Natural
a} :: GetIpamAddressHistory)

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

-- | The start of the time period for which you are looking for history. If
-- you omit this option, it will default to the value of EndTime.
getIpamAddressHistory_startTime :: Lens.Lens' GetIpamAddressHistory (Prelude.Maybe Prelude.UTCTime)
getIpamAddressHistory_startTime :: Lens' GetIpamAddressHistory (Maybe UTCTime)
getIpamAddressHistory_startTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetIpamAddressHistory' {Maybe ISO8601
startTime :: Maybe ISO8601
$sel:startTime:GetIpamAddressHistory' :: GetIpamAddressHistory -> Maybe ISO8601
startTime} -> Maybe ISO8601
startTime) (\s :: GetIpamAddressHistory
s@GetIpamAddressHistory' {} Maybe ISO8601
a -> GetIpamAddressHistory
s {$sel:startTime:GetIpamAddressHistory' :: Maybe ISO8601
startTime = Maybe ISO8601
a} :: GetIpamAddressHistory) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The ID of the VPC you want your history records filtered by.
getIpamAddressHistory_vpcId :: Lens.Lens' GetIpamAddressHistory (Prelude.Maybe Prelude.Text)
getIpamAddressHistory_vpcId :: Lens' GetIpamAddressHistory (Maybe Text)
getIpamAddressHistory_vpcId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetIpamAddressHistory' {Maybe Text
vpcId :: Maybe Text
$sel:vpcId:GetIpamAddressHistory' :: GetIpamAddressHistory -> Maybe Text
vpcId} -> Maybe Text
vpcId) (\s :: GetIpamAddressHistory
s@GetIpamAddressHistory' {} Maybe Text
a -> GetIpamAddressHistory
s {$sel:vpcId:GetIpamAddressHistory' :: Maybe Text
vpcId = Maybe Text
a} :: GetIpamAddressHistory)

-- | The CIDR you want the history of. The CIDR can be an IPv4 or IPv6 IP
-- address range. If you enter a \/16 IPv4 CIDR, you will get records that
-- match it exactly. You will not get records for any subnets within the
-- \/16 CIDR.
getIpamAddressHistory_cidr :: Lens.Lens' GetIpamAddressHistory Prelude.Text
getIpamAddressHistory_cidr :: Lens' GetIpamAddressHistory Text
getIpamAddressHistory_cidr = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetIpamAddressHistory' {Text
cidr :: Text
$sel:cidr:GetIpamAddressHistory' :: GetIpamAddressHistory -> Text
cidr} -> Text
cidr) (\s :: GetIpamAddressHistory
s@GetIpamAddressHistory' {} Text
a -> GetIpamAddressHistory
s {$sel:cidr:GetIpamAddressHistory' :: Text
cidr = Text
a} :: GetIpamAddressHistory)

-- | The ID of the IPAM scope that the CIDR is in.
getIpamAddressHistory_ipamScopeId :: Lens.Lens' GetIpamAddressHistory Prelude.Text
getIpamAddressHistory_ipamScopeId :: Lens' GetIpamAddressHistory Text
getIpamAddressHistory_ipamScopeId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetIpamAddressHistory' {Text
ipamScopeId :: Text
$sel:ipamScopeId:GetIpamAddressHistory' :: GetIpamAddressHistory -> Text
ipamScopeId} -> Text
ipamScopeId) (\s :: GetIpamAddressHistory
s@GetIpamAddressHistory' {} Text
a -> GetIpamAddressHistory
s {$sel:ipamScopeId:GetIpamAddressHistory' :: Text
ipamScopeId = Text
a} :: GetIpamAddressHistory)

instance Core.AWSPager GetIpamAddressHistory where
  page :: GetIpamAddressHistory
-> AWSResponse GetIpamAddressHistory -> Maybe GetIpamAddressHistory
page GetIpamAddressHistory
rq AWSResponse GetIpamAddressHistory
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse GetIpamAddressHistory
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' GetIpamAddressHistoryResponse (Maybe Text)
getIpamAddressHistoryResponse_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 GetIpamAddressHistory
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens'
  GetIpamAddressHistoryResponse (Maybe [IpamAddressHistoryRecord])
getIpamAddressHistoryResponse_historyRecords
            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.$ GetIpamAddressHistory
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' GetIpamAddressHistory (Maybe Text)
getIpamAddressHistory_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse GetIpamAddressHistory
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' GetIpamAddressHistoryResponse (Maybe Text)
getIpamAddressHistoryResponse_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 GetIpamAddressHistory where
  type
    AWSResponse GetIpamAddressHistory =
      GetIpamAddressHistoryResponse
  request :: (Service -> Service)
-> GetIpamAddressHistory -> Request GetIpamAddressHistory
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 GetIpamAddressHistory
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetIpamAddressHistory)))
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 [IpamAddressHistoryRecord]
-> Maybe Text -> Int -> GetIpamAddressHistoryResponse
GetIpamAddressHistoryResponse'
            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
"historyRecordSet"
                            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
"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 GetIpamAddressHistory where
  hashWithSalt :: Int -> GetIpamAddressHistory -> Int
hashWithSalt Int
_salt GetIpamAddressHistory' {Maybe Bool
Maybe Natural
Maybe Text
Maybe ISO8601
Text
ipamScopeId :: Text
cidr :: Text
vpcId :: Maybe Text
startTime :: Maybe ISO8601
nextToken :: Maybe Text
maxResults :: Maybe Natural
endTime :: Maybe ISO8601
dryRun :: Maybe Bool
$sel:ipamScopeId:GetIpamAddressHistory' :: GetIpamAddressHistory -> Text
$sel:cidr:GetIpamAddressHistory' :: GetIpamAddressHistory -> Text
$sel:vpcId:GetIpamAddressHistory' :: GetIpamAddressHistory -> Maybe Text
$sel:startTime:GetIpamAddressHistory' :: GetIpamAddressHistory -> Maybe ISO8601
$sel:nextToken:GetIpamAddressHistory' :: GetIpamAddressHistory -> Maybe Text
$sel:maxResults:GetIpamAddressHistory' :: GetIpamAddressHistory -> Maybe Natural
$sel:endTime:GetIpamAddressHistory' :: GetIpamAddressHistory -> Maybe ISO8601
$sel:dryRun:GetIpamAddressHistory' :: GetIpamAddressHistory -> 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 ISO8601
endTime
      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` Maybe ISO8601
startTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
vpcId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
cidr
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
ipamScopeId

instance Prelude.NFData GetIpamAddressHistory where
  rnf :: GetIpamAddressHistory -> ()
rnf GetIpamAddressHistory' {Maybe Bool
Maybe Natural
Maybe Text
Maybe ISO8601
Text
ipamScopeId :: Text
cidr :: Text
vpcId :: Maybe Text
startTime :: Maybe ISO8601
nextToken :: Maybe Text
maxResults :: Maybe Natural
endTime :: Maybe ISO8601
dryRun :: Maybe Bool
$sel:ipamScopeId:GetIpamAddressHistory' :: GetIpamAddressHistory -> Text
$sel:cidr:GetIpamAddressHistory' :: GetIpamAddressHistory -> Text
$sel:vpcId:GetIpamAddressHistory' :: GetIpamAddressHistory -> Maybe Text
$sel:startTime:GetIpamAddressHistory' :: GetIpamAddressHistory -> Maybe ISO8601
$sel:nextToken:GetIpamAddressHistory' :: GetIpamAddressHistory -> Maybe Text
$sel:maxResults:GetIpamAddressHistory' :: GetIpamAddressHistory -> Maybe Natural
$sel:endTime:GetIpamAddressHistory' :: GetIpamAddressHistory -> Maybe ISO8601
$sel:dryRun:GetIpamAddressHistory' :: GetIpamAddressHistory -> 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 ISO8601
endTime
      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 Maybe ISO8601
startTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
vpcId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
cidr
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
ipamScopeId

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

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

instance Data.ToQuery GetIpamAddressHistory where
  toQuery :: GetIpamAddressHistory -> QueryString
toQuery GetIpamAddressHistory' {Maybe Bool
Maybe Natural
Maybe Text
Maybe ISO8601
Text
ipamScopeId :: Text
cidr :: Text
vpcId :: Maybe Text
startTime :: Maybe ISO8601
nextToken :: Maybe Text
maxResults :: Maybe Natural
endTime :: Maybe ISO8601
dryRun :: Maybe Bool
$sel:ipamScopeId:GetIpamAddressHistory' :: GetIpamAddressHistory -> Text
$sel:cidr:GetIpamAddressHistory' :: GetIpamAddressHistory -> Text
$sel:vpcId:GetIpamAddressHistory' :: GetIpamAddressHistory -> Maybe Text
$sel:startTime:GetIpamAddressHistory' :: GetIpamAddressHistory -> Maybe ISO8601
$sel:nextToken:GetIpamAddressHistory' :: GetIpamAddressHistory -> Maybe Text
$sel:maxResults:GetIpamAddressHistory' :: GetIpamAddressHistory -> Maybe Natural
$sel:endTime:GetIpamAddressHistory' :: GetIpamAddressHistory -> Maybe ISO8601
$sel:dryRun:GetIpamAddressHistory' :: GetIpamAddressHistory -> Maybe Bool
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"GetIpamAddressHistory" :: 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,
        ByteString
"EndTime" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe ISO8601
endTime,
        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
"StartTime" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe ISO8601
startTime,
        ByteString
"VpcId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
vpcId,
        ByteString
"Cidr" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
cidr,
        ByteString
"IpamScopeId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
ipamScopeId
      ]

-- | /See:/ 'newGetIpamAddressHistoryResponse' smart constructor.
data GetIpamAddressHistoryResponse = GetIpamAddressHistoryResponse'
  { -- | A historical record for a CIDR within an IPAM scope. If the CIDR is
    -- associated with an EC2 instance, you will see an object in the response
    -- for the instance and one for the network interface.
    GetIpamAddressHistoryResponse -> Maybe [IpamAddressHistoryRecord]
historyRecords :: Prelude.Maybe [IpamAddressHistoryRecord],
    -- | The token to use to retrieve the next page of results. This value is
    -- @null@ when there are no more results to return.
    GetIpamAddressHistoryResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    GetIpamAddressHistoryResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetIpamAddressHistoryResponse
-> GetIpamAddressHistoryResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetIpamAddressHistoryResponse
-> GetIpamAddressHistoryResponse -> Bool
$c/= :: GetIpamAddressHistoryResponse
-> GetIpamAddressHistoryResponse -> Bool
== :: GetIpamAddressHistoryResponse
-> GetIpamAddressHistoryResponse -> Bool
$c== :: GetIpamAddressHistoryResponse
-> GetIpamAddressHistoryResponse -> Bool
Prelude.Eq, ReadPrec [GetIpamAddressHistoryResponse]
ReadPrec GetIpamAddressHistoryResponse
Int -> ReadS GetIpamAddressHistoryResponse
ReadS [GetIpamAddressHistoryResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetIpamAddressHistoryResponse]
$creadListPrec :: ReadPrec [GetIpamAddressHistoryResponse]
readPrec :: ReadPrec GetIpamAddressHistoryResponse
$creadPrec :: ReadPrec GetIpamAddressHistoryResponse
readList :: ReadS [GetIpamAddressHistoryResponse]
$creadList :: ReadS [GetIpamAddressHistoryResponse]
readsPrec :: Int -> ReadS GetIpamAddressHistoryResponse
$creadsPrec :: Int -> ReadS GetIpamAddressHistoryResponse
Prelude.Read, Int -> GetIpamAddressHistoryResponse -> ShowS
[GetIpamAddressHistoryResponse] -> ShowS
GetIpamAddressHistoryResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetIpamAddressHistoryResponse] -> ShowS
$cshowList :: [GetIpamAddressHistoryResponse] -> ShowS
show :: GetIpamAddressHistoryResponse -> String
$cshow :: GetIpamAddressHistoryResponse -> String
showsPrec :: Int -> GetIpamAddressHistoryResponse -> ShowS
$cshowsPrec :: Int -> GetIpamAddressHistoryResponse -> ShowS
Prelude.Show, forall x.
Rep GetIpamAddressHistoryResponse x
-> GetIpamAddressHistoryResponse
forall x.
GetIpamAddressHistoryResponse
-> Rep GetIpamAddressHistoryResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetIpamAddressHistoryResponse x
-> GetIpamAddressHistoryResponse
$cfrom :: forall x.
GetIpamAddressHistoryResponse
-> Rep GetIpamAddressHistoryResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetIpamAddressHistoryResponse' 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:
--
-- 'historyRecords', 'getIpamAddressHistoryResponse_historyRecords' - A historical record for a CIDR within an IPAM scope. If the CIDR is
-- associated with an EC2 instance, you will see an object in the response
-- for the instance and one for the network interface.
--
-- 'nextToken', 'getIpamAddressHistoryResponse_nextToken' - The token to use to retrieve the next page of results. This value is
-- @null@ when there are no more results to return.
--
-- 'httpStatus', 'getIpamAddressHistoryResponse_httpStatus' - The response's http status code.
newGetIpamAddressHistoryResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetIpamAddressHistoryResponse
newGetIpamAddressHistoryResponse :: Int -> GetIpamAddressHistoryResponse
newGetIpamAddressHistoryResponse Int
pHttpStatus_ =
  GetIpamAddressHistoryResponse'
    { $sel:historyRecords:GetIpamAddressHistoryResponse' :: Maybe [IpamAddressHistoryRecord]
historyRecords =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:GetIpamAddressHistoryResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetIpamAddressHistoryResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A historical record for a CIDR within an IPAM scope. If the CIDR is
-- associated with an EC2 instance, you will see an object in the response
-- for the instance and one for the network interface.
getIpamAddressHistoryResponse_historyRecords :: Lens.Lens' GetIpamAddressHistoryResponse (Prelude.Maybe [IpamAddressHistoryRecord])
getIpamAddressHistoryResponse_historyRecords :: Lens'
  GetIpamAddressHistoryResponse (Maybe [IpamAddressHistoryRecord])
getIpamAddressHistoryResponse_historyRecords = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetIpamAddressHistoryResponse' {Maybe [IpamAddressHistoryRecord]
historyRecords :: Maybe [IpamAddressHistoryRecord]
$sel:historyRecords:GetIpamAddressHistoryResponse' :: GetIpamAddressHistoryResponse -> Maybe [IpamAddressHistoryRecord]
historyRecords} -> Maybe [IpamAddressHistoryRecord]
historyRecords) (\s :: GetIpamAddressHistoryResponse
s@GetIpamAddressHistoryResponse' {} Maybe [IpamAddressHistoryRecord]
a -> GetIpamAddressHistoryResponse
s {$sel:historyRecords:GetIpamAddressHistoryResponse' :: Maybe [IpamAddressHistoryRecord]
historyRecords = Maybe [IpamAddressHistoryRecord]
a} :: GetIpamAddressHistoryResponse) 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 use to retrieve the next page of results. This value is
-- @null@ when there are no more results to return.
getIpamAddressHistoryResponse_nextToken :: Lens.Lens' GetIpamAddressHistoryResponse (Prelude.Maybe Prelude.Text)
getIpamAddressHistoryResponse_nextToken :: Lens' GetIpamAddressHistoryResponse (Maybe Text)
getIpamAddressHistoryResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetIpamAddressHistoryResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:GetIpamAddressHistoryResponse' :: GetIpamAddressHistoryResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: GetIpamAddressHistoryResponse
s@GetIpamAddressHistoryResponse' {} Maybe Text
a -> GetIpamAddressHistoryResponse
s {$sel:nextToken:GetIpamAddressHistoryResponse' :: Maybe Text
nextToken = Maybe Text
a} :: GetIpamAddressHistoryResponse)

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

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