{-# 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.Shield.CreateProtectionGroup
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Creates a grouping of protected resources so they can be handled as a
-- collective. This resource grouping improves the accuracy of detection
-- and reduces false positives.
module Amazonka.Shield.CreateProtectionGroup
  ( -- * Creating a Request
    CreateProtectionGroup (..),
    newCreateProtectionGroup,

    -- * Request Lenses
    createProtectionGroup_members,
    createProtectionGroup_resourceType,
    createProtectionGroup_tags,
    createProtectionGroup_protectionGroupId,
    createProtectionGroup_aggregation,
    createProtectionGroup_pattern,

    -- * Destructuring the Response
    CreateProtectionGroupResponse (..),
    newCreateProtectionGroupResponse,

    -- * Response Lenses
    createProtectionGroupResponse_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.Shield.Types

-- | /See:/ 'newCreateProtectionGroup' smart constructor.
data CreateProtectionGroup = CreateProtectionGroup'
  { -- | The Amazon Resource Names (ARNs) of the resources to include in the
    -- protection group. You must set this when you set @Pattern@ to
    -- @ARBITRARY@ and you must not set it for any other @Pattern@ setting.
    CreateProtectionGroup -> Maybe [Text]
members :: Prelude.Maybe [Prelude.Text],
    -- | The resource type to include in the protection group. All protected
    -- resources of this type are included in the protection group. Newly
    -- protected resources of this type are automatically added to the group.
    -- You must set this when you set @Pattern@ to @BY_RESOURCE_TYPE@ and you
    -- must not set it for any other @Pattern@ setting.
    CreateProtectionGroup -> Maybe ProtectedResourceType
resourceType :: Prelude.Maybe ProtectedResourceType,
    -- | One or more tag key-value pairs for the protection group.
    CreateProtectionGroup -> Maybe [Tag]
tags :: Prelude.Maybe [Tag],
    -- | The name of the protection group. You use this to identify the
    -- protection group in lists and to manage the protection group, for
    -- example to update, delete, or describe it.
    CreateProtectionGroup -> Text
protectionGroupId :: Prelude.Text,
    -- | Defines how Shield combines resource data for the group in order to
    -- detect, mitigate, and report events.
    --
    -- -   Sum - Use the total traffic across the group. This is a good choice
    --     for most cases. Examples include Elastic IP addresses for EC2
    --     instances that scale manually or automatically.
    --
    -- -   Mean - Use the average of the traffic across the group. This is a
    --     good choice for resources that share traffic uniformly. Examples
    --     include accelerators and load balancers.
    --
    -- -   Max - Use the highest traffic from each resource. This is useful for
    --     resources that don\'t share traffic and for resources that share
    --     that traffic in a non-uniform way. Examples include Amazon
    --     CloudFront and origin resources for CloudFront distributions.
    CreateProtectionGroup -> ProtectionGroupAggregation
aggregation :: ProtectionGroupAggregation,
    -- | The criteria to use to choose the protected resources for inclusion in
    -- the group. You can include all resources that have protections, provide
    -- a list of resource Amazon Resource Names (ARNs), or include all
    -- resources of a specified resource type.
    CreateProtectionGroup -> ProtectionGroupPattern
pattern' :: ProtectionGroupPattern
  }
  deriving (CreateProtectionGroup -> CreateProtectionGroup -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateProtectionGroup -> CreateProtectionGroup -> Bool
$c/= :: CreateProtectionGroup -> CreateProtectionGroup -> Bool
== :: CreateProtectionGroup -> CreateProtectionGroup -> Bool
$c== :: CreateProtectionGroup -> CreateProtectionGroup -> Bool
Prelude.Eq, ReadPrec [CreateProtectionGroup]
ReadPrec CreateProtectionGroup
Int -> ReadS CreateProtectionGroup
ReadS [CreateProtectionGroup]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateProtectionGroup]
$creadListPrec :: ReadPrec [CreateProtectionGroup]
readPrec :: ReadPrec CreateProtectionGroup
$creadPrec :: ReadPrec CreateProtectionGroup
readList :: ReadS [CreateProtectionGroup]
$creadList :: ReadS [CreateProtectionGroup]
readsPrec :: Int -> ReadS CreateProtectionGroup
$creadsPrec :: Int -> ReadS CreateProtectionGroup
Prelude.Read, Int -> CreateProtectionGroup -> ShowS
[CreateProtectionGroup] -> ShowS
CreateProtectionGroup -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateProtectionGroup] -> ShowS
$cshowList :: [CreateProtectionGroup] -> ShowS
show :: CreateProtectionGroup -> String
$cshow :: CreateProtectionGroup -> String
showsPrec :: Int -> CreateProtectionGroup -> ShowS
$cshowsPrec :: Int -> CreateProtectionGroup -> ShowS
Prelude.Show, forall x. Rep CreateProtectionGroup x -> CreateProtectionGroup
forall x. CreateProtectionGroup -> Rep CreateProtectionGroup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateProtectionGroup x -> CreateProtectionGroup
$cfrom :: forall x. CreateProtectionGroup -> Rep CreateProtectionGroup x
Prelude.Generic)

