{-# 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.AdminForgetDevice
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Forgets the device, as an administrator.
--
-- Calling this action requires developer credentials.
module Amazonka.CognitoIdentityProvider.AdminForgetDevice
  ( -- * Creating a Request
    AdminForgetDevice (..),
    newAdminForgetDevice,

    -- * Request Lenses
    adminForgetDevice_userPoolId,
    adminForgetDevice_username,
    adminForgetDevice_deviceKey,

    -- * Destructuring the Response
    AdminForgetDeviceResponse (..),
    newAdminForgetDeviceResponse,
  )
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

-- | Sends the forgot device request, as an administrator.
--
-- /See:/ 'newAdminForgetDevice' smart constructor.
data AdminForgetDevice = AdminForgetDevice'
  { -- | The user pool ID.
    AdminForgetDevice -> Text
userPoolId :: Prelude.Text,
    -- | The user name.
    AdminForgetDevice -> Sensitive Text
username :: Data.Sensitive Prelude.Text,
    -- | The device key.
    AdminForgetDevice -> Text
deviceKey :: Prelude.Text
  }
  deriving (AdminForgetDevice -> AdminForgetDevice -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AdminForgetDevice -> AdminForgetDevice -> Bool
$c/= :: AdminForgetDevice -> AdminForgetDevice -> Bool
== :: AdminForgetDevice -> AdminForgetDevice -> Bool
$c== :: AdminForgetDevice -> AdminForgetDevice -> Bool
Prelude.Eq, Int -> AdminForgetDevice -> ShowS
[AdminForgetDevice] -> ShowS
AdminForgetDevice -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AdminForgetDevice] -> ShowS
$cshowList :: [AdminForgetDevice] -> ShowS
show :: AdminForgetDevice -> String
$cshow :: AdminForgetDevice -> String
showsPrec :: Int -> AdminForgetDevice -> ShowS
$cshowsPrec :: Int -> AdminForgetDevice -> ShowS
Prelude.Show, forall x. Rep AdminForgetDevice x -> AdminForgetDevice
forall x. AdminForgetDevice -> Rep AdminForgetDevice x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AdminForgetDevice x -> AdminForgetDevice
$cfrom :: forall x. AdminForgetDevice -> Rep AdminForgetDevice x
Prelude.Generic)

-- |
-- Create a value of 'AdminForgetDevice' 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', 'adminForgetDevice_userPoolId' - The user pool ID.
--
-- 'username', 'adminForgetDevice_username' - The user name.
--
-- 'deviceKey', 'adminForgetDevice_deviceKey' - The device key.
newAdminForgetDevice ::
  -- | 'userPoolId'
  Prelude.Text ->
  -- | 'username'
  Prelude.Text ->
  -- | 'deviceKey'
  Prelude.Text ->
  AdminForgetDevice
newAdminForgetDevice :: Text -> Text -> Text -> AdminForgetDevice
newAdminForgetDevice
  Text
pUserPoolId_
  Text
pUsername_
  Text
pDeviceKey_ =
    AdminForgetDevice'
      { $sel:userPoolId:AdminForgetDevice' :: Text
userPoolId = Text
pUserPoolId_,
        $sel:username:AdminForgetDevice' :: Sensitive Text
username = forall a. Iso' (Sensitive a) a
Data._Sensitive forall t b. AReview t b -> b -> t
Lens.# Text
pUsername_,
        $sel:deviceKey:AdminForgetDevice' :: Text
deviceKey = Text
pDeviceKey_
      }

-- | The user pool ID.
adminForgetDevice_userPoolId :: Lens.Lens' AdminForgetDevice Prelude.Text
adminForgetDevice_userPoolId :: Lens' AdminForgetDevice Text
adminForgetDevice_userPoolId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AdminForgetDevice' {Text
userPoolId :: Text
$sel:userPoolId:AdminForgetDevice' :: AdminForgetDevice -> Text
userPoolId} -> Text
userPoolId) (\s :: AdminForgetDevice
s@AdminForgetDevice' {} Text
a -> AdminForgetDevice
s {$sel:userPoolId:AdminForgetDevice' :: Text
userPoolId = Text
a} :: AdminForgetDevice)

-- | The user name.
adminForgetDevice_username :: Lens.Lens' AdminForgetDevice Prelude.Text
adminForgetDevice_username :: Lens' AdminForgetDevice Text
adminForgetDevice_username = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AdminForgetDevice' {Sensitive Text
username :: Sensitive Text
$sel:username:AdminForgetDevice' :: AdminForgetDevice -> Sensitive Text
username} -> Sensitive Text
username) (\s :: AdminForgetDevice
s@AdminForgetDevice' {} Sensitive Text
a -> AdminForgetDevice
s {$sel:username:AdminForgetDevice' :: Sensitive Text
username = Sensitive Text
a} :: AdminForgetDevice) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a. Iso' (Sensitive a) a
Data._Sensitive

-- | The device key.
adminForgetDevice_deviceKey :: Lens.Lens' AdminForgetDevice Prelude.Text
adminForgetDevice_deviceKey :: Lens' AdminForgetDevice Text
adminForgetDevice_deviceKey = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AdminForgetDevice' {Text
deviceKey :: Text
$sel:deviceKey:AdminForgetDevice' :: AdminForgetDevice -> Text
deviceKey} -> Text
deviceKey) (\s :: AdminForgetDevice
s@AdminForgetDevice' {} Text
a -> AdminForgetDevice
s {$sel:deviceKey:AdminForgetDevice' :: Text
deviceKey = Text
a} :: AdminForgetDevice)

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

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

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

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

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

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

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

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

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