{-# 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.DisassociateSubnets
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Removes the specified subnet associations from the firewall. This
-- removes the firewall endpoints from the subnets and removes any network
-- filtering protections that the endpoints were providing.
module Amazonka.NetworkFirewall.DisassociateSubnets
  ( -- * Creating a Request
    DisassociateSubnets (..),
    newDisassociateSubnets,

    -- * Request Lenses
    disassociateSubnets_firewallArn,
    disassociateSubnets_firewallName,
    disassociateSubnets_updateToken,
    disassociateSubnets_subnetIds,

    -- * Destructuring the Response
    DisassociateSubnetsResponse (..),
    newDisassociateSubnetsResponse,

    -- * Response Lenses
    disassociateSubnetsResponse_firewallArn,
    disassociateSubnetsResponse_firewallName,
    disassociateSubnetsResponse_subnetMappings,
    disassociateSubnetsResponse_updateToken,
    disassociateSubnetsResponse_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:/ 'newDisassociateSubnets' smart constructor.
data DisassociateSubnets = DisassociateSubnets'
  { -- | The Amazon Resource Name (ARN) of the firewall.
    --
    -- You must specify the ARN or the name, and you can specify both.
    DisassociateSubnets -> 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.
    DisassociateSubnets -> 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.
    DisassociateSubnets -> Maybe Text
updateToken :: Prelude.Maybe Prelude.Text,
    -- | The unique identifiers for the subnets that you want to disassociate.
    DisassociateSubnets -> [Text]
subnetIds :: [Prelude.Text]
  }
  deriving (DisassociateSubnets -> DisassociateSubnets -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DisassociateSubnets -> DisassociateSubnets -> Bool
$c/= :: DisassociateSubnets -> DisassociateSubnets -> Bool
== :: DisassociateSubnets -> DisassociateSubnets -> Bool
$c== :: DisassociateSubnets -> DisassociateSubnets -> Bool
Prelude.Eq, ReadPrec [DisassociateSubnets]
ReadPrec DisassociateSubnets
Int -> ReadS DisassociateSubnets
ReadS [DisassociateSubnets]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DisassociateSubnets]
$creadListPrec :: ReadPrec [DisassociateSubnets]
readPrec :: ReadPrec DisassociateSubnets
$creadPrec :: ReadPrec DisassociateSubnets
readList :: ReadS [DisassociateSubnets]
$creadList :: ReadS [DisassociateSubnets]
readsPrec :: Int -> ReadS DisassociateSubnets
$creadsPrec :: Int -> ReadS DisassociateSubnets
Prelude.Read, Int -> DisassociateSubnets -> ShowS
[DisassociateSubnets] -> ShowS
DisassociateSubnets -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DisassociateSubnets] -> ShowS
$cshowList :: [DisassociateSubnets] -> ShowS
show :: DisassociateSubnets -> String
$cshow :: DisassociateSubnets -> String
showsPrec :: Int -> DisassociateSubnets -> ShowS
$cshowsPrec :: Int -> DisassociateSubnets -> ShowS
Prelude.Show, forall x. Rep DisassociateSubnets x -> DisassociateSubnets
forall x. DisassociateSubnets -> Rep DisassociateSubnets x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DisassociateSubnets x -> DisassociateSubnets
$cfrom :: forall x. DisassociateSubnets -> Rep DisassociateSubnets x
Prelude.Generic)

-- |
-- Create a value of 'DisassociateSubnets' 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', 'disassociateSubnets_firewallArn' - The Amazon Resource Name (ARN) of the firewall.
--
-- You must specify the ARN or the name, and you can specify both.
--
-- 'firewallName', 'disassociateSubnets_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', 'disassociateSubnets_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.
--
-- 'subnetIds', 'disassociateSubnets_subnetIds' - The unique identifiers for the subnets that you want to disassociate.
newDisassociateSubnets ::
  DisassociateSubnets
newDisassociateSubnets :: DisassociateSubnets
newDisassociateSubnets =
  DisassociateSubnets'
    { $sel:firewallArn:DisassociateSubnets' :: Maybe Text
firewallArn = forall a. Maybe a
Prelude.Nothing,
      $sel:firewallName:DisassociateSubnets' :: Maybe Text
firewallName = forall a. Maybe a
Prelude.Nothing,
      $sel:updateToken:DisassociateSubnets' :: Maybe Text
updateToken = forall a. Maybe a
Prelude.Nothing,
      $sel:subnetIds:DisassociateSubnets' :: [Text]
subnetIds = forall a. Monoid a => a
Prelude.mempty
    }

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

