{-# 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.SES.DeleteIdentityPolicy
(
DeleteIdentityPolicy (..),
newDeleteIdentityPolicy,
deleteIdentityPolicy_identity,
deleteIdentityPolicy_policyName,
DeleteIdentityPolicyResponse (..),
newDeleteIdentityPolicyResponse,
deleteIdentityPolicyResponse_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.SES.Types
data DeleteIdentityPolicy = DeleteIdentityPolicy'
{
DeleteIdentityPolicy -> Text
identity :: Prelude.Text,
DeleteIdentityPolicy -> Text
policyName :: Prelude.Text
}
deriving (DeleteIdentityPolicy -> DeleteIdentityPolicy -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteIdentityPolicy -> DeleteIdentityPolicy -> Bool
$c/= :: DeleteIdentityPolicy -> DeleteIdentityPolicy -> Bool
== :: DeleteIdentityPolicy -> DeleteIdentityPolicy -> Bool
$c== :: DeleteIdentityPolicy -> DeleteIdentityPolicy -> Bool
Prelude.Eq, ReadPrec [DeleteIdentityPolicy]
ReadPrec DeleteIdentityPolicy
Int -> ReadS DeleteIdentityPolicy
ReadS [DeleteIdentityPolicy]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteIdentityPolicy]
$creadListPrec :: ReadPrec [DeleteIdentityPolicy]
readPrec :: ReadPrec DeleteIdentityPolicy
$creadPrec :: ReadPrec DeleteIdentityPolicy
readList :: ReadS [DeleteIdentityPolicy]
$creadList :: ReadS [DeleteIdentityPolicy]
readsPrec :: Int -> ReadS DeleteIdentityPolicy
$creadsPrec :: Int -> ReadS DeleteIdentityPolicy
Prelude.Read, Int -> DeleteIdentityPolicy -> ShowS
[DeleteIdentityPolicy] -> ShowS
DeleteIdentityPolicy -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteIdentityPolicy] -> ShowS
$cshowList :: [DeleteIdentityPolicy] -> ShowS
show :: DeleteIdentityPolicy -> String
$cshow :: DeleteIdentityPolicy -> String
showsPrec :: Int -> DeleteIdentityPolicy -> ShowS
$cshowsPrec :: Int -> DeleteIdentityPolicy -> ShowS
Prelude.Show, forall x. Rep DeleteIdentityPolicy x -> DeleteIdentityPolicy
forall x. DeleteIdentityPolicy -> Rep DeleteIdentityPolicy x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteIdentityPolicy x -> DeleteIdentityPolicy
$cfrom :: forall x. DeleteIdentityPolicy -> Rep DeleteIdentityPolicy x
Prelude.Generic)
newDeleteIdentityPolicy ::
Prelude.Text ->
Prelude.Text ->
DeleteIdentityPolicy
newDeleteIdentityPolicy :: Text -> Text -> DeleteIdentityPolicy
newDeleteIdentityPolicy Text
pIdentity_ Text
pPolicyName_ =
DeleteIdentityPolicy'
{ $sel:identity:DeleteIdentityPolicy' :: Text
identity = Text
pIdentity_,
$sel:policyName:DeleteIdentityPolicy' :: Text
policyName = Text
pPolicyName_
}
deleteIdentityPolicy_identity :: Lens.Lens' DeleteIdentityPolicy Prelude.Text
deleteIdentityPolicy_identity :: Lens' DeleteIdentityPolicy Text
deleteIdentityPolicy_identity = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteIdentityPolicy' {Text
identity :: Text
$sel:identity:DeleteIdentityPolicy' :: DeleteIdentityPolicy -> Text
identity} -> Text
identity) (\s :: DeleteIdentityPolicy
s@DeleteIdentityPolicy' {} Text
a -> DeleteIdentityPolicy
s {$sel:identity:DeleteIdentityPolicy' :: Text
identity = Text
a} :: DeleteIdentityPolicy)
deleteIdentityPolicy_policyName :: Lens.Lens' DeleteIdentityPolicy Prelude.Text
deleteIdentityPolicy_policyName :: Lens' DeleteIdentityPolicy Text
deleteIdentityPolicy_policyName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteIdentityPolicy' {Text
policyName :: Text
$sel:policyName:DeleteIdentityPolicy' :: DeleteIdentityPolicy -> Text
policyName} -> Text
policyName) (\s :: DeleteIdentityPolicy
s@DeleteIdentityPolicy' {} Text
a -> DeleteIdentityPolicy
s {$sel:policyName:DeleteIdentityPolicy' :: Text
policyName = Text
a} :: DeleteIdentityPolicy)
instance Core.AWSRequest DeleteIdentityPolicy where
type
AWSResponse DeleteIdentityPolicy =
DeleteIdentityPolicyResponse
request :: (Service -> Service)
-> DeleteIdentityPolicy -> Request DeleteIdentityPolicy
request Service -> Service
overrides =
forall a. ToRequest a => Service -> a -> Request a
Request.postQuery (Service -> Service
overrides Service
defaultService)
response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DeleteIdentityPolicy
-> ClientResponse ClientBody
-> m (Either
Error (ClientResponse (AWSResponse DeleteIdentityPolicy)))
response =
forall (m :: * -> *) a.
MonadResource m =>
Text
-> (Int
-> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXMLWrapper
Text
"DeleteIdentityPolicyResult"
( \Int
s ResponseHeaders
h [Node]
x ->
Int -> DeleteIdentityPolicyResponse
DeleteIdentityPolicyResponse'
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 DeleteIdentityPolicy where
hashWithSalt :: Int -> DeleteIdentityPolicy -> Int
hashWithSalt Int
_salt DeleteIdentityPolicy' {Text
policyName :: Text
identity :: Text
$sel:policyName:DeleteIdentityPolicy' :: DeleteIdentityPolicy -> Text
$sel:identity:DeleteIdentityPolicy' :: DeleteIdentityPolicy -> Text
..} =
Int
_salt
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
identity
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
policyName
instance Prelude.NFData DeleteIdentityPolicy where
rnf :: DeleteIdentityPolicy -> ()
rnf DeleteIdentityPolicy' {Text
policyName :: Text
identity :: Text
$sel:policyName:DeleteIdentityPolicy' :: DeleteIdentityPolicy -> Text
$sel:identity:DeleteIdentityPolicy' :: DeleteIdentityPolicy -> Text
..} =
forall a. NFData a => a -> ()
Prelude.rnf Text
identity
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
policyName
instance Data.ToHeaders DeleteIdentityPolicy where
toHeaders :: DeleteIdentityPolicy -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
instance Data.ToPath DeleteIdentityPolicy where
toPath :: DeleteIdentityPolicy -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"
instance Data.ToQuery DeleteIdentityPolicy where
toQuery :: DeleteIdentityPolicy -> QueryString
toQuery DeleteIdentityPolicy' {Text
policyName :: Text
identity :: Text
$sel:policyName:DeleteIdentityPolicy' :: DeleteIdentityPolicy -> Text
$sel:identity:DeleteIdentityPolicy' :: DeleteIdentityPolicy -> Text
..} =
forall a. Monoid a => [a] -> a
Prelude.mconcat
[ ByteString
"Action"
forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"DeleteIdentityPolicy" :: Prelude.ByteString),
ByteString
"Version"
forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2010-12-01" :: Prelude.ByteString),
ByteString
"Identity" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
identity,
ByteString
"PolicyName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
policyName
]
data DeleteIdentityPolicyResponse = DeleteIdentityPolicyResponse'
{
DeleteIdentityPolicyResponse -> Int
httpStatus :: Prelude.Int
}
deriving (DeleteIdentityPolicyResponse
-> DeleteIdentityPolicyResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteIdentityPolicyResponse
-> DeleteIdentityPolicyResponse -> Bool
$c/= :: DeleteIdentityPolicyResponse
-> DeleteIdentityPolicyResponse -> Bool
== :: DeleteIdentityPolicyResponse
-> DeleteIdentityPolicyResponse -> Bool
$c== :: DeleteIdentityPolicyResponse
-> DeleteIdentityPolicyResponse -> Bool
Prelude.Eq, ReadPrec [DeleteIdentityPolicyResponse]
ReadPrec DeleteIdentityPolicyResponse
Int -> ReadS DeleteIdentityPolicyResponse
ReadS [DeleteIdentityPolicyResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteIdentityPolicyResponse]
$creadListPrec :: ReadPrec [DeleteIdentityPolicyResponse]
readPrec :: ReadPrec DeleteIdentityPolicyResponse
$creadPrec :: ReadPrec DeleteIdentityPolicyResponse
readList :: ReadS [DeleteIdentityPolicyResponse]
$creadList :: ReadS [DeleteIdentityPolicyResponse]
readsPrec :: Int -> ReadS DeleteIdentityPolicyResponse
$creadsPrec :: Int -> ReadS DeleteIdentityPolicyResponse
Prelude.Read, Int -> DeleteIdentityPolicyResponse -> ShowS
[DeleteIdentityPolicyResponse] -> ShowS
DeleteIdentityPolicyResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteIdentityPolicyResponse] -> ShowS
$cshowList :: [DeleteIdentityPolicyResponse] -> ShowS
show :: DeleteIdentityPolicyResponse -> String
$cshow :: DeleteIdentityPolicyResponse -> String
showsPrec :: Int -> DeleteIdentityPolicyResponse -> ShowS
$cshowsPrec :: Int -> DeleteIdentityPolicyResponse -> ShowS
Prelude.Show, forall x.
Rep DeleteIdentityPolicyResponse x -> DeleteIdentityPolicyResponse
forall x.
DeleteIdentityPolicyResponse -> Rep DeleteIdentityPolicyResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeleteIdentityPolicyResponse x -> DeleteIdentityPolicyResponse
$cfrom :: forall x.
DeleteIdentityPolicyResponse -> Rep DeleteIdentityPolicyResponse x
Prelude.Generic)
newDeleteIdentityPolicyResponse ::
Prelude.Int ->
DeleteIdentityPolicyResponse
newDeleteIdentityPolicyResponse :: Int -> DeleteIdentityPolicyResponse
newDeleteIdentityPolicyResponse Int
pHttpStatus_ =
DeleteIdentityPolicyResponse'
{ $sel:httpStatus:DeleteIdentityPolicyResponse' :: Int
httpStatus =
Int
pHttpStatus_
}
deleteIdentityPolicyResponse_httpStatus :: Lens.Lens' DeleteIdentityPolicyResponse Prelude.Int
deleteIdentityPolicyResponse_httpStatus :: Lens' DeleteIdentityPolicyResponse Int
deleteIdentityPolicyResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteIdentityPolicyResponse' {Int
httpStatus :: Int
$sel:httpStatus:DeleteIdentityPolicyResponse' :: DeleteIdentityPolicyResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: DeleteIdentityPolicyResponse
s@DeleteIdentityPolicyResponse' {} Int
a -> DeleteIdentityPolicyResponse
s {$sel:httpStatus:DeleteIdentityPolicyResponse' :: Int
httpStatus = Int
a} :: DeleteIdentityPolicyResponse)
instance Prelude.NFData DeleteIdentityPolicyResponse where
rnf :: DeleteIdentityPolicyResponse -> ()
rnf DeleteIdentityPolicyResponse' {Int
httpStatus :: Int
$sel:httpStatus:DeleteIdentityPolicyResponse' :: DeleteIdentityPolicyResponse -> Int
..} =
forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus