{-# 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.CloudWatchEvents.RemovePermission
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Revokes the permission of another Amazon Web Services account to be able
-- to put events to the specified event bus. Specify the account to revoke
-- by the @StatementId@ value that you associated with the account when you
-- granted it permission with @PutPermission@. You can find the
-- @StatementId@ by using
-- <https://docs.aws.amazon.com/eventbridge/latest/APIReference/API_DescribeEventBus.html DescribeEventBus>.
module Amazonka.CloudWatchEvents.RemovePermission
  ( -- * Creating a Request
    RemovePermission (..),
    newRemovePermission,

    -- * Request Lenses
    removePermission_eventBusName,
    removePermission_removeAllPermissions,
    removePermission_statementId,

    -- * Destructuring the Response
    RemovePermissionResponse (..),
    newRemovePermissionResponse,
  )
where

import Amazonka.CloudWatchEvents.Types
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

-- | /See:/ 'newRemovePermission' smart constructor.
data RemovePermission = RemovePermission'
  { -- | The name of the event bus to revoke permissions for. If you omit this,
    -- the default event bus is used.
    RemovePermission -> Maybe Text
eventBusName :: Prelude.Maybe Prelude.Text,
    -- | Specifies whether to remove all permissions.
    RemovePermission -> Maybe Bool
removeAllPermissions :: Prelude.Maybe Prelude.Bool,
    -- | The statement ID corresponding to the account that is no longer allowed
    -- to put events to the default event bus.
    RemovePermission -> Maybe Text
statementId :: Prelude.Maybe Prelude.Text
  }
  deriving (RemovePermission -> RemovePermission -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RemovePermission -> RemovePermission -> Bool
$c/= :: RemovePermission -> RemovePermission -> Bool
== :: RemovePermission -> RemovePermission -> Bool
$c== :: RemovePermission -> RemovePermission -> Bool
Prelude.Eq, ReadPrec [RemovePermission]
ReadPrec RemovePermission
Int -> ReadS RemovePermission
ReadS [RemovePermission]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RemovePermission]
$creadListPrec :: ReadPrec [RemovePermission]
readPrec :: ReadPrec RemovePermission
$creadPrec :: ReadPrec RemovePermission
readList :: ReadS [RemovePermission]
$creadList :: ReadS [RemovePermission]
readsPrec :: Int -> ReadS RemovePermission
$creadsPrec :: Int -> ReadS RemovePermission
Prelude.Read, Int -> RemovePermission -> ShowS
[RemovePermission] -> ShowS
RemovePermission -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RemovePermission] -> ShowS
$cshowList :: [RemovePermission] -> ShowS
show :: RemovePermission -> String
$cshow :: RemovePermission -> String
showsPrec :: Int -> RemovePermission -> ShowS
$cshowsPrec :: Int -> RemovePermission -> ShowS
Prelude.Show, forall x. Rep RemovePermission x -> RemovePermission
forall x. RemovePermission -> Rep RemovePermission x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RemovePermission x -> RemovePermission
$cfrom :: forall x. RemovePermission -> Rep RemovePermission x
Prelude.Generic)

-- |
-- Create a value of 'RemovePermission' 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:
--
-- 'eventBusName', 'removePermission_eventBusName' - The name of the event bus to revoke permissions for. If you omit this,
-- the default event bus is used.
--
-- 'removeAllPermissions', 'removePermission_removeAllPermissions' - Specifies whether to remove all permissions.
--
-- 'statementId', 'removePermission_statementId' - The statement ID corresponding to the account that is no longer allowed
-- to put events to the default event bus.
newRemovePermission ::
  RemovePermission
newRemovePermission :: RemovePermission
newRemovePermission =
  RemovePermission'
    { $sel:eventBusName:RemovePermission' :: Maybe Text
eventBusName = forall a. Maybe a
Prelude.Nothing,
      $sel:removeAllPermissions:RemovePermission' :: Maybe Bool
removeAllPermissions = forall a. Maybe a
Prelude.Nothing,
      $sel:statementId:RemovePermission' :: Maybe Text
statementId = forall a. Maybe a
Prelude.Nothing
    }

-- | The name of the event bus to revoke permissions for. If you omit this,
-- the default event bus is used.
removePermission_eventBusName :: Lens.Lens' RemovePermission (Prelude.Maybe Prelude.Text)
removePermission_eventBusName :: Lens' RemovePermission (Maybe Text)
removePermission_eventBusName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RemovePermission' {Maybe Text
eventBusName :: Maybe Text
$sel:eventBusName:RemovePermission' :: RemovePermission -> Maybe Text
eventBusName} -> Maybe Text
eventBusName) (\s :: RemovePermission
s@RemovePermission' {} Maybe Text
a -> RemovePermission
s {$sel:eventBusName:RemovePermission' :: Maybe Text
eventBusName = Maybe Text
a} :: RemovePermission)

-- | Specifies whether to remove all permissions.
removePermission_removeAllPermissions :: Lens.Lens' RemovePermission (Prelude.Maybe Prelude.Bool)
removePermission_removeAllPermissions :: Lens' RemovePermission (Maybe Bool)
removePermission_removeAllPermissions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RemovePermission' {Maybe Bool
removeAllPermissions :: Maybe Bool
$sel:removeAllPermissions:RemovePermission' :: RemovePermission -> Maybe Bool
removeAllPermissions} -> Maybe Bool
removeAllPermissions) (\s :: RemovePermission
s@RemovePermission' {} Maybe Bool
a -> RemovePermission
s {$sel:removeAllPermissions:RemovePermission' :: Maybe Bool
removeAllPermissions = Maybe Bool
a} :: RemovePermission)

-- | The statement ID corresponding to the account that is no longer allowed
-- to put events to the default event bus.
removePermission_statementId :: Lens.Lens' RemovePermission (Prelude.Maybe Prelude.Text)
removePermission_statementId :: Lens' RemovePermission (Maybe Text)
removePermission_statementId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RemovePermission' {Maybe Text
statementId :: Maybe Text
$sel:statementId:RemovePermission' :: RemovePermission -> Maybe Text
statementId} -> Maybe Text
statementId) (\s :: RemovePermission
s@RemovePermission' {} Maybe Text
a -> RemovePermission
s {$sel:statementId:RemovePermission' :: Maybe Text
statementId = Maybe Text
a} :: RemovePermission)

instance Core.AWSRequest RemovePermission where
  type
    AWSResponse RemovePermission =
      RemovePermissionResponse
  request :: (Service -> Service)
-> RemovePermission -> Request RemovePermission
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 RemovePermission
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse RemovePermission)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull RemovePermissionResponse
RemovePermissionResponse'

instance Prelude.Hashable RemovePermission where
  hashWithSalt :: Int -> RemovePermission -> Int
hashWithSalt Int
_salt RemovePermission' {Maybe Bool
Maybe Text
statementId :: Maybe Text
removeAllPermissions :: Maybe Bool
eventBusName :: Maybe Text
$sel:statementId:RemovePermission' :: RemovePermission -> Maybe Text
$sel:removeAllPermissions:RemovePermission' :: RemovePermission -> Maybe Bool
$sel:eventBusName:RemovePermission' :: RemovePermission -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
eventBusName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
removeAllPermissions
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
statementId

instance Prelude.NFData RemovePermission where
  rnf :: RemovePermission -> ()
rnf RemovePermission' {Maybe Bool
Maybe Text
statementId :: Maybe Text
removeAllPermissions :: Maybe Bool
eventBusName :: Maybe Text
$sel:statementId:RemovePermission' :: RemovePermission -> Maybe Text
$sel:removeAllPermissions:RemovePermission' :: RemovePermission -> Maybe Bool
$sel:eventBusName:RemovePermission' :: RemovePermission -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
eventBusName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
removeAllPermissions
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
statementId

instance Data.ToHeaders RemovePermission where
  toHeaders :: RemovePermission -> [Header]
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 -> [Header]
Data.=# (ByteString
"AWSEvents.RemovePermission" :: Prelude.ByteString),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> [Header]
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON RemovePermission where
  toJSON :: RemovePermission -> Value
toJSON RemovePermission' {Maybe Bool
Maybe Text
statementId :: Maybe Text
removeAllPermissions :: Maybe Bool
eventBusName :: Maybe Text
$sel:statementId:RemovePermission' :: RemovePermission -> Maybe Text
$sel:removeAllPermissions:RemovePermission' :: RemovePermission -> Maybe Bool
$sel:eventBusName:RemovePermission' :: RemovePermission -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"EventBusName" 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
eventBusName,
            (Key
"RemoveAllPermissions" 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 Bool
removeAllPermissions,
            (Key
"StatementId" 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
statementId
          ]
      )

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

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

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

-- |
-- Create a value of 'RemovePermissionResponse' 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.
newRemovePermissionResponse ::
  RemovePermissionResponse
newRemovePermissionResponse :: RemovePermissionResponse
newRemovePermissionResponse =
  RemovePermissionResponse
RemovePermissionResponse'

instance Prelude.NFData RemovePermissionResponse where
  rnf :: RemovePermissionResponse -> ()
rnf RemovePermissionResponse
_ = ()