{-# 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.NetworkFirewall.UpdateSubnetChangeProtection
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.NetworkFirewall.UpdateSubnetChangeProtection
  ( -- * Creating a Request
    UpdateSubnetChangeProtection (..),
    newUpdateSubnetChangeProtection,

    -- * Request Lenses
    updateSubnetChangeProtection_firewallArn,
    updateSubnetChangeProtection_firewallName,
    updateSubnetChangeProtection_updateToken,
    updateSubnetChangeProtection_subnetChangeProtection,

    -- * Destructuring the Response
    UpdateSubnetChangeProtectionResponse (..),
    newUpdateSubnetChangeProtectionResponse,

    -- * Response Lenses
    updateSubnetChangeProtectionResponse_firewallArn,
    updateSubnetChangeProtectionResponse_firewallName,
    updateSubnetChangeProtectionResponse_subnetChangeProtection,
    updateSubnetChangeProtectionResponse_updateToken,
    updateSubnetChangeProtectionResponse_httpStatus,
  )
where

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

-- | /See:/ 'newUpdateSubnetChangeProtection' smart constructor.
data UpdateSubnetChangeProtection = UpdateSubnetChangeProtection'
  { -- | The Amazon Resource Name (ARN) of the firewall.
    --
    -- You must specify the ARN or the name, and you can specify both.
    UpdateSubnetChangeProtection -> Maybe Text
firewallArn :: Prelude.Maybe Prelude.Text,
    -- | The descriptive name of the firewall. You can\'t change the name of a
    -- firewall after you create it.
    --
    -- You must specify the ARN or the name, and you can specify both.
    UpdateSubnetChangeProtection -> Maybe Text
firewallName :: Prelude.Maybe Prelude.Text,
    -- | An optional token that you can use for optimistic locking. Network
    -- Firewall returns a token to your requests that access the firewall. The
    -- token marks the state of the firewall resource at the time of the
    -- request.
    --
    -- To make an unconditional change to the firewall, omit the token in your
    -- update request. Without the token, Network Firewall performs your
    -- updates regardless of whether the firewall has changed since you last
    -- retrieved it.
    --
    -- To make a conditional change to the firewall, provide the token in your
    -- update request. Network Firewall uses the token to ensure that the
    -- firewall hasn\'t changed since you last retrieved it. If it has changed,
    -- the operation fails with an @InvalidTokenException@. If this happens,
    -- retrieve the firewall again to get a current copy of it with a new
    -- token. Reapply your changes as needed, then try the operation again
    -- using the new token.
    UpdateSubnetChangeProtection -> Maybe Text
updateToken :: Prelude.Maybe Prelude.Text,
    -- | A setting indicating whether the firewall is protected against changes
    -- to the subnet associations. Use this setting to protect against
    -- accidentally modifying the subnet associations for a firewall that is in
    -- use. When you create a firewall, the operation initializes this setting
    -- to @TRUE@.
    UpdateSubnetChangeProtection -> Bool
subnetChangeProtection :: Prelude.Bool
  }
  deriving (UpdateSubnetChangeProtection
-> UpdateSubnetChangeProtection -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateSubnetChangeProtection
-> UpdateSubnetChangeProtection -> Bool
$c/= :: UpdateSubnetChangeProtection
-> UpdateSubnetChangeProtection -> Bool
== :: UpdateSubnetChangeProtection
-> UpdateSubnetChangeProtection -> Bool
$c== :: UpdateSubnetChangeProtection
-> UpdateSubnetChangeProtection -> Bool
Prelude.Eq, ReadPrec [UpdateSubnetChangeProtection]
ReadPrec UpdateSubnetChangeProtection
Int -> ReadS UpdateSubnetChangeProtection
ReadS [UpdateSubnetChangeProtection]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateSubnetChangeProtection]
$creadListPrec :: ReadPrec [UpdateSubnetChangeProtection]
readPrec :: ReadPrec UpdateSubnetChangeProtection
$creadPrec :: ReadPrec UpdateSubnetChangeProtection
readList :: ReadS [UpdateSubnetChangeProtection]
$creadList :: ReadS [UpdateSubnetChangeProtection]
readsPrec :: Int -> ReadS UpdateSubnetChangeProtection
$creadsPrec :: Int -> ReadS UpdateSubnetChangeProtection
Prelude.Read, Int -> UpdateSubnetChangeProtection -> ShowS
[UpdateSubnetChangeProtection] -> ShowS
UpdateSubnetChangeProtection -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateSubnetChangeProtection] -> ShowS
$cshowList :: [UpdateSubnetChangeProtection] -> ShowS
show :: UpdateSubnetChangeProtection -> String
$cshow :: UpdateSubnetChangeProtection -> String
showsPrec :: Int -> UpdateSubnetChangeProtection -> ShowS
$cshowsPrec :: Int -> UpdateSubnetChangeProtection -> ShowS
Prelude.Show, forall x.
Rep UpdateSubnetChangeProtection x -> UpdateSubnetChangeProtection
forall x.
UpdateSubnetChangeProtection -> Rep UpdateSubnetChangeProtection x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateSubnetChangeProtection x -> UpdateSubnetChangeProtection
$cfrom :: forall x.
UpdateSubnetChangeProtection -> Rep UpdateSubnetChangeProtection x
Prelude.Generic)

