{-# 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.DescribeRuleGroup
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Returns the data objects for the specified rule group.
module Amazonka.NetworkFirewall.DescribeRuleGroup
  ( -- * Creating a Request
    DescribeRuleGroup (..),
    newDescribeRuleGroup,

    -- * Request Lenses
    describeRuleGroup_ruleGroupArn,
    describeRuleGroup_ruleGroupName,
    describeRuleGroup_type,

    -- * Destructuring the Response
    DescribeRuleGroupResponse (..),
    newDescribeRuleGroupResponse,

    -- * Response Lenses
    describeRuleGroupResponse_ruleGroup,
    describeRuleGroupResponse_httpStatus,
    describeRuleGroupResponse_updateToken,
    describeRuleGroupResponse_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:/ 'newDescribeRuleGroup' smart constructor.
data DescribeRuleGroup = DescribeRuleGroup'
  { -- | The Amazon Resource Name (ARN) of the rule group.
    --
    -- You must specify the ARN or the name, and you can specify both.
    DescribeRuleGroup -> 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.
    DescribeRuleGroup -> 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@.
    DescribeRuleGroup -> Maybe RuleGroupType
type' :: Prelude.Maybe RuleGroupType
  }
  deriving (DescribeRuleGroup -> DescribeRuleGroup -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeRuleGroup -> DescribeRuleGroup -> Bool
$c/= :: DescribeRuleGroup -> DescribeRuleGroup -> Bool
== :: DescribeRuleGroup -> DescribeRuleGroup -> Bool
$c== :: DescribeRuleGroup -> DescribeRuleGroup -> Bool
Prelude.Eq, ReadPrec [DescribeRuleGroup]
ReadPrec DescribeRuleGroup
Int -> ReadS DescribeRuleGroup
ReadS [DescribeRuleGroup]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeRuleGroup]
$creadListPrec :: ReadPrec [DescribeRuleGroup]
readPrec :: ReadPrec DescribeRuleGroup
$creadPrec :: ReadPrec DescribeRuleGroup
readList :: ReadS [DescribeRuleGroup]
$creadList :: ReadS [DescribeRuleGroup]
readsPrec :: Int -> ReadS DescribeRuleGroup
$creadsPrec :: Int -> ReadS DescribeRuleGroup
Prelude.Read, Int -> DescribeRuleGroup -> ShowS
[DescribeRuleGroup] -> ShowS
DescribeRuleGroup -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeRuleGroup] -> ShowS
$cshowList :: [DescribeRuleGroup] -> ShowS
show :: DescribeRuleGroup -> String
$cshow :: DescribeRuleGroup -> String
showsPrec :: Int -> DescribeRuleGroup -> ShowS
$cshowsPrec :: Int -> DescribeRuleGroup -> ShowS
Prelude.Show, forall x. Rep DescribeRuleGroup x -> DescribeRuleGroup
forall x. DescribeRuleGroup -> Rep DescribeRuleGroup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeRuleGroup x -> DescribeRuleGroup
$cfrom :: forall x. DescribeRuleGroup -> Rep DescribeRuleGroup x
Prelude.Generic)

-- |
-- Create a value of 'DescribeRuleGroup' 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', 'describeRuleGroup_ruleGroupArn' - The Amazon Resource Name (ARN) of the rule group.
--
-- You must specify the ARN or the name, and you can specify both.
--
-- 'ruleGroupName', 'describeRuleGroup_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'', 'describeRuleGroup_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@.
newDescribeRuleGroup ::
  DescribeRuleGroup
