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

    -- * Request Lenses
    deleteRuleGroup_ruleGroupArn,
    deleteRuleGroup_ruleGroupName,
    deleteRuleGroup_type,

    -- * Destructuring the Response
    DeleteRuleGroupResponse (..),
    newDeleteRuleGroupResponse,

    -- * Response Lenses
    deleteRuleGroupResponse_httpStatus,
    deleteRuleGroupResponse_ruleGroupResponse,
  )
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:/ 'newDeleteRuleGroup' smart constructor.
data DeleteRuleGroup = DeleteRuleGroup'
  { -- | The Amazon Resource Name (ARN) of the rule group.
    --
    -- You must specify the ARN or the name, and you can specify both.
    DeleteRuleGroup -> Maybe Text
ruleGroupArn :: Prelude.Maybe Prelude.Text,
    -- | The descriptive name of the rule group. You can\'t change the name of a
    -- rule group after you create it.
    --
    -- You must specify the ARN or the name, and you can specify both.
    DeleteRuleGroup -> Maybe Text
ruleGroupName :: Prelude.Maybe Prelude.Text,
    -- | Indicates whether the rule group is stateless or stateful. If the rule
    -- group is stateless, it contains stateless rules. If it is stateful, it
    -- contains stateful rules.
    --
    -- This setting is required for requests that do not include the
    -- @RuleGroupARN@.
    DeleteRuleGroup -> Maybe RuleGroupType
type' :: Prelude.Maybe RuleGroupType
  }
  deriving (DeleteRuleGroup -> DeleteRuleGroup -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteRuleGroup -> DeleteRuleGroup -> Bool
$c/= :: DeleteRuleGroup -> DeleteRuleGroup -> Bool
== :: DeleteRuleGroup -> DeleteRuleGroup -> Bool
$c== :: DeleteRuleGroup -> DeleteRuleGroup -> Bool
Prelude.Eq, ReadPrec [DeleteRuleGroup]
ReadPrec DeleteRuleGroup
Int -> ReadS DeleteRuleGroup
ReadS [DeleteRuleGroup]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteRuleGroup]
$creadListPrec :: ReadPrec [DeleteRuleGroup]
readPrec :: ReadPrec DeleteRuleGroup
$creadPrec :: ReadPrec DeleteRuleGroup
readList :: ReadS [DeleteRuleGroup]
$creadList :: ReadS [DeleteRuleGroup]
readsPrec :: Int -> ReadS DeleteRuleGroup
$creadsPrec :: Int -> ReadS DeleteRuleGroup
Prelude.Read, Int -> DeleteRuleGroup -> ShowS
[DeleteRuleGroup] -> ShowS
DeleteRuleGroup -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteRuleGroup] -> ShowS
$cshowList :: [DeleteRuleGroup] -> ShowS
show :: DeleteRuleGroup -> String
$cshow :: DeleteRuleGroup -> String
showsPrec :: Int -> DeleteRuleGroup -> ShowS
$cshowsPrec :: Int -> DeleteRuleGroup -> ShowS
Prelude.Show, forall x. Rep DeleteRuleGroup x -> DeleteRuleGroup
forall x. DeleteRuleGroup -> Rep DeleteRuleGroup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteRuleGroup x -> DeleteRuleGroup
$cfrom :: forall x. DeleteRuleGroup -> Rep DeleteRuleGroup x
Prelude.Generic)

-- |
-- Create a value of 'DeleteRuleGroup' 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:
--
-- 'ruleGroupArn', 'deleteRuleGroup_ruleGroupArn' - The Amazon Resource Name (ARN) of the rule group.
--
-- You must specify the ARN or the name, and you can specify both.
--
-- 'ruleGroupName', 'deleteRuleGroup_ruleGroupName' - The descriptive name of the rule group. You can\'t change the name of a
-- rule group after you create it.
--
-- You must specify the ARN or the name, and you can specify both.
--
-- 'type'', 'deleteRuleGroup_type' - Indicates whether the rule group is stateless or stateful. If the rule
-- group is stateless, it contains stateless rules. If it is stateful, it
-- contains stateful rules.
--
-- This setting is required for requests that do not include the
-- @RuleGroupARN@.
newDeleteRuleGroup ::
  DeleteRuleGroup
newDeleteRuleGroup :: DeleteRuleGroup
newDeleteRuleGroup =
  DeleteRuleGroup'
    { $sel:ruleGroupArn:DeleteRuleGroup' :: Maybe Text
ruleGroupArn = forall a. Maybe a
Prelude.Nothing,
      $sel:ruleGroupName:DeleteRuleGroup' :: Maybe Text
ruleGroupName = forall a. Maybe a
Prelude.Nothing,
      $sel:type':DeleteRuleGroup' :: Maybe RuleGroupType
type' = forall a. Maybe a
Prelude.Nothing
    }

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

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

-- | Indicates whether the rule group is stateless or stateful. If the rule
-- group is stateless, it contains stateless rules. If it is stateful, it
-- contains stateful rules.
--
-- This setting is required for requests that do not include the
-- @RuleGroupARN@.
deleteRuleGroup_type :: Lens.Lens' DeleteRuleGroup (Prelude.Maybe RuleGroupType)
deleteRuleGroup_type :: Lens' DeleteRuleGroup (Maybe RuleGroupType)
deleteRuleGroup_type = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteRuleGroup' {Maybe RuleGroupType
type' :: Maybe RuleGroupType
$sel:type':DeleteRuleGroup' :: DeleteRuleGroup -> Maybe RuleGroupType
type'} -> Maybe RuleGroupType
type') (\s :: DeleteRuleGroup
s@DeleteRuleGroup' {} Maybe RuleGroupType
a -> DeleteRuleGroup
s {$sel:type':DeleteRuleGroup' :: Maybe RuleGroupType
type' = Maybe RuleGroupType
a} :: DeleteRuleGroup)

instance Core.AWSRequest DeleteRuleGroup where
  type
    AWSResponse DeleteRuleGroup =
      DeleteRuleGroupResponse
  request :: (Service -> Service) -> DeleteRuleGroup -> Request DeleteRuleGroup
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 DeleteRuleGroup
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DeleteRuleGroup)))
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 ->
          Int -> RuleGroupResponse -> DeleteRuleGroupResponse
DeleteRuleGroupResponse'
            forall (f :: * -> *) a b. Functor 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))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"RuleGroupResponse")
      )

instance Prelude.Hashable DeleteRuleGroup where
  hashWithSalt :: Int -> DeleteRuleGroup -> Int
hashWithSalt Int
_salt DeleteRuleGroup' {Maybe Text
Maybe RuleGroupType
type' :: Maybe RuleGroupType
ruleGroupName :: Maybe Text
ruleGroupArn :: Maybe Text
$sel:type':DeleteRuleGroup' :: DeleteRuleGroup -> Maybe RuleGroupType
$sel:ruleGroupName:DeleteRuleGroup' :: DeleteRuleGroup -> Maybe Text
$sel:ruleGroupArn:DeleteRuleGroup' :: DeleteRuleGroup -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
ruleGroupArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
ruleGroupName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe RuleGroupType
type'

instance Prelude.NFData DeleteRuleGroup where
  rnf :: DeleteRuleGroup -> ()
rnf DeleteRuleGroup' {Maybe Text
Maybe RuleGroupType
type' :: Maybe RuleGroupType
ruleGroupName :: Maybe Text
ruleGroupArn :: Maybe Text
$sel:type':DeleteRuleGroup' :: DeleteRuleGroup -> Maybe RuleGroupType
$sel:ruleGroupName:DeleteRuleGroup' :: DeleteRuleGroup -> Maybe Text
$sel:ruleGroupArn:DeleteRuleGroup' :: DeleteRuleGroup -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
ruleGroupArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
ruleGroupName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe RuleGroupType
type'

instance Data.ToHeaders DeleteRuleGroup where
  toHeaders :: DeleteRuleGroup -> 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.DeleteRuleGroup" ::
                          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 DeleteRuleGroup where
  toJSON :: DeleteRuleGroup -> Value
toJSON DeleteRuleGroup' {Maybe Text
Maybe RuleGroupType
type' :: Maybe RuleGroupType
ruleGroupName :: Maybe Text
ruleGroupArn :: Maybe Text
$sel:type':DeleteRuleGroup' :: DeleteRuleGroup -> Maybe RuleGroupType
$sel:ruleGroupName:DeleteRuleGroup' :: DeleteRuleGroup -> Maybe Text
$sel:ruleGroupArn:DeleteRuleGroup' :: DeleteRuleGroup -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"RuleGroupArn" 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
ruleGroupArn,
            (Key
"RuleGroupName" 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
ruleGroupName,
            (Key
"Type" 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 RuleGroupType
type'
          ]
      )

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

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

-- | /See:/ 'newDeleteRuleGroupResponse' smart constructor.
data DeleteRuleGroupResponse = DeleteRuleGroupResponse'
  { -- | The response's http status code.
    DeleteRuleGroupResponse -> Int
httpStatus :: Prelude.Int,
    -- | The high-level properties of a rule group. This, along with the
    -- RuleGroup, define the rule group. You can retrieve all objects for a
    -- rule group by calling DescribeRuleGroup.
    DeleteRuleGroupResponse -> RuleGroupResponse
ruleGroupResponse :: RuleGroupResponse
  }
  deriving (DeleteRuleGroupResponse -> DeleteRuleGroupResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteRuleGroupResponse -> DeleteRuleGroupResponse -> Bool
$c/= :: DeleteRuleGroupResponse -> DeleteRuleGroupResponse -> Bool
== :: DeleteRuleGroupResponse -> DeleteRuleGroupResponse -> Bool
$c== :: DeleteRuleGroupResponse -> DeleteRuleGroupResponse -> Bool
Prelude.Eq, ReadPrec [DeleteRuleGroupResponse]
ReadPrec DeleteRuleGroupResponse
Int -> ReadS DeleteRuleGroupResponse
ReadS [DeleteRuleGroupResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteRuleGroupResponse]
$creadListPrec :: ReadPrec [DeleteRuleGroupResponse]
readPrec :: ReadPrec DeleteRuleGroupResponse
$creadPrec :: ReadPrec DeleteRuleGroupResponse
readList :: ReadS [DeleteRuleGroupResponse]
$creadList :: ReadS [DeleteRuleGroupResponse]
readsPrec :: Int -> ReadS DeleteRuleGroupResponse
$creadsPrec :: Int -> ReadS DeleteRuleGroupResponse
Prelude.Read, Int -> DeleteRuleGroupResponse -> ShowS
[DeleteRuleGroupResponse] -> ShowS
DeleteRuleGroupResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteRuleGroupResponse] -> ShowS
$cshowList :: [DeleteRuleGroupResponse] -> ShowS
show :: DeleteRuleGroupResponse -> String
$cshow :: DeleteRuleGroupResponse -> String
showsPrec :: Int -> DeleteRuleGroupResponse -> ShowS
$cshowsPrec :: Int -> DeleteRuleGroupResponse -> ShowS
Prelude.Show, forall x. Rep DeleteRuleGroupResponse x -> DeleteRuleGroupResponse
forall x. DeleteRuleGroupResponse -> Rep DeleteRuleGroupResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteRuleGroupResponse x -> DeleteRuleGroupResponse
$cfrom :: forall x. DeleteRuleGroupResponse -> Rep DeleteRuleGroupResponse x
Prelude.Generic)

-- |
-- Create a value of 'DeleteRuleGroupResponse' 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:
--
-- 'httpStatus', 'deleteRuleGroupResponse_httpStatus' - The response's http status code.
--
-- 'ruleGroupResponse', 'deleteRuleGroupResponse_ruleGroupResponse' - The high-level properties of a rule group. This, along with the
-- RuleGroup, define the rule group. You can retrieve all objects for a
-- rule group by calling DescribeRuleGroup.
newDeleteRuleGroupResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'ruleGroupResponse'
  RuleGroupResponse ->
  DeleteRuleGroupResponse
newDeleteRuleGroupResponse :: Int -> RuleGroupResponse -> DeleteRuleGroupResponse
newDeleteRuleGroupResponse
  Int
pHttpStatus_
  RuleGroupResponse
pRuleGroupResponse_ =
    DeleteRuleGroupResponse'
      { $sel:httpStatus:DeleteRuleGroupResponse' :: Int
httpStatus = Int
pHttpStatus_,
        $sel:ruleGroupResponse:DeleteRuleGroupResponse' :: RuleGroupResponse
ruleGroupResponse = RuleGroupResponse
pRuleGroupResponse_
      }

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

-- | The high-level properties of a rule group. This, along with the
-- RuleGroup, define the rule group. You can retrieve all objects for a
-- rule group by calling DescribeRuleGroup.
deleteRuleGroupResponse_ruleGroupResponse :: Lens.Lens' DeleteRuleGroupResponse RuleGroupResponse
deleteRuleGroupResponse_ruleGroupResponse :: Lens' DeleteRuleGroupResponse RuleGroupResponse
deleteRuleGroupResponse_ruleGroupResponse = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteRuleGroupResponse' {RuleGroupResponse
ruleGroupResponse :: RuleGroupResponse
$sel:ruleGroupResponse:DeleteRuleGroupResponse' :: DeleteRuleGroupResponse -> RuleGroupResponse
ruleGroupResponse} -> RuleGroupResponse
ruleGroupResponse) (\s :: DeleteRuleGroupResponse
s@DeleteRuleGroupResponse' {} RuleGroupResponse
a -> DeleteRuleGroupResponse
s {$sel:ruleGroupResponse:DeleteRuleGroupResponse' :: RuleGroupResponse
ruleGroupResponse = RuleGroupResponse
a} :: DeleteRuleGroupResponse)

instance Prelude.NFData DeleteRuleGroupResponse where
  rnf :: DeleteRuleGroupResponse -> ()
rnf DeleteRuleGroupResponse' {Int
RuleGroupResponse
ruleGroupResponse :: RuleGroupResponse
httpStatus :: Int
$sel:ruleGroupResponse:DeleteRuleGroupResponse' :: DeleteRuleGroupResponse -> RuleGroupResponse
$sel:httpStatus:DeleteRuleGroupResponse' :: DeleteRuleGroupResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf RuleGroupResponse
ruleGroupResponse