{-# 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.DeleteUserByPrincipalId
-- 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 user identified by its principal ID.
module Amazonka.QuickSight.DeleteUserByPrincipalId
  ( -- * Creating a Request
    DeleteUserByPrincipalId (..),
    newDeleteUserByPrincipalId,

    -- * Request Lenses
    deleteUserByPrincipalId_principalId,
    deleteUserByPrincipalId_awsAccountId,
    deleteUserByPrincipalId_namespace,

    -- * Destructuring the Response
    DeleteUserByPrincipalIdResponse (..),
    newDeleteUserByPrincipalIdResponse,

    -- * Response Lenses
    deleteUserByPrincipalIdResponse_requestId,
    deleteUserByPrincipalIdResponse_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:/ 'newDeleteUserByPrincipalId' smart constructor.
data DeleteUserByPrincipalId = DeleteUserByPrincipalId'
  { -- | The principal ID of the user.
    DeleteUserByPrincipalId -> Text
principalId :: Prelude.Text,
    -- | The ID for the Amazon Web Services account that the user is in.
    -- Currently, you use the ID for the Amazon Web Services account that
    -- contains your Amazon QuickSight account.
    DeleteUserByPrincipalId -> Text
awsAccountId :: Prelude.Text,
    -- | The namespace. Currently, you should set this to @default@.
    DeleteUserByPrincipalId -> Text
namespace :: Prelude.Text
  }
  deriving (DeleteUserByPrincipalId -> DeleteUserByPrincipalId -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteUserByPrincipalId -> DeleteUserByPrincipalId -> Bool
$c/= :: DeleteUserByPrincipalId -> DeleteUserByPrincipalId -> Bool
== :: DeleteUserByPrincipalId -> DeleteUserByPrincipalId -> Bool
$c== :: DeleteUserByPrincipalId -> DeleteUserByPrincipalId -> Bool
Prelude.Eq, ReadPrec [DeleteUserByPrincipalId]
ReadPrec DeleteUserByPrincipalId
Int -> ReadS DeleteUserByPrincipalId
ReadS [DeleteUserByPrincipalId]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteUserByPrincipalId]
$creadListPrec :: ReadPrec [DeleteUserByPrincipalId]
readPrec :: ReadPrec DeleteUserByPrincipalId
$creadPrec :: ReadPrec DeleteUserByPrincipalId
readList :: ReadS [DeleteUserByPrincipalId]
$creadList :: ReadS [DeleteUserByPrincipalId]
readsPrec :: Int -> ReadS DeleteUserByPrincipalId
$creadsPrec :: Int -> ReadS DeleteUserByPrincipalId
Prelude.Read, Int -> DeleteUserByPrincipalId -> ShowS
[DeleteUserByPrincipalId] -> ShowS
DeleteUserByPrincipalId -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteUserByPrincipalId] -> ShowS
$cshowList :: [DeleteUserByPrincipalId] -> ShowS
show :: DeleteUserByPrincipalId -> String
$cshow :: DeleteUserByPrincipalId -> String
showsPrec :: Int -> DeleteUserByPrincipalId -> ShowS
$cshowsPrec :: Int -> DeleteUserByPrincipalId -> ShowS
Prelude.Show, forall x. Rep DeleteUserByPrincipalId x -> DeleteUserByPrincipalId
forall x. DeleteUserByPrincipalId -> Rep DeleteUserByPrincipalId x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteUserByPrincipalId x -> DeleteUserByPrincipalId
$cfrom :: forall x. DeleteUserByPrincipalId -> Rep DeleteUserByPrincipalId x
Prelude.Generic)

-- |
-- Create a value of 'DeleteUserByPrincipalId' 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:
--
-- 'principalId', 'deleteUserByPrincipalId_principalId' - The principal ID of the user.
--
-- 'awsAccountId', 'deleteUserByPrincipalId_awsAccountId' - The ID for the Amazon Web Services account that the user is in.
-- Currently, you use the ID for the Amazon Web Services account that
-- contains your Amazon QuickSight account.
--
-- 'namespace', 'deleteUserByPrincipalId_namespace' - The namespace. Currently, you should set this to @default@.
newDeleteUserByPrincipalId ::
  -- | 'principalId'
  Prelude.Text ->
  -- | 'awsAccountId'
  Prelude.Text ->
  -- | 'namespace'
  Prelude.Text ->
  DeleteUserByPrincipalId
newDeleteUserByPrincipalId :: Text -> Text -> Text -> DeleteUserByPrincipalId
newDeleteUserByPrincipalId
  Text
pPrincipalId_
  Text
pAwsAccountId_
  Text
pNamespace_ =
    DeleteUserByPrincipalId'
      { $sel:principalId:DeleteUserByPrincipalId' :: Text
principalId =
          Text
pPrincipalId_,
        $sel:awsAccountId:DeleteUserByPrincipalId' :: Text
awsAccountId = Text
pAwsAccountId_,
        $sel:namespace:DeleteUserByPrincipalId' :: Text
namespace = Text
pNamespace_
      }

-- | The principal ID of the user.
deleteUserByPrincipalId_principalId :: Lens.Lens' DeleteUserByPrincipalId Prelude.Text
deleteUserByPrincipalId_principalId :: Lens' DeleteUserByPrincipalId Text
deleteUserByPrincipalId_principalId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteUserByPrincipalId' {Text
principalId :: Text
$sel:principalId:DeleteUserByPrincipalId' :: DeleteUserByPrincipalId -> Text
principalId} -> Text
principalId) (\s :: DeleteUserByPrincipalId
s@DeleteUserByPrincipalId' {} Text
a -> DeleteUserByPrincipalId
s {$sel:principalId:DeleteUserByPrincipalId' :: Text
principalId = Text
a} :: DeleteUserByPrincipalId)

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

-- | The namespace. Currently, you should set this to @default@.
deleteUserByPrincipalId_namespace :: Lens.Lens' DeleteUserByPrincipalId Prelude.Text
deleteUserByPrincipalId_namespace :: Lens' DeleteUserByPrincipalId Text
deleteUserByPrincipalId_namespace = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteUserByPrincipalId' {Text
namespace :: Text
$sel:namespace:DeleteUserByPrincipalId' :: DeleteUserByPrincipalId -> Text
namespace} -> Text
namespace) (\s :: DeleteUserByPrincipalId
s@DeleteUserByPrincipalId' {} Text
a -> DeleteUserByPrincipalId
s {$sel:namespace:DeleteUserByPrincipalId' :: Text
namespace = Text
a} :: DeleteUserByPrincipalId)

instance Core.AWSRequest DeleteUserByPrincipalId where
  type
    AWSResponse DeleteUserByPrincipalId =
      DeleteUserByPrincipalIdResponse
  request :: (Service -> Service)
-> DeleteUserByPrincipalId -> Request DeleteUserByPrincipalId
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 DeleteUserByPrincipalId
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DeleteUserByPrincipalId)))
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 -> DeleteUserByPrincipalIdResponse
DeleteUserByPrincipalIdResponse'
            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 DeleteUserByPrincipalId where
  hashWithSalt :: Int -> DeleteUserByPrincipalId -> Int
hashWithSalt Int
_salt DeleteUserByPrincipalId' {Text
namespace :: Text
awsAccountId :: Text
principalId :: Text
$sel:namespace:DeleteUserByPrincipalId' :: DeleteUserByPrincipalId -> Text
$sel:awsAccountId:DeleteUserByPrincipalId' :: DeleteUserByPrincipalId -> Text
$sel:principalId:DeleteUserByPrincipalId' :: DeleteUserByPrincipalId -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
principalId
      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 DeleteUserByPrincipalId where
  rnf :: DeleteUserByPrincipalId -> ()
rnf DeleteUserByPrincipalId' {Text
namespace :: Text
awsAccountId :: Text
principalId :: Text
$sel:namespace:DeleteUserByPrincipalId' :: DeleteUserByPrincipalId -> Text
$sel:awsAccountId:DeleteUserByPrincipalId' :: DeleteUserByPrincipalId -> Text
$sel:principalId:DeleteUserByPrincipalId' :: DeleteUserByPrincipalId -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
principalId
      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 DeleteUserByPrincipalId where
  toHeaders :: DeleteUserByPrincipalId -> 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 DeleteUserByPrincipalId where
  toPath :: DeleteUserByPrincipalId -> ByteString
toPath DeleteUserByPrincipalId' {Text
namespace :: Text
awsAccountId :: Text
principalId :: Text
$sel:namespace:DeleteUserByPrincipalId' :: DeleteUserByPrincipalId -> Text
$sel:awsAccountId:DeleteUserByPrincipalId' :: DeleteUserByPrincipalId -> Text
$sel:principalId:DeleteUserByPrincipalId' :: DeleteUserByPrincipalId -> 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
"/user-principals/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
principalId
      ]

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

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

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

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

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

instance
  Prelude.NFData
    DeleteUserByPrincipalIdResponse
  where
  rnf :: DeleteUserByPrincipalIdResponse -> ()
rnf DeleteUserByPrincipalIdResponse' {Int
Maybe Text
status :: Int
requestId :: Maybe Text
$sel:status:DeleteUserByPrincipalIdResponse' :: DeleteUserByPrincipalIdResponse -> Int
$sel:requestId:DeleteUserByPrincipalIdResponse' :: DeleteUserByPrincipalIdResponse -> 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