newDescribeRuleGroup :: DescribeRuleGroup
newDescribeRuleGroup =
  DescribeRuleGroup'
    { $sel:ruleGroupArn:DescribeRuleGroup' :: Maybe Text
ruleGroupArn = forall a. Maybe a
Prelude.Nothing,
      $sel:ruleGroupName:DescribeRuleGroup' :: Maybe Text
ruleGroupName = forall a. Maybe a
Prelude.Nothing,
      $sel:type':DescribeRuleGroup' :: 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.
describeRuleGroup_ruleGroupArn :: Lens.Lens' DescribeRuleGroup (Prelude.Maybe Prelude.Text)
describeRuleGroup_ruleGroupArn :: Lens' DescribeRuleGroup (Maybe Text)
describeRuleGroup_ruleGroupArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeRuleGroup' {Maybe Text
ruleGroupArn :: Maybe Text
$sel:ruleGroupArn:DescribeRuleGroup' :: DescribeRuleGroup -> Maybe Text
ruleGroupArn} -> Maybe Text
ruleGroupArn) (\s :: DescribeRuleGroup
s@DescribeRuleGroup' {} Maybe Text
a -> DescribeRuleGroup
s {$sel:ruleGroupArn:DescribeRuleGroup' :: Maybe Text
ruleGroupArn = Maybe Text
a} :: DescribeRuleGroup)

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

-- | 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@.
describeRuleGroup_type :: Lens.Lens' DescribeRuleGroup (Prelude.Maybe RuleGroupType)
describeRuleGroup_type :: Lens' DescribeRuleGroup (Maybe RuleGroupType)
describeRuleGroup_type = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeRuleGroup' {Maybe RuleGroupType
type' :: Maybe RuleGroupType
$sel:type':DescribeRuleGroup' :: DescribeRuleGroup -> Maybe RuleGroupType
type'} -> Maybe RuleGroupType
type') (\s :: DescribeRuleGroup
s@DescribeRuleGroup' {} Maybe RuleGroupType
a -> DescribeRuleGroup
s {$sel:type':DescribeRuleGroup' :: Maybe RuleGroupType
type' = Maybe RuleGroupType
a} :: DescribeRuleGroup)

instance Core.AWSRequest DescribeRuleGroup where
  type
    AWSResponse DescribeRuleGroup =
      DescribeRuleGroupResponse
  request :: (Service -> Service)
-> DescribeRuleGroup -> Request DescribeRuleGroup
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 DescribeRuleGroup
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeRuleGroup)))
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 RuleGroup
-> Int -> Text -> RuleGroupResponse -> DescribeRuleGroupResponse
DescribeRuleGroupResponse'
            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
"RuleGroup")
            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))
            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
"UpdateToken")
            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 DescribeRuleGroup where
  hashWithSalt :: Int -> DescribeRuleGroup -> Int
hashWithSalt Int
_salt DescribeRuleGroup' {Maybe Text
Maybe RuleGroupType
type' :: Maybe RuleGroupType
ruleGroupName :: Maybe Text
ruleGroupArn :: Maybe Text
$sel:type':DescribeRuleGroup' :: DescribeRuleGroup -> Maybe RuleGroupType
$sel:ruleGroupName:DescribeRuleGroup' :: DescribeRuleGroup -> Maybe Text
$sel:ruleGroupArn:DescribeRuleGroup' :: DescribeRuleGroup -> 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 DescribeRuleGroup where
  rnf :: DescribeRuleGroup -> ()
rnf DescribeRuleGroup' {Maybe Text
Maybe RuleGroupType
type' :: Maybe RuleGroupType
ruleGroupName :: Maybe Text
ruleGroupArn :: Maybe Text
$sel:type':DescribeRuleGroup' :: DescribeRuleGroup -> Maybe RuleGroupType
$sel:ruleGroupName:DescribeRuleGroup' :: DescribeRuleGroup -> Maybe Text
$sel:ruleGroupArn:DescribeRuleGroup' :: DescribeRuleGroup -> 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 DescribeRuleGroup where
  toHeaders :: DescribeRuleGroup -> 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.DescribeRuleGroup" ::
                          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 DescribeRuleGroup where
  toJSON :: DescribeRuleGroup -> Value