-- | 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.
disassociateSubnets_firewallName :: Lens.Lens' DisassociateSubnets (Prelude.Maybe Prelude.Text)
disassociateSubnets_firewallName :: Lens' DisassociateSubnets (Maybe Text)
disassociateSubnets_firewallName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DisassociateSubnets' {Maybe Text
firewallName :: Maybe Text
$sel:firewallName:DisassociateSubnets' :: DisassociateSubnets -> Maybe Text
firewallName} -> Maybe Text
firewallName) (\s :: DisassociateSubnets
s@DisassociateSubnets' {} Maybe Text
a -> DisassociateSubnets
s {$sel:firewallName:DisassociateSubnets' :: Maybe Text
firewallName = Maybe Text
a} :: DisassociateSubnets)

-- | 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.
disassociateSubnets_updateToken :: Lens.Lens' DisassociateSubnets (Prelude.Maybe Prelude.Text)
disassociateSubnets_updateToken :: Lens' DisassociateSubnets (Maybe Text)
disassociateSubnets_updateToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DisassociateSubnets' {Maybe Text
updateToken :: Maybe Text
$sel:updateToken:DisassociateSubnets' :: DisassociateSubnets -> Maybe Text
updateToken} -> Maybe Text
updateToken) (\s :: DisassociateSubnets
s@DisassociateSubnets' {} Maybe Text
a -> DisassociateSubnets
s {$sel:updateToken:DisassociateSubnets' :: Maybe Text
updateToken = Maybe Text
a} :: DisassociateSubnets)

-- | The unique identifiers for the subnets that you want to disassociate.
disassociateSubnets_subnetIds :: Lens.Lens' DisassociateSubnets [Prelude.Text]
disassociateSubnets_subnetIds :: Lens' DisassociateSubnets [Text]
disassociateSubnets_subnetIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DisassociateSubnets' {[Text]
subnetIds :: [Text]
$sel:subnetIds:DisassociateSubnets' :: DisassociateSubnets -> [Text]
subnetIds} -> [Text]
subnetIds) (\s :: DisassociateSubnets
s@DisassociateSubnets' {} [Text]
a -> DisassociateSubnets
s {$sel:subnetIds:DisassociateSubnets' :: [Text]
subnetIds = [Text]
a} :: DisassociateSubnets) 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 DisassociateSubnets where
  type
    AWSResponse DisassociateSubnets =
      DisassociateSubnetsResponse
  request :: (Service -> Service)
-> DisassociateSubnets -> Request DisassociateSubnets
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 DisassociateSubnets
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DisassociateSubnets)))
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 [SubnetMapping]
-> Maybe Text
-> Int
-> DisassociateSubnetsResponse
DisassociateSubnetsResponse'
            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
"SubnetMappings" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
            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 DisassociateSubnets where
  hashWithSalt :: Int -> DisassociateSubnets -> Int
hashWithSalt Int
_salt DisassociateSubnets' {[Text]
Maybe Text
subnetIds :: [Text]
updateToken :: Maybe Text
firewallName :: Maybe Text
firewallArn :: Maybe Text
$sel:subnetIds:DisassociateSubnets' :: DisassociateSubnets -> [Text]
$sel:updateToken:DisassociateSubnets' :: DisassociateSubnets -> Maybe Text
$sel:firewallName:DisassociateSubnets' :: DisassociateSubnets -> Maybe Text
$sel:firewallArn:DisassociateSubnets' :: DisassociateSubnets -> 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` [Text]
subnetIds

instance Prelude.NFData DisassociateSubnets where
  rnf :: DisassociateSubnets -> ()
rnf DisassociateSubnets' {[Text]
Maybe Text
subnetIds :: [Text]
updateToken :: Maybe Text
firewallName :: Maybe Text
firewallArn :: Maybe Text
$sel:subnetIds:DisassociateSubnets' :: DisassociateSubnets -> [Text]
$sel:updateToken:DisassociateSubnets' :: DisassociateSubnets -> Maybe Text
$sel:firewallName:DisassociateSubnets' :: DisassociateSubnets -> Maybe Text
$sel:firewallArn:DisassociateSubnets' :: DisassociateSubnets -> 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 [Text]
subnetIds

