{-# 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.AssociateSubnets
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Associates the specified subnets in the Amazon VPC to the firewall. You
-- can specify one subnet for each of the Availability Zones that the VPC
-- spans.
--
-- This request creates an Network Firewall firewall endpoint in each of
-- the subnets. To enable the firewall\'s protections, you must also modify
-- the VPC\'s route tables for each subnet\'s Availability Zone, to
-- redirect the traffic that\'s coming into and going out of the zone
-- through the firewall endpoint.
module Amazonka.NetworkFirewall.AssociateSubnets
  ( -- * Creating a Request
    AssociateSubnets (..),
    newAssociateSubnets,

    -- * Request Lenses
    associateSubnets_firewallArn,
    associateSubnets_firewallName,
    associateSubnets_updateToken,
    associateSubnets_subnetMappings,

    -- * Destructuring the Response
    AssociateSubnetsResponse (..),
    newAssociateSubnetsResponse,

    -- * Response Lenses
    associateSubnetsResponse_firewallArn,
    associateSubnetsResponse_firewallName,
    associateSubnetsResponse_subnetMappings,
    associateSubnetsResponse_updateToken,
    associateSubnetsResponse_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:/ 'newAssociateSubnets' smart constructor.
data AssociateSubnets = AssociateSubnets'
  { -- | The Amazon Resource Name (ARN) of the firewall.
    --
    -- You must specify the ARN or the name, and you can specify both.
    AssociateSubnets -> 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.
    AssociateSubnets -> 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.
    AssociateSubnets -> Maybe Text
updateToken :: Prelude.Maybe Prelude.Text,
    -- | The IDs of the subnets that you want to associate with the firewall.
    AssociateSubnets -> [SubnetMapping]
subnetMappings :: [SubnetMapping]
  }
  deriving (AssociateSubnets -> AssociateSubnets -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AssociateSubnets -> AssociateSubnets -> Bool
$c/= :: AssociateSubnets -> AssociateSubnets -> Bool
== :: AssociateSubnets -> AssociateSubnets -> Bool
$c== :: AssociateSubnets -> AssociateSubnets -> Bool
Prelude.Eq, ReadPrec [AssociateSubnets]
ReadPrec AssociateSubnets
Int -> ReadS AssociateSubnets
ReadS [AssociateSubnets]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AssociateSubnets]
$creadListPrec :: ReadPrec [AssociateSubnets]
readPrec :: ReadPrec AssociateSubnets
$creadPrec :: ReadPrec AssociateSubnets
readList :: ReadS [AssociateSubnets]
$creadList :: ReadS [AssociateSubnets]
readsPrec :: Int -> ReadS AssociateSubnets
$creadsPrec :: Int -> ReadS AssociateSubnets
Prelude.Read, Int -> AssociateSubnets -> ShowS
[AssociateSubnets] -> ShowS
AssociateSubnets -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AssociateSubnets] -> ShowS
$cshowList :: [AssociateSubnets] -> ShowS
show :: AssociateSubnets -> String
$cshow :: AssociateSubnets -> String
showsPrec :: Int -> AssociateSubnets -> ShowS
$cshowsPrec :: Int -> AssociateSubnets -> ShowS
Prelude.Show, forall x. Rep AssociateSubnets x -> AssociateSubnets
forall x. AssociateSubnets -> Rep AssociateSubnets x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AssociateSubnets x -> AssociateSubnets
$cfrom :: forall x. AssociateSubnets -> Rep AssociateSubnets x
Prelude.Generic)

-- |
-- Create a value of 'AssociateSubnets' 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', 'associateSubnets_firewallArn' - The Amazon Resource Name (ARN) of the firewall.
--
-- You must specify the ARN or the name, and you can specify both.
--
-- 'firewallName', 'associateSubnets_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', 'associateSubnets_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.
--
-- 'subnetMappings', 'associateSubnets_subnetMappings' - The IDs of the subnets that you want to associate with the firewall.
newAssociateSubnets ::
  AssociateSubnets
newAssociateSubnets :: AssociateSubnets
newAssociateSubnets =
  AssociateSubnets'
    { $sel:firewallArn:AssociateSubnets' :: Maybe Text
firewallArn = forall a. Maybe a
Prelude.Nothing,
      $sel:firewallName:AssociateSubnets' :: Maybe Text
firewallName = forall a. Maybe a
Prelude.Nothing,
      $sel:updateToken:AssociateSubnets' :: Maybe Text
updateToken = forall a. Maybe a
Prelude.Nothing,
      $sel:subnetMappings:AssociateSubnets' :: [SubnetMapping]
subnetMappings = 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.
associateSubnets_firewallArn :: Lens.Lens' AssociateSubnets (Prelude.Maybe Prelude.Text)
associateSubnets_firewallArn :: Lens' AssociateSubnets (Maybe Text)
associateSubnets_firewallArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AssociateSubnets' {Maybe Text
firewallArn :: Maybe Text
$sel:firewallArn:AssociateSubnets' :: AssociateSubnets -> Maybe Text
firewallArn} -> Maybe Text
firewallArn) (\s :: AssociateSubnets
s@AssociateSubnets' {} Maybe Text
a -> AssociateSubnets
s {$sel:firewallArn:AssociateSubnets' :: Maybe Text
firewallArn = Maybe Text
a} :: AssociateSubnets)

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

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

-- | The IDs of the subnets that you want to associate with the firewall.
associateSubnets_subnetMappings :: Lens.Lens' AssociateSubnets [SubnetMapping]
associateSubnets_subnetMappings :: Lens' AssociateSubnets [SubnetMapping]
associateSubnets_subnetMappings = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AssociateSubnets' {[SubnetMapping]
subnetMappings :: [SubnetMapping]
$sel:subnetMappings:AssociateSubnets' :: AssociateSubnets -> [SubnetMapping]
subnetMappings} -> [SubnetMapping]
subnetMappings) (\s :: AssociateSubnets
s@AssociateSubnets' {} [SubnetMapping]
a -> AssociateSubnets
s {$sel:subnetMappings:AssociateSubnets' :: [SubnetMapping]
subnetMappings = [SubnetMapping]
a} :: AssociateSubnets) 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 AssociateSubnets where
  type
    AWSResponse AssociateSubnets =
      AssociateSubnetsResponse
  request :: (Service -> Service)
-> AssociateSubnets -> Request AssociateSubnets
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 AssociateSubnets
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse AssociateSubnets)))
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
-> AssociateSubnetsResponse
AssociateSubnetsResponse'
            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 AssociateSubnets where
  hashWithSalt :: Int -> AssociateSubnets -> Int
hashWithSalt Int
_salt AssociateSubnets' {[SubnetMapping]
Maybe Text
subnetMappings :: [SubnetMapping]
updateToken :: Maybe Text
firewallName :: Maybe Text
firewallArn :: Maybe Text
$sel:subnetMappings:AssociateSubnets' :: AssociateSubnets -> [SubnetMapping]
$sel:updateToken:AssociateSubnets' :: AssociateSubnets -> Maybe Text
$sel:firewallName:AssociateSubnets' :: AssociateSubnets -> Maybe Text
$sel:firewallArn:AssociateSubnets' :: AssociateSubnets -> 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` [SubnetMapping]
subnetMappings

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

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

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

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

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

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

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

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

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

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

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