toJSON DescribeRuleGroup' {Maybe Text
Maybe RuleGroupType
type' :: Maybe RuleGroupType
ruleGroupName :: Maybe Text
ruleGroupArn :: Maybe Text
$sel:type':DescribeRuleGroup' :: DescribeRuleGroup -> Maybe RuleGroupType
$sel:ruleGroupName:DescribeRuleGroup' :: DescribeRuleGroup -> Maybe Text
$sel:ruleGroupArn:DescribeRuleGroup' :: DescribeRuleGroup -> 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 DescribeRuleGroup where
  toPath :: DescribeRuleGroup -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

-- | /See:/ 'newDescribeRuleGroupResponse' smart constructor.
data DescribeRuleGroupResponse = DescribeRuleGroupResponse'
  { -- | The object that defines the rules in a rule group. This, along with
    -- RuleGroupResponse, define the rule group. You can retrieve all objects
    -- for a rule group by calling DescribeRuleGroup.
    --
    -- Network Firewall uses a rule group to inspect and control network
    -- traffic. You define stateless rule groups to inspect individual packets
    -- and you define stateful rule groups to inspect packets in the context of
    -- their traffic flow.
    --
    -- To use a rule group, you include it by reference in an Network Firewall
    -- firewall policy, then you use the policy in a firewall. You can
    -- reference a rule group from more than one firewall policy, and you can
    -- use a firewall policy in more than one firewall.
    DescribeRuleGroupResponse -> Maybe RuleGroup
ruleGroup :: Prelude.Maybe RuleGroup,
    -- | The response's http status code.
    DescribeRuleGroupResponse -> Int
httpStatus :: Prelude.Int,
    -- | A token used for optimistic locking. Network Firewall returns a token to
    -- your requests that access the rule group. The token marks the state of
    -- the rule group resource at the time of the request.
    --
    -- To make changes to the rule group, you provide the token in your
    -- request. Network Firewall uses the token to ensure that the rule group
    -- hasn\'t changed since you last retrieved it. If it has changed, the
    -- operation fails with an @InvalidTokenException@. If this happens,
    -- retrieve the rule group again to get a current copy of it with a current
    -- token. Reapply your changes as needed, then try the operation again
    -- using the new token.
    DescribeRuleGroupResponse -> Text
updateToken :: Prelude.Text,
    -- | 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.
    DescribeRuleGroupResponse -> RuleGroupResponse
ruleGroupResponse :: RuleGroupResponse
  }
  deriving (DescribeRuleGroupResponse -> DescribeRuleGroupResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeRuleGroupResponse -> DescribeRuleGroupResponse -> Bool
$c/= :: DescribeRuleGroupResponse -> DescribeRuleGroupResponse -> Bool
== :: DescribeRuleGroupResponse -> DescribeRuleGroupResponse -> Bool
$c== :: DescribeRuleGroupResponse -> DescribeRuleGroupResponse -> Bool
Prelude.Eq, ReadPrec [DescribeRuleGroupResponse]
ReadPrec DescribeRuleGroupResponse
Int -> ReadS DescribeRuleGroupResponse
ReadS [DescribeRuleGroupResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeRuleGroupResponse]
$creadListPrec :: ReadPrec [DescribeRuleGroupResponse]
readPrec :: ReadPrec DescribeRuleGroupResponse
$creadPrec :: ReadPrec DescribeRuleGroupResponse
readList :: ReadS [DescribeRuleGroupResponse]
$creadList :: ReadS [DescribeRuleGroupResponse]
readsPrec :: Int -> ReadS DescribeRuleGroupResponse
$creadsPrec :: Int -> ReadS DescribeRuleGroupResponse
Prelude.Read, Int -> DescribeRuleGroupResponse -> ShowS
[DescribeRuleGroupResponse] -> ShowS
DescribeRuleGroupResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeRuleGroupResponse] -> ShowS
$cshowList :: [DescribeRuleGroupResponse] -> ShowS
show :: DescribeRuleGroupResponse -> String
$cshow :: DescribeRuleGroupResponse -> String
showsPrec :: Int -> DescribeRuleGroupResponse -> ShowS
$cshowsPrec :: Int -> DescribeRuleGroupResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeRuleGroupResponse x -> DescribeRuleGroupResponse
forall x.
DescribeRuleGroupResponse -> Rep DescribeRuleGroupResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeRuleGroupResponse x -> DescribeRuleGroupResponse
$cfrom :: forall x.
DescribeRuleGroupResponse -> Rep DescribeRuleGroupResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeRuleGroupResponse' 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:
--
-- 'ruleGroup', 'describeRuleGroupResponse_ruleGroup' - The object that defines the rules in a rule group. This, along with
-- RuleGroupResponse, define the rule group. You can retrieve all objects
-- for a rule group by calling DescribeRuleGroup.
--
-- Network Firewall uses a rule group to inspect and control network
-- traffic. You define stateless rule groups to inspect individual packets
-- and you define stateful rule groups to inspect packets in the context of
-- their traffic flow.
--
-- To use a rule group, you include it by reference in an Network Firewall
-- firewall policy, then you use the policy in a firewall. You can
-- reference a rule group from more than one firewall policy, and you can
-- use a firewall policy in more than one firewall.
--
-- 'httpStatus', 'describeRuleGroupResponse_httpStatus' - The response's http status code.
--
-- 'updateToken', 'describeRuleGroupResponse_updateToken' - A token used for optimistic locking. Network Firewall returns a token to
-- your requests that access the rule group. The token marks the state of
-- the rule group resource at the time of the request.
--
-- To make changes to the rule group, you provide the token in your
-- request. Network Firewall uses the token to ensure that the rule group
-- hasn\'t changed since you last retrieved it. If it has changed, the
-- operation fails with an @InvalidTokenException@. If this happens,
-- retrieve the rule group again to get a current copy of it with a current
-- token. Reapply your changes as needed, then try the operation again
-- using the new token.
--
-- 'ruleGroupResponse', 'describeRuleGroupResponse_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.
newDescribeRuleGroupResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'updateToken'
  Prelude.Text ->
  -- | 'ruleGroupResponse'
  RuleGroupResponse ->
  DescribeRuleGroupResponse