-- |
-- Create a value of 'UpdateSubnetChangeProtection' 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:
--
-- 'firewallArn', 'updateSubnetChangeProtection_firewallArn' - The Amazon Resource Name (ARN) of the firewall.
--
-- You must specify the ARN or the name, and you can specify both.
--
-- 'firewallName', 'updateSubnetChangeProtection_firewallName' - The descriptive name of the firewall. You can\'t change the name of a
-- firewall after you create it.
--
-- You must specify the ARN or the name, and you can specify both.
--
-- 'updateToken', 'updateSubnetChangeProtection_updateToken' - An optional token that you can use for optimistic locking. Network
-- Firewall returns a token to your requests that access the firewall. The
-- token marks the state of the firewall resource at the time of the
-- request.
--
-- To make an unconditional change to the firewall, omit the token in your
-- update request. Without the token, Network Firewall performs your
-- updates regardless of whether the firewall has changed since you last
-- retrieved it.
--
-- To make a conditional change to the firewall, provide the token in your
-- update request. Network Firewall uses the token to ensure that the
-- firewall hasn\'t changed since you last retrieved it. If it has changed,
-- the operation fails with an @InvalidTokenException@. If this happens,
-- retrieve the firewall again to get a current copy of it with a new
-- token. Reapply your changes as needed, then try the operation again
-- using the new token.
--
-- 'subnetChangeProtection', 'updateSubnetChangeProtection_subnetChangeProtection' - A setting indicating whether the firewall is protected against changes
-- to the subnet associations. Use this setting to protect against
-- accidentally modifying the subnet associations for a firewall that is in
-- use. When you create a firewall, the operation initializes this setting
-- to @TRUE@.
newUpdateSubnetChangeProtection ::
  -- | 'subnetChangeProtection'
  Prelude.Bool ->
  UpdateSubnetChangeProtection
newUpdateSubnetChangeProtection :: Bool -> UpdateSubnetChangeProtection
newUpdateSubnetChangeProtection
  Bool
pSubnetChangeProtection_ =
    UpdateSubnetChangeProtection'
      { $sel:firewallArn:UpdateSubnetChangeProtection' :: Maybe Text
firewallArn =
          forall a. Maybe a
Prelude.Nothing,
        $sel:firewallName:UpdateSubnetChangeProtection' :: Maybe Text
firewallName = forall a. Maybe a
Prelude.Nothing,
        $sel:updateToken:UpdateSubnetChangeProtection' :: Maybe Text
updateToken = forall a. Maybe a
Prelude.Nothing,
        $sel:subnetChangeProtection:UpdateSubnetChangeProtection' :: Bool
subnetChangeProtection =
          Bool
pSubnetChangeProtection_
      }

-- | The Amazon Resource Name (ARN) of the firewall.
--
-- You must specify the ARN or the name, and you can specify both.
updateSubnetChangeProtection_firewallArn :: Lens.Lens' UpdateSubnetChangeProtection (Prelude.Maybe Prelude.Text)
updateSubnetChangeProtection_firewallArn :: Lens' UpdateSubnetChangeProtection (Maybe Text)
updateSubnetChangeProtection_firewallArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSubnetChangeProtection' {Maybe Text
firewallArn :: Maybe Text
$sel:firewallArn:UpdateSubnetChangeProtection' :: UpdateSubnetChangeProtection -> Maybe Text
firewallArn} -> Maybe Text
firewallArn) (\s :: UpdateSubnetChangeProtection
s@UpdateSubnetChangeProtection' {} Maybe Text
a -> UpdateSubnetChangeProtection
s {$sel:firewallArn:UpdateSubnetChangeProtection' :: Maybe Text
firewallArn = Maybe Text
a} :: UpdateSubnetChangeProtection)