instance Data.ToHeaders DisassociateSubnets where
  toHeaders :: DisassociateSubnets -> 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.DisassociateSubnets" ::
                          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 DisassociateSubnets where
  toJSON :: DisassociateSubnets -> Value
toJSON DisassociateSubnets' {[Text]
Maybe Text
subnetIds :: [Text]
updateToken :: Maybe Text
firewallName :: Maybe Text
firewallArn :: Maybe Text
$sel:subnetIds:DisassociateSubnets' :: DisassociateSubnets -> [Text]
$sel:updateToken:DisassociateSubnets' :: DisassociateSubnets -> Maybe Text
$sel:firewallName:DisassociateSubnets' :: DisassociateSubnets -> Maybe Text
$sel:firewallArn:DisassociateSubnets' :: DisassociateSubnets -> 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
"SubnetIds" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= [Text]
subnetIds)
          ]
      )

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

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

-- | /See:/ 'newDisassociateSubnetsResponse' smart constructor.
data DisassociateSubnetsResponse = DisassociateSubnetsResponse'
  { -- | The Amazon Resource Name (ARN) of the firewall.
    DisassociateSubnetsResponse -> 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.
    DisassociateSubnetsResponse -> Maybe Text
firewallName :: Prelude.Maybe Prelude.Text,
    -- | The IDs of the subnets that are associated with the firewall.
    DisassociateSubnetsResponse -> Maybe [SubnetMapping]
subnetMappings :: Prelude.Maybe [SubnetMapping],
    -- | 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.
    DisassociateSubnetsResponse -> Maybe Text
updateToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    DisassociateSubnetsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DisassociateSubnetsResponse -> DisassociateSubnetsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DisassociateSubnetsResponse -> DisassociateSubnetsResponse -> Bool
$c/= :: DisassociateSubnetsResponse -> DisassociateSubnetsResponse -> Bool
== :: DisassociateSubnetsResponse -> DisassociateSubnetsResponse -> Bool
$c== :: DisassociateSubnetsResponse -> DisassociateSubnetsResponse -> Bool
Prelude.Eq, ReadPrec [DisassociateSubnetsResponse]
ReadPrec DisassociateSubnetsResponse
Int -> ReadS DisassociateSubnetsResponse
ReadS [DisassociateSubnetsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DisassociateSubnetsResponse]
$creadListPrec :: ReadPrec [DisassociateSubnetsResponse]
readPrec :: ReadPrec DisassociateSubnetsResponse
$creadPrec :: ReadPrec DisassociateSubnetsResponse
readList :: ReadS [DisassociateSubnetsResponse]
$creadList :: ReadS [DisassociateSubnetsResponse]
readsPrec :: Int -> ReadS DisassociateSubnetsResponse
$creadsPrec :: Int -> ReadS DisassociateSubnetsResponse
Prelude.Read, Int -> DisassociateSubnetsResponse -> ShowS
[DisassociateSubnetsResponse] -> ShowS
DisassociateSubnetsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DisassociateSubnetsResponse] -> ShowS
$cshowList :: [DisassociateSubnetsResponse] -> ShowS
show :: DisassociateSubnetsResponse -> String
$cshow :: DisassociateSubnetsResponse -> String
showsPrec :: Int -> DisassociateSubnetsResponse -> ShowS
$cshowsPrec :: Int -> DisassociateSubnetsResponse -> ShowS
Prelude.Show, forall x.
Rep DisassociateSubnetsResponse x -> DisassociateSubnetsResponse
forall x.
DisassociateSubnetsResponse -> Rep DisassociateSubnetsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DisassociateSubnetsResponse x -> DisassociateSubnetsResponse
$cfrom :: forall x.
DisassociateSubnetsResponse -> Rep DisassociateSubnetsResponse x
Prelude.Generic)

-- |
-- Create a value of 'DisassociateSubnetsResponse' 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', 'disassociateSubnetsResponse_firewallArn' - The Amazon Resource Name (ARN) of the firewall.
--
-- 'firewallName', 'disassociateSubnetsResponse_firewallName' - The descriptive name of the firewall. You can\'t change the name of a
-- firewall after you create it.
--
-- 'subnetMappings', 'disassociateSubnetsResponse_subnetMappings' - The IDs of the subnets that are associated with the firewall.
--
-- 'updateToken', 'disassociateSubnetsResponse_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', 'disassociateSubnetsResponse_httpStatus' - The response's http status code.
newDisassociateSubnetsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DisassociateSubnetsResponse
newDisassociateSubnetsResponse :: Int -> DisassociateSubnetsResponse
newDisassociateSubnetsResponse Int
pHttpStatus_ =
  DisassociateSubnetsResponse'
    { $sel:firewallArn:DisassociateSubnetsResponse' :: Maybe Text
firewallArn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:firewallName:DisassociateSubnetsResponse' :: Maybe Text
firewallName = forall a. Maybe a
Prelude.Nothing,
      $sel:subnetMappings:DisassociateSubnetsResponse' :: Maybe [SubnetMapping]
subnetMappings = forall a. Maybe a
Prelude.Nothing,
      $sel:updateToken:DisassociateSubnetsResponse' :: Maybe Text
updateToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DisassociateSubnetsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

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

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

-- | The IDs of the subnets that are associated with the firewall.
disassociateSubnetsResponse_subnetMappings :: Lens.Lens' DisassociateSubnetsResponse (Prelude.Maybe [SubnetMapping])
disassociateSubnetsResponse_subnetMappings :: Lens' DisassociateSubnetsResponse (Maybe [SubnetMapping])
disassociateSubnetsResponse_subnetMappings = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DisassociateSubnetsResponse' {Maybe [SubnetMapping]
subnetMappings :: Maybe [SubnetMapping]
$sel:subnetMappings:DisassociateSubnetsResponse' :: DisassociateSubnetsResponse -> Maybe [SubnetMapping]
subnetMappings} -> Maybe [SubnetMapping]
subnetMappings) (\s :: DisassociateSubnetsResponse
s@DisassociateSubnetsResponse' {} Maybe [SubnetMapping]
a -> DisassociateSubnetsResponse
s {$sel:subnetMappings:DisassociateSubnetsResponse' :: Maybe [SubnetMapping]
subnetMappings = Maybe [SubnetMapping]
a} :: DisassociateSubnetsResponse) 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

-- | 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.
disassociateSubnetsResponse_updateToken :: Lens.Lens' DisassociateSubnetsResponse (Prelude.Maybe Prelude.Text)
disassociateSubnetsResponse_updateToken :: Lens' DisassociateSubnetsResponse (Maybe Text)
disassociateSubnetsResponse_updateToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DisassociateSubnetsResponse' {Maybe Text
updateToken :: Maybe Text
$sel:updateToken:DisassociateSubnetsResponse' :: DisassociateSubnetsResponse -> Maybe Text
updateToken} -> Maybe Text
updateToken) (\s :: DisassociateSubnetsResponse
s@DisassociateSubnetsResponse' {} Maybe Text
a -> DisassociateSubnetsResponse
s {$sel:updateToken:DisassociateSubnetsResponse' :: Maybe Text
updateToken = Maybe Text
a} :: DisassociateSubnetsResponse)

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

instance Prelude.NFData DisassociateSubnetsResponse where
  rnf :: DisassociateSubnetsResponse -> ()
rnf DisassociateSubnetsResponse' {Int
Maybe [SubnetMapping]
Maybe Text
httpStatus :: Int
updateToken :: Maybe Text
subnetMappings :: Maybe [SubnetMapping]
firewallName :: Maybe Text
firewallArn :: Maybe Text
$sel:httpStatus:DisassociateSubnetsResponse' :: DisassociateSubnetsResponse -> Int
$sel:updateToken:DisassociateSubnetsResponse' :: DisassociateSubnetsResponse -> Maybe Text
$sel:subnetMappings:DisassociateSubnetsResponse' :: DisassociateSubnetsResponse -> Maybe [SubnetMapping]
$sel:firewallName:DisassociateSubnetsResponse' :: DisassociateSubnetsResponse -> Maybe Text
$sel:firewallArn:DisassociateSubnetsResponse' :: DisassociateSubnetsResponse -> 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 [SubnetMapping]
subnetMappings
      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