{-# 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.FinSpaceData.DeletePermissionGroup
-- 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 a permission group. This action is irreversible.
module Amazonka.FinSpaceData.DeletePermissionGroup
  ( -- * Creating a Request
    DeletePermissionGroup (..),
    newDeletePermissionGroup,

    -- * Request Lenses
    deletePermissionGroup_clientToken,
    deletePermissionGroup_permissionGroupId,

    -- * Destructuring the Response
    DeletePermissionGroupResponse (..),
    newDeletePermissionGroupResponse,

    -- * Response Lenses
    deletePermissionGroupResponse_permissionGroupId,
    deletePermissionGroupResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.FinSpaceData.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newDeletePermissionGroup' smart constructor.
data DeletePermissionGroup = DeletePermissionGroup'
  { -- | A token that ensures idempotency. This token expires in 10 minutes.
    DeletePermissionGroup -> Maybe Text
clientToken :: Prelude.Maybe Prelude.Text,
    -- | The unique identifier for the permission group that you want to delete.
    DeletePermissionGroup -> Text
permissionGroupId :: Prelude.Text
  }
  deriving (DeletePermissionGroup -> DeletePermissionGroup -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeletePermissionGroup -> DeletePermissionGroup -> Bool
$c/= :: DeletePermissionGroup -> DeletePermissionGroup -> Bool
== :: DeletePermissionGroup -> DeletePermissionGroup -> Bool
$c== :: DeletePermissionGroup -> DeletePermissionGroup -> Bool
Prelude.Eq, ReadPrec [DeletePermissionGroup]
ReadPrec DeletePermissionGroup
Int -> ReadS DeletePermissionGroup
ReadS [DeletePermissionGroup]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeletePermissionGroup]
$creadListPrec :: ReadPrec [DeletePermissionGroup]
readPrec :: ReadPrec DeletePermissionGroup
$creadPrec :: ReadPrec DeletePermissionGroup
readList :: ReadS [DeletePermissionGroup]
$creadList :: ReadS [DeletePermissionGroup]
readsPrec :: Int -> ReadS DeletePermissionGroup
$creadsPrec :: Int -> ReadS DeletePermissionGroup
Prelude.Read, Int -> DeletePermissionGroup -> ShowS
[DeletePermissionGroup] -> ShowS
DeletePermissionGroup -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeletePermissionGroup] -> ShowS
$cshowList :: [DeletePermissionGroup] -> ShowS
show :: DeletePermissionGroup -> String
$cshow :: DeletePermissionGroup -> String
showsPrec :: Int -> DeletePermissionGroup -> ShowS
$cshowsPrec :: Int -> DeletePermissionGroup -> ShowS
Prelude.Show, forall x. Rep DeletePermissionGroup x -> DeletePermissionGroup
forall x. DeletePermissionGroup -> Rep DeletePermissionGroup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeletePermissionGroup x -> DeletePermissionGroup
$cfrom :: forall x. DeletePermissionGroup -> Rep DeletePermissionGroup x
Prelude.Generic)

-- |
-- Create a value of 'DeletePermissionGroup' 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:
--
-- 'clientToken', 'deletePermissionGroup_clientToken' - A token that ensures idempotency. This token expires in 10 minutes.
--
-- 'permissionGroupId', 'deletePermissionGroup_permissionGroupId' - The unique identifier for the permission group that you want to delete.
newDeletePermissionGroup ::
  -- | 'permissionGroupId'
  Prelude.Text ->
  DeletePermissionGroup
newDeletePermissionGroup :: Text -> DeletePermissionGroup
newDeletePermissionGroup Text
pPermissionGroupId_ =
  DeletePermissionGroup'
    { $sel:clientToken:DeletePermissionGroup' :: Maybe Text
clientToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:permissionGroupId:DeletePermissionGroup' :: Text
permissionGroupId = Text
pPermissionGroupId_
    }

-- | A token that ensures idempotency. This token expires in 10 minutes.
deletePermissionGroup_clientToken :: Lens.Lens' DeletePermissionGroup (Prelude.Maybe Prelude.Text)
deletePermissionGroup_clientToken :: Lens' DeletePermissionGroup (Maybe Text)
deletePermissionGroup_clientToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeletePermissionGroup' {Maybe Text
clientToken :: Maybe Text
$sel:clientToken:DeletePermissionGroup' :: DeletePermissionGroup -> Maybe Text
clientToken} -> Maybe Text
clientToken) (\s :: DeletePermissionGroup
s@DeletePermissionGroup' {} Maybe Text
a -> DeletePermissionGroup
s {$sel:clientToken:DeletePermissionGroup' :: Maybe Text
clientToken = Maybe Text
a} :: DeletePermissionGroup)

