{-# 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.Route53Resolver.UpdateFirewallRuleGroupAssociation
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Changes the association of a FirewallRuleGroup with a VPC. The
-- association enables DNS filtering for the VPC.
module Amazonka.Route53Resolver.UpdateFirewallRuleGroupAssociation
  ( -- * Creating a Request
    UpdateFirewallRuleGroupAssociation (..),
    newUpdateFirewallRuleGroupAssociation,

    -- * Request Lenses
    updateFirewallRuleGroupAssociation_mutationProtection,
    updateFirewallRuleGroupAssociation_name,
    updateFirewallRuleGroupAssociation_priority,
    updateFirewallRuleGroupAssociation_firewallRuleGroupAssociationId,

    -- * Destructuring the Response
    UpdateFirewallRuleGroupAssociationResponse (..),
    newUpdateFirewallRuleGroupAssociationResponse,

    -- * Response Lenses
    updateFirewallRuleGroupAssociationResponse_firewallRuleGroupAssociation,
    updateFirewallRuleGroupAssociationResponse_httpStatus,
  )
where

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

-- | /See:/ 'newUpdateFirewallRuleGroupAssociation' smart constructor.
data UpdateFirewallRuleGroupAssociation = UpdateFirewallRuleGroupAssociation'
  { -- | If enabled, this setting disallows modification or removal of the
    -- association, to help prevent against accidentally altering DNS firewall
    -- protections.
    UpdateFirewallRuleGroupAssociation
-> Maybe MutationProtectionStatus
mutationProtection :: Prelude.Maybe MutationProtectionStatus,
    -- | The name of the rule group association.
    UpdateFirewallRuleGroupAssociation -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | The setting that determines the processing order of the rule group among
    -- the rule groups that you associate with the specified VPC. DNS Firewall
    -- filters VPC traffic starting from the rule group with the lowest numeric
    -- priority setting.
    --
    -- You must specify a unique priority for each rule group that you
    -- associate with a single VPC. To make it easier to insert rule groups
    -- later, leave space between the numbers, for example, use 100, 200, and
    -- so on. You can change the priority setting for a rule group association
    -- after you create it.
    UpdateFirewallRuleGroupAssociation -> Maybe Int
priority :: Prelude.Maybe Prelude.Int,
    -- | The identifier of the FirewallRuleGroupAssociation.
    UpdateFirewallRuleGroupAssociation -> Text
firewallRuleGroupAssociationId :: Prelude.Text
  }
  deriving (UpdateFirewallRuleGroupAssociation
-> UpdateFirewallRuleGroupAssociation -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateFirewallRuleGroupAssociation
-> UpdateFirewallRuleGroupAssociation -> Bool
$c/= :: UpdateFirewallRuleGroupAssociation
-> UpdateFirewallRuleGroupAssociation -> Bool
== :: UpdateFirewallRuleGroupAssociation
-> UpdateFirewallRuleGroupAssociation -> Bool
$c== :: UpdateFirewallRuleGroupAssociation
-> UpdateFirewallRuleGroupAssociation -> Bool
Prelude.Eq, ReadPrec [UpdateFirewallRuleGroupAssociation]
ReadPrec UpdateFirewallRuleGroupAssociation
Int -> ReadS UpdateFirewallRuleGroupAssociation
ReadS [UpdateFirewallRuleGroupAssociation]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateFirewallRuleGroupAssociation]
$creadListPrec :: ReadPrec [UpdateFirewallRuleGroupAssociation]
readPrec :: ReadPrec UpdateFirewallRuleGroupAssociation
$creadPrec :: ReadPrec UpdateFirewallRuleGroupAssociation
readList :: ReadS [UpdateFirewallRuleGroupAssociation]
$creadList :: ReadS [UpdateFirewallRuleGroupAssociation]
readsPrec :: Int -> ReadS UpdateFirewallRuleGroupAssociation
$creadsPrec :: Int -> ReadS UpdateFirewallRuleGroupAssociation
Prelude.Read, Int -> UpdateFirewallRuleGroupAssociation -> ShowS
[UpdateFirewallRuleGroupAssociation] -> ShowS
UpdateFirewallRuleGroupAssociation -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateFirewallRuleGroupAssociation] -> ShowS
$cshowList :: [UpdateFirewallRuleGroupAssociation] -> ShowS
show :: UpdateFirewallRuleGroupAssociation -> String
$cshow :: UpdateFirewallRuleGroupAssociation -> String
showsPrec :: Int -> UpdateFirewallRuleGroupAssociation -> ShowS
$cshowsPrec :: Int -> UpdateFirewallRuleGroupAssociation -> ShowS
Prelude.Show, forall x.
Rep UpdateFirewallRuleGroupAssociation x
-> UpdateFirewallRuleGroupAssociation
forall x.
UpdateFirewallRuleGroupAssociation
-> Rep UpdateFirewallRuleGroupAssociation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateFirewallRuleGroupAssociation x
-> UpdateFirewallRuleGroupAssociation
$cfrom :: forall x.
UpdateFirewallRuleGroupAssociation
-> Rep UpdateFirewallRuleGroupAssociation x
Prelude.Generic)

-- |
-- Create a value of 'UpdateFirewallRuleGroupAssociation' 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:
--
-- 'mutationProtection', 'updateFirewallRuleGroupAssociation_mutationProtection' - If enabled, this setting disallows modification or removal of the
-- association, to help prevent against accidentally altering DNS firewall
-- protections.
--
-- 'name', 'updateFirewallRuleGroupAssociation_name' - The name of the rule group association.
--
-- 'priority', 'updateFirewallRuleGroupAssociation_priority' - The setting that determines the processing order of the rule group among
-- the rule groups that you associate with the specified VPC. DNS Firewall
-- filters VPC traffic starting from the rule group with the lowest numeric
-- priority setting.
--
-- You must specify a unique priority for each rule group that you
-- associate with a single VPC. To make it easier to insert rule groups
-- later, leave space between the numbers, for example, use 100, 200, and
-- so on. You can change the priority setting for a rule group association
-- after you create it.
--
-- 'firewallRuleGroupAssociationId', 'updateFirewallRuleGroupAssociation_firewallRuleGroupAssociationId' - The identifier of the FirewallRuleGroupAssociation.
newUpdateFirewallRuleGroupAssociation ::
  -- | 'firewallRuleGroupAssociationId'
  Prelude.Text ->
  UpdateFirewallRuleGroupAssociation
newUpdateFirewallRuleGroupAssociation :: Text -> UpdateFirewallRuleGroupAssociation
newUpdateFirewallRuleGroupAssociation
  Text
pFirewallRuleGroupAssociationId_ =
    UpdateFirewallRuleGroupAssociation'
      { $sel:mutationProtection:UpdateFirewallRuleGroupAssociation' :: Maybe MutationProtectionStatus
mutationProtection =
          forall a. Maybe a
Prelude.Nothing,
        $sel:name:UpdateFirewallRuleGroupAssociation' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
        $sel:priority:UpdateFirewallRuleGroupAssociation' :: Maybe Int
priority = forall a. Maybe a
Prelude.Nothing,
        $sel:firewallRuleGroupAssociationId:UpdateFirewallRuleGroupAssociation' :: Text
firewallRuleGroupAssociationId =
          Text
pFirewallRuleGroupAssociationId_
      }

-- | If enabled, this setting disallows modification or removal of the
-- association, to help prevent against accidentally altering DNS firewall
-- protections.
updateFirewallRuleGroupAssociation_mutationProtection :: Lens.Lens' UpdateFirewallRuleGroupAssociation (Prelude.Maybe MutationProtectionStatus)
updateFirewallRuleGroupAssociation_mutationProtection :: Lens'
  UpdateFirewallRuleGroupAssociation (Maybe MutationProtectionStatus)
updateFirewallRuleGroupAssociation_mutationProtection = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateFirewallRuleGroupAssociation' {Maybe MutationProtectionStatus
mutationProtection :: Maybe MutationProtectionStatus
$sel:mutationProtection:UpdateFirewallRuleGroupAssociation' :: UpdateFirewallRuleGroupAssociation
-> Maybe MutationProtectionStatus
mutationProtection} -> Maybe MutationProtectionStatus
mutationProtection) (\s :: UpdateFirewallRuleGroupAssociation
s@UpdateFirewallRuleGroupAssociation' {} Maybe MutationProtectionStatus
a -> UpdateFirewallRuleGroupAssociation
s {$sel:mutationProtection:UpdateFirewallRuleGroupAssociation' :: Maybe MutationProtectionStatus
mutationProtection = Maybe MutationProtectionStatus
a} :: UpdateFirewallRuleGroupAssociation)

-- | The name of the rule group association.
updateFirewallRuleGroupAssociation_name :: Lens.Lens' UpdateFirewallRuleGroupAssociation (Prelude.Maybe Prelude.Text)
updateFirewallRuleGroupAssociation_name :: Lens' UpdateFirewallRuleGroupAssociation (Maybe Text)
updateFirewallRuleGroupAssociation_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateFirewallRuleGroupAssociation' {Maybe Text
name :: Maybe Text
$sel:name:UpdateFirewallRuleGroupAssociation' :: UpdateFirewallRuleGroupAssociation -> Maybe Text
name} -> Maybe Text
name) (\s :: UpdateFirewallRuleGroupAssociation
s@UpdateFirewallRuleGroupAssociation' {} Maybe Text
a -> UpdateFirewallRuleGroupAssociation
s {$sel:name:UpdateFirewallRuleGroupAssociation' :: Maybe Text
name = Maybe Text
a} :: UpdateFirewallRuleGroupAssociation)

-- | The setting that determines the processing order of the rule group among
-- the rule groups that you associate with the specified VPC. DNS Firewall
-- filters VPC traffic starting from the rule group with the lowest numeric
-- priority setting.
--
-- You must specify a unique priority for each rule group that you
-- associate with a single VPC. To make it easier to insert rule groups
-- later, leave space between the numbers, for example, use 100, 200, and
-- so on. You can change the priority setting for a rule group association
-- after you create it.
updateFirewallRuleGroupAssociation_priority :: Lens.Lens' UpdateFirewallRuleGroupAssociation (Prelude.Maybe Prelude.Int)
updateFirewallRuleGroupAssociation_priority :: Lens' UpdateFirewallRuleGroupAssociation (Maybe Int)
updateFirewallRuleGroupAssociation_priority = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateFirewallRuleGroupAssociation' {Maybe Int
priority :: Maybe Int
$sel:priority:UpdateFirewallRuleGroupAssociation' :: UpdateFirewallRuleGroupAssociation -> Maybe Int
priority} -> Maybe Int
priority) (\s :: UpdateFirewallRuleGroupAssociation
s@UpdateFirewallRuleGroupAssociation' {} Maybe Int
a -> UpdateFirewallRuleGroupAssociation
s {$sel:priority:UpdateFirewallRuleGroupAssociation' :: Maybe Int
priority = Maybe Int
a} :: UpdateFirewallRuleGroupAssociation)

-- | The identifier of the FirewallRuleGroupAssociation.
updateFirewallRuleGroupAssociation_firewallRuleGroupAssociationId :: Lens.Lens' UpdateFirewallRuleGroupAssociation Prelude.Text
updateFirewallRuleGroupAssociation_firewallRuleGroupAssociationId :: Lens' UpdateFirewallRuleGroupAssociation Text
updateFirewallRuleGroupAssociation_firewallRuleGroupAssociationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateFirewallRuleGroupAssociation' {Text
firewallRuleGroupAssociationId :: Text
$sel:firewallRuleGroupAssociationId:UpdateFirewallRuleGroupAssociation' :: UpdateFirewallRuleGroupAssociation -> Text
firewallRuleGroupAssociationId} -> Text
firewallRuleGroupAssociationId) (\s :: UpdateFirewallRuleGroupAssociation
s@UpdateFirewallRuleGroupAssociation' {} Text
a -> UpdateFirewallRuleGroupAssociation
s {$sel:firewallRuleGroupAssociationId:UpdateFirewallRuleGroupAssociation' :: Text
firewallRuleGroupAssociationId = Text
a} :: UpdateFirewallRuleGroupAssociation)

instance
  Core.AWSRequest
    UpdateFirewallRuleGroupAssociation
  where
  type
    AWSResponse UpdateFirewallRuleGroupAssociation =
      UpdateFirewallRuleGroupAssociationResponse
  request :: (Service -> Service)
-> UpdateFirewallRuleGroupAssociation
-> Request UpdateFirewallRuleGroupAssociation
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 UpdateFirewallRuleGroupAssociation
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse (AWSResponse UpdateFirewallRuleGroupAssociation)))
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 FirewallRuleGroupAssociation
-> Int -> UpdateFirewallRuleGroupAssociationResponse
UpdateFirewallRuleGroupAssociationResponse'
            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
"FirewallRuleGroupAssociation")
            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
    UpdateFirewallRuleGroupAssociation
  where
  hashWithSalt :: Int -> UpdateFirewallRuleGroupAssociation -> Int
hashWithSalt
    Int
_salt
    UpdateFirewallRuleGroupAssociation' {Maybe Int
Maybe Text
Maybe MutationProtectionStatus
Text
firewallRuleGroupAssociationId :: Text
priority :: Maybe Int
name :: Maybe Text
mutationProtection :: Maybe MutationProtectionStatus
$sel:firewallRuleGroupAssociationId:UpdateFirewallRuleGroupAssociation' :: UpdateFirewallRuleGroupAssociation -> Text
$sel:priority:UpdateFirewallRuleGroupAssociation' :: UpdateFirewallRuleGroupAssociation -> Maybe Int
$sel:name:UpdateFirewallRuleGroupAssociation' :: UpdateFirewallRuleGroupAssociation -> Maybe Text
$sel:mutationProtection:UpdateFirewallRuleGroupAssociation' :: UpdateFirewallRuleGroupAssociation
-> Maybe MutationProtectionStatus
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe MutationProtectionStatus
mutationProtection
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
name
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
priority
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
firewallRuleGroupAssociationId

instance
  Prelude.NFData
    UpdateFirewallRuleGroupAssociation
  where
  rnf :: UpdateFirewallRuleGroupAssociation -> ()
rnf UpdateFirewallRuleGroupAssociation' {Maybe Int
Maybe Text
Maybe MutationProtectionStatus
Text
firewallRuleGroupAssociationId :: Text
priority :: Maybe Int
name :: Maybe Text
mutationProtection :: Maybe MutationProtectionStatus
$sel:firewallRuleGroupAssociationId:UpdateFirewallRuleGroupAssociation' :: UpdateFirewallRuleGroupAssociation -> Text
$sel:priority:UpdateFirewallRuleGroupAssociation' :: UpdateFirewallRuleGroupAssociation -> Maybe Int
$sel:name:UpdateFirewallRuleGroupAssociation' :: UpdateFirewallRuleGroupAssociation -> Maybe Text
$sel:mutationProtection:UpdateFirewallRuleGroupAssociation' :: UpdateFirewallRuleGroupAssociation
-> Maybe MutationProtectionStatus
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe MutationProtectionStatus
mutationProtection
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
priority
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
firewallRuleGroupAssociationId

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

instance
  Data.ToJSON
    UpdateFirewallRuleGroupAssociation
  where
  toJSON :: UpdateFirewallRuleGroupAssociation -> Value
toJSON UpdateFirewallRuleGroupAssociation' {Maybe Int
Maybe Text
Maybe MutationProtectionStatus
Text
firewallRuleGroupAssociationId :: Text
priority :: Maybe Int
name :: Maybe Text
mutationProtection :: Maybe MutationProtectionStatus
$sel:firewallRuleGroupAssociationId:UpdateFirewallRuleGroupAssociation' :: UpdateFirewallRuleGroupAssociation -> Text
$sel:priority:UpdateFirewallRuleGroupAssociation' :: UpdateFirewallRuleGroupAssociation -> Maybe Int
$sel:name:UpdateFirewallRuleGroupAssociation' :: UpdateFirewallRuleGroupAssociation -> Maybe Text
$sel:mutationProtection:UpdateFirewallRuleGroupAssociation' :: UpdateFirewallRuleGroupAssociation
-> Maybe MutationProtectionStatus
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"MutationProtection" 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 MutationProtectionStatus
mutationProtection,
            (Key
"Name" 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
name,
            (Key
"Priority" 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 Int
priority,
            forall a. a -> Maybe a
Prelude.Just
              ( Key
"FirewallRuleGroupAssociationId"
                  forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
firewallRuleGroupAssociationId
              )
          ]
      )

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

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

-- | /See:/ 'newUpdateFirewallRuleGroupAssociationResponse' smart constructor.
data UpdateFirewallRuleGroupAssociationResponse = UpdateFirewallRuleGroupAssociationResponse'
  { -- | The association that you just updated.
    UpdateFirewallRuleGroupAssociationResponse
-> Maybe FirewallRuleGroupAssociation
firewallRuleGroupAssociation :: Prelude.Maybe FirewallRuleGroupAssociation,
    -- | The response's http status code.
    UpdateFirewallRuleGroupAssociationResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (UpdateFirewallRuleGroupAssociationResponse
-> UpdateFirewallRuleGroupAssociationResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateFirewallRuleGroupAssociationResponse
-> UpdateFirewallRuleGroupAssociationResponse -> Bool
$c/= :: UpdateFirewallRuleGroupAssociationResponse
-> UpdateFirewallRuleGroupAssociationResponse -> Bool
== :: UpdateFirewallRuleGroupAssociationResponse
-> UpdateFirewallRuleGroupAssociationResponse -> Bool
$c== :: UpdateFirewallRuleGroupAssociationResponse
-> UpdateFirewallRuleGroupAssociationResponse -> Bool
Prelude.Eq, ReadPrec [UpdateFirewallRuleGroupAssociationResponse]
ReadPrec UpdateFirewallRuleGroupAssociationResponse
Int -> ReadS UpdateFirewallRuleGroupAssociationResponse
ReadS [UpdateFirewallRuleGroupAssociationResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateFirewallRuleGroupAssociationResponse]
$creadListPrec :: ReadPrec [UpdateFirewallRuleGroupAssociationResponse]
readPrec :: ReadPrec UpdateFirewallRuleGroupAssociationResponse
$creadPrec :: ReadPrec UpdateFirewallRuleGroupAssociationResponse
readList :: ReadS [UpdateFirewallRuleGroupAssociationResponse]
$creadList :: ReadS [UpdateFirewallRuleGroupAssociationResponse]
readsPrec :: Int -> ReadS UpdateFirewallRuleGroupAssociationResponse
$creadsPrec :: Int -> ReadS UpdateFirewallRuleGroupAssociationResponse
Prelude.Read, Int -> UpdateFirewallRuleGroupAssociationResponse -> ShowS
[UpdateFirewallRuleGroupAssociationResponse] -> ShowS
UpdateFirewallRuleGroupAssociationResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateFirewallRuleGroupAssociationResponse] -> ShowS
$cshowList :: [UpdateFirewallRuleGroupAssociationResponse] -> ShowS
show :: UpdateFirewallRuleGroupAssociationResponse -> String
$cshow :: UpdateFirewallRuleGroupAssociationResponse -> String
showsPrec :: Int -> UpdateFirewallRuleGroupAssociationResponse -> ShowS
$cshowsPrec :: Int -> UpdateFirewallRuleGroupAssociationResponse -> ShowS
Prelude.Show, forall x.
Rep UpdateFirewallRuleGroupAssociationResponse x
-> UpdateFirewallRuleGroupAssociationResponse
forall x.
UpdateFirewallRuleGroupAssociationResponse
-> Rep UpdateFirewallRuleGroupAssociationResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateFirewallRuleGroupAssociationResponse x
-> UpdateFirewallRuleGroupAssociationResponse
$cfrom :: forall x.
UpdateFirewallRuleGroupAssociationResponse
-> Rep UpdateFirewallRuleGroupAssociationResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateFirewallRuleGroupAssociationResponse' 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:
--
-- 'firewallRuleGroupAssociation', 'updateFirewallRuleGroupAssociationResponse_firewallRuleGroupAssociation' - The association that you just updated.
--
-- 'httpStatus', 'updateFirewallRuleGroupAssociationResponse_httpStatus' - The response's http status code.
newUpdateFirewallRuleGroupAssociationResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateFirewallRuleGroupAssociationResponse
newUpdateFirewallRuleGroupAssociationResponse :: Int -> UpdateFirewallRuleGroupAssociationResponse
newUpdateFirewallRuleGroupAssociationResponse
  Int
pHttpStatus_ =
    UpdateFirewallRuleGroupAssociationResponse'
      { $sel:firewallRuleGroupAssociation:UpdateFirewallRuleGroupAssociationResponse' :: Maybe FirewallRuleGroupAssociation
firewallRuleGroupAssociation =
          forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:UpdateFirewallRuleGroupAssociationResponse' :: Int
httpStatus = Int
pHttpStatus_
      }

-- | The association that you just updated.
updateFirewallRuleGroupAssociationResponse_firewallRuleGroupAssociation :: Lens.Lens' UpdateFirewallRuleGroupAssociationResponse (Prelude.Maybe FirewallRuleGroupAssociation)
updateFirewallRuleGroupAssociationResponse_firewallRuleGroupAssociation :: Lens'
  UpdateFirewallRuleGroupAssociationResponse
  (Maybe FirewallRuleGroupAssociation)
updateFirewallRuleGroupAssociationResponse_firewallRuleGroupAssociation = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateFirewallRuleGroupAssociationResponse' {Maybe FirewallRuleGroupAssociation
firewallRuleGroupAssociation :: Maybe FirewallRuleGroupAssociation
$sel:firewallRuleGroupAssociation:UpdateFirewallRuleGroupAssociationResponse' :: UpdateFirewallRuleGroupAssociationResponse
-> Maybe FirewallRuleGroupAssociation
firewallRuleGroupAssociation} -> Maybe FirewallRuleGroupAssociation
firewallRuleGroupAssociation) (\s :: UpdateFirewallRuleGroupAssociationResponse
s@UpdateFirewallRuleGroupAssociationResponse' {} Maybe FirewallRuleGroupAssociation
a -> UpdateFirewallRuleGroupAssociationResponse
s {$sel:firewallRuleGroupAssociation:UpdateFirewallRuleGroupAssociationResponse' :: Maybe FirewallRuleGroupAssociation
firewallRuleGroupAssociation = Maybe FirewallRuleGroupAssociation
a} :: UpdateFirewallRuleGroupAssociationResponse)

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

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