{-# 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.DisassociateFirewallRuleGroup
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Disassociates a FirewallRuleGroup from a VPC, to remove DNS filtering
-- from the VPC.
module Amazonka.Route53Resolver.DisassociateFirewallRuleGroup
  ( -- * Creating a Request
    DisassociateFirewallRuleGroup (..),
    newDisassociateFirewallRuleGroup,

    -- * Request Lenses
    disassociateFirewallRuleGroup_firewallRuleGroupAssociationId,

    -- * Destructuring the Response
    DisassociateFirewallRuleGroupResponse (..),
    newDisassociateFirewallRuleGroupResponse,

    -- * Response Lenses
    disassociateFirewallRuleGroupResponse_firewallRuleGroupAssociation,
    disassociateFirewallRuleGroupResponse_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:/ 'newDisassociateFirewallRuleGroup' smart constructor.
data DisassociateFirewallRuleGroup = DisassociateFirewallRuleGroup'
  { -- | The identifier of the FirewallRuleGroupAssociation.
    DisassociateFirewallRuleGroup -> Text
firewallRuleGroupAssociationId :: Prelude.Text
  }
  deriving (DisassociateFirewallRuleGroup
-> DisassociateFirewallRuleGroup -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DisassociateFirewallRuleGroup
-> DisassociateFirewallRuleGroup -> Bool
$c/= :: DisassociateFirewallRuleGroup
-> DisassociateFirewallRuleGroup -> Bool
== :: DisassociateFirewallRuleGroup
-> DisassociateFirewallRuleGroup -> Bool
$c== :: DisassociateFirewallRuleGroup
-> DisassociateFirewallRuleGroup -> Bool
Prelude.Eq, ReadPrec [DisassociateFirewallRuleGroup]
ReadPrec DisassociateFirewallRuleGroup
Int -> ReadS DisassociateFirewallRuleGroup
ReadS [DisassociateFirewallRuleGroup]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DisassociateFirewallRuleGroup]
$creadListPrec :: ReadPrec [DisassociateFirewallRuleGroup]
readPrec :: ReadPrec DisassociateFirewallRuleGroup
$creadPrec :: ReadPrec DisassociateFirewallRuleGroup
readList :: ReadS [DisassociateFirewallRuleGroup]
$creadList :: ReadS [DisassociateFirewallRuleGroup]
readsPrec :: Int -> ReadS DisassociateFirewallRuleGroup
$creadsPrec :: Int -> ReadS DisassociateFirewallRuleGroup
Prelude.Read, Int -> DisassociateFirewallRuleGroup -> ShowS
[DisassociateFirewallRuleGroup] -> ShowS
DisassociateFirewallRuleGroup -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DisassociateFirewallRuleGroup] -> ShowS
$cshowList :: [DisassociateFirewallRuleGroup] -> ShowS
show :: DisassociateFirewallRuleGroup -> String
$cshow :: DisassociateFirewallRuleGroup -> String
showsPrec :: Int -> DisassociateFirewallRuleGroup -> ShowS
$cshowsPrec :: Int -> DisassociateFirewallRuleGroup -> ShowS
Prelude.Show, forall x.
Rep DisassociateFirewallRuleGroup x
-> DisassociateFirewallRuleGroup
forall x.
DisassociateFirewallRuleGroup
-> Rep DisassociateFirewallRuleGroup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DisassociateFirewallRuleGroup x
-> DisassociateFirewallRuleGroup
$cfrom :: forall x.
DisassociateFirewallRuleGroup
-> Rep DisassociateFirewallRuleGroup x
Prelude.Generic)

-- |
-- Create a value of 'DisassociateFirewallRuleGroup' 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:
--
-- 'firewallRuleGroupAssociationId', 'disassociateFirewallRuleGroup_firewallRuleGroupAssociationId' - The identifier of the FirewallRuleGroupAssociation.
newDisassociateFirewallRuleGroup ::
  -- | 'firewallRuleGroupAssociationId'
  Prelude.Text ->
  DisassociateFirewallRuleGroup
newDisassociateFirewallRuleGroup :: Text -> DisassociateFirewallRuleGroup
newDisassociateFirewallRuleGroup
  Text
pFirewallRuleGroupAssociationId_ =
    DisassociateFirewallRuleGroup'
      { $sel:firewallRuleGroupAssociationId:DisassociateFirewallRuleGroup' :: Text
firewallRuleGroupAssociationId =
          Text
pFirewallRuleGroupAssociationId_
      }

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

instance
  Core.AWSRequest
    DisassociateFirewallRuleGroup
  where
  type
    AWSResponse DisassociateFirewallRuleGroup =
      DisassociateFirewallRuleGroupResponse
  request :: (Service -> Service)