-- |
-- Create a value of 'CreateProtectionGroup' 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:
--
-- 'members', 'createProtectionGroup_members' - The Amazon Resource Names (ARNs) of the resources to include in the
-- protection group. You must set this when you set @Pattern@ to
-- @ARBITRARY@ and you must not set it for any other @Pattern@ setting.
--
-- 'resourceType', 'createProtectionGroup_resourceType' - The resource type to include in the protection group. All protected
-- resources of this type are included in the protection group. Newly
-- protected resources of this type are automatically added to the group.
-- You must set this when you set @Pattern@ to @BY_RESOURCE_TYPE@ and you
-- must not set it for any other @Pattern@ setting.
--
-- 'tags', 'createProtectionGroup_tags' - One or more tag key-value pairs for the protection group.
--
-- 'protectionGroupId', 'createProtectionGroup_protectionGroupId' - The name of the protection group. You use this to identify the
-- protection group in lists and to manage the protection group, for
-- example to update, delete, or describe it.
--
-- 'aggregation', 'createProtectionGroup_aggregation' - Defines how Shield combines resource data for the group in order to
-- detect, mitigate, and report events.
--
-- -   Sum - Use the total traffic across the group. This is a good choice
--     for most cases. Examples include Elastic IP addresses for EC2
--     instances that scale manually or automatically.
--
-- -   Mean - Use the average of the traffic across the group. This is a
--     good choice for resources that share traffic uniformly. Examples
--     include accelerators and load balancers.
--
-- -   Max - Use the highest traffic from each resource. This is useful for
--     resources that don\'t share traffic and for resources that share
--     that traffic in a non-uniform way. Examples include Amazon
--     CloudFront and origin resources for CloudFront distributions.
--
-- 'pattern'', 'createProtectionGroup_pattern' - The criteria to use to choose the protected resources for inclusion in
-- the group. You can include all resources that have protections, provide
-- a list of resource Amazon Resource Names (ARNs), or include all
-- resources of a specified resource type.
newCreateProtectionGroup ::
  -- | 'protectionGroupId'
  Prelude.Text ->
  -- | 'aggregation'
  ProtectionGroupAggregation ->
  -- | 'pattern''
  ProtectionGroupPattern ->
  CreateProtectionGroup
newCreateProtectionGroup :: Text
-> ProtectionGroupAggregation
-> ProtectionGroupPattern
-> CreateProtectionGroup
newCreateProtectionGroup
  Text
pProtectionGroupId_
  ProtectionGroupAggregation
pAggregation_
  ProtectionGroupPattern
pPattern_ =
    CreateProtectionGroup'
      { $sel:members:CreateProtectionGroup' :: Maybe [Text]
members = forall a. Maybe a
Prelude.Nothing,
        $sel:resourceType:CreateProtectionGroup' :: Maybe ProtectedResourceType
resourceType = forall a. Maybe a
Prelude.Nothing,
        $sel:tags:CreateProtectionGroup' :: Maybe [Tag]
tags = forall a. Maybe a
Prelude.Nothing,
        $sel:protectionGroupId:CreateProtectionGroup' :: Text
protectionGroupId = Text
pProtectionGroupId_,
        $sel:aggregation:CreateProtectionGroup' :: ProtectionGroupAggregation
aggregation = ProtectionGroupAggregation
pAggregation_,
        $sel:pattern':CreateProtectionGroup' :: ProtectionGroupPattern
pattern' = ProtectionGroupPattern
pPattern_
      }

