{-# 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.ForgetDevice
-- 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 specified device.
module Amazonka.CognitoIdentityProvider.ForgetDevice
  ( -- * Creating a Request
    ForgetDevice (..),
    newForgetDevice,

    -- * Request Lenses
    forgetDevice_accessToken,
    forgetDevice_deviceKey,

    -- * Destructuring the Response
    ForgetDeviceResponse (..),
    newForgetDeviceResponse,
  )
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 forget the device.
--
-- /See:/ 'newForgetDevice' smart constructor.
data ForgetDevice = ForgetDevice'
  { -- | A valid access token that Amazon Cognito issued to the user whose
    -- registered device you want to forget.
    ForgetDevice -> Maybe (Sensitive Text)
accessToken :: Prelude.Maybe (Data.Sensitive Prelude.Text),
    -- | The device key.
    ForgetDevice -> Text
deviceKey :: Prelude.Text
  }
  deriving (ForgetDevice -> ForgetDevice -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ForgetDevice -> ForgetDevice -> Bool
$c/= :: ForgetDevice -> ForgetDevice -> Bool
== :: ForgetDevice -> ForgetDevice -> Bool
$c== :: ForgetDevice -> ForgetDevice -> Bool
Prelude.Eq, Int -> ForgetDevice -> ShowS
[ForgetDevice] -> ShowS
ForgetDevice -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ForgetDevice] -> ShowS
$cshowList :: [ForgetDevice] -> ShowS
show :: ForgetDevice -> String
$cshow :: ForgetDevice -> String
showsPrec :: Int -> ForgetDevice -> ShowS
$cshowsPrec :: Int -> ForgetDevice -> ShowS
Prelude.Show, forall x. Rep ForgetDevice x -> ForgetDevice
forall x. ForgetDevice -> Rep ForgetDevice x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ForgetDevice x -> ForgetDevice
$cfrom :: forall x. ForgetDevice -> Rep ForgetDevice x
Prelude.Generic)

-- |
-- Create a value of 'ForgetDevice' 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:
--
-- 'accessToken', 'forgetDevice_accessToken' - A valid access token that Amazon Cognito issued to the user whose
-- registered device you want to forget.
--
-- 'deviceKey', 'forgetDevice_deviceKey' - The device key.
newForgetDevice ::
  -- | 'deviceKey'
  Prelude.Text ->
  ForgetDevice
newForgetDevice :: Text -> ForgetDevice
newForgetDevice Text
pDeviceKey_ =
  ForgetDevice'
    { $sel:accessToken:ForgetDevice' :: Maybe (Sensitive Text)
accessToken = forall a. Maybe a
Prelude.Nothing,
      $sel:deviceKey:ForgetDevice' :: Text
deviceKey = Text
pDeviceKey_
    }

-- | A valid access token that Amazon Cognito issued to the user whose
-- registered device you want to forget.
forgetDevice_accessToken :: Lens.Lens' ForgetDevice (Prelude.Maybe Prelude.Text)
forgetDevice_accessToken :: Lens' ForgetDevice (Maybe Text)
forgetDevice_accessToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ForgetDevice' {Maybe (Sensitive Text)
accessToken :: Maybe (Sensitive Text)
$sel:accessToken:ForgetDevice' :: ForgetDevice -> Maybe (Sensitive Text)
accessToken} -> Maybe (Sensitive Text)
accessToken) (\s :: ForgetDevice
s@ForgetDevice' {} Maybe (Sensitive Text)
a -> ForgetDevice
s {$sel:accessToken:ForgetDevice' :: Maybe (Sensitive Text)
accessToken = Maybe (Sensitive Text)
a} :: ForgetDevice) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall a. Iso' (Sensitive a) a
Data._Sensitive

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

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

instance Prelude.Hashable ForgetDevice where
  hashWithSalt :: Int -> ForgetDevice -> Int
hashWithSalt Int
_salt ForgetDevice' {Maybe (Sensitive Text)
Text
deviceKey :: Text
accessToken :: Maybe (Sensitive Text)
$sel:deviceKey:ForgetDevice' :: ForgetDevice -> Text
$sel:accessToken:ForgetDevice' :: ForgetDevice -> Maybe (Sensitive Text)
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (Sensitive Text)
accessToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
deviceKey

instance Prelude.NFData ForgetDevice where
  rnf :: ForgetDevice -> ()
rnf ForgetDevice' {Maybe (Sensitive Text)
Text
deviceKey :: Text
accessToken :: Maybe (Sensitive Text)
$sel:deviceKey:ForgetDevice' :: ForgetDevice -> Text
$sel:accessToken:ForgetDevice' :: ForgetDevice -> Maybe (Sensitive Text)
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe (Sensitive Text)
accessToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
deviceKey

instance Data.ToHeaders ForgetDevice where
  toHeaders :: ForgetDevice -> [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.ForgetDevice" ::
                          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 ForgetDevice where
  toJSON :: ForgetDevice -> Value
toJSON ForgetDevice' {Maybe (Sensitive Text)
Text
deviceKey :: Text
accessToken :: Maybe (Sensitive Text)
$sel:deviceKey:ForgetDevice' :: ForgetDevice -> Text
$sel:accessToken:ForgetDevice' :: ForgetDevice -> Maybe (Sensitive Text)
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"AccessToken" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Sensitive Text)
accessToken,
            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 ForgetDevice where
  toPath :: ForgetDevice -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

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

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

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