-> DisassociateFirewallRuleGroup
-> Request DisassociateFirewallRuleGroup
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 DisassociateFirewallRuleGroup
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DisassociateFirewallRuleGroup)))
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 -> DisassociateFirewallRuleGroupResponse
DisassociateFirewallRuleGroupResponse'
            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
    DisassociateFirewallRuleGroup
  where
  hashWithSalt :: Int -> DisassociateFirewallRuleGroup -> Int
hashWithSalt Int
_salt DisassociateFirewallRuleGroup' {Text
firewallRuleGroupAssociationId :: Text
$sel:firewallRuleGroupAssociationId:DisassociateFirewallRuleGroup' :: DisassociateFirewallRuleGroup -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
firewallRuleGroupAssociationId

instance Prelude.NFData DisassociateFirewallRuleGroup where
  rnf :: DisassociateFirewallRuleGroup -> ()
rnf DisassociateFirewallRuleGroup' {Text
firewallRuleGroupAssociationId :: Text
$sel:firewallRuleGroupAssociationId:DisassociateFirewallRuleGroup' :: DisassociateFirewallRuleGroup -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
firewallRuleGroupAssociationId

instance Data.ToHeaders DisassociateFirewallRuleGroup where
  toHeaders :: DisassociateFirewallRuleGroup -> 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.DisassociateFirewallRuleGroup" ::
                          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 DisassociateFirewallRuleGroup where
  toJSON :: DisassociateFirewallRuleGroup -> Value
toJSON DisassociateFirewallRuleGroup' {Text
firewallRuleGroupAssociationId :: Text
$sel:firewallRuleGroupAssociationId:DisassociateFirewallRuleGroup' :: DisassociateFirewallRuleGroup -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ 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 DisassociateFirewallRuleGroup where
  toPath :: DisassociateFirewallRuleGroup -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

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

-- |
-- Create a value of 'DisassociateFirewallRuleGroupResponse' 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', 'disassociateFirewallRuleGroupResponse_firewallRuleGroupAssociation' - The firewall rule group association that you just removed.
--
-- 'httpStatus', 'disassociateFirewallRuleGroupResponse_httpStatus' - The response's http status code.
newDisassociateFirewallRuleGroupResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DisassociateFirewallRuleGroupResponse
newDisassociateFirewallRuleGroupResponse :: Int -> DisassociateFirewallRuleGroupResponse
newDisassociateFirewallRuleGroupResponse Int
pHttpStatus_ =
  DisassociateFirewallRuleGroupResponse'
    { $sel:firewallRuleGroupAssociation:DisassociateFirewallRuleGroupResponse' :: Maybe FirewallRuleGroupAssociation
firewallRuleGroupAssociation =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DisassociateFirewallRuleGroupResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The firewall rule group association that you just removed.
disassociateFirewallRuleGroupResponse_firewallRuleGroupAssociation :: Lens.Lens' DisassociateFirewallRuleGroupResponse (Prelude.Maybe FirewallRuleGroupAssociation)
disassociateFirewallRuleGroupResponse_firewallRuleGroupAssociation :: Lens'
  DisassociateFirewallRuleGroupResponse
  (Maybe FirewallRuleGroupAssociation)
disassociateFirewallRuleGroupResponse_firewallRuleGroupAssociation = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DisassociateFirewallRuleGroupResponse' {Maybe FirewallRuleGroupAssociation
firewallRuleGroupAssociation :: Maybe FirewallRuleGroupAssociation
$sel:firewallRuleGroupAssociation:DisassociateFirewallRuleGroupResponse' :: DisassociateFirewallRuleGroupResponse
-> Maybe FirewallRuleGroupAssociation
firewallRuleGroupAssociation} -> Maybe FirewallRuleGroupAssociation
firewallRuleGroupAssociation) (\s :: DisassociateFirewallRuleGroupResponse
s@DisassociateFirewallRuleGroupResponse' {} Maybe FirewallRuleGroupAssociation
a -> DisassociateFirewallRuleGroupResponse
s {$sel:firewallRuleGroupAssociation:DisassociateFirewallRuleGroupResponse' :: Maybe FirewallRuleGroupAssociation
firewallRuleGroupAssociation = Maybe FirewallRuleGroupAssociation
a} :: DisassociateFirewallRuleGroupResponse)

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

instance
  Prelude.NFData
    DisassociateFirewallRuleGroupResponse
  where
  rnf :: DisassociateFirewallRuleGroupResponse -> ()
rnf DisassociateFirewallRuleGroupResponse' {Int
Maybe FirewallRuleGroupAssociation
httpStatus :: Int
firewallRuleGroupAssociation :: Maybe FirewallRuleGroupAssociation
$sel:httpStatus:DisassociateFirewallRuleGroupResponse' :: DisassociateFirewallRuleGroupResponse -> Int
$sel:firewallRuleGroupAssociation:DisassociateFirewallRuleGroupResponse' :: DisassociateFirewallRuleGroupResponse
-> 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