-- | The Amazon Resource Names (ARNs) of the resources to include in the
-- protection group. You must set this when you set @Pattern@ to
-- @ARBITRARY@ and you must not set it for any other @Pattern@ setting.
createProtectionGroup_members :: Lens.Lens' CreateProtectionGroup (Prelude.Maybe [Prelude.Text])
createProtectionGroup_members :: Lens' CreateProtectionGroup (Maybe [Text])
createProtectionGroup_members = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateProtectionGroup' {Maybe [Text]
members :: Maybe [Text]
$sel:members:CreateProtectionGroup' :: CreateProtectionGroup -> Maybe [Text]
members} -> Maybe [Text]
members) (\s :: CreateProtectionGroup
s@CreateProtectionGroup' {} Maybe [Text]
a -> CreateProtectionGroup
s {$sel:members:CreateProtectionGroup' :: Maybe [Text]
members = Maybe [Text]
a} :: CreateProtectionGroup) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The resource type to include in the protection group. All protected
-- resources of this type are included in the protection group. Newly
-- protected resources of this type are automatically added to the group.
-- You must set this when you set @Pattern@ to @BY_RESOURCE_TYPE@ and you
-- must not set it for any other @Pattern@ setting.
createProtectionGroup_resourceType :: Lens.Lens' CreateProtectionGroup (Prelude.Maybe ProtectedResourceType)
createProtectionGroup_resourceType :: Lens' CreateProtectionGroup (Maybe ProtectedResourceType)
createProtectionGroup_resourceType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateProtectionGroup' {Maybe ProtectedResourceType
resourceType :: Maybe ProtectedResourceType
$sel:resourceType:CreateProtectionGroup' :: CreateProtectionGroup -> Maybe ProtectedResourceType
resourceType} -> Maybe ProtectedResourceType
resourceType) (\s :: CreateProtectionGroup
s@CreateProtectionGroup' {} Maybe ProtectedResourceType
a -> CreateProtectionGroup
s {$sel:resourceType:CreateProtectionGroup' :: Maybe ProtectedResourceType
resourceType = Maybe ProtectedResourceType
a} :: CreateProtectionGroup)

-- | One or more tag key-value pairs for the protection group.
createProtectionGroup_tags :: Lens.Lens' CreateProtectionGroup (Prelude.Maybe [Tag])
createProtectionGroup_tags :: Lens' CreateProtectionGroup (Maybe [Tag])
createProtectionGroup_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateProtectionGroup' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:CreateProtectionGroup' :: CreateProtectionGroup -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: CreateProtectionGroup
s@CreateProtectionGroup' {} Maybe [Tag]
a -> CreateProtectionGroup
s {$sel:tags:CreateProtectionGroup' :: Maybe [Tag]
tags = Maybe [Tag]
a} :: CreateProtectionGroup) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The name of the protection group. You use this to identify the
-- protection group in lists and to manage the protection group, for
-- example to update, delete, or describe it.
createProtectionGroup_protectionGroupId :: Lens.Lens' CreateProtectionGroup Prelude.Text
createProtectionGroup_protectionGroupId :: Lens' CreateProtectionGroup Text
createProtectionGroup_protectionGroupId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateProtectionGroup' {Text
protectionGroupId :: Text
$sel:protectionGroupId:CreateProtectionGroup' :: CreateProtectionGroup -> Text
protectionGroupId} -> Text
protectionGroupId) (\s :: CreateProtectionGroup
s@CreateProtectionGroup' {} Text
a -> CreateProtectionGroup
s {$sel:protectionGroupId:CreateProtectionGroup' :: Text
protectionGroupId = Text
a} :: CreateProtectionGroup)