newDescribeRuleGroupResponse :: Int -> Text -> RuleGroupResponse -> DescribeRuleGroupResponse
newDescribeRuleGroupResponse
  Int
pHttpStatus_
  Text
pUpdateToken_
  RuleGroupResponse
pRuleGroupResponse_ =
    DescribeRuleGroupResponse'
      { $sel:ruleGroup:DescribeRuleGroupResponse' :: Maybe RuleGroup
ruleGroup =
          forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:DescribeRuleGroupResponse' :: Int
httpStatus = Int
pHttpStatus_,
        $sel:updateToken:DescribeRuleGroupResponse' :: Text
updateToken = Text
pUpdateToken_,
        $sel:ruleGroupResponse:DescribeRuleGroupResponse' :: RuleGroupResponse
ruleGroupResponse = RuleGroupResponse
pRuleGroupResponse_
      }

-- | The object that defines the rules in a rule group. This, along with
-- RuleGroupResponse, define the rule group. You can retrieve all objects
-- for a rule group by calling DescribeRuleGroup.
--
-- Network Firewall uses a rule group to inspect and control network
-- traffic. You define stateless rule groups to inspect individual packets
-- and you define stateful rule groups to inspect packets in the context of
-- their traffic flow.
--
-- To use a rule group, you include it by reference in an Network Firewall
-- firewall policy, then you use the policy in a firewall. You can
-- reference a rule group from more than one firewall policy, and you can
-- use a firewall policy in more than one firewall.
describeRuleGroupResponse_ruleGroup :: Lens.Lens' DescribeRuleGroupResponse (Prelude.Maybe RuleGroup)
describeRuleGroupResponse_ruleGroup :: Lens' DescribeRuleGroupResponse (Maybe RuleGroup)
describeRuleGroupResponse_ruleGroup = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeRuleGroupResponse' {Maybe RuleGroup
ruleGroup :: Maybe RuleGroup
$sel:ruleGroup:DescribeRuleGroupResponse' :: DescribeRuleGroupResponse -> Maybe RuleGroup
ruleGroup} -> Maybe RuleGroup
ruleGroup) (\s :: DescribeRuleGroupResponse
s@DescribeRuleGroupResponse' {} Maybe RuleGroup
a -> DescribeRuleGroupResponse
s {$sel:ruleGroup:DescribeRuleGroupResponse' :: Maybe RuleGroup
ruleGroup = Maybe RuleGroup
a} :: DescribeRuleGroupResponse)

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

-- | A token used for optimistic locking. Network Firewall returns a token to
-- your requests that access the rule group. The token marks the state of
-- the rule group resource at the time of the request.
--
-- To make changes to the rule group, you provide the token in your
-- request. Network Firewall uses the token to ensure that the rule group
-- hasn\'t changed since you last retrieved it. If it has changed, the
-- operation fails with an @InvalidTokenException@. If this happens,
-- retrieve the rule group again to get a current copy of it with a current
-- token. Reapply your changes as needed, then try the operation again
-- using the new token.
describeRuleGroupResponse_updateToken :: Lens.Lens' DescribeRuleGroupResponse Prelude.Text
describeRuleGroupResponse_updateToken :: Lens' DescribeRuleGroupResponse Text
describeRuleGroupResponse_updateToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeRuleGroupResponse' {Text
updateToken :: Text
$sel:updateToken:DescribeRuleGroupResponse' :: DescribeRuleGroupResponse -> Text
updateToken} -> Text
updateToken) (\s :: DescribeRuleGroupResponse
s@DescribeRuleGroupResponse' {} Text
a -> DescribeRuleGroupResponse
s {$sel:updateToken:DescribeRuleGroupResponse' :: Text
updateToken = Text
a} :: DescribeRuleGroupResponse)

-- | 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.
describeRuleGroupResponse_ruleGroupResponse :: Lens.Lens' DescribeRuleGroupResponse RuleGroupResponse
describeRuleGroupResponse_ruleGroupResponse :: Lens' DescribeRuleGroupResponse RuleGroupResponse
describeRuleGroupResponse_ruleGroupResponse = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeRuleGroupResponse' {RuleGroupResponse
ruleGroupResponse :: RuleGroupResponse
$sel:ruleGroupResponse:DescribeRuleGroupResponse' :: DescribeRuleGroupResponse -> RuleGroupResponse
ruleGroupResponse} -> RuleGroupResponse
ruleGroupResponse) (\s :: DescribeRuleGroupResponse
s@DescribeRuleGroupResponse' {} RuleGroupResponse
a -> DescribeRuleGroupResponse
s {$sel:ruleGroupResponse:DescribeRuleGroupResponse' :: RuleGroupResponse
ruleGroupResponse = RuleGroupResponse
a} :: DescribeRuleGroupResponse)

instance Prelude.NFData DescribeRuleGroupResponse where
  rnf :: DescribeRuleGroupResponse -> ()
rnf DescribeRuleGroupResponse' {Int
Maybe RuleGroup
Text
RuleGroupResponse
ruleGroupResponse :: RuleGroupResponse
updateToken :: Text
httpStatus :: Int
ruleGroup :: Maybe RuleGroup
$sel:ruleGroupResponse:DescribeRuleGroupResponse' :: DescribeRuleGroupResponse -> RuleGroupResponse
$sel:updateToken:DescribeRuleGroupResponse' :: DescribeRuleGroupResponse -> Text
$sel:httpStatus:DescribeRuleGroupResponse' :: DescribeRuleGroupResponse -> Int
$sel:ruleGroup:DescribeRuleGroupResponse' :: DescribeRuleGroupResponse -> Maybe RuleGroup
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe RuleGroup
ruleGroup
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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 Text
updateToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf RuleGroupResponse
ruleGroupResponse