{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.FMS.Types.PolicySummary
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.FMS.Types.PolicySummary where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.FMS.Types.SecurityServiceType
import qualified Amazonka.Prelude as Prelude

-- | Details of the Firewall Manager policy.
--
-- /See:/ 'newPolicySummary' smart constructor.
data PolicySummary = PolicySummary'
  { -- | Indicates whether Firewall Manager should automatically remove
    -- protections from resources that leave the policy scope and clean up
    -- resources that Firewall Manager is managing for accounts when those
    -- accounts leave policy scope. For example, Firewall Manager will
    -- disassociate a Firewall Manager managed web ACL from a protected
    -- customer resource when the customer resource leaves policy scope.
    --
    -- By default, Firewall Manager doesn\'t remove protections or delete
    -- Firewall Manager managed resources.
    --
    -- This option is not available for Shield Advanced or WAF Classic
    -- policies.
    PolicySummary -> Maybe Bool
deleteUnusedFMManagedResources :: Prelude.Maybe Prelude.Bool,
    -- | The Amazon Resource Name (ARN) of the specified policy.
    PolicySummary -> Maybe Text
policyArn :: Prelude.Maybe Prelude.Text,
    -- | The ID of the specified policy.
    PolicySummary -> Maybe Text
policyId :: Prelude.Maybe Prelude.Text,
    -- | The name of the specified policy.
    PolicySummary -> Maybe Text
policyName :: Prelude.Maybe Prelude.Text,
    -- | Indicates if the policy should be automatically applied to new
    -- resources.
    PolicySummary -> Maybe Bool
remediationEnabled :: Prelude.Maybe Prelude.Bool,
    -- | The type of resource protected by or in scope of the policy. This is in
    -- the format shown in the
    -- <https://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-template-resource-type-ref.html Amazon Web Services Resource Types Reference>.
    -- For WAF and Shield Advanced, examples include
    -- @AWS::ElasticLoadBalancingV2::LoadBalancer@ and
    -- @AWS::CloudFront::Distribution@. For a security group common policy,
    -- valid values are @AWS::EC2::NetworkInterface@ and @AWS::EC2::Instance@.
    -- For a security group content audit policy, valid values are
    -- @AWS::EC2::SecurityGroup@, @AWS::EC2::NetworkInterface@, and
    -- @AWS::EC2::Instance@. For a security group usage audit policy, the value
    -- is @AWS::EC2::SecurityGroup@. For an Network Firewall policy or DNS
    -- Firewall policy, the value is @AWS::EC2::VPC@.
    PolicySummary -> Maybe Text
resourceType :: Prelude.Maybe Prelude.Text,
    -- | The service that the policy is using to protect the resources. This
    -- specifies the type of policy that is created, either an WAF policy, a
    -- Shield Advanced policy, or a security group policy.
    PolicySummary -> Maybe SecurityServiceType
securityServiceType :: Prelude.Maybe SecurityServiceType
  }
  deriving (PolicySummary -> PolicySummary -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PolicySummary -> PolicySummary -> Bool
$c/= :: PolicySummary -> PolicySummary -> Bool
== :: PolicySummary -> PolicySummary -> Bool
$c== :: PolicySummary -> PolicySummary -> Bool
Prelude.Eq, ReadPrec [PolicySummary]
ReadPrec PolicySummary
Int -> ReadS PolicySummary
ReadS [PolicySummary]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PolicySummary]
$creadListPrec :: ReadPrec [PolicySummary]
readPrec :: ReadPrec PolicySummary
$creadPrec :: ReadPrec PolicySummary
readList :: ReadS [PolicySummary]
$creadList :: ReadS [PolicySummary]
readsPrec :: Int -> ReadS PolicySummary
$creadsPrec :: Int -> ReadS PolicySummary
Prelude.Read, Int -> PolicySummary -> ShowS
[PolicySummary] -> ShowS
PolicySummary -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PolicySummary] -> ShowS
$cshowList :: [PolicySummary] -> ShowS
show :: PolicySummary -> String
$cshow :: PolicySummary -> String
showsPrec :: Int -> PolicySummary -> ShowS
$cshowsPrec :: Int -> PolicySummary -> ShowS
Prelude.Show, forall x. Rep PolicySummary x -> PolicySummary
forall x. PolicySummary -> Rep PolicySummary x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PolicySummary x -> PolicySummary
$cfrom :: forall x. PolicySummary -> Rep PolicySummary x
Prelude.Generic)

-- |
-- Create a value of 'PolicySummary' 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:
--
-- 'deleteUnusedFMManagedResources', 'policySummary_deleteUnusedFMManagedResources' - Indicates whether Firewall Manager should automatically remove
-- protections from resources that leave the policy scope and clean up
-- resources that Firewall Manager is managing for accounts when those
-- accounts leave policy scope. For example, Firewall Manager will
-- disassociate a Firewall Manager managed web ACL from a protected
-- customer resource when the customer resource leaves policy scope.
--
-- By default, Firewall Manager doesn\'t remove protections or delete
-- Firewall Manager managed resources.
--
-- This option is not available for Shield Advanced or WAF Classic
-- policies.
--
-- 'policyArn', 'policySummary_policyArn' - The Amazon Resource Name (ARN) of the specified policy.
--
-- 'policyId', 'policySummary_policyId' - The ID of the specified policy.
--
-- 'policyName', 'policySummary_policyName' - The name of the specified policy.
--
-- 'remediationEnabled', 'policySummary_remediationEnabled' - Indicates if the policy should be automatically applied to new
-- resources.
--
-- 'resourceType', 'policySummary_resourceType' - The type of resource protected by or in scope of the policy. This is in
-- the format shown in the
-- <https://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-template-resource-type-ref.html Amazon Web Services Resource Types Reference>.
-- For WAF and Shield Advanced, examples include
-- @AWS::ElasticLoadBalancingV2::LoadBalancer@ and
-- @AWS::CloudFront::Distribution@. For a security group common policy,
-- valid values are @AWS::EC2::NetworkInterface@ and @AWS::EC2::Instance@.
-- For a security group content audit policy, valid values are
-- @AWS::EC2::SecurityGroup@, @AWS::EC2::NetworkInterface@, and
-- @AWS::EC2::Instance@. For a security group usage audit policy, the value
-- is @AWS::EC2::SecurityGroup@. For an Network Firewall policy or DNS
-- Firewall policy, the value is @AWS::EC2::VPC@.
--
-- 'securityServiceType', 'policySummary_securityServiceType' - The service that the policy is using to protect the resources. This
-- specifies the type of policy that is created, either an WAF policy, a
-- Shield Advanced policy, or a security group policy.
newPolicySummary ::
  PolicySummary
newPolicySummary :: PolicySummary
newPolicySummary =
  PolicySummary'
    { $sel:deleteUnusedFMManagedResources:PolicySummary' :: Maybe Bool
deleteUnusedFMManagedResources =
        forall a. Maybe a
Prelude.Nothing,
      $sel:policyArn:PolicySummary' :: Maybe Text
policyArn = forall a. Maybe a
Prelude.Nothing,
      $sel:policyId:PolicySummary' :: Maybe Text
policyId = forall a. Maybe a
Prelude.Nothing,
      $sel:policyName:PolicySummary' :: Maybe Text
policyName = forall a. Maybe a
Prelude.Nothing,
      $sel:remediationEnabled:PolicySummary' :: Maybe Bool
remediationEnabled = forall a. Maybe a
Prelude.Nothing,
      $sel:resourceType:PolicySummary' :: Maybe Text
resourceType = forall a. Maybe a
Prelude.Nothing,
      $sel:securityServiceType:PolicySummary' :: Maybe SecurityServiceType
securityServiceType = forall a. Maybe a
Prelude.Nothing
    }

-- | Indicates whether Firewall Manager should automatically remove
-- protections from resources that leave the policy scope and clean up
-- resources that Firewall Manager is managing for accounts when those
-- accounts leave policy scope. For example, Firewall Manager will
-- disassociate a Firewall Manager managed web ACL from a protected
-- customer resource when the customer resource leaves policy scope.
--
-- By default, Firewall Manager doesn\'t remove protections or delete
-- Firewall Manager managed resources.
--
-- This option is not available for Shield Advanced or WAF Classic
-- policies.
policySummary_deleteUnusedFMManagedResources :: Lens.Lens' PolicySummary (Prelude.Maybe Prelude.Bool)
policySummary_deleteUnusedFMManagedResources :: Lens' PolicySummary (Maybe Bool)
policySummary_deleteUnusedFMManagedResources = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PolicySummary' {Maybe Bool
deleteUnusedFMManagedResources :: Maybe Bool
$sel:deleteUnusedFMManagedResources:PolicySummary' :: PolicySummary -> Maybe Bool
deleteUnusedFMManagedResources} -> Maybe Bool
deleteUnusedFMManagedResources) (\s :: PolicySummary
s@PolicySummary' {} Maybe Bool
a -> PolicySummary
s {$sel:deleteUnusedFMManagedResources:PolicySummary' :: Maybe Bool
deleteUnusedFMManagedResources = Maybe Bool
a} :: PolicySummary)

-- | The Amazon Resource Name (ARN) of the specified policy.
policySummary_policyArn :: Lens.Lens' PolicySummary (Prelude.Maybe Prelude.Text)
policySummary_policyArn :: Lens' PolicySummary (Maybe Text)
policySummary_policyArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PolicySummary' {Maybe Text
policyArn :: Maybe Text
$sel:policyArn:PolicySummary' :: PolicySummary -> Maybe Text
policyArn} -> Maybe Text
policyArn) (\s :: PolicySummary
s@PolicySummary' {} Maybe Text
a -> PolicySummary
s {$sel:policyArn:PolicySummary' :: Maybe Text
policyArn = Maybe Text
a} :: PolicySummary)

-- | The ID of the specified policy.
policySummary_policyId :: Lens.Lens' PolicySummary (Prelude.Maybe Prelude.Text)
policySummary_policyId :: Lens' PolicySummary (Maybe Text)
policySummary_policyId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PolicySummary' {Maybe Text
policyId :: Maybe Text
$sel:policyId:PolicySummary' :: PolicySummary -> Maybe Text
policyId} -> Maybe Text
policyId) (\s :: PolicySummary
s@PolicySummary' {} Maybe Text
a -> PolicySummary
s {$sel:policyId:PolicySummary' :: Maybe Text
policyId = Maybe Text
a} :: PolicySummary)

-- | The name of the specified policy.
policySummary_policyName :: Lens.Lens' PolicySummary (Prelude.Maybe Prelude.Text)
policySummary_policyName :: Lens' PolicySummary (Maybe Text)
policySummary_policyName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PolicySummary' {Maybe Text
policyName :: Maybe Text
$sel:policyName:PolicySummary' :: PolicySummary -> Maybe Text
policyName} -> Maybe Text
policyName) (\s :: PolicySummary
s@PolicySummary' {} Maybe Text
a -> PolicySummary
s {$sel:policyName:PolicySummary' :: Maybe Text
policyName = Maybe Text
a} :: PolicySummary)

-- | Indicates if the policy should be automatically applied to new
-- resources.
policySummary_remediationEnabled :: Lens.Lens' PolicySummary (Prelude.Maybe Prelude.Bool)
policySummary_remediationEnabled :: Lens' PolicySummary (Maybe Bool)
policySummary_remediationEnabled = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PolicySummary' {Maybe Bool
remediationEnabled :: Maybe Bool
$sel:remediationEnabled:PolicySummary' :: PolicySummary -> Maybe Bool
remediationEnabled} -> Maybe Bool
remediationEnabled) (\s :: PolicySummary
s@PolicySummary' {} Maybe Bool
a -> PolicySummary
s {$sel:remediationEnabled:PolicySummary' :: Maybe Bool
remediationEnabled = Maybe Bool
a} :: PolicySummary)

-- | The type of resource protected by or in scope of the policy. This is in
-- the format shown in the
-- <https://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-template-resource-type-ref.html Amazon Web Services Resource Types Reference>.
-- For WAF and Shield Advanced, examples include
-- @AWS::ElasticLoadBalancingV2::LoadBalancer@ and
-- @AWS::CloudFront::Distribution@. For a security group common policy,
-- valid values are @AWS::EC2::NetworkInterface@ and @AWS::EC2::Instance@.
-- For a security group content audit policy, valid values are
-- @AWS::EC2::SecurityGroup@, @AWS::EC2::NetworkInterface@, and
-- @AWS::EC2::Instance@. For a security group usage audit policy, the value
-- is @AWS::EC2::SecurityGroup@. For an Network Firewall policy or DNS
-- Firewall policy, the value is @AWS::EC2::VPC@.
policySummary_resourceType :: Lens.Lens' PolicySummary (Prelude.Maybe Prelude.Text)
policySummary_resourceType :: Lens' PolicySummary (Maybe Text)
policySummary_resourceType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PolicySummary' {Maybe Text
resourceType :: Maybe Text
$sel:resourceType:PolicySummary' :: PolicySummary -> Maybe Text
resourceType} -> Maybe Text
resourceType) (\s :: PolicySummary
s@PolicySummary' {} Maybe Text
a -> PolicySummary
s {$sel:resourceType:PolicySummary' :: Maybe Text
resourceType = Maybe Text
a} :: PolicySummary)

-- | The service that the policy is using to protect the resources. This
-- specifies the type of policy that is created, either an WAF policy, a
-- Shield Advanced policy, or a security group policy.
policySummary_securityServiceType :: Lens.Lens' PolicySummary (Prelude.Maybe SecurityServiceType)
policySummary_securityServiceType :: Lens' PolicySummary (Maybe SecurityServiceType)
policySummary_securityServiceType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PolicySummary' {Maybe SecurityServiceType
securityServiceType :: Maybe SecurityServiceType
$sel:securityServiceType:PolicySummary' :: PolicySummary -> Maybe SecurityServiceType
securityServiceType} -> Maybe SecurityServiceType
securityServiceType) (\s :: PolicySummary
s@PolicySummary' {} Maybe SecurityServiceType
a -> PolicySummary
s {$sel:securityServiceType:PolicySummary' :: Maybe SecurityServiceType
securityServiceType = Maybe SecurityServiceType
a} :: PolicySummary)

instance Data.FromJSON PolicySummary where
  parseJSON :: Value -> Parser PolicySummary
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"PolicySummary"
      ( \Object
x ->
          Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe SecurityServiceType
-> PolicySummary
PolicySummary'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"DeleteUnusedFMManagedResources")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"PolicyArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"PolicyId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"PolicyName")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"RemediationEnabled")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"ResourceType")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"SecurityServiceType")
      )

instance Prelude.Hashable PolicySummary where
  hashWithSalt :: Int -> PolicySummary -> Int
hashWithSalt Int
_salt PolicySummary' {Maybe Bool
Maybe Text
Maybe SecurityServiceType
securityServiceType :: Maybe SecurityServiceType
resourceType :: Maybe Text
remediationEnabled :: Maybe Bool
policyName :: Maybe Text
policyId :: Maybe Text
policyArn :: Maybe Text
deleteUnusedFMManagedResources :: Maybe Bool
$sel:securityServiceType:PolicySummary' :: PolicySummary -> Maybe SecurityServiceType
$sel:resourceType:PolicySummary' :: PolicySummary -> Maybe Text
$sel:remediationEnabled:PolicySummary' :: PolicySummary -> Maybe Bool
$sel:policyName:PolicySummary' :: PolicySummary -> Maybe Text
$sel:policyId:PolicySummary' :: PolicySummary -> Maybe Text
$sel:policyArn:PolicySummary' :: PolicySummary -> Maybe Text
$sel:deleteUnusedFMManagedResources:PolicySummary' :: PolicySummary -> Maybe Bool
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
deleteUnusedFMManagedResources
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
policyArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
policyId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
policyName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
remediationEnabled
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
resourceType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe SecurityServiceType
securityServiceType

instance Prelude.NFData PolicySummary where
  rnf :: PolicySummary -> ()
rnf PolicySummary' {Maybe Bool
Maybe Text
Maybe SecurityServiceType
securityServiceType :: Maybe SecurityServiceType
resourceType :: Maybe Text
remediationEnabled :: Maybe Bool
policyName :: Maybe Text
policyId :: Maybe Text
policyArn :: Maybe Text
deleteUnusedFMManagedResources :: Maybe Bool
$sel:securityServiceType:PolicySummary' :: PolicySummary -> Maybe SecurityServiceType
$sel:resourceType:PolicySummary' :: PolicySummary -> Maybe Text
$sel:remediationEnabled:PolicySummary' :: PolicySummary -> Maybe Bool
$sel:policyName:PolicySummary' :: PolicySummary -> Maybe Text
$sel:policyId:PolicySummary' :: PolicySummary -> Maybe Text
$sel:policyArn:PolicySummary' :: PolicySummary -> Maybe Text
$sel:deleteUnusedFMManagedResources:PolicySummary' :: PolicySummary -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
deleteUnusedFMManagedResources
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
policyArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
policyId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
policyName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
remediationEnabled
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
resourceType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe SecurityServiceType
securityServiceType