-- | Defines how Shield combines resource data for the group in order to
-- detect, mitigate, and report events.
--
-- -   Sum - Use the total traffic across the group. This is a good choice
--     for most cases. Examples include Elastic IP addresses for EC2
--     instances that scale manually or automatically.
--
-- -   Mean - Use the average of the traffic across the group. This is a
--     good choice for resources that share traffic uniformly. Examples
--     include accelerators and load balancers.
--
-- -   Max - Use the highest traffic from each resource. This is useful for
--     resources that don\'t share traffic and for resources that share
--     that traffic in a non-uniform way. Examples include Amazon
--     CloudFront and origin resources for CloudFront distributions.
createProtectionGroup_aggregation :: Lens.Lens' CreateProtectionGroup ProtectionGroupAggregation
createProtectionGroup_aggregation :: Lens' CreateProtectionGroup ProtectionGroupAggregation
createProtectionGroup_aggregation = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateProtectionGroup' {ProtectionGroupAggregation
aggregation :: ProtectionGroupAggregation
$sel:aggregation:CreateProtectionGroup' :: CreateProtectionGroup -> ProtectionGroupAggregation
aggregation} -> ProtectionGroupAggregation
aggregation) (\s :: CreateProtectionGroup
s@CreateProtectionGroup' {} ProtectionGroupAggregation
a -> CreateProtectionGroup
s {$sel:aggregation:CreateProtectionGroup' :: ProtectionGroupAggregation
aggregation = ProtectionGroupAggregation
a} :: CreateProtectionGroup)

-- | The criteria to use to choose the protected resources for inclusion in
-- the group. You can include all resources that have protections, provide
-- a list of resource Amazon Resource Names (ARNs), or include all
-- resources of a specified resource type.
createProtectionGroup_pattern :: Lens.Lens' CreateProtectionGroup ProtectionGroupPattern
createProtectionGroup_pattern :: Lens' CreateProtectionGroup ProtectionGroupPattern
createProtectionGroup_pattern = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateProtectionGroup' {ProtectionGroupPattern
pattern' :: ProtectionGroupPattern
$sel:pattern':CreateProtectionGroup' :: CreateProtectionGroup -> ProtectionGroupPattern
pattern'} -> ProtectionGroupPattern
pattern') (\s :: CreateProtectionGroup
s@CreateProtectionGroup' {} ProtectionGroupPattern
a -> CreateProtectionGroup
s {$sel:pattern':CreateProtectionGroup' :: ProtectionGroupPattern
pattern' = ProtectionGroupPattern
a} :: CreateProtectionGroup)

instance Core.AWSRequest CreateProtectionGroup where
  type
    AWSResponse CreateProtectionGroup =
      CreateProtectionGroupResponse
  request :: (Service -> Service)
-> CreateProtectionGroup -> Request CreateProtectionGroup
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 CreateProtectionGroup
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CreateProtectionGroup)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> () -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveEmpty
      ( \Int
s ResponseHeaders
h ()
x ->
          Int -> CreateProtectionGroupResponse
CreateProtectionGroupResponse'
            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))
      )

instance Prelude.Hashable CreateProtectionGroup where
  hashWithSalt :: Int -> CreateProtectionGroup -> Int
hashWithSalt Int
_salt CreateProtectionGroup' {Maybe [Text]
Maybe [Tag]
Maybe ProtectedResourceType
Text
ProtectionGroupAggregation
ProtectionGroupPattern
pattern' :: ProtectionGroupPattern
aggregation :: ProtectionGroupAggregation
protectionGroupId :: Text
tags :: Maybe [Tag]
resourceType :: Maybe ProtectedResourceType
members :: Maybe [Text]
$sel:pattern':CreateProtectionGroup' :: CreateProtectionGroup -> ProtectionGroupPattern
$sel:aggregation:CreateProtectionGroup' :: CreateProtectionGroup -> ProtectionGroupAggregation
$sel:protectionGroupId:CreateProtectionGroup' :: CreateProtectionGroup -> Text
$sel:tags:CreateProtectionGroup' :: CreateProtectionGroup -> Maybe [Tag]
$sel:resourceType:CreateProtectionGroup' :: CreateProtectionGroup -> Maybe ProtectedResourceType
$sel:members:CreateProtectionGroup' :: CreateProtectionGroup -> Maybe [Text]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
members
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ProtectedResourceType
resourceType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Tag]
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
protectionGroupId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ProtectionGroupAggregation
aggregation
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ProtectionGroupPattern
pattern'