-- | The descriptive name of the firewall. You can\'t change the name of a
-- firewall after you create it.
--
-- You must specify the ARN or the name, and you can specify both.
updateSubnetChangeProtection_firewallName :: Lens.Lens' UpdateSubnetChangeProtection (Prelude.Maybe Prelude.Text)
updateSubnetChangeProtection_firewallName :: Lens' UpdateSubnetChangeProtection (Maybe Text)
updateSubnetChangeProtection_firewallName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSubnetChangeProtection' {Maybe Text
firewallName :: Maybe Text
$sel:firewallName:UpdateSubnetChangeProtection' :: UpdateSubnetChangeProtection -> Maybe Text
firewallName} -> Maybe Text
firewallName) (\s :: UpdateSubnetChangeProtection
s@UpdateSubnetChangeProtection' {} Maybe Text
a -> UpdateSubnetChangeProtection
s {$sel:firewallName:UpdateSubnetChangeProtection' :: Maybe Text
firewallName = Maybe Text
a} :: UpdateSubnetChangeProtection)

-- | An optional token that you can use for optimistic locking. Network
-- Firewall returns a token to your requests that access the firewall. The
-- token marks the state of the firewall resource at the time of the
-- request.
--
-- To make an unconditional change to the firewall, omit the token in your
-- update request. Without the token, Network Firewall performs your
-- updates regardless of whether the firewall has changed since you last
-- retrieved it.
--
-- To make a conditional change to the firewall, provide the token in your
-- update request. Network Firewall uses the token to ensure that the
-- firewall hasn\'t changed since you last retrieved it. If it has changed,
-- the operation fails with an @InvalidTokenException@. If this happens,
-- retrieve the firewall again to get a current copy of it with a new
-- token. Reapply your changes as needed, then try the operation again
-- using the new token.
updateSubnetChangeProtection_updateToken :: Lens.Lens' UpdateSubnetChangeProtection (Prelude.Maybe Prelude.Text)
updateSubnetChangeProtection_updateToken :: Lens' UpdateSubnetChangeProtection (Maybe Text)
updateSubnetChangeProtection_updateToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSubnetChangeProtection' {Maybe Text
updateToken :: Maybe Text
$sel:updateToken:UpdateSubnetChangeProtection' :: UpdateSubnetChangeProtection -> Maybe Text
updateToken} -> Maybe Text
updateToken) (\s :: UpdateSubnetChangeProtection
s@UpdateSubnetChangeProtection' {} Maybe Text
a -> UpdateSubnetChangeProtection
s {$sel:updateToken:UpdateSubnetChangeProtection' :: Maybe Text
updateToken = Maybe Text
a} :: UpdateSubnetChangeProtection)

-- | A setting indicating whether the firewall is protected against changes
-- to the subnet associations. Use this setting to protect against
-- accidentally modifying the subnet associations for a firewall that is in
-- use. When you create a firewall, the operation initializes this setting
-- to @TRUE@.
updateSubnetChangeProtection_subnetChangeProtection :: Lens.Lens' UpdateSubnetChangeProtection Prelude.Bool
updateSubnetChangeProtection_subnetChangeProtection :: Lens' UpdateSubnetChangeProtection Bool
updateSubnetChangeProtection_subnetChangeProtection = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSubnetChangeProtection' {Bool
subnetChangeProtection :: Bool
$sel:subnetChangeProtection:UpdateSubnetChangeProtection' :: UpdateSubnetChangeProtection -> Bool
subnetChangeProtection} -> Bool
subnetChangeProtection) (\s :: UpdateSubnetChangeProtection
s@UpdateSubnetChangeProtection' {} Bool
a -> UpdateSubnetChangeProtection
s {$sel:subnetChangeProtection:UpdateSubnetChangeProtection' :: Bool
subnetChangeProtection = Bool
a} :: UpdateSubnetChangeProtection)

instance Core.AWSRequest UpdateSubnetChangeProtection where
  type
    AWSResponse UpdateSubnetChangeProtection =
      UpdateSubnetChangeProtectionResponse
  request :: (Service -> Service)