-- | The unique identifier for the permission group that you want to delete.
deletePermissionGroup_permissionGroupId :: Lens.Lens' DeletePermissionGroup Prelude.Text
deletePermissionGroup_permissionGroupId :: Lens' DeletePermissionGroup Text
deletePermissionGroup_permissionGroupId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeletePermissionGroup' {Text
permissionGroupId :: Text
$sel:permissionGroupId:DeletePermissionGroup' :: DeletePermissionGroup -> Text
permissionGroupId} -> Text
permissionGroupId) (\s :: DeletePermissionGroup
s@DeletePermissionGroup' {} Text
a -> DeletePermissionGroup
s {$sel:permissionGroupId:DeletePermissionGroup' :: Text
permissionGroupId = Text
a} :: DeletePermissionGroup)

instance Core.AWSRequest DeletePermissionGroup where
  type
    AWSResponse DeletePermissionGroup =
      DeletePermissionGroupResponse
  request :: (Service -> Service)
-> DeletePermissionGroup -> Request DeletePermissionGroup
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.delete (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DeletePermissionGroup
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DeletePermissionGroup)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe Text -> Int -> DeletePermissionGroupResponse
DeletePermissionGroupResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"permissionGroupId")
            forall (f :: * -> *) a b. Applicative f => 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 DeletePermissionGroup where
  hashWithSalt :: Int -> DeletePermissionGroup -> Int
hashWithSalt Int
_salt DeletePermissionGroup' {Maybe Text
Text
permissionGroupId :: Text
clientToken :: Maybe Text
$sel:permissionGroupId:DeletePermissionGroup' :: DeletePermissionGroup -> Text
$sel:clientToken:DeletePermissionGroup' :: DeletePermissionGroup -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
clientToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
permissionGroupId

instance Prelude.NFData DeletePermissionGroup where
  rnf :: DeletePermissionGroup -> ()
rnf DeletePermissionGroup' {Maybe Text
Text
permissionGroupId :: Text
clientToken :: Maybe Text
$sel:permissionGroupId:DeletePermissionGroup' :: DeletePermissionGroup -> Text
$sel:clientToken:DeletePermissionGroup' :: DeletePermissionGroup -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
clientToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
permissionGroupId

instance Data.ToHeaders DeletePermissionGroup where
  toHeaders :: DeletePermissionGroup -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToPath DeletePermissionGroup where
  toPath :: DeletePermissionGroup -> ByteString
toPath DeletePermissionGroup' {Maybe Text
Text
permissionGroupId :: Text
clientToken :: Maybe Text
$sel:permissionGroupId:DeletePermissionGroup' :: DeletePermissionGroup -> Text
$sel:clientToken:DeletePermissionGroup' :: DeletePermissionGroup -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/permission-group/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
permissionGroupId]

instance Data.ToQuery DeletePermissionGroup where
  toQuery :: DeletePermissionGroup -> QueryString
toQuery DeletePermissionGroup' {Maybe Text
Text
permissionGroupId :: Text
clientToken :: Maybe Text
$sel:permissionGroupId:DeletePermissionGroup' :: DeletePermissionGroup -> Text
$sel:clientToken:DeletePermissionGroup' :: DeletePermissionGroup -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat [ByteString
"clientToken" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
clientToken]

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

-- |
-- Create a value of 'DeletePermissionGroupResponse' 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:
--
-- 'permissionGroupId', 'deletePermissionGroupResponse_permissionGroupId' - The unique identifier for the deleted permission group.
--
-- 'httpStatus', 'deletePermissionGroupResponse_httpStatus' - The response's http status code.
newDeletePermissionGroupResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DeletePermissionGroupResponse
newDeletePermissionGroupResponse :: Int -> DeletePermissionGroupResponse
newDeletePermissionGroupResponse Int
pHttpStatus_ =
  DeletePermissionGroupResponse'
    { $sel:permissionGroupId:DeletePermissionGroupResponse' :: Maybe Text
permissionGroupId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DeletePermissionGroupResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The unique identifier for the deleted permission group.
deletePermissionGroupResponse_permissionGroupId :: Lens.Lens' DeletePermissionGroupResponse (Prelude.Maybe Prelude.Text)
deletePermissionGroupResponse_permissionGroupId :: Lens' DeletePermissionGroupResponse (Maybe Text)
deletePermissionGroupResponse_permissionGroupId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeletePermissionGroupResponse' {Maybe Text
permissionGroupId :: Maybe Text
$sel:permissionGroupId:DeletePermissionGroupResponse' :: DeletePermissionGroupResponse -> Maybe Text
permissionGroupId} -> Maybe Text
permissionGroupId) (\s :: DeletePermissionGroupResponse
s@DeletePermissionGroupResponse' {} Maybe Text
a -> DeletePermissionGroupResponse
s {$sel:permissionGroupId:DeletePermissionGroupResponse' :: Maybe Text
permissionGroupId = Maybe Text
a} :: DeletePermissionGroupResponse)

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

instance Prelude.NFData DeletePermissionGroupResponse where
  rnf :: DeletePermissionGroupResponse -> ()
rnf DeletePermissionGroupResponse' {Int
Maybe Text
httpStatus :: Int
permissionGroupId :: Maybe Text
$sel:httpStatus:DeletePermissionGroupResponse' :: DeletePermissionGroupResponse -> Int
$sel:permissionGroupId:DeletePermissionGroupResponse' :: DeletePermissionGroupResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
permissionGroupId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus