{-# 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.QuickSight.DeleteGroup
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Removes a user group from Amazon QuickSight.
module Amazonka.QuickSight.DeleteGroup
  ( -- * Creating a Request
    DeleteGroup (..),
    newDeleteGroup,

    -- * Request Lenses
    deleteGroup_groupName,
    deleteGroup_awsAccountId,
    deleteGroup_namespace,

    -- * Destructuring the Response
    DeleteGroupResponse (..),
    newDeleteGroupResponse,

    -- * Response Lenses
    deleteGroupResponse_requestId,
    deleteGroupResponse_status,
  )
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 Amazonka.QuickSight.Types
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newDeleteGroup' smart constructor.
data DeleteGroup = DeleteGroup'
  { -- | The name of the group that you want to delete.
    DeleteGroup -> Text
groupName :: Prelude.Text,
    -- | The ID for the Amazon Web Services account that the group is in.
    -- Currently, you use the ID for the Amazon Web Services account that
    -- contains your Amazon QuickSight account.
    DeleteGroup -> Text
awsAccountId :: Prelude.Text,
    -- | The namespace of the group that you want to delete.
    DeleteGroup -> Text
namespace :: Prelude.Text
  }
  deriving (DeleteGroup -> DeleteGroup -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteGroup -> DeleteGroup -> Bool
$c/= :: DeleteGroup -> DeleteGroup -> Bool
== :: DeleteGroup -> DeleteGroup -> Bool
$c== :: DeleteGroup -> DeleteGroup -> Bool
Prelude.Eq, ReadPrec [DeleteGroup]
ReadPrec DeleteGroup
Int -> ReadS DeleteGroup
ReadS [DeleteGroup]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteGroup]
$creadListPrec :: ReadPrec [DeleteGroup]
readPrec :: ReadPrec DeleteGroup
$creadPrec :: ReadPrec DeleteGroup
readList :: ReadS [DeleteGroup]
$creadList :: ReadS [DeleteGroup]
readsPrec :: Int -> ReadS DeleteGroup
$creadsPrec :: Int -> ReadS DeleteGroup
Prelude.Read, Int -> DeleteGroup -> ShowS
[DeleteGroup] -> ShowS
DeleteGroup -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteGroup] -> ShowS
$cshowList :: [DeleteGroup] -> ShowS
show :: DeleteGroup -> String
$cshow :: DeleteGroup -> String
showsPrec :: Int -> DeleteGroup -> ShowS
$cshowsPrec :: Int -> DeleteGroup -> ShowS
Prelude.Show, forall x. Rep DeleteGroup x -> DeleteGroup
forall x. DeleteGroup -> Rep DeleteGroup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteGroup x -> DeleteGroup
$cfrom :: forall x. DeleteGroup -> Rep DeleteGroup x
Prelude.Generic)

-- |
-- Create a value of 'DeleteGroup' 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:
--
-- 'groupName', 'deleteGroup_groupName' - The name of the group that you want to delete.
--
-- 'awsAccountId', 'deleteGroup_awsAccountId' - The ID for the Amazon Web Services account that the group is in.
-- Currently, you use the ID for the Amazon Web Services account that
-- contains your Amazon QuickSight account.
--
-- 'namespace', 'deleteGroup_namespace' - The namespace of the group that you want to delete.
newDeleteGroup ::
  -- | 'groupName'
  Prelude.Text ->
  -- | 'awsAccountId'
  Prelude.Text ->
  -- | 'namespace'
  Prelude.Text ->
  DeleteGroup
newDeleteGroup :: Text -> Text -> Text -> DeleteGroup
newDeleteGroup Text
pGroupName_ Text
pAwsAccountId_ Text
pNamespace_ =
  DeleteGroup'
    { $sel:groupName:DeleteGroup' :: Text
groupName = Text
pGroupName_,
      $sel:awsAccountId:DeleteGroup' :: Text
awsAccountId = Text
pAwsAccountId_,
      $sel:namespace:DeleteGroup' :: Text
namespace = Text
pNamespace_
    }

-- | The name of the group that you want to delete.
deleteGroup_groupName :: Lens.Lens' DeleteGroup Prelude.Text
deleteGroup_groupName :: Lens' DeleteGroup Text
deleteGroup_groupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteGroup' {Text
groupName :: Text
$sel:groupName:DeleteGroup' :: DeleteGroup -> Text
groupName} -> Text
groupName) (\s :: DeleteGroup
s@DeleteGroup' {} Text
a -> DeleteGroup
s {$sel:groupName:DeleteGroup' :: Text
groupName = Text
a} :: DeleteGroup)

-- | The ID for the Amazon Web Services account that the group is in.
-- Currently, you use the ID for the Amazon Web Services account that
-- contains your Amazon QuickSight account.
deleteGroup_awsAccountId :: Lens.Lens' DeleteGroup Prelude.Text
deleteGroup_awsAccountId :: Lens' DeleteGroup Text
deleteGroup_awsAccountId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteGroup' {Text
awsAccountId :: Text
$sel:awsAccountId:DeleteGroup' :: DeleteGroup -> Text
awsAccountId} -> Text
awsAccountId) (\s :: DeleteGroup
s@DeleteGroup' {} Text
a -> DeleteGroup
s {$sel:awsAccountId:DeleteGroup' :: Text
awsAccountId = Text
a} :: DeleteGroup)

-- | The namespace of the group that you want to delete.
deleteGroup_namespace :: Lens.Lens' DeleteGroup Prelude.Text
deleteGroup_namespace :: Lens' DeleteGroup Text
deleteGroup_namespace = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteGroup' {Text
namespace :: Text
$sel:namespace:DeleteGroup' :: DeleteGroup -> Text
namespace} -> Text
namespace) (\s :: DeleteGroup
s@DeleteGroup' {} Text
a -> DeleteGroup
s {$sel:namespace:DeleteGroup' :: Text
namespace = Text
a} :: DeleteGroup)

instance Core.AWSRequest DeleteGroup where
  type AWSResponse DeleteGroup = DeleteGroupResponse
  request :: (Service -> Service) -> DeleteGroup -> Request DeleteGroup
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 DeleteGroup
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DeleteGroup)))
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 -> DeleteGroupResponse
DeleteGroupResponse'
            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
"RequestId")
            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 DeleteGroup where
  hashWithSalt :: Int -> DeleteGroup -> Int
hashWithSalt Int
_salt DeleteGroup' {Text
namespace :: Text
awsAccountId :: Text
groupName :: Text
$sel:namespace:DeleteGroup' :: DeleteGroup -> Text
$sel:awsAccountId:DeleteGroup' :: DeleteGroup -> Text
$sel:groupName:DeleteGroup' :: DeleteGroup -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
groupName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
awsAccountId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
namespace

instance Prelude.NFData DeleteGroup where
  rnf :: DeleteGroup -> ()
rnf DeleteGroup' {Text
namespace :: Text
awsAccountId :: Text
groupName :: Text
$sel:namespace:DeleteGroup' :: DeleteGroup -> Text
$sel:awsAccountId:DeleteGroup' :: DeleteGroup -> Text
$sel:groupName:DeleteGroup' :: DeleteGroup -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
groupName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
awsAccountId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
namespace

instance Data.ToHeaders DeleteGroup where
  toHeaders :: DeleteGroup -> 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.0" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToPath DeleteGroup where
  toPath :: DeleteGroup -> ByteString
toPath DeleteGroup' {Text
namespace :: Text
awsAccountId :: Text
groupName :: Text
$sel:namespace:DeleteGroup' :: DeleteGroup -> Text
$sel:awsAccountId:DeleteGroup' :: DeleteGroup -> Text
$sel:groupName:DeleteGroup' :: DeleteGroup -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/accounts/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
awsAccountId,
        ByteString
"/namespaces/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
namespace,
        ByteString
"/groups/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
groupName
      ]

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

-- | /See:/ 'newDeleteGroupResponse' smart constructor.
data DeleteGroupResponse = DeleteGroupResponse'
  { -- | The Amazon Web Services request ID for this operation.
    DeleteGroupResponse -> Maybe Text
requestId :: Prelude.Maybe Prelude.Text,
    -- | The HTTP status of the request.
    DeleteGroupResponse -> Int
status :: Prelude.Int
  }
  deriving (DeleteGroupResponse -> DeleteGroupResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteGroupResponse -> DeleteGroupResponse -> Bool
$c/= :: DeleteGroupResponse -> DeleteGroupResponse -> Bool
== :: DeleteGroupResponse -> DeleteGroupResponse -> Bool
$c== :: DeleteGroupResponse -> DeleteGroupResponse -> Bool
Prelude.Eq, ReadPrec [DeleteGroupResponse]
ReadPrec DeleteGroupResponse
Int -> ReadS DeleteGroupResponse
ReadS [DeleteGroupResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteGroupResponse]
$creadListPrec :: ReadPrec [DeleteGroupResponse]
readPrec :: ReadPrec DeleteGroupResponse
$creadPrec :: ReadPrec DeleteGroupResponse
readList :: ReadS [DeleteGroupResponse]
$creadList :: ReadS [DeleteGroupResponse]
readsPrec :: Int -> ReadS DeleteGroupResponse
$creadsPrec :: Int -> ReadS DeleteGroupResponse
Prelude.Read, Int -> DeleteGroupResponse -> ShowS
[DeleteGroupResponse] -> ShowS
DeleteGroupResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteGroupResponse] -> ShowS
$cshowList :: [DeleteGroupResponse] -> ShowS
show :: DeleteGroupResponse -> String
$cshow :: DeleteGroupResponse -> String
showsPrec :: Int -> DeleteGroupResponse -> ShowS
$cshowsPrec :: Int -> DeleteGroupResponse -> ShowS
Prelude.Show, forall x. Rep DeleteGroupResponse x -> DeleteGroupResponse
forall x. DeleteGroupResponse -> Rep DeleteGroupResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteGroupResponse x -> DeleteGroupResponse
$cfrom :: forall x. DeleteGroupResponse -> Rep DeleteGroupResponse x
Prelude.Generic)

-- |
-- Create a value of 'DeleteGroupResponse' 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:
--
-- 'requestId', 'deleteGroupResponse_requestId' - The Amazon Web Services request ID for this operation.
--
-- 'status', 'deleteGroupResponse_status' - The HTTP status of the request.
newDeleteGroupResponse ::
  -- | 'status'
  Prelude.Int ->
  DeleteGroupResponse
newDeleteGroupResponse :: Int -> DeleteGroupResponse
newDeleteGroupResponse Int
pStatus_ =
  DeleteGroupResponse'
    { $sel:requestId:DeleteGroupResponse' :: Maybe Text
requestId = forall a. Maybe a
Prelude.Nothing,
      $sel:status:DeleteGroupResponse' :: Int
status = Int
pStatus_
    }

-- | The Amazon Web Services request ID for this operation.
deleteGroupResponse_requestId :: Lens.Lens' DeleteGroupResponse (Prelude.Maybe Prelude.Text)
deleteGroupResponse_requestId :: Lens' DeleteGroupResponse (Maybe Text)
deleteGroupResponse_requestId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteGroupResponse' {Maybe Text
requestId :: Maybe Text
$sel:requestId:DeleteGroupResponse' :: DeleteGroupResponse -> Maybe Text
requestId} -> Maybe Text
requestId) (\s :: DeleteGroupResponse
s@DeleteGroupResponse' {} Maybe Text
a -> DeleteGroupResponse
s {$sel:requestId:DeleteGroupResponse' :: Maybe Text
requestId = Maybe Text
a} :: DeleteGroupResponse)

-- | The HTTP status of the request.
deleteGroupResponse_status :: Lens.Lens' DeleteGroupResponse Prelude.Int
deleteGroupResponse_status :: Lens' DeleteGroupResponse Int
deleteGroupResponse_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteGroupResponse' {Int
status :: Int
$sel:status:DeleteGroupResponse' :: DeleteGroupResponse -> Int
status} -> Int
status) (\s :: DeleteGroupResponse
s@DeleteGroupResponse' {} Int
a -> DeleteGroupResponse
s {$sel:status:DeleteGroupResponse' :: Int
status = Int
a} :: DeleteGroupResponse)

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