-> UpdateSubnetChangeProtection
-> Request UpdateSubnetChangeProtection
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 UpdateSubnetChangeProtection
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse UpdateSubnetChangeProtection)))
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
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Int
-> UpdateSubnetChangeProtectionResponse
UpdateSubnetChangeProtectionResponse'
            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
"FirewallArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"FirewallName")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"SubnetChangeProtection")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"UpdateToken")
            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
    UpdateSubnetChangeProtection
  where
  hashWithSalt :: Int -> UpdateSubnetChangeProtection -> Int
hashWithSalt Int
_salt UpdateSubnetChangeProtection' {Bool
Maybe Text
subnetChangeProtection :: Bool
updateToken :: Maybe Text
firewallName :: Maybe Text
firewallArn :: Maybe Text
$sel:subnetChangeProtection:UpdateSubnetChangeProtection' :: UpdateSubnetChangeProtection -> Bool
$sel:updateToken:UpdateSubnetChangeProtection' :: UpdateSubnetChangeProtection -> Maybe Text
$sel:firewallName:UpdateSubnetChangeProtection' :: UpdateSubnetChangeProtection -> Maybe Text
$sel:firewallArn:UpdateSubnetChangeProtection' :: UpdateSubnetChangeProtection -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
firewallArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
firewallName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
updateToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Bool
subnetChangeProtection

instance Prelude.NFData UpdateSubnetChangeProtection where
  rnf :: UpdateSubnetChangeProtection -> ()
rnf UpdateSubnetChangeProtection' {Bool
Maybe Text
subnetChangeProtection :: Bool
updateToken :: Maybe Text
firewallName :: Maybe Text
firewallArn :: Maybe Text
$sel:subnetChangeProtection:UpdateSubnetChangeProtection' :: UpdateSubnetChangeProtection -> Bool
$sel:updateToken:UpdateSubnetChangeProtection' :: UpdateSubnetChangeProtection -> Maybe Text
$sel:firewallName:UpdateSubnetChangeProtection' :: UpdateSubnetChangeProtection -> Maybe Text
$sel:firewallArn:UpdateSubnetChangeProtection' :: UpdateSubnetChangeProtection -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
firewallArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
firewallName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
updateToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Bool
subnetChangeProtection

instance Data.ToHeaders UpdateSubnetChangeProtection where
  toHeaders :: UpdateSubnetChangeProtection -> 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
"NetworkFirewall_20201112.UpdateSubnetChangeProtection" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.0" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON UpdateSubnetChangeProtection where
  toJSON :: UpdateSubnetChangeProtection -> Value
toJSON UpdateSubnetChangeProtection' {Bool
Maybe Text
subnetChangeProtection :: Bool
updateToken :: Maybe Text
firewallName :: Maybe Text
firewallArn :: Maybe Text
$sel:subnetChangeProtection:UpdateSubnetChangeProtection' :: UpdateSubnetChangeProtection -> Bool
$sel:updateToken:UpdateSubnetChangeProtection' :: UpdateSubnetChangeProtection -> Maybe Text
$sel:firewallName:UpdateSubnetChangeProtection' :: UpdateSubnetChangeProtection -> Maybe Text
$sel:firewallArn:UpdateSubnetChangeProtection' :: UpdateSubnetChangeProtection -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"FirewallArn" 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
firewallArn,
            (Key
"FirewallName" 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
firewallName,
            (Key
"UpdateToken" 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
updateToken,
            forall a. a -> Maybe a
Prelude.Just
              ( Key
"SubnetChangeProtection"
                  forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Bool
subnetChangeProtection
              )
          ]
      )

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

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

-- | /See:/ 'newUpdateSubnetChangeProtectionResponse' smart constructor.
data UpdateSubnetChangeProtectionResponse = UpdateSubnetChangeProtectionResponse'
  { -- | The Amazon Resource Name (ARN) of the firewall.
    UpdateSubnetChangeProtectionResponse -> Maybe Text
firewallArn :: Prelude.Maybe Prelude.Text,
    -- | The descriptive name of the firewall. You can\'t change the name of a
    -- firewall after you create it.
    UpdateSubnetChangeProtectionResponse -> Maybe Text
firewallName :: Prelude.Maybe Prelude.Text,
    -- | A setting indicating whether the firewall is protected against changes
    -- to the subnet associations. Use this setting to protect against
    -- accidentally modifying the subnet associations for a firewall that is in
    -- use. When you create a firewall, the operation initializes this setting
    -- to @TRUE@.
    UpdateSubnetChangeProtectionResponse -> Maybe Bool
subnetChangeProtection :: Prelude.Maybe Prelude.Bool,
    -- | An optional token that you can use for optimistic locking. Network
    -- Firewall returns a token to your requests that access the firewall. The
    -- token marks the state of the firewall resource at the time of the
    -- request.
    --
    -- To make an unconditional change to the firewall, omit the token in your
    -- update request. Without the token, Network Firewall performs your
    -- updates regardless of whether the firewall has changed since you last
    -- retrieved it.
    --
    -- To make a conditional change to the firewall, provide the token in your
    -- update request. Network Firewall uses the token to ensure that the
    -- firewall hasn\'t changed since you last retrieved it. If it has changed,
    -- the operation fails with an @InvalidTokenException@. If this happens,
    -- retrieve the firewall again to get a current copy of it with a new
    -- token. Reapply your changes as needed, then try the operation again
    -- using the new token.
    UpdateSubnetChangeProtectionResponse -> Maybe Text
updateToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    UpdateSubnetChangeProtectionResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (UpdateSubnetChangeProtectionResponse
-> UpdateSubnetChangeProtectionResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateSubnetChangeProtectionResponse
-> UpdateSubnetChangeProtectionResponse -> Bool
$c/= :: UpdateSubnetChangeProtectionResponse
-> UpdateSubnetChangeProtectionResponse -> Bool
== :: UpdateSubnetChangeProtectionResponse
-> UpdateSubnetChangeProtectionResponse -> Bool
$c== :: UpdateSubnetChangeProtectionResponse
-> UpdateSubnetChangeProtectionResponse -> Bool
Prelude.Eq, ReadPrec [UpdateSubnetChangeProtectionResponse]
ReadPrec UpdateSubnetChangeProtectionResponse
Int -> ReadS UpdateSubnetChangeProtectionResponse
ReadS [UpdateSubnetChangeProtectionResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateSubnetChangeProtectionResponse]
$creadListPrec :: ReadPrec [UpdateSubnetChangeProtectionResponse]
readPrec :: ReadPrec UpdateSubnetChangeProtectionResponse
$creadPrec :: ReadPrec UpdateSubnetChangeProtectionResponse
readList :: ReadS [UpdateSubnetChangeProtectionResponse]
$creadList :: ReadS [UpdateSubnetChangeProtectionResponse]
readsPrec :: Int -> ReadS UpdateSubnetChangeProtectionResponse
$creadsPrec :: Int -> ReadS UpdateSubnetChangeProtectionResponse
Prelude.Read, Int -> UpdateSubnetChangeProtectionResponse -> ShowS
[UpdateSubnetChangeProtectionResponse] -> ShowS
UpdateSubnetChangeProtectionResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateSubnetChangeProtectionResponse] -> ShowS
$cshowList :: [UpdateSubnetChangeProtectionResponse] -> ShowS
show :: UpdateSubnetChangeProtectionResponse -> String
$cshow :: UpdateSubnetChangeProtectionResponse -> String
showsPrec :: Int -> UpdateSubnetChangeProtectionResponse -> ShowS
$cshowsPrec :: Int -> UpdateSubnetChangeProtectionResponse -> ShowS
Prelude.Show, forall x.
Rep UpdateSubnetChangeProtectionResponse x
-> UpdateSubnetChangeProtectionResponse
forall x.
UpdateSubnetChangeProtectionResponse
-> Rep UpdateSubnetChangeProtectionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateSubnetChangeProtectionResponse x
-> UpdateSubnetChangeProtectionResponse
$cfrom :: forall x.
UpdateSubnetChangeProtectionResponse
-> Rep UpdateSubnetChangeProtectionResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateSubnetChangeProtectionResponse' 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:
--
-- 'firewallArn', 'updateSubnetChangeProtectionResponse_firewallArn' - The Amazon Resource Name (ARN) of the firewall.
--
-- 'firewallName', 'updateSubnetChangeProtectionResponse_firewallName' - The descriptive name of the firewall. You can\'t change the name of a
-- firewall after you create it.
--
-- 'subnetChangeProtection', 'updateSubnetChangeProtectionResponse_subnetChangeProtection' - A setting indicating whether the firewall is protected against changes
-- to the subnet associations. Use this setting to protect against
-- accidentally modifying the subnet associations for a firewall that is in
-- use. When you create a firewall, the operation initializes this setting
-- to @TRUE@.
--
-- 'updateToken', 'updateSubnetChangeProtectionResponse_updateToken' - An optional token that you can use for optimistic locking. Network
-- Firewall returns a token to your requests that access the firewall. The
-- token marks the state of the firewall resource at the time of the
-- request.
--
-- To make an unconditional change to the firewall, omit the token in your
-- update request. Without the token, Network Firewall performs your
-- updates regardless of whether the firewall has changed since you last
-- retrieved it.
--
-- To make a conditional change to the firewall, provide the token in your
-- update request. Network Firewall uses the token to ensure that the
-- firewall hasn\'t changed since you last retrieved it. If it has changed,
-- the operation fails with an @InvalidTokenException@. If this happens,
-- retrieve the firewall again to get a current copy of it with a new
-- token. Reapply your changes as needed, then try the operation again
-- using the new token.
--
-- 'httpStatus', 'updateSubnetChangeProtectionResponse_httpStatus' - The response's http status code.
newUpdateSubnetChangeProtectionResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateSubnetChangeProtectionResponse
newUpdateSubnetChangeProtectionResponse :: Int -> UpdateSubnetChangeProtectionResponse
newUpdateSubnetChangeProtectionResponse Int
pHttpStatus_ =
  UpdateSubnetChangeProtectionResponse'
    { $sel:firewallArn:UpdateSubnetChangeProtectionResponse' :: Maybe Text
firewallArn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:firewallName:UpdateSubnetChangeProtectionResponse' :: Maybe Text
firewallName = forall a. Maybe a
Prelude.Nothing,
      $sel:subnetChangeProtection:UpdateSubnetChangeProtectionResponse' :: Maybe Bool
subnetChangeProtection =
        forall a. Maybe a
Prelude.Nothing,
      $sel:updateToken:UpdateSubnetChangeProtectionResponse' :: Maybe Text
updateToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UpdateSubnetChangeProtectionResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The Amazon Resource Name (ARN) of the firewall.
updateSubnetChangeProtectionResponse_firewallArn :: Lens.Lens' UpdateSubnetChangeProtectionResponse (Prelude.Maybe Prelude.Text)
updateSubnetChangeProtectionResponse_firewallArn :: Lens' UpdateSubnetChangeProtectionResponse (Maybe Text)
updateSubnetChangeProtectionResponse_firewallArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSubnetChangeProtectionResponse' {Maybe Text
firewallArn :: Maybe Text
$sel:firewallArn:UpdateSubnetChangeProtectionResponse' :: UpdateSubnetChangeProtectionResponse -> Maybe Text
firewallArn} -> Maybe Text
firewallArn) (\s :: UpdateSubnetChangeProtectionResponse
s@UpdateSubnetChangeProtectionResponse' {} Maybe Text
a -> UpdateSubnetChangeProtectionResponse
s {$sel:firewallArn:UpdateSubnetChangeProtectionResponse' :: Maybe Text
firewallArn = Maybe Text
a} :: UpdateSubnetChangeProtectionResponse)

-- | The descriptive name of the firewall. You can\'t change the name of a
-- firewall after you create it.
updateSubnetChangeProtectionResponse_firewallName :: Lens.Lens' UpdateSubnetChangeProtectionResponse (Prelude.Maybe Prelude.Text)
updateSubnetChangeProtectionResponse_firewallName :: Lens' UpdateSubnetChangeProtectionResponse (Maybe Text)
updateSubnetChangeProtectionResponse_firewallName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSubnetChangeProtectionResponse' {Maybe Text
firewallName :: Maybe Text
$sel:firewallName:UpdateSubnetChangeProtectionResponse' :: UpdateSubnetChangeProtectionResponse -> Maybe Text
firewallName} -> Maybe Text
firewallName) (\s :: UpdateSubnetChangeProtectionResponse
s@UpdateSubnetChangeProtectionResponse' {} Maybe Text
a -> UpdateSubnetChangeProtectionResponse
s {$sel:firewallName:UpdateSubnetChangeProtectionResponse' :: Maybe Text
firewallName = Maybe Text
a} :: UpdateSubnetChangeProtectionResponse)

-- | A setting indicating whether the firewall is protected against changes
-- to the subnet associations. Use this setting to protect against
-- accidentally modifying the subnet associations for a firewall that is in
-- use. When you create a firewall, the operation initializes this setting
-- to @TRUE@.
updateSubnetChangeProtectionResponse_subnetChangeProtection :: Lens.Lens' UpdateSubnetChangeProtectionResponse (Prelude.Maybe Prelude.Bool)
updateSubnetChangeProtectionResponse_subnetChangeProtection :: Lens' UpdateSubnetChangeProtectionResponse (Maybe Bool)
updateSubnetChangeProtectionResponse_subnetChangeProtection = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSubnetChangeProtectionResponse' {Maybe Bool
subnetChangeProtection :: Maybe Bool
$sel:subnetChangeProtection:UpdateSubnetChangeProtectionResponse' :: UpdateSubnetChangeProtectionResponse -> Maybe Bool
subnetChangeProtection} -> Maybe Bool
subnetChangeProtection) (\s :: UpdateSubnetChangeProtectionResponse
s@UpdateSubnetChangeProtectionResponse' {} Maybe Bool
a -> UpdateSubnetChangeProtectionResponse
s {$sel:subnetChangeProtection:UpdateSubnetChangeProtectionResponse' :: Maybe Bool
subnetChangeProtection = Maybe Bool
a} :: UpdateSubnetChangeProtectionResponse)

-- | An optional token that you can use for optimistic locking. Network
-- Firewall returns a token to your requests that access the firewall. The
-- token marks the state of the firewall resource at the time of the
-- request.
--
-- To make an unconditional change to the firewall, omit the token in your
-- update request. Without the token, Network Firewall performs your
-- updates regardless of whether the firewall has changed since you last
-- retrieved it.
--
-- To make a conditional change to the firewall, provide the token in your
-- update request. Network Firewall uses the token to ensure that the
-- firewall hasn\'t changed since you last retrieved it. If it has changed,
-- the operation fails with an @InvalidTokenException@. If this happens,
-- retrieve the firewall again to get a current copy of it with a new
-- token. Reapply your changes as needed, then try the operation again
-- using the new token.
updateSubnetChangeProtectionResponse_updateToken :: Lens.Lens' UpdateSubnetChangeProtectionResponse (Prelude.Maybe Prelude.Text)
updateSubnetChangeProtectionResponse_updateToken :: Lens' UpdateSubnetChangeProtectionResponse (Maybe Text)
updateSubnetChangeProtectionResponse_updateToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSubnetChangeProtectionResponse' {Maybe Text
updateToken :: Maybe Text
$sel:updateToken:UpdateSubnetChangeProtectionResponse' :: UpdateSubnetChangeProtectionResponse -> Maybe Text
updateToken} -> Maybe Text
updateToken) (\s :: UpdateSubnetChangeProtectionResponse
s@UpdateSubnetChangeProtectionResponse' {} Maybe Text
a -> UpdateSubnetChangeProtectionResponse
s {$sel:updateToken:UpdateSubnetChangeProtectionResponse' :: Maybe Text
updateToken = Maybe Text
a} :: UpdateSubnetChangeProtectionResponse)

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

instance
  Prelude.NFData
    UpdateSubnetChangeProtectionResponse
  where
  rnf :: UpdateSubnetChangeProtectionResponse -> ()
rnf UpdateSubnetChangeProtectionResponse' {Int
Maybe Bool
Maybe Text
httpStatus :: Int
updateToken :: Maybe Text
subnetChangeProtection :: Maybe Bool
firewallName :: Maybe Text
firewallArn :: Maybe Text
$sel:httpStatus:UpdateSubnetChangeProtectionResponse' :: UpdateSubnetChangeProtectionResponse -> Int
$sel:updateToken:UpdateSubnetChangeProtectionResponse' :: UpdateSubnetChangeProtectionResponse -> Maybe Text
$sel:subnetChangeProtection:UpdateSubnetChangeProtectionResponse' :: UpdateSubnetChangeProtectionResponse -> Maybe Bool
$sel:firewallName:UpdateSubnetChangeProtectionResponse' :: UpdateSubnetChangeProtectionResponse -> Maybe Text
$sel:firewallArn:UpdateSubnetChangeProtectionResponse' :: UpdateSubnetChangeProtectionResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
firewallArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
firewallName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
subnetChangeProtection
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
updateToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus