{-# 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.DeleteUserPoolClient
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Allows the developer to delete the user pool client.
module Amazonka.CognitoIdentityProvider.DeleteUserPoolClient
  ( -- * Creating a Request
    DeleteUserPoolClient (..),
    newDeleteUserPoolClient,

    -- * Request Lenses
    deleteUserPoolClient_userPoolId,
    deleteUserPoolClient_clientId,

    -- * Destructuring the Response
    DeleteUserPoolClientResponse (..),
    newDeleteUserPoolClientResponse,
  )
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 a user pool client.
--
-- /See:/ 'newDeleteUserPoolClient' smart constructor.
data DeleteUserPoolClient = DeleteUserPoolClient'
  { -- | The user pool ID for the user pool where you want to delete the client.
    DeleteUserPoolClient -> Text
userPoolId :: Prelude.Text,
    -- | The app client ID of the app associated with the user pool.
    DeleteUserPoolClient -> Sensitive Text
clientId :: Data.Sensitive Prelude.Text
  }
  deriving (DeleteUserPoolClient -> DeleteUserPoolClient -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteUserPoolClient -> DeleteUserPoolClient -> Bool
$c/= :: DeleteUserPoolClient -> DeleteUserPoolClient -> Bool
== :: DeleteUserPoolClient -> DeleteUserPoolClient -> Bool
$c== :: DeleteUserPoolClient -> DeleteUserPoolClient -> Bool
Prelude.Eq, Int -> DeleteUserPoolClient -> ShowS
[DeleteUserPoolClient] -> ShowS
DeleteUserPoolClient -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteUserPoolClient] -> ShowS
$cshowList :: [DeleteUserPoolClient] -> ShowS
show :: DeleteUserPoolClient -> String
$cshow :: DeleteUserPoolClient -> String
showsPrec :: Int -> DeleteUserPoolClient -> ShowS
$cshowsPrec :: Int -> DeleteUserPoolClient -> ShowS
Prelude.Show, forall x. Rep DeleteUserPoolClient x -> DeleteUserPoolClient
forall x. DeleteUserPoolClient -> Rep DeleteUserPoolClient x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteUserPoolClient x -> DeleteUserPoolClient
$cfrom :: forall x. DeleteUserPoolClient -> Rep DeleteUserPoolClient x
Prelude.Generic)

-- |
-- Create a value of 'DeleteUserPoolClient' 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', 'deleteUserPoolClient_userPoolId' - The user pool ID for the user pool where you want to delete the client.
--
-- 'clientId', 'deleteUserPoolClient_clientId' - The app client ID of the app associated with the user pool.
newDeleteUserPoolClient ::
  -- | 'userPoolId'
  Prelude.Text ->
  -- | 'clientId'
  Prelude.Text ->
  DeleteUserPoolClient
newDeleteUserPoolClient :: Text -> Text -> DeleteUserPoolClient
newDeleteUserPoolClient Text
pUserPoolId_ Text
pClientId_ =
  DeleteUserPoolClient'
    { $sel:userPoolId:DeleteUserPoolClient' :: Text
userPoolId = Text
pUserPoolId_,
      $sel:clientId:DeleteUserPoolClient' :: Sensitive Text
clientId = forall a. Iso' (Sensitive a) a
Data._Sensitive forall t b. AReview t b -> b -> t
Lens.# Text
pClientId_
    }

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

-- | The app client ID of the app associated with the user pool.
deleteUserPoolClient_clientId :: Lens.Lens' DeleteUserPoolClient Prelude.Text
deleteUserPoolClient_clientId :: Lens' DeleteUserPoolClient Text
deleteUserPoolClient_clientId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteUserPoolClient' {Sensitive Text
clientId :: Sensitive Text
$sel:clientId:DeleteUserPoolClient' :: DeleteUserPoolClient -> Sensitive Text
clientId} -> Sensitive Text
clientId) (\s :: DeleteUserPoolClient
s@DeleteUserPoolClient' {} Sensitive Text
a -> DeleteUserPoolClient
s {$sel:clientId:DeleteUserPoolClient' :: Sensitive Text
clientId = Sensitive Text
a} :: DeleteUserPoolClient) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a. Iso' (Sensitive a) a
Data._Sensitive

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

instance Prelude.Hashable DeleteUserPoolClient where
  hashWithSalt :: Int -> DeleteUserPoolClient -> Int
hashWithSalt Int
_salt DeleteUserPoolClient' {Text
Sensitive Text
clientId :: Sensitive Text
userPoolId :: Text
$sel:clientId:DeleteUserPoolClient' :: DeleteUserPoolClient -> Sensitive Text
$sel:userPoolId:DeleteUserPoolClient' :: DeleteUserPoolClient -> 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
clientId

instance Prelude.NFData DeleteUserPoolClient where
  rnf :: DeleteUserPoolClient -> ()
rnf DeleteUserPoolClient' {Text
Sensitive Text
clientId :: Sensitive Text
userPoolId :: Text
$sel:clientId:DeleteUserPoolClient' :: DeleteUserPoolClient -> Sensitive Text
$sel:userPoolId:DeleteUserPoolClient' :: DeleteUserPoolClient -> 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
clientId

instance Data.ToHeaders DeleteUserPoolClient where
  toHeaders :: DeleteUserPoolClient -> [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
"AWSCognitoIdentityProviderService.DeleteUserPoolClient" ::
                          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 DeleteUserPoolClient where
  toJSON :: DeleteUserPoolClient -> Value
toJSON DeleteUserPoolClient' {Text
Sensitive Text
clientId :: Sensitive Text
userPoolId :: Text
$sel:clientId:DeleteUserPoolClient' :: DeleteUserPoolClient -> Sensitive Text
$sel:userPoolId:DeleteUserPoolClient' :: DeleteUserPoolClient -> 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
"ClientId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Sensitive Text
clientId)
          ]
      )

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

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

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

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

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