{-# 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.WorkMail.DeleteImpersonationRole
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Deletes an impersonation role for the given WorkMail organization.
module Amazonka.WorkMail.DeleteImpersonationRole
  ( -- * Creating a Request
    DeleteImpersonationRole (..),
    newDeleteImpersonationRole,

    -- * Request Lenses
    deleteImpersonationRole_organizationId,
    deleteImpersonationRole_impersonationRoleId,

    -- * Destructuring the Response
    DeleteImpersonationRoleResponse (..),
    newDeleteImpersonationRoleResponse,

    -- * Response Lenses
    deleteImpersonationRoleResponse_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.WorkMail.Types

-- | /See:/ 'newDeleteImpersonationRole' smart constructor.
data DeleteImpersonationRole = DeleteImpersonationRole'
  { -- | The WorkMail organization from which to delete the impersonation role.
    DeleteImpersonationRole -> Text
organizationId :: Prelude.Text,
    -- | The ID of the impersonation role to delete.
    DeleteImpersonationRole -> Text
impersonationRoleId :: Prelude.Text
  }
  deriving (DeleteImpersonationRole -> DeleteImpersonationRole -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteImpersonationRole -> DeleteImpersonationRole -> Bool
$c/= :: DeleteImpersonationRole -> DeleteImpersonationRole -> Bool
== :: DeleteImpersonationRole -> DeleteImpersonationRole -> Bool
$c== :: DeleteImpersonationRole -> DeleteImpersonationRole -> Bool
Prelude.Eq, ReadPrec [DeleteImpersonationRole]
ReadPrec DeleteImpersonationRole
Int -> ReadS DeleteImpersonationRole
ReadS [DeleteImpersonationRole]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteImpersonationRole]
$creadListPrec :: ReadPrec [DeleteImpersonationRole]
readPrec :: ReadPrec DeleteImpersonationRole
$creadPrec :: ReadPrec DeleteImpersonationRole
readList :: ReadS [DeleteImpersonationRole]
$creadList :: ReadS [DeleteImpersonationRole]
readsPrec :: Int -> ReadS DeleteImpersonationRole
$creadsPrec :: Int -> ReadS DeleteImpersonationRole
Prelude.Read, Int -> DeleteImpersonationRole -> ShowS
[DeleteImpersonationRole] -> ShowS
DeleteImpersonationRole -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteImpersonationRole] -> ShowS
$cshowList :: [DeleteImpersonationRole] -> ShowS
show :: DeleteImpersonationRole -> String
$cshow :: DeleteImpersonationRole -> String
showsPrec :: Int -> DeleteImpersonationRole -> ShowS
$cshowsPrec :: Int -> DeleteImpersonationRole -> ShowS
Prelude.Show, forall x. Rep DeleteImpersonationRole x -> DeleteImpersonationRole
forall x. DeleteImpersonationRole -> Rep DeleteImpersonationRole x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteImpersonationRole x -> DeleteImpersonationRole
$cfrom :: forall x. DeleteImpersonationRole -> Rep DeleteImpersonationRole x
Prelude.Generic)

-- |
-- Create a value of 'DeleteImpersonationRole' 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:
--
-- 'organizationId', 'deleteImpersonationRole_organizationId' - The WorkMail organization from which to delete the impersonation role.
--
-- 'impersonationRoleId', 'deleteImpersonationRole_impersonationRoleId' - The ID of the impersonation role to delete.
newDeleteImpersonationRole ::
  -- | 'organizationId'
  Prelude.Text ->
  -- | 'impersonationRoleId'
  Prelude.Text ->
  DeleteImpersonationRole
newDeleteImpersonationRole :: Text -> Text -> DeleteImpersonationRole
newDeleteImpersonationRole
  Text
pOrganizationId_
  Text
pImpersonationRoleId_ =
    DeleteImpersonationRole'
      { $sel:organizationId:DeleteImpersonationRole' :: Text
organizationId =
          Text
pOrganizationId_,
        $sel:impersonationRoleId:DeleteImpersonationRole' :: Text
impersonationRoleId = Text
pImpersonationRoleId_
      }

-- | The WorkMail organization from which to delete the impersonation role.
deleteImpersonationRole_organizationId :: Lens.Lens' DeleteImpersonationRole Prelude.Text
deleteImpersonationRole_organizationId :: Lens' DeleteImpersonationRole Text
deleteImpersonationRole_organizationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteImpersonationRole' {Text
organizationId :: Text
$sel:organizationId:DeleteImpersonationRole' :: DeleteImpersonationRole -> Text
organizationId} -> Text
organizationId) (\s :: DeleteImpersonationRole
s@DeleteImpersonationRole' {} Text
a -> DeleteImpersonationRole
s {$sel:organizationId:DeleteImpersonationRole' :: Text
organizationId = Text
a} :: DeleteImpersonationRole)

-- | The ID of the impersonation role to delete.
deleteImpersonationRole_impersonationRoleId :: Lens.Lens' DeleteImpersonationRole Prelude.Text
deleteImpersonationRole_impersonationRoleId :: Lens' DeleteImpersonationRole Text
deleteImpersonationRole_impersonationRoleId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteImpersonationRole' {Text
impersonationRoleId :: Text
$sel:impersonationRoleId:DeleteImpersonationRole' :: DeleteImpersonationRole -> Text
impersonationRoleId} -> Text
impersonationRoleId) (\s :: DeleteImpersonationRole
s@DeleteImpersonationRole' {} Text
a -> DeleteImpersonationRole
s {$sel:impersonationRoleId:DeleteImpersonationRole' :: Text
impersonationRoleId = Text
a} :: DeleteImpersonationRole)

instance Core.AWSRequest DeleteImpersonationRole where
  type
    AWSResponse DeleteImpersonationRole =
      DeleteImpersonationRoleResponse
  request :: (Service -> Service)
-> DeleteImpersonationRole -> Request DeleteImpersonationRole
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 DeleteImpersonationRole
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DeleteImpersonationRole)))
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 -> DeleteImpersonationRoleResponse
DeleteImpersonationRoleResponse'
            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 DeleteImpersonationRole where
  hashWithSalt :: Int -> DeleteImpersonationRole -> Int
hashWithSalt Int
_salt DeleteImpersonationRole' {Text
impersonationRoleId :: Text
organizationId :: Text
$sel:impersonationRoleId:DeleteImpersonationRole' :: DeleteImpersonationRole -> Text
$sel:organizationId:DeleteImpersonationRole' :: DeleteImpersonationRole -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
organizationId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
impersonationRoleId

instance Prelude.NFData DeleteImpersonationRole where
  rnf :: DeleteImpersonationRole -> ()
rnf DeleteImpersonationRole' {Text
impersonationRoleId :: Text
organizationId :: Text
$sel:impersonationRoleId:DeleteImpersonationRole' :: DeleteImpersonationRole -> Text
$sel:organizationId:DeleteImpersonationRole' :: DeleteImpersonationRole -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
organizationId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
impersonationRoleId

instance Data.ToHeaders DeleteImpersonationRole where
  toHeaders :: DeleteImpersonationRole -> 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
"WorkMailService.DeleteImpersonationRole" ::
                          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 DeleteImpersonationRole where
  toJSON :: DeleteImpersonationRole -> Value
toJSON DeleteImpersonationRole' {Text
impersonationRoleId :: Text
organizationId :: Text
$sel:impersonationRoleId:DeleteImpersonationRole' :: DeleteImpersonationRole -> Text
$sel:organizationId:DeleteImpersonationRole' :: DeleteImpersonationRole -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just
              (Key
"OrganizationId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
organizationId),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"ImpersonationRoleId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
impersonationRoleId)
          ]
      )

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

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

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

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

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

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