{-# 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.WAFV2.UpdateIPSet
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Updates the specified IPSet.
--
-- This operation completely replaces the mutable specifications that you
-- already have for the IP set with the ones that you provide to this call.
-- To modify the IP set, retrieve it by calling GetIPSet, update the
-- settings as needed, and then provide the complete IP set specification
-- to this call.
--
-- When you make changes to web ACLs or web ACL components, like rules and
-- rule groups, WAF propagates the changes everywhere that the web ACL and
-- its components are stored and used. Your changes are applied within
-- seconds, but there might be a brief period of inconsistency when the
-- changes have arrived in some places and not in others. So, for example,
-- if you change a rule action setting, the action might be the old action
-- in one area and the new action in another area. Or if you add an IP
-- address to an IP set used in a blocking rule, the new address might
-- briefly be blocked in one area while still allowed in another. This
-- temporary inconsistency can occur when you first associate a web ACL
-- with an Amazon Web Services resource and when you change a web ACL that
-- is already associated with a resource. Generally, any inconsistencies of
-- this type last only a few seconds.
module Amazonka.WAFV2.UpdateIPSet
  ( -- * Creating a Request
    UpdateIPSet (..),
    newUpdateIPSet,

    -- * Request Lenses
    updateIPSet_description,
    updateIPSet_name,
    updateIPSet_scope,
    updateIPSet_id,
    updateIPSet_addresses,
    updateIPSet_lockToken,

    -- * Destructuring the Response
    UpdateIPSetResponse (..),
    newUpdateIPSetResponse,

    -- * Response Lenses
    updateIPSetResponse_nextLockToken,
    updateIPSetResponse_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.WAFV2.Types

-- | /See:/ 'newUpdateIPSet' smart constructor.
data UpdateIPSet = UpdateIPSet'
  { -- | A description of the IP set that helps with identification.
    UpdateIPSet -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | The name of the IP set. You cannot change the name of an @IPSet@ after
    -- you create it.
    UpdateIPSet -> Text
name :: Prelude.Text,
    -- | Specifies whether this is for an Amazon CloudFront distribution or for a
    -- regional application. A regional application can be an Application Load
    -- Balancer (ALB), an Amazon API Gateway REST API, an AppSync GraphQL API,
    -- or an Amazon Cognito user pool.
    --
    -- To work with CloudFront, you must also specify the Region US East (N.
    -- Virginia) as follows:
    --
    -- -   CLI - Specify the Region when you use the CloudFront scope:
    --     @--scope=CLOUDFRONT --region=us-east-1@.
    --
    -- -   API and SDKs - For all calls, use the Region endpoint us-east-1.
    UpdateIPSet -> Scope
scope :: Scope,
    -- | A unique identifier for the set. This ID is returned in the responses to
    -- create and list commands. You provide it to operations like update and
    -- delete.
    UpdateIPSet -> Text
id :: Prelude.Text,
    -- | Contains an array of strings that specifies zero or more IP addresses or
    -- blocks of IP addresses. All addresses must be specified using Classless
    -- Inter-Domain Routing (CIDR) notation. WAF supports all IPv4 and IPv6
    -- CIDR ranges except for @\/0@.
    --
    -- Example address strings:
    --
    -- -   To configure WAF to allow, block, or count requests that originated
    --     from the IP address 192.0.2.44, specify @192.0.2.44\/32@.
    --
    -- -   To configure WAF to allow, block, or count requests that originated
    --     from IP addresses from 192.0.2.0 to 192.0.2.255, specify
    --     @192.0.2.0\/24@.
    --
    -- -   To configure WAF to allow, block, or count requests that originated
    --     from the IP address 1111:0000:0000:0000:0000:0000:0000:0111, specify
    --     @1111:0000:0000:0000:0000:0000:0000:0111\/128@.
    --
    -- -   To configure WAF to allow, block, or count requests that originated
    --     from IP addresses 1111:0000:0000:0000:0000:0000:0000:0000 to
    --     1111:0000:0000:0000:ffff:ffff:ffff:ffff, specify
    --     @1111:0000:0000:0000:0000:0000:0000:0000\/64@.
    --
    -- For more information about CIDR notation, see the Wikipedia entry
    -- <https://en.wikipedia.org/wiki/Classless_Inter-Domain_Routing Classless Inter-Domain Routing>.
    --
    -- Example JSON @Addresses@ specifications:
    --
    -- -   Empty array: @\"Addresses\": []@
    --
    -- -   Array with one address: @\"Addresses\": [\"192.0.2.44\/32\"]@
    --
    -- -   Array with three addresses:
    --     @\"Addresses\": [\"192.0.2.44\/32\", \"192.0.2.0\/24\", \"192.0.0.0\/16\"]@
    --
    -- -   INVALID specification: @\"Addresses\": [\"\"]@ INVALID
    UpdateIPSet -> [Text]
addresses :: [Prelude.Text],
    -- | A token used for optimistic locking. WAF returns a token to your @get@
    -- and @list@ requests, to mark the state of the entity at the time of the
    -- request. To make changes to the entity associated with the token, you
    -- provide the token to operations like @update@ and @delete@. WAF uses the
    -- token to ensure that no changes have been made to the entity since you
    -- last retrieved it. If a change has been made, the update fails with a
    -- @WAFOptimisticLockException@. If this happens, perform another @get@,
    -- and use the new token returned by that operation.
    UpdateIPSet -> Text
lockToken :: Prelude.Text
  }
  deriving (UpdateIPSet -> UpdateIPSet -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateIPSet -> UpdateIPSet -> Bool
$c/= :: UpdateIPSet -> UpdateIPSet -> Bool
== :: UpdateIPSet -> UpdateIPSet -> Bool
$c== :: UpdateIPSet -> UpdateIPSet -> Bool
Prelude.Eq, ReadPrec [UpdateIPSet]
ReadPrec UpdateIPSet
Int -> ReadS UpdateIPSet
ReadS [UpdateIPSet]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateIPSet]
$creadListPrec :: ReadPrec [UpdateIPSet]
readPrec :: ReadPrec UpdateIPSet
$creadPrec :: ReadPrec UpdateIPSet
readList :: ReadS [UpdateIPSet]
$creadList :: ReadS [UpdateIPSet]
readsPrec :: Int -> ReadS UpdateIPSet
$creadsPrec :: Int -> ReadS UpdateIPSet
Prelude.Read, Int -> UpdateIPSet -> ShowS
[UpdateIPSet] -> ShowS
UpdateIPSet -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateIPSet] -> ShowS
$cshowList :: [UpdateIPSet] -> ShowS
show :: UpdateIPSet -> String
$cshow :: UpdateIPSet -> String
showsPrec :: Int -> UpdateIPSet -> ShowS
$cshowsPrec :: Int -> UpdateIPSet -> ShowS
Prelude.Show, forall x. Rep UpdateIPSet x -> UpdateIPSet
forall x. UpdateIPSet -> Rep UpdateIPSet x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateIPSet x -> UpdateIPSet
$cfrom :: forall x. UpdateIPSet -> Rep UpdateIPSet x
Prelude.Generic)

