{-# 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.ChangeCidrCollection
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Creates, changes, or deletes CIDR blocks within a collection. Contains
-- authoritative IP information mapping blocks to one or multiple
-- locations.
--
-- A change request can update multiple locations in a collection at a
-- time, which is helpful if you want to move one or more CIDR blocks from
-- one location to another in one transaction, without downtime.
--
-- __Limits__
--
-- The max number of CIDR blocks included in the request is 1000. As a
-- result, big updates require multiple API calls.
--
-- __PUT and DELETE_IF_EXISTS__
--
-- Use @ChangeCidrCollection@ to perform the following actions:
--
-- -   @PUT@: Create a CIDR block within the specified collection.
--
-- -   @ DELETE_IF_EXISTS@: Delete an existing CIDR block from the
--     collection.
module Amazonka.Route53.ChangeCidrCollection
  ( -- * Creating a Request
    ChangeCidrCollection (..),
    newChangeCidrCollection,

    -- * Request Lenses
    changeCidrCollection_collectionVersion,
    changeCidrCollection_id,
    changeCidrCollection_changes,

    -- * Destructuring the Response
    ChangeCidrCollectionResponse (..),
    newChangeCidrCollectionResponse,

    -- * Response Lenses
    changeCidrCollectionResponse_httpStatus,
    changeCidrCollectionResponse_id,
  )
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:/ 'newChangeCidrCollection' smart constructor.
data ChangeCidrCollection = ChangeCidrCollection'
  { -- | A sequential counter that Amazon Route 53 sets to 1 when you create a
    -- collection and increments it by 1 each time you update the collection.
    --
    -- We recommend that you use @ListCidrCollection@ to get the current value
    -- of @CollectionVersion@ for the collection that you want to update, and
    -- then include that value with the change request. This prevents Route 53
    -- from overwriting an intervening update:
    --
    -- -   If the value in the request matches the value of @CollectionVersion@
    --     in the collection, Route 53 updates the collection.
    --
    -- -   If the value of @CollectionVersion@ in the collection is greater
    --     than the value in the request, the collection was changed after you
    --     got the version number. Route 53 does not update the collection, and
    --     it returns a @CidrCollectionVersionMismatch@ error.
    ChangeCidrCollection -> Maybe Natural
collectionVersion :: Prelude.Maybe Prelude.Natural,
    -- | The UUID of the CIDR collection to update.
    ChangeCidrCollection -> Text
id :: Prelude.Text,
    -- | Information about changes to a CIDR collection.
    ChangeCidrCollection -> NonEmpty CidrCollectionChange
changes :: Prelude.NonEmpty CidrCollectionChange
  }
  deriving (ChangeCidrCollection -> ChangeCidrCollection -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ChangeCidrCollection -> ChangeCidrCollection -> Bool
$c/= :: ChangeCidrCollection -> ChangeCidrCollection -> Bool
== :: ChangeCidrCollection -> ChangeCidrCollection -> Bool
$c== :: ChangeCidrCollection -> ChangeCidrCollection -> Bool
Prelude.Eq, ReadPrec [ChangeCidrCollection]
ReadPrec ChangeCidrCollection
Int -> ReadS ChangeCidrCollection
ReadS [ChangeCidrCollection]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ChangeCidrCollection]
$creadListPrec :: ReadPrec [ChangeCidrCollection]
readPrec :: ReadPrec ChangeCidrCollection
$creadPrec :: ReadPrec ChangeCidrCollection
readList :: ReadS [ChangeCidrCollection]
$creadList :: ReadS [ChangeCidrCollection]
readsPrec :: Int -> ReadS ChangeCidrCollection
$creadsPrec :: Int -> ReadS ChangeCidrCollection
Prelude.Read, Int -> ChangeCidrCollection -> ShowS
[ChangeCidrCollection] -> ShowS
ChangeCidrCollection -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ChangeCidrCollection] -> ShowS
$cshowList :: [ChangeCidrCollection] -> ShowS
show :: ChangeCidrCollection -> String
$cshow :: ChangeCidrCollection -> String
showsPrec :: Int -> ChangeCidrCollection -> ShowS
$cshowsPrec :: Int -> ChangeCidrCollection -> ShowS
Prelude.Show, forall x. Rep ChangeCidrCollection x -> ChangeCidrCollection
forall x. ChangeCidrCollection -> Rep ChangeCidrCollection x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ChangeCidrCollection x -> ChangeCidrCollection
$cfrom :: forall x. ChangeCidrCollection -> Rep ChangeCidrCollection x
Prelude.Generic)

-- |
-- Create a value of 'ChangeCidrCollection' 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:
--
-- 'collectionVersion', 'changeCidrCollection_collectionVersion' - A sequential counter that Amazon Route 53 sets to 1 when you create a
-- collection and increments it by 1 each time you update the collection.
--
-- We recommend that you use @ListCidrCollection@ to get the current value
-- of @CollectionVersion@ for the collection that you want to update, and
-- then include that value with the change request. This prevents Route 53
-- from overwriting an intervening update:
--
-- -   If the value in the request matches the value of @CollectionVersion@
--     in the collection, Route 53 updates the collection.
--
-- -   If the value of @CollectionVersion@ in the collection is greater
--     than the value in the request, the collection was changed after you
--     got the version number. Route 53 does not update the collection, and
--     it returns a @CidrCollectionVersionMismatch@ error.
--
-- 'id', 'changeCidrCollection_id' - The UUID of the CIDR collection to update.
--
-- 'changes', 'changeCidrCollection_changes' - Information about changes to a CIDR collection.
newChangeCidrCollection ::
  -- | 'id'
  Prelude.Text ->
  -- | 'changes'
  Prelude.NonEmpty CidrCollectionChange ->
  ChangeCidrCollection
newChangeCidrCollection :: Text -> NonEmpty CidrCollectionChange -> ChangeCidrCollection
newChangeCidrCollection Text
pId_ NonEmpty CidrCollectionChange
pChanges_ =
  ChangeCidrCollection'
    { $sel:collectionVersion:ChangeCidrCollection' :: Maybe Natural
collectionVersion =
        forall a. Maybe a
Prelude.Nothing,
      $sel:id:ChangeCidrCollection' :: Text
id = Text
pId_,
      $sel:changes:ChangeCidrCollection' :: NonEmpty CidrCollectionChange
changes = forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced forall t b. AReview t b -> b -> t
Lens.# NonEmpty CidrCollectionChange
pChanges_
    }

-- | A sequential counter that Amazon Route 53 sets to 1 when you create a
-- collection and increments it by 1 each time you update the collection.
--
-- We recommend that you use @ListCidrCollection@ to get the current value
-- of @CollectionVersion@ for the collection that you want to update, and
-- then include that value with the change request. This prevents Route 53
-- from overwriting an intervening update:
--
-- -   If the value in the request matches the value of @CollectionVersion@
--     in the collection, Route 53 updates the collection.
--
-- -   If the value of @CollectionVersion@ in the collection is greater
--     than the value in the request, the collection was changed after you
--     got the version number. Route 53 does not update the collection, and
--     it returns a @CidrCollectionVersionMismatch@ error.
changeCidrCollection_collectionVersion :: Lens.Lens' ChangeCidrCollection (Prelude.Maybe Prelude.Natural)
changeCidrCollection_collectionVersion :: Lens' ChangeCidrCollection (Maybe Natural)
changeCidrCollection_collectionVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ChangeCidrCollection' {Maybe Natural
collectionVersion :: Maybe Natural
$sel:collectionVersion:ChangeCidrCollection' :: ChangeCidrCollection -> Maybe Natural
collectionVersion} -> Maybe Natural
collectionVersion) (\s :: ChangeCidrCollection
s@ChangeCidrCollection' {} Maybe Natural
a -> ChangeCidrCollection
s {$sel:collectionVersion:ChangeCidrCollection' :: Maybe Natural
collectionVersion = Maybe Natural
a} :: ChangeCidrCollection)

-- | The UUID of the CIDR collection to update.
changeCidrCollection_id :: Lens.Lens' ChangeCidrCollection Prelude.Text
changeCidrCollection_id :: Lens' ChangeCidrCollection Text
changeCidrCollection_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ChangeCidrCollection' {Text
id :: Text
$sel:id:ChangeCidrCollection' :: ChangeCidrCollection -> Text
id} -> Text
id) (\s :: ChangeCidrCollection
s@ChangeCidrCollection' {} Text
a -> ChangeCidrCollection
s {$sel:id:ChangeCidrCollection' :: Text
id = Text
a} :: ChangeCidrCollection)

-- | Information about changes to a CIDR collection.
changeCidrCollection_changes :: Lens.Lens' ChangeCidrCollection (Prelude.NonEmpty CidrCollectionChange)
changeCidrCollection_changes :: Lens' ChangeCidrCollection (NonEmpty CidrCollectionChange)
changeCidrCollection_changes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ChangeCidrCollection' {NonEmpty CidrCollectionChange
changes :: NonEmpty CidrCollectionChange
$sel:changes:ChangeCidrCollection' :: ChangeCidrCollection -> NonEmpty CidrCollectionChange
changes} -> NonEmpty CidrCollectionChange
changes) (\s :: ChangeCidrCollection
s@ChangeCidrCollection' {} NonEmpty CidrCollectionChange
a -> ChangeCidrCollection
s {$sel:changes:ChangeCidrCollection' :: NonEmpty CidrCollectionChange
changes = NonEmpty CidrCollectionChange
a} :: ChangeCidrCollection) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

instance Core.AWSRequest ChangeCidrCollection where
  type
    AWSResponse ChangeCidrCollection =
      ChangeCidrCollectionResponse
  request :: (Service -> Service)
-> ChangeCidrCollection -> Request ChangeCidrCollection
request Service -> Service
overrides =
    forall a. (ToRequest a, ToElement a) => Service -> a -> Request a
Request.postXML (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy ChangeCidrCollection
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ChangeCidrCollection)))
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 ->
          Int -> Text -> ChangeCidrCollectionResponse
ChangeCidrCollectionResponse'
            forall (f :: * -> *) a b. Functor 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))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String a
Data..@ Text
"Id")
      )

instance Prelude.Hashable ChangeCidrCollection where
  hashWithSalt :: Int -> ChangeCidrCollection -> Int
hashWithSalt Int
_salt ChangeCidrCollection' {Maybe Natural
NonEmpty CidrCollectionChange
Text
changes :: NonEmpty CidrCollectionChange
id :: Text
collectionVersion :: Maybe Natural
$sel:changes:ChangeCidrCollection' :: ChangeCidrCollection -> NonEmpty CidrCollectionChange
$sel:id:ChangeCidrCollection' :: ChangeCidrCollection -> Text
$sel:collectionVersion:ChangeCidrCollection' :: ChangeCidrCollection -> Maybe Natural
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
collectionVersion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
id
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` NonEmpty CidrCollectionChange
changes

instance Prelude.NFData ChangeCidrCollection where
  rnf :: ChangeCidrCollection -> ()
rnf ChangeCidrCollection' {Maybe Natural
NonEmpty CidrCollectionChange
Text
changes :: NonEmpty CidrCollectionChange
id :: Text
collectionVersion :: Maybe Natural
$sel:changes:ChangeCidrCollection' :: ChangeCidrCollection -> NonEmpty CidrCollectionChange
$sel:id:ChangeCidrCollection' :: ChangeCidrCollection -> Text
$sel:collectionVersion:ChangeCidrCollection' :: ChangeCidrCollection -> Maybe Natural
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
collectionVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
id
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf NonEmpty CidrCollectionChange
changes

instance Data.ToElement ChangeCidrCollection where
  toElement :: ChangeCidrCollection -> Element
toElement =
    forall a. ToXML a => Name -> a -> Element
Data.mkElement
      Name
"{https://route53.amazonaws.com/doc/2013-04-01/}ChangeCidrCollectionRequest"

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

instance Data.ToPath ChangeCidrCollection where
  toPath :: ChangeCidrCollection -> ByteString
toPath ChangeCidrCollection' {Maybe Natural
NonEmpty CidrCollectionChange
Text
changes :: NonEmpty CidrCollectionChange
id :: Text
collectionVersion :: Maybe Natural
$sel:changes:ChangeCidrCollection' :: ChangeCidrCollection -> NonEmpty CidrCollectionChange
$sel:id:ChangeCidrCollection' :: ChangeCidrCollection -> Text
$sel:collectionVersion:ChangeCidrCollection' :: ChangeCidrCollection -> Maybe Natural
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/2013-04-01/cidrcollection/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
id]

instance Data.ToQuery ChangeCidrCollection where
  toQuery :: ChangeCidrCollection -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

instance Data.ToXML ChangeCidrCollection where
  toXML :: ChangeCidrCollection -> XML
toXML ChangeCidrCollection' {Maybe Natural
NonEmpty CidrCollectionChange
Text
changes :: NonEmpty CidrCollectionChange
id :: Text
collectionVersion :: Maybe Natural
$sel:changes:ChangeCidrCollection' :: ChangeCidrCollection -> NonEmpty CidrCollectionChange
$sel:id:ChangeCidrCollection' :: ChangeCidrCollection -> Text
$sel:collectionVersion:ChangeCidrCollection' :: ChangeCidrCollection -> Maybe Natural
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ Name
"CollectionVersion" forall a. ToXML a => Name -> a -> XML
Data.@= Maybe Natural
collectionVersion,
        Name
"Changes" forall a. ToXML a => Name -> a -> XML
Data.@= forall a. (IsList a, ToXML (Item a)) => Name -> a -> XML
Data.toXMLList Name
"member" NonEmpty CidrCollectionChange
changes
      ]

-- | /See:/ 'newChangeCidrCollectionResponse' smart constructor.
data ChangeCidrCollectionResponse = ChangeCidrCollectionResponse'
  { -- | The response's http status code.
    ChangeCidrCollectionResponse -> Int
httpStatus :: Prelude.Int,
    -- | The ID that is returned by @ChangeCidrCollection@. You can use it as
    -- input to @GetChange@ to see if a CIDR collection change has propagated
    -- or not.
    ChangeCidrCollectionResponse -> Text
id :: Prelude.Text
  }
  deriving (ChangeCidrCollectionResponse
-> ChangeCidrCollectionResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ChangeCidrCollectionResponse
-> ChangeCidrCollectionResponse -> Bool
$c/= :: ChangeCidrCollectionResponse
-> ChangeCidrCollectionResponse -> Bool
== :: ChangeCidrCollectionResponse
-> ChangeCidrCollectionResponse -> Bool
$c== :: ChangeCidrCollectionResponse
-> ChangeCidrCollectionResponse -> Bool
Prelude.Eq, ReadPrec [ChangeCidrCollectionResponse]
ReadPrec ChangeCidrCollectionResponse
Int -> ReadS ChangeCidrCollectionResponse
ReadS [ChangeCidrCollectionResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ChangeCidrCollectionResponse]
$creadListPrec :: ReadPrec [ChangeCidrCollectionResponse]
readPrec :: ReadPrec ChangeCidrCollectionResponse
$creadPrec :: ReadPrec ChangeCidrCollectionResponse
readList :: ReadS [ChangeCidrCollectionResponse]
$creadList :: ReadS [ChangeCidrCollectionResponse]
readsPrec :: Int -> ReadS ChangeCidrCollectionResponse
$creadsPrec :: Int -> ReadS ChangeCidrCollectionResponse
Prelude.Read, Int -> ChangeCidrCollectionResponse -> ShowS
[ChangeCidrCollectionResponse] -> ShowS
ChangeCidrCollectionResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ChangeCidrCollectionResponse] -> ShowS
$cshowList :: [ChangeCidrCollectionResponse] -> ShowS
show :: ChangeCidrCollectionResponse -> String
$cshow :: ChangeCidrCollectionResponse -> String
showsPrec :: Int -> ChangeCidrCollectionResponse -> ShowS
$cshowsPrec :: Int -> ChangeCidrCollectionResponse -> ShowS
Prelude.Show, forall x.
Rep ChangeCidrCollectionResponse x -> ChangeCidrCollectionResponse
forall x.
ChangeCidrCollectionResponse -> Rep ChangeCidrCollectionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ChangeCidrCollectionResponse x -> ChangeCidrCollectionResponse
$cfrom :: forall x.
ChangeCidrCollectionResponse -> Rep ChangeCidrCollectionResponse x
Prelude.Generic)

-- |
-- Create a value of 'ChangeCidrCollectionResponse' 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:
--
-- 'httpStatus', 'changeCidrCollectionResponse_httpStatus' - The response's http status code.
--
-- 'id', 'changeCidrCollectionResponse_id' - The ID that is returned by @ChangeCidrCollection@. You can use it as
-- input to @GetChange@ to see if a CIDR collection change has propagated
-- or not.
newChangeCidrCollectionResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'id'
  Prelude.Text ->
  ChangeCidrCollectionResponse
newChangeCidrCollectionResponse :: Int -> Text -> ChangeCidrCollectionResponse
newChangeCidrCollectionResponse Int
pHttpStatus_ Text
pId_ =
  ChangeCidrCollectionResponse'
    { $sel:httpStatus:ChangeCidrCollectionResponse' :: Int
httpStatus =
        Int
pHttpStatus_,
      $sel:id:ChangeCidrCollectionResponse' :: Text
id = Text
pId_
    }

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

-- | The ID that is returned by @ChangeCidrCollection@. You can use it as
-- input to @GetChange@ to see if a CIDR collection change has propagated
-- or not.
changeCidrCollectionResponse_id :: Lens.Lens' ChangeCidrCollectionResponse Prelude.Text
changeCidrCollectionResponse_id :: Lens' ChangeCidrCollectionResponse Text
changeCidrCollectionResponse_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ChangeCidrCollectionResponse' {Text
id :: Text
$sel:id:ChangeCidrCollectionResponse' :: ChangeCidrCollectionResponse -> Text
id} -> Text
id) (\s :: ChangeCidrCollectionResponse
s@ChangeCidrCollectionResponse' {} Text
a -> ChangeCidrCollectionResponse
s {$sel:id:ChangeCidrCollectionResponse' :: Text
id = Text
a} :: ChangeCidrCollectionResponse)

instance Prelude.NFData ChangeCidrCollectionResponse where
  rnf :: ChangeCidrCollectionResponse -> ()
rnf ChangeCidrCollectionResponse' {Int
Text
id :: Text
httpStatus :: Int
$sel:id:ChangeCidrCollectionResponse' :: ChangeCidrCollectionResponse -> Text
$sel:httpStatus:ChangeCidrCollectionResponse' :: ChangeCidrCollectionResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
id