{-# 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.CognitoIdentityProvider.AdminDeleteUserAttributes
-- 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 the user attributes in a user pool as an administrator. Works on
-- any user.
--
-- Calling this action requires developer credentials.
module Amazonka.CognitoIdentityProvider.AdminDeleteUserAttributes
  ( -- * Creating a Request
    AdminDeleteUserAttributes (..),
    newAdminDeleteUserAttributes,

    -- * Request Lenses
    adminDeleteUserAttributes_userPoolId,
    adminDeleteUserAttributes_username,
    adminDeleteUserAttributes_userAttributeNames,

    -- * Destructuring the Response
    AdminDeleteUserAttributesResponse (..),
    newAdminDeleteUserAttributesResponse,

    -- * Response Lenses
    adminDeleteUserAttributesResponse_httpStatus,
  )
where

import Amazonka.CognitoIdentityProvider.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

-- | Represents the request to delete user attributes as an administrator.
--
-- /See:/ 'newAdminDeleteUserAttributes' smart constructor.
data AdminDeleteUserAttributes = AdminDeleteUserAttributes'
  { -- | The user pool ID for the user pool where you want to delete user
    -- attributes.
    AdminDeleteUserAttributes -> Text
userPoolId :: Prelude.Text,
    -- | The user name of the user from which you would like to delete
    -- attributes.
    AdminDeleteUserAttributes -> Sensitive Text
username :: Data.Sensitive Prelude.Text,
    -- | An array of strings representing the user attribute names you want to
    -- delete.
    --
    -- For custom attributes, you must prepend the @custom:@ prefix to the
    -- attribute name.
    AdminDeleteUserAttributes -> [Text]
userAttributeNames :: [Prelude.Text]
  }
  deriving (AdminDeleteUserAttributes -> AdminDeleteUserAttributes -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AdminDeleteUserAttributes -> AdminDeleteUserAttributes -> Bool
$c/= :: AdminDeleteUserAttributes -> AdminDeleteUserAttributes -> Bool
== :: AdminDeleteUserAttributes -> AdminDeleteUserAttributes -> Bool
$c== :: AdminDeleteUserAttributes -> AdminDeleteUserAttributes -> Bool
Prelude.Eq, Int -> AdminDeleteUserAttributes -> ShowS
[AdminDeleteUserAttributes] -> ShowS
AdminDeleteUserAttributes -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AdminDeleteUserAttributes] -> ShowS
$cshowList :: [AdminDeleteUserAttributes] -> ShowS
show :: AdminDeleteUserAttributes -> String
$cshow :: AdminDeleteUserAttributes -> String
showsPrec :: Int -> AdminDeleteUserAttributes -> ShowS
$cshowsPrec :: Int -> AdminDeleteUserAttributes -> ShowS
Prelude.Show, forall x.
Rep AdminDeleteUserAttributes x -> AdminDeleteUserAttributes
forall x.
AdminDeleteUserAttributes -> Rep AdminDeleteUserAttributes x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep AdminDeleteUserAttributes x -> AdminDeleteUserAttributes
$cfrom :: forall x.
AdminDeleteUserAttributes -> Rep AdminDeleteUserAttributes x
Prelude.Generic)

-- |
-- Create a value of 'AdminDeleteUserAttributes' 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:
--
-- 'userPoolId', 'adminDeleteUserAttributes_userPoolId' - The user pool ID for the user pool where you want to delete user
-- attributes.
--
-- 'username', 'adminDeleteUserAttributes_username' - The user name of the user from which you would like to delete
-- attributes.
--
-- 'userAttributeNames', 'adminDeleteUserAttributes_userAttributeNames' - An array of strings representing the user attribute names you want to
-- delete.
--
-- For custom attributes, you must prepend the @custom:@ prefix to the
-- attribute name.
newAdminDeleteUserAttributes ::
  -- | 'userPoolId'
  Prelude.Text ->
  -- | 'username'
  Prelude.Text ->
  AdminDeleteUserAttributes
newAdminDeleteUserAttributes :: Text -> Text -> AdminDeleteUserAttributes
newAdminDeleteUserAttributes Text
pUserPoolId_ Text
pUsername_ =
  AdminDeleteUserAttributes'
    { $sel:userPoolId:AdminDeleteUserAttributes' :: Text
userPoolId =
        Text
pUserPoolId_,
      $sel:username:AdminDeleteUserAttributes' :: Sensitive Text
username = forall a. Iso' (Sensitive a) a
Data._Sensitive forall t b. AReview t b -> b -> t
Lens.# Text
pUsername_,
      $sel:userAttributeNames:AdminDeleteUserAttributes' :: [Text]
userAttributeNames = forall a. Monoid a => a
Prelude.mempty
    }

-- | The user pool ID for the user pool where you want to delete user
-- attributes.
adminDeleteUserAttributes_userPoolId :: Lens.Lens' AdminDeleteUserAttributes Prelude.Text
adminDeleteUserAttributes_userPoolId :: Lens' AdminDeleteUserAttributes Text
adminDeleteUserAttributes_userPoolId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AdminDeleteUserAttributes' {Text
userPoolId :: Text
$sel:userPoolId:AdminDeleteUserAttributes' :: AdminDeleteUserAttributes -> Text
userPoolId} -> Text
userPoolId) (\s :: AdminDeleteUserAttributes
s@AdminDeleteUserAttributes' {} Text
a -> AdminDeleteUserAttributes
s {$sel:userPoolId:AdminDeleteUserAttributes' :: Text
userPoolId = Text
a} :: AdminDeleteUserAttributes)

-- | The user name of the user from which you would like to delete
-- attributes.
adminDeleteUserAttributes_username :: Lens.Lens' AdminDeleteUserAttributes Prelude.Text
adminDeleteUserAttributes_username :: Lens' AdminDeleteUserAttributes Text
adminDeleteUserAttributes_username = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AdminDeleteUserAttributes' {Sensitive Text
username :: Sensitive Text
$sel:username:AdminDeleteUserAttributes' :: AdminDeleteUserAttributes -> Sensitive Text
username} -> Sensitive Text
username) (\s :: AdminDeleteUserAttributes
s@AdminDeleteUserAttributes' {} Sensitive Text
a -> AdminDeleteUserAttributes
s {$sel:username:AdminDeleteUserAttributes' :: Sensitive Text
username = Sensitive Text
a} :: AdminDeleteUserAttributes) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a. Iso' (Sensitive a) a
Data._Sensitive

-- | An array of strings representing the user attribute names you want to
-- delete.
--
-- For custom attributes, you must prepend the @custom:@ prefix to the
-- attribute name.
adminDeleteUserAttributes_userAttributeNames :: Lens.Lens' AdminDeleteUserAttributes [Prelude.Text]
adminDeleteUserAttributes_userAttributeNames :: Lens' AdminDeleteUserAttributes [Text]
adminDeleteUserAttributes_userAttributeNames = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AdminDeleteUserAttributes' {[Text]
userAttributeNames :: [Text]
$sel:userAttributeNames:AdminDeleteUserAttributes' :: AdminDeleteUserAttributes -> [Text]
userAttributeNames} -> [Text]
userAttributeNames) (\s :: AdminDeleteUserAttributes
s@AdminDeleteUserAttributes' {} [Text]
a -> AdminDeleteUserAttributes
s {$sel:userAttributeNames:AdminDeleteUserAttributes' :: [Text]
userAttributeNames = [Text]
a} :: AdminDeleteUserAttributes) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

instance Core.AWSRequest AdminDeleteUserAttributes where
  type
    AWSResponse AdminDeleteUserAttributes =
      AdminDeleteUserAttributesResponse
  request :: (Service -> Service)
-> AdminDeleteUserAttributes -> Request AdminDeleteUserAttributes
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 AdminDeleteUserAttributes
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse AdminDeleteUserAttributes)))
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 -> AdminDeleteUserAttributesResponse
AdminDeleteUserAttributesResponse'
            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 AdminDeleteUserAttributes where
  hashWithSalt :: Int -> AdminDeleteUserAttributes -> Int
hashWithSalt Int
_salt AdminDeleteUserAttributes' {[Text]
Text
Sensitive Text
userAttributeNames :: [Text]
username :: Sensitive Text
userPoolId :: Text
$sel:userAttributeNames:AdminDeleteUserAttributes' :: AdminDeleteUserAttributes -> [Text]
$sel:username:AdminDeleteUserAttributes' :: AdminDeleteUserAttributes -> Sensitive Text
$sel:userPoolId:AdminDeleteUserAttributes' :: AdminDeleteUserAttributes -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
userPoolId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Sensitive Text
username
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [Text]
userAttributeNames

instance Prelude.NFData AdminDeleteUserAttributes where
  rnf :: AdminDeleteUserAttributes -> ()
rnf AdminDeleteUserAttributes' {[Text]
Text
Sensitive Text
userAttributeNames :: [Text]
username :: Sensitive Text
userPoolId :: Text
$sel:userAttributeNames:AdminDeleteUserAttributes' :: AdminDeleteUserAttributes -> [Text]
$sel:username:AdminDeleteUserAttributes' :: AdminDeleteUserAttributes -> Sensitive Text
$sel:userPoolId:AdminDeleteUserAttributes' :: AdminDeleteUserAttributes -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
userPoolId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Sensitive Text
username
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [Text]
userAttributeNames

instance Data.ToHeaders AdminDeleteUserAttributes where
  toHeaders :: AdminDeleteUserAttributes -> 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
"AWSCognitoIdentityProviderService.AdminDeleteUserAttributes" ::
                          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 AdminDeleteUserAttributes where
  toJSON :: AdminDeleteUserAttributes -> Value
toJSON AdminDeleteUserAttributes' {[Text]
Text
Sensitive Text
userAttributeNames :: [Text]
username :: Sensitive Text
userPoolId :: Text
$sel:userAttributeNames:AdminDeleteUserAttributes' :: AdminDeleteUserAttributes -> [Text]
$sel:username:AdminDeleteUserAttributes' :: AdminDeleteUserAttributes -> Sensitive Text
$sel:userPoolId:AdminDeleteUserAttributes' :: AdminDeleteUserAttributes -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just (Key
"UserPoolId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
userPoolId),
            forall a. a -> Maybe a
Prelude.Just (Key
"Username" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Sensitive Text
username),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"UserAttributeNames" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= [Text]
userAttributeNames)
          ]
      )

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

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

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

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

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

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