-- |
-- Create a value of 'UpdateIPSet' 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:
--
-- 'description', 'updateIPSet_description' - A description of the IP set that helps with identification.
--
-- 'name', 'updateIPSet_name' - The name of the IP set. You cannot change the name of an @IPSet@ after
-- you create it.
--
-- 'scope', 'updateIPSet_scope' - Specifies whether this is for an Amazon CloudFront distribution or for a
-- regional application. A regional application can be an Application Load
-- Balancer (ALB), an Amazon API Gateway REST API, an AppSync GraphQL API,
-- or an Amazon Cognito user pool.
--
-- To work with CloudFront, you must also specify the Region US East (N.
-- Virginia) as follows:
--
-- -   CLI - Specify the Region when you use the CloudFront scope:
--     @--scope=CLOUDFRONT --region=us-east-1@.
--
-- -   API and SDKs - For all calls, use the Region endpoint us-east-1.
--
-- 'id', 'updateIPSet_id' - A unique identifier for the set. This ID is returned in the responses to
-- create and list commands. You provide it to operations like update and
-- delete.
--
-- 'addresses', 'updateIPSet_addresses' - Contains an array of strings that specifies zero or more IP addresses or
-- blocks of IP addresses. All addresses must be specified using Classless
-- Inter-Domain Routing (CIDR) notation. WAF supports all IPv4 and IPv6
-- CIDR ranges except for @\/0@.
--
-- Example address strings:
--
-- -   To configure WAF to allow, block, or count requests that originated
--     from the IP address 192.0.2.44, specify @192.0.2.44\/32@.
--
-- -   To configure WAF to allow, block, or count requests that originated
--     from IP addresses from 192.0.2.0 to 192.0.2.255, specify
--     @192.0.2.0\/24@.
--
-- -   To configure WAF to allow, block, or count requests that originated
--     from the IP address 1111:0000:0000:0000:0000:0000:0000:0111, specify
--     @1111:0000:0000:0000:0000:0000:0000:0111\/128@.
--
-- -   To configure WAF to allow, block, or count requests that originated
--     from IP addresses 1111:0000:0000:0000:0000:0000:0000:0000 to
--     1111:0000:0000:0000:ffff:ffff:ffff:ffff, specify
--     @1111:0000:0000:0000:0000:0000:0000:0000\/64@.
--
-- For more information about CIDR notation, see the Wikipedia entry
-- <https://en.wikipedia.org/wiki/Classless_Inter-Domain_Routing Classless Inter-Domain Routing>.
--
-- Example JSON @Addresses@ specifications:
--
-- -   Empty array: @\"Addresses\": []@
--
-- -   Array with one address: @\"Addresses\": [\"192.0.2.44\/32\"]@
--
-- -   Array with three addresses:
--     @\"Addresses\": [\"192.0.2.44\/32\", \"192.0.2.0\/24\", \"192.0.0.0\/16\"]@
--
-- -   INVALID specification: @\"Addresses\": [\"\"]@ INVALID
--
-- 'lockToken', 'updateIPSet_lockToken' - A token used for optimistic locking. WAF returns a token to your @get@
-- and @list@ requests, to mark the state of the entity at the time of the
-- request. To make changes to the entity associated with the token, you
-- provide the token to operations like @update@ and @delete@. WAF uses the
-- token to ensure that no changes have been made to the entity since you
-- last retrieved it. If a change has been made, the update fails with a
-- @WAFOptimisticLockException@. If this happens, perform another @get@,
-- and use the new token returned by that operation.
newUpdateIPSet ::
  -- | 'name'
  Prelude.Text ->
  -- | 'scope'
  Scope ->
  -- | 'id'
  Prelude.Text ->
  -- | 'lockToken'
  Prelude.Text ->
  UpdateIPSet
newUpdateIPSet :: Text -> Scope -> Text -> Text -> UpdateIPSet
newUpdateIPSet Text
pName_ Scope
pScope_ Text
pId_ Text
pLockToken_ =
  UpdateIPSet'
    { $sel:description:UpdateIPSet' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:name:UpdateIPSet' :: Text
name = Text
pName_,
      $sel:scope:UpdateIPSet' :: Scope
scope = Scope
pScope_,
      $sel:id:UpdateIPSet' :: Text
id = Text
pId_,
      $sel:addresses:UpdateIPSet' :: [Text]
addresses = forall a. Monoid a => a
Prelude.mempty,
      $sel:lockToken:UpdateIPSet' :: Text
lockToken = Text
pLockToken_
    }

-- | A description of the IP set that helps with identification.
updateIPSet_description :: Lens.Lens' UpdateIPSet (Prelude.Maybe Prelude.Text)
updateIPSet_description :: Lens' UpdateIPSet (Maybe Text)
updateIPSet_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateIPSet' {Maybe Text
description :: Maybe Text
$sel:description:UpdateIPSet' :: UpdateIPSet -> Maybe Text
description} -> Maybe Text
description) (\s :: UpdateIPSet
s@UpdateIPSet' {} Maybe Text
a -> UpdateIPSet
s {$sel:description:UpdateIPSet' :: Maybe Text
description = Maybe Text
a} :: UpdateIPSet)

-- | The name of the IP set. You cannot change the name of an @IPSet@ after
-- you create it.
updateIPSet_name :: Lens.Lens' UpdateIPSet Prelude.Text
updateIPSet_name :: Lens' UpdateIPSet Text
updateIPSet_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateIPSet' {Text
name :: Text
$sel:name:UpdateIPSet' :: UpdateIPSet -> Text
name} -> Text
name) (\s :: UpdateIPSet
s@UpdateIPSet' {} Text
a -> UpdateIPSet
s {$sel:name:UpdateIPSet' :: Text
name = Text
a} :: UpdateIPSet)

-- | Specifies whether this is for an Amazon CloudFront distribution or for a
-- regional application. A regional application can be an Application Load
-- Balancer (ALB), an Amazon API Gateway REST API, an AppSync GraphQL API,
-- or an Amazon Cognito user pool.
--
-- To work with CloudFront, you must also specify the Region US East (N.
-- Virginia) as follows:
--
-- -   CLI - Specify the Region when you use the CloudFront scope:
--     @--scope=CLOUDFRONT --region=us-east-1@.
--
-- -   API and SDKs - For all calls, use the Region endpoint us-east-1.
updateIPSet_scope :: Lens.Lens' UpdateIPSet Scope
updateIPSet_scope :: Lens' UpdateIPSet Scope
updateIPSet_scope = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateIPSet' {Scope
scope :: Scope
$sel:scope:UpdateIPSet' :: UpdateIPSet -> Scope
scope} -> Scope
scope) (\s :: UpdateIPSet
s@UpdateIPSet' {} Scope
a -> UpdateIPSet
s {$sel:scope:UpdateIPSet' :: Scope
scope = Scope
a} :: UpdateIPSet)

-- | A unique identifier for the set. This ID is returned in the responses to
-- create and list commands. You provide it to operations like update and
-- delete.
updateIPSet_id :: Lens.Lens' UpdateIPSet Prelude.Text
updateIPSet_id :: Lens' UpdateIPSet Text
updateIPSet_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateIPSet' {Text
id :: Text
$sel:id:UpdateIPSet' :: UpdateIPSet -> Text
id} -> Text
id) (\s :: UpdateIPSet
s@UpdateIPSet' {} Text
a -> UpdateIPSet
s {$sel:id:UpdateIPSet' :: Text
id = Text
a} :: UpdateIPSet)

-- | Contains an array of strings that specifies zero or more IP addresses or
-- blocks of IP addresses. All addresses must be specified using Classless
-- Inter-Domain Routing (CIDR) notation. WAF supports all IPv4 and IPv6
-- CIDR ranges except for @\/0@.
--
-- Example address strings:
--
-- -   To configure WAF to allow, block, or count requests that originated
--     from the IP address 192.0.2.44, specify @192.0.2.44\/32@.
--
-- -   To configure WAF to allow, block, or count requests that originated
--     from IP addresses from 192.0.2.0 to 192.0.2.255, specify
--     @192.0.2.0\/24@.
--
-- -   To configure WAF to allow, block, or count requests that originated
--     from the IP address 1111:0000:0000:0000:0000:0000:0000:0111, specify
--     @1111:0000:0000:0000:0000:0000:0000:0111\/128@.
--
-- -   To configure WAF to allow, block, or count requests that originated
--     from IP addresses 1111:0000:0000:0000:0000:0000:0000:0000 to
--     1111:0000:0000:0000:ffff:ffff:ffff:ffff, specify
--     @1111:0000:0000:0000:0000:0000:0000:0000\/64@.
--
-- For more information about CIDR notation, see the Wikipedia entry
-- <https://en.wikipedia.org/wiki/Classless_Inter-Domain_Routing Classless Inter-Domain Routing>.
--
-- Example JSON @Addresses@ specifications:
--
-- -   Empty array: @\"Addresses\": []@
--
-- -   Array with one address: @\"Addresses\": [\"192.0.2.44\/32\"]@
--
-- -   Array with three addresses:
--     @\"Addresses\": [\"192.0.2.44\/32\", \"192.0.2.0\/24\", \"192.0.0.0\/16\"]@
--
-- -   INVALID specification: @\"Addresses\": [\"\"]@ INVALID
updateIPSet_addresses :: Lens.Lens' UpdateIPSet [Prelude.Text]
updateIPSet_addresses :: Lens' UpdateIPSet [Text]
updateIPSet_addresses = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateIPSet' {[Text]
addresses :: [Text]
$sel:addresses:UpdateIPSet' :: UpdateIPSet -> [Text]
addresses} -> [Text]
addresses) (\s :: UpdateIPSet
s@UpdateIPSet' {} [Text]
a -> UpdateIPSet
s {$sel:addresses:UpdateIPSet' :: [Text]
addresses = [Text]
a} :: UpdateIPSet) 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

-- | A token used for optimistic locking. WAF returns a token to your @get@
-- and @list@ requests, to mark the state of the entity at the time of the
-- request. To make changes to the entity associated with the token, you
-- provide the token to operations like @update@ and @delete@. WAF uses the
-- token to ensure that no changes have been made to the entity since you
-- last retrieved it. If a change has been made, the update fails with a
-- @WAFOptimisticLockException@. If this happens, perform another @get@,
-- and use the new token returned by that operation.
updateIPSet_lockToken :: Lens.Lens' UpdateIPSet Prelude.Text
updateIPSet_lockToken :: Lens' UpdateIPSet Text
updateIPSet_lockToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateIPSet' {Text
lockToken :: Text
$sel:lockToken:UpdateIPSet' :: UpdateIPSet -> Text
lockToken} -> Text
lockToken) (\s :: UpdateIPSet
s@UpdateIPSet' {} Text
a -> UpdateIPSet
s {$sel:lockToken:UpdateIPSet' :: Text
lockToken = Text
a} :: UpdateIPSet)

instance Core.AWSRequest UpdateIPSet where
  type AWSResponse UpdateIPSet = UpdateIPSetResponse
  request :: (Service -> Service) -> UpdateIPSet -> Request UpdateIPSet
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy UpdateIPSet
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse UpdateIPSet)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe Text -> Int -> UpdateIPSetResponse
UpdateIPSetResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"NextLockToken")
            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 UpdateIPSet where
  hashWithSalt :: Int -> UpdateIPSet -> Int
hashWithSalt Int
_salt UpdateIPSet' {[Text]
Maybe Text
Text
Scope
lockToken :: Text
addresses :: [Text]
id :: Text
scope :: Scope
name :: Text
description :: Maybe Text
$sel:lockToken:UpdateIPSet' :: UpdateIPSet -> Text
$sel:addresses:UpdateIPSet' :: UpdateIPSet -> [Text]
$sel:id:UpdateIPSet' :: UpdateIPSet -> Text
$sel:scope:UpdateIPSet' :: UpdateIPSet -> Scope
$sel:name:UpdateIPSet' :: UpdateIPSet -> Text
$sel:description:UpdateIPSet' :: UpdateIPSet -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Scope
scope
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
id
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [Text]
addresses
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
lockToken

instance Prelude.NFData UpdateIPSet where
  rnf :: UpdateIPSet -> ()
rnf UpdateIPSet' {[Text]
Maybe Text
Text
Scope
lockToken :: Text
addresses :: [Text]
id :: Text
scope :: Scope
name :: Text
description :: Maybe Text
$sel:lockToken:UpdateIPSet' :: UpdateIPSet -> Text
$sel:addresses:UpdateIPSet' :: UpdateIPSet -> [Text]
$sel:id:UpdateIPSet' :: UpdateIPSet -> Text
$sel:scope:UpdateIPSet' :: UpdateIPSet -> Scope
$sel:name:UpdateIPSet' :: UpdateIPSet -> Text
$sel:description:UpdateIPSet' :: UpdateIPSet -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Scope
scope
      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 [Text]
addresses
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
lockToken

instance Data.ToHeaders UpdateIPSet where
  toHeaders :: UpdateIPSet -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"AWSWAF_20190729.UpdateIPSet" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON UpdateIPSet where
  toJSON :: UpdateIPSet -> Value
toJSON UpdateIPSet' {[Text]
Maybe Text
Text
Scope
lockToken :: Text
addresses :: [Text]
id :: Text
scope :: Scope
name :: Text
description :: Maybe Text
$sel:lockToken:UpdateIPSet' :: UpdateIPSet -> Text
$sel:addresses:UpdateIPSet' :: UpdateIPSet -> [Text]
$sel:id:UpdateIPSet' :: UpdateIPSet -> Text
$sel:scope:UpdateIPSet' :: UpdateIPSet -> Scope
$sel:name:UpdateIPSet' :: UpdateIPSet -> Text
$sel:description:UpdateIPSet' :: UpdateIPSet -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Description" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
description,
            forall a. a -> Maybe a
Prelude.Just (Key
"Name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
name),
            forall a. a -> Maybe a
Prelude.Just (Key
"Scope" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Scope
scope),
            forall a. a -> Maybe a
Prelude.Just (Key
"Id" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
id),
            forall a. a -> Maybe a
Prelude.Just (Key
"Addresses" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= [Text]
addresses),
            forall a. a -> Maybe a
Prelude.Just (Key
"LockToken" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
lockToken)
          ]
      )

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

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

-- | /See:/ 'newUpdateIPSetResponse' smart constructor.
data UpdateIPSetResponse = UpdateIPSetResponse'
  { -- | A token used for optimistic locking. WAF returns this token to your
    -- @update@ requests. You use @NextLockToken@ in the same manner as you use
    -- @LockToken@.
    UpdateIPSetResponse -> Maybe Text
nextLockToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    UpdateIPSetResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (UpdateIPSetResponse -> UpdateIPSetResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateIPSetResponse -> UpdateIPSetResponse -> Bool
$c/= :: UpdateIPSetResponse -> UpdateIPSetResponse -> Bool
== :: UpdateIPSetResponse -> UpdateIPSetResponse -> Bool
$c== :: UpdateIPSetResponse -> UpdateIPSetResponse -> Bool
Prelude.Eq, ReadPrec [UpdateIPSetResponse]
ReadPrec UpdateIPSetResponse
Int -> ReadS UpdateIPSetResponse
ReadS [UpdateIPSetResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateIPSetResponse]
$creadListPrec :: ReadPrec [UpdateIPSetResponse]
readPrec :: ReadPrec UpdateIPSetResponse
$creadPrec :: ReadPrec UpdateIPSetResponse
readList :: ReadS [UpdateIPSetResponse]
$creadList :: ReadS [UpdateIPSetResponse]
readsPrec :: Int -> ReadS UpdateIPSetResponse
$creadsPrec :: Int -> ReadS UpdateIPSetResponse
Prelude.Read, Int -> UpdateIPSetResponse -> ShowS
[UpdateIPSetResponse] -> ShowS
UpdateIPSetResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateIPSetResponse] -> ShowS
$cshowList :: [UpdateIPSetResponse] -> ShowS
show :: UpdateIPSetResponse -> String
$cshow :: UpdateIPSetResponse -> String
showsPrec :: Int -> UpdateIPSetResponse -> ShowS
$cshowsPrec :: Int -> UpdateIPSetResponse -> ShowS
Prelude.Show, forall x. Rep UpdateIPSetResponse x -> UpdateIPSetResponse
forall x. UpdateIPSetResponse -> Rep UpdateIPSetResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateIPSetResponse x -> UpdateIPSetResponse
$cfrom :: forall x. UpdateIPSetResponse -> Rep UpdateIPSetResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateIPSetResponse' 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:
--
-- 'nextLockToken', 'updateIPSetResponse_nextLockToken' - A token used for optimistic locking. WAF returns this token to your
-- @update@ requests. You use @NextLockToken@ in the same manner as you use
-- @LockToken@.
--
-- 'httpStatus', 'updateIPSetResponse_httpStatus' - The response's http status code.
newUpdateIPSetResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateIPSetResponse
newUpdateIPSetResponse :: Int -> UpdateIPSetResponse
newUpdateIPSetResponse Int
pHttpStatus_ =
  UpdateIPSetResponse'
    { $sel:nextLockToken:UpdateIPSetResponse' :: Maybe Text
nextLockToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UpdateIPSetResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A token used for optimistic locking. WAF returns this token to your
-- @update@ requests. You use @NextLockToken@ in the same manner as you use
-- @LockToken@.
updateIPSetResponse_nextLockToken :: Lens.Lens' UpdateIPSetResponse (Prelude.Maybe Prelude.Text)
updateIPSetResponse_nextLockToken :: Lens' UpdateIPSetResponse (Maybe Text)
updateIPSetResponse_nextLockToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateIPSetResponse' {Maybe Text
nextLockToken :: Maybe Text
$sel:nextLockToken:UpdateIPSetResponse' :: UpdateIPSetResponse -> Maybe Text
nextLockToken} -> Maybe Text
nextLockToken) (\s :: UpdateIPSetResponse
s@UpdateIPSetResponse' {} Maybe Text
a -> UpdateIPSetResponse
s {$sel:nextLockToken:UpdateIPSetResponse' :: Maybe Text
nextLockToken = Maybe Text
a} :: UpdateIPSetResponse)

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

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