instance Prelude.NFData CreateProtectionGroup where
  rnf :: CreateProtectionGroup -> ()
rnf CreateProtectionGroup' {Maybe [Text]
Maybe [Tag]
Maybe ProtectedResourceType
Text
ProtectionGroupAggregation
ProtectionGroupPattern
pattern' :: ProtectionGroupPattern
aggregation :: ProtectionGroupAggregation
protectionGroupId :: Text
tags :: Maybe [Tag]
resourceType :: Maybe ProtectedResourceType
members :: Maybe [Text]
$sel:pattern':CreateProtectionGroup' :: CreateProtectionGroup -> ProtectionGroupPattern
$sel:aggregation:CreateProtectionGroup' :: CreateProtectionGroup -> ProtectionGroupAggregation
$sel:protectionGroupId:CreateProtectionGroup' :: CreateProtectionGroup -> Text
$sel:tags:CreateProtectionGroup' :: CreateProtectionGroup -> Maybe [Tag]
$sel:resourceType:CreateProtectionGroup' :: CreateProtectionGroup -> Maybe ProtectedResourceType
$sel:members:CreateProtectionGroup' :: CreateProtectionGroup -> Maybe [Text]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
members
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ProtectedResourceType
resourceType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Tag]
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
protectionGroupId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf ProtectionGroupAggregation
aggregation
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf ProtectionGroupPattern
pattern'

instance Data.ToHeaders CreateProtectionGroup where
  toHeaders :: CreateProtectionGroup -> 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
"AWSShield_20160616.CreateProtectionGroup" ::
                          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 CreateProtectionGroup where
  toJSON :: CreateProtectionGroup -> Value
toJSON CreateProtectionGroup' {Maybe [Text]
Maybe [Tag]
Maybe ProtectedResourceType
Text
ProtectionGroupAggregation
ProtectionGroupPattern
pattern' :: ProtectionGroupPattern
aggregation :: ProtectionGroupAggregation
protectionGroupId :: Text
tags :: Maybe [Tag]
resourceType :: Maybe ProtectedResourceType
members :: Maybe [Text]
$sel:pattern':CreateProtectionGroup' :: CreateProtectionGroup -> ProtectionGroupPattern
$sel:aggregation:CreateProtectionGroup' :: CreateProtectionGroup -> ProtectionGroupAggregation
$sel:protectionGroupId:CreateProtectionGroup' :: CreateProtectionGroup -> Text
$sel:tags:CreateProtectionGroup' :: CreateProtectionGroup -> Maybe [Tag]
$sel:resourceType:CreateProtectionGroup' :: CreateProtectionGroup -> Maybe ProtectedResourceType
$sel:members:CreateProtectionGroup' :: CreateProtectionGroup -> Maybe [Text]
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Members" 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]
members,
            (Key
"ResourceType" 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 ProtectedResourceType
resourceType,
            (Key
"Tags" 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 [Tag]
tags,
            forall a. a -> Maybe a
Prelude.Just
              (Key
"ProtectionGroupId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
protectionGroupId),
            forall a. a -> Maybe a
Prelude.Just (Key
"Aggregation" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= ProtectionGroupAggregation
aggregation),
            forall a. a -> Maybe a
Prelude.Just (Key
"Pattern" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= ProtectionGroupPattern
pattern')
          ]
      )

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

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

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

-- |
-- Create a value of 'CreateProtectionGroupResponse' 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', 'createProtectionGroupResponse_httpStatus' - The response's http status code.
newCreateProtectionGroupResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateProtectionGroupResponse
newCreateProtectionGroupResponse :: Int -> CreateProtectionGroupResponse
newCreateProtectionGroupResponse Int
pHttpStatus_ =
  CreateProtectionGroupResponse'
    { $sel:httpStatus:CreateProtectionGroupResponse' :: Int
httpStatus =
        Int
pHttpStatus_
    }

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

instance Prelude.NFData CreateProtectionGroupResponse where
  rnf :: CreateProtectionGroupResponse -> ()
rnf CreateProtectionGroupResponse' {Int
httpStatus :: Int
$sel:httpStatus:CreateProtectionGroupResponse' :: CreateProtectionGroupResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus