{-# 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 #-}
module Amazonka.Shield.UpdateProtectionGroup
(
UpdateProtectionGroup (..),
newUpdateProtectionGroup,
updateProtectionGroup_members,
updateProtectionGroup_resourceType,
updateProtectionGroup_protectionGroupId,
updateProtectionGroup_aggregation,
updateProtectionGroup_pattern,
UpdateProtectionGroupResponse (..),
newUpdateProtectionGroupResponse,
updateProtectionGroupResponse_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
data UpdateProtectionGroup = UpdateProtectionGroup'
{
UpdateProtectionGroup -> Maybe [Text]
members :: Prelude.Maybe [Prelude.Text],
UpdateProtectionGroup -> Maybe ProtectedResourceType
resourceType :: Prelude.Maybe ProtectedResourceType,
UpdateProtectionGroup -> Text
protectionGroupId :: Prelude.Text,
UpdateProtectionGroup -> ProtectionGroupAggregation
aggregation :: ProtectionGroupAggregation,
UpdateProtectionGroup -> ProtectionGroupPattern
pattern' :: ProtectionGroupPattern
}
deriving (UpdateProtectionGroup -> UpdateProtectionGroup -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateProtectionGroup -> UpdateProtectionGroup -> Bool
$c/= :: UpdateProtectionGroup -> UpdateProtectionGroup -> Bool
== :: UpdateProtectionGroup -> UpdateProtectionGroup -> Bool
$c== :: UpdateProtectionGroup -> UpdateProtectionGroup -> Bool
Prelude.Eq, ReadPrec [UpdateProtectionGroup]
ReadPrec UpdateProtectionGroup
Int -> ReadS UpdateProtectionGroup
ReadS [UpdateProtectionGroup]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateProtectionGroup]
$creadListPrec :: ReadPrec [UpdateProtectionGroup]
readPrec :: ReadPrec UpdateProtectionGroup
$creadPrec :: ReadPrec UpdateProtectionGroup
readList :: ReadS [UpdateProtectionGroup]
$creadList :: ReadS [UpdateProtectionGroup]
readsPrec :: Int -> ReadS UpdateProtectionGroup
$creadsPrec :: Int -> ReadS UpdateProtectionGroup
Prelude.Read, Int -> UpdateProtectionGroup -> ShowS
[UpdateProtectionGroup] -> ShowS
UpdateProtectionGroup -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateProtectionGroup] -> ShowS
$cshowList :: [UpdateProtectionGroup] -> ShowS
show :: UpdateProtectionGroup -> String
$cshow :: UpdateProtectionGroup -> String
showsPrec :: Int -> UpdateProtectionGroup -> ShowS
$cshowsPrec :: Int -> UpdateProtectionGroup -> ShowS
Prelude.Show, forall x. Rep UpdateProtectionGroup x -> UpdateProtectionGroup
forall x. UpdateProtectionGroup -> Rep UpdateProtectionGroup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateProtectionGroup x -> UpdateProtectionGroup
$cfrom :: forall x. UpdateProtectionGroup -> Rep UpdateProtectionGroup x
Prelude.Generic)
newUpdateProtectionGroup ::
Prelude.Text ->
ProtectionGroupAggregation ->
ProtectionGroupPattern ->
UpdateProtectionGroup
newUpdateProtectionGroup :: Text
-> ProtectionGroupAggregation
-> ProtectionGroupPattern
-> UpdateProtectionGroup
newUpdateProtectionGroup
Text
pProtectionGroupId_
ProtectionGroupAggregation
pAggregation_
ProtectionGroupPattern
pPattern_ =
UpdateProtectionGroup'
{ $sel:members:UpdateProtectionGroup' :: Maybe [Text]
members = forall a. Maybe a
Prelude.Nothing,
$sel:resourceType:UpdateProtectionGroup' :: Maybe ProtectedResourceType
resourceType = forall a. Maybe a
Prelude.Nothing,
$sel:protectionGroupId:UpdateProtectionGroup' :: Text
protectionGroupId = Text
pProtectionGroupId_,
$sel:aggregation:UpdateProtectionGroup' :: ProtectionGroupAggregation
aggregation = ProtectionGroupAggregation
pAggregation_,
$sel:pattern':UpdateProtectionGroup' :: ProtectionGroupPattern
pattern' = ProtectionGroupPattern
pPattern_
}
updateProtectionGroup_members :: Lens.Lens' UpdateProtectionGroup (Prelude.Maybe [Prelude.Text])
updateProtectionGroup_members :: Lens' UpdateProtectionGroup (Maybe [Text])
updateProtectionGroup_members = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateProtectionGroup' {Maybe [Text]
members :: Maybe [Text]
$sel:members:UpdateProtectionGroup' :: UpdateProtectionGroup -> Maybe [Text]
members} -> Maybe [Text]
members) (\s :: UpdateProtectionGroup
s@UpdateProtectionGroup' {} Maybe [Text]
a -> UpdateProtectionGroup
s {$sel:members:UpdateProtectionGroup' :: Maybe [Text]
members = Maybe [Text]
a} :: UpdateProtectionGroup) 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
updateProtectionGroup_resourceType :: Lens.Lens' UpdateProtectionGroup (Prelude.Maybe ProtectedResourceType)
updateProtectionGroup_resourceType :: Lens' UpdateProtectionGroup (Maybe ProtectedResourceType)
updateProtectionGroup_resourceType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateProtectionGroup' {Maybe ProtectedResourceType
resourceType :: Maybe ProtectedResourceType
$sel:resourceType:UpdateProtectionGroup' :: UpdateProtectionGroup -> Maybe ProtectedResourceType
resourceType} -> Maybe ProtectedResourceType
resourceType) (\s :: UpdateProtectionGroup
s@UpdateProtectionGroup' {} Maybe ProtectedResourceType
a -> UpdateProtectionGroup
s {$sel:resourceType:UpdateProtectionGroup' :: Maybe ProtectedResourceType
resourceType = Maybe ProtectedResourceType
a} :: UpdateProtectionGroup)
updateProtectionGroup_protectionGroupId :: Lens.Lens' UpdateProtectionGroup Prelude.Text
updateProtectionGroup_protectionGroupId :: Lens' UpdateProtectionGroup Text
updateProtectionGroup_protectionGroupId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateProtectionGroup' {Text
protectionGroupId :: Text
$sel:protectionGroupId:UpdateProtectionGroup' :: UpdateProtectionGroup -> Text
protectionGroupId} -> Text
protectionGroupId) (\s :: UpdateProtectionGroup
s@UpdateProtectionGroup' {} Text
a -> UpdateProtectionGroup
s {$sel:protectionGroupId:UpdateProtectionGroup' :: Text
protectionGroupId = Text
a} :: UpdateProtectionGroup)
updateProtectionGroup_aggregation :: Lens.Lens' UpdateProtectionGroup ProtectionGroupAggregation
updateProtectionGroup_aggregation :: Lens' UpdateProtectionGroup ProtectionGroupAggregation
updateProtectionGroup_aggregation = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateProtectionGroup' {ProtectionGroupAggregation
aggregation :: ProtectionGroupAggregation
$sel:aggregation:UpdateProtectionGroup' :: UpdateProtectionGroup -> ProtectionGroupAggregation
aggregation} -> ProtectionGroupAggregation
aggregation) (\s :: UpdateProtectionGroup
s@UpdateProtectionGroup' {} ProtectionGroupAggregation
a -> UpdateProtectionGroup
s {$sel:aggregation:UpdateProtectionGroup' :: ProtectionGroupAggregation
aggregation = ProtectionGroupAggregation
a} :: UpdateProtectionGroup)
updateProtectionGroup_pattern :: Lens.Lens' UpdateProtectionGroup ProtectionGroupPattern
updateProtectionGroup_pattern :: Lens' UpdateProtectionGroup ProtectionGroupPattern
updateProtectionGroup_pattern = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateProtectionGroup' {ProtectionGroupPattern
pattern' :: ProtectionGroupPattern
$sel:pattern':UpdateProtectionGroup' :: UpdateProtectionGroup -> ProtectionGroupPattern
pattern'} -> ProtectionGroupPattern
pattern') (\s :: UpdateProtectionGroup
s@UpdateProtectionGroup' {} ProtectionGroupPattern
a -> UpdateProtectionGroup
s {$sel:pattern':UpdateProtectionGroup' :: ProtectionGroupPattern
pattern' = ProtectionGroupPattern
a} :: UpdateProtectionGroup)
instance Core.AWSRequest UpdateProtectionGroup where
type
AWSResponse UpdateProtectionGroup =
UpdateProtectionGroupResponse
request :: (Service -> Service)
-> UpdateProtectionGroup -> Request UpdateProtectionGroup
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 UpdateProtectionGroup
-> ClientResponse ClientBody
-> m (Either
Error (ClientResponse (AWSResponse UpdateProtectionGroup)))
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 -> UpdateProtectionGroupResponse
UpdateProtectionGroupResponse'
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 UpdateProtectionGroup where
hashWithSalt :: Int -> UpdateProtectionGroup -> Int
hashWithSalt Int
_salt UpdateProtectionGroup' {Maybe [Text]
Maybe ProtectedResourceType
Text
ProtectionGroupAggregation
ProtectionGroupPattern
pattern' :: ProtectionGroupPattern
aggregation :: ProtectionGroupAggregation
protectionGroupId :: Text
resourceType :: Maybe ProtectedResourceType
members :: Maybe [Text]
$sel:pattern':UpdateProtectionGroup' :: UpdateProtectionGroup -> ProtectionGroupPattern
$sel:aggregation:UpdateProtectionGroup' :: UpdateProtectionGroup -> ProtectionGroupAggregation
$sel:protectionGroupId:UpdateProtectionGroup' :: UpdateProtectionGroup -> Text
$sel:resourceType:UpdateProtectionGroup' :: UpdateProtectionGroup -> Maybe ProtectedResourceType
$sel:members:UpdateProtectionGroup' :: UpdateProtectionGroup -> 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` 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 UpdateProtectionGroup where
rnf :: UpdateProtectionGroup -> ()
rnf UpdateProtectionGroup' {Maybe [Text]
Maybe ProtectedResourceType
Text
ProtectionGroupAggregation
ProtectionGroupPattern
pattern' :: ProtectionGroupPattern
aggregation :: ProtectionGroupAggregation
protectionGroupId :: Text
resourceType :: Maybe ProtectedResourceType
members :: Maybe [Text]
$sel:pattern':UpdateProtectionGroup' :: UpdateProtectionGroup -> ProtectionGroupPattern
$sel:aggregation:UpdateProtectionGroup' :: UpdateProtectionGroup -> ProtectionGroupAggregation
$sel:protectionGroupId:UpdateProtectionGroup' :: UpdateProtectionGroup -> Text
$sel:resourceType:UpdateProtectionGroup' :: UpdateProtectionGroup -> Maybe ProtectedResourceType
$sel:members:UpdateProtectionGroup' :: UpdateProtectionGroup -> 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 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 UpdateProtectionGroup where
toHeaders :: UpdateProtectionGroup -> 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.UpdateProtectionGroup" ::
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 UpdateProtectionGroup where
toJSON :: UpdateProtectionGroup -> Value
toJSON UpdateProtectionGroup' {Maybe [Text]
Maybe ProtectedResourceType
Text
ProtectionGroupAggregation
ProtectionGroupPattern
pattern' :: ProtectionGroupPattern
aggregation :: ProtectionGroupAggregation
protectionGroupId :: Text
resourceType :: Maybe ProtectedResourceType
members :: Maybe [Text]
$sel:pattern':UpdateProtectionGroup' :: UpdateProtectionGroup -> ProtectionGroupPattern
$sel:aggregation:UpdateProtectionGroup' :: UpdateProtectionGroup -> ProtectionGroupAggregation
$sel:protectionGroupId:UpdateProtectionGroup' :: UpdateProtectionGroup -> Text
$sel:resourceType:UpdateProtectionGroup' :: UpdateProtectionGroup -> Maybe ProtectedResourceType
$sel:members:UpdateProtectionGroup' :: UpdateProtectionGroup -> 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,
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 UpdateProtectionGroup where
toPath :: UpdateProtectionGroup -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"
instance Data.ToQuery UpdateProtectionGroup where
toQuery :: UpdateProtectionGroup -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data UpdateProtectionGroupResponse = UpdateProtectionGroupResponse'
{
UpdateProtectionGroupResponse -> Int
httpStatus :: Prelude.Int
}
deriving (UpdateProtectionGroupResponse
-> UpdateProtectionGroupResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateProtectionGroupResponse
-> UpdateProtectionGroupResponse -> Bool
$c/= :: UpdateProtectionGroupResponse
-> UpdateProtectionGroupResponse -> Bool
== :: UpdateProtectionGroupResponse
-> UpdateProtectionGroupResponse -> Bool
$c== :: UpdateProtectionGroupResponse
-> UpdateProtectionGroupResponse -> Bool
Prelude.Eq, ReadPrec [UpdateProtectionGroupResponse]
ReadPrec UpdateProtectionGroupResponse
Int -> ReadS UpdateProtectionGroupResponse
ReadS [UpdateProtectionGroupResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateProtectionGroupResponse]
$creadListPrec :: ReadPrec [UpdateProtectionGroupResponse]
readPrec :: ReadPrec UpdateProtectionGroupResponse
$creadPrec :: ReadPrec UpdateProtectionGroupResponse
readList :: ReadS [UpdateProtectionGroupResponse]
$creadList :: ReadS [UpdateProtectionGroupResponse]
readsPrec :: Int -> ReadS UpdateProtectionGroupResponse
$creadsPrec :: Int -> ReadS UpdateProtectionGroupResponse
Prelude.Read, Int -> UpdateProtectionGroupResponse -> ShowS
[UpdateProtectionGroupResponse] -> ShowS
UpdateProtectionGroupResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateProtectionGroupResponse] -> ShowS
$cshowList :: [UpdateProtectionGroupResponse] -> ShowS
show :: UpdateProtectionGroupResponse -> String
$cshow :: UpdateProtectionGroupResponse -> String
showsPrec :: Int -> UpdateProtectionGroupResponse -> ShowS
$cshowsPrec :: Int -> UpdateProtectionGroupResponse -> ShowS
Prelude.Show, forall x.
Rep UpdateProtectionGroupResponse x
-> UpdateProtectionGroupResponse
forall x.
UpdateProtectionGroupResponse
-> Rep UpdateProtectionGroupResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateProtectionGroupResponse x
-> UpdateProtectionGroupResponse
$cfrom :: forall x.
UpdateProtectionGroupResponse
-> Rep UpdateProtectionGroupResponse x
Prelude.Generic)
newUpdateProtectionGroupResponse ::
Prelude.Int ->
UpdateProtectionGroupResponse
newUpdateProtectionGroupResponse :: Int -> UpdateProtectionGroupResponse
newUpdateProtectionGroupResponse Int
pHttpStatus_ =
UpdateProtectionGroupResponse'
{ $sel:httpStatus:UpdateProtectionGroupResponse' :: Int
httpStatus =
Int
pHttpStatus_
}
updateProtectionGroupResponse_httpStatus :: Lens.Lens' UpdateProtectionGroupResponse Prelude.Int
updateProtectionGroupResponse_httpStatus :: Lens' UpdateProtectionGroupResponse Int
updateProtectionGroupResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateProtectionGroupResponse' {Int
httpStatus :: Int
$sel:httpStatus:UpdateProtectionGroupResponse' :: UpdateProtectionGroupResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: UpdateProtectionGroupResponse
s@UpdateProtectionGroupResponse' {} Int
a -> UpdateProtectionGroupResponse
s {$sel:httpStatus:UpdateProtectionGroupResponse' :: Int
httpStatus = Int
a} :: UpdateProtectionGroupResponse)
instance Prelude.NFData UpdateProtectionGroupResponse where
rnf :: UpdateProtectionGroupResponse -> ()
rnf UpdateProtectionGroupResponse' {Int
httpStatus :: Int
$sel:httpStatus:UpdateProtectionGroupResponse' :: UpdateProtectionGroupResponse -> Int
..} =
forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus