{-# 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.AdminUserGlobalSignOut
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Signs out a user from all devices. You must sign
-- @AdminUserGlobalSignOut@ requests with Amazon Web Services credentials.
-- It also invalidates all refresh tokens that Amazon Cognito has issued to
-- a user. The user\'s current access and ID tokens remain valid until they
-- expire. By default, access and ID tokens expire one hour after they\'re
-- issued. A user can still use a hosted UI cookie to retrieve new tokens
-- for the duration of the cookie validity period of 1 hour.
--
-- Calling this action requires developer credentials.
module Amazonka.CognitoIdentityProvider.AdminUserGlobalSignOut
  ( -- * Creating a Request
    AdminUserGlobalSignOut (..),
    newAdminUserGlobalSignOut,

    -- * Request Lenses
    adminUserGlobalSignOut_userPoolId,
    adminUserGlobalSignOut_username,

    -- * Destructuring the Response
    AdminUserGlobalSignOutResponse (..),
    newAdminUserGlobalSignOutResponse,

    -- * Response Lenses
    adminUserGlobalSignOutResponse_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

-- | The request to sign out of all devices, as an administrator.
--
-- /See:/ 'newAdminUserGlobalSignOut' smart constructor.
data AdminUserGlobalSignOut = AdminUserGlobalSignOut'
  { -- | The user pool ID.
    AdminUserGlobalSignOut -> Text
userPoolId :: Prelude.Text,
    -- | The user name.
    AdminUserGlobalSignOut -> Sensitive Text
username :: Data.Sensitive Prelude.Text
  }
  deriving (AdminUserGlobalSignOut -> AdminUserGlobalSignOut -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AdminUserGlobalSignOut -> AdminUserGlobalSignOut -> Bool
$c/= :: AdminUserGlobalSignOut -> AdminUserGlobalSignOut -> Bool
== :: AdminUserGlobalSignOut -> AdminUserGlobalSignOut -> Bool
$c== :: AdminUserGlobalSignOut -> AdminUserGlobalSignOut -> Bool
Prelude.Eq, Int -> AdminUserGlobalSignOut -> ShowS
[AdminUserGlobalSignOut] -> ShowS
AdminUserGlobalSignOut -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AdminUserGlobalSignOut] -> ShowS
$cshowList :: [AdminUserGlobalSignOut] -> ShowS
show :: AdminUserGlobalSignOut -> String
$cshow :: AdminUserGlobalSignOut -> String
showsPrec :: Int -> AdminUserGlobalSignOut -> ShowS
$cshowsPrec :: Int -> AdminUserGlobalSignOut -> ShowS
Prelude.Show, forall x. Rep AdminUserGlobalSignOut x -> AdminUserGlobalSignOut
forall x. AdminUserGlobalSignOut -> Rep AdminUserGlobalSignOut x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AdminUserGlobalSignOut x -> AdminUserGlobalSignOut
$cfrom :: forall x. AdminUserGlobalSignOut -> Rep AdminUserGlobalSignOut x
Prelude.Generic)

-- |
-- Create a value of 'AdminUserGlobalSignOut' 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', 'adminUserGlobalSignOut_userPoolId' - The user pool ID.
--
-- 'username', 'adminUserGlobalSignOut_username' - The user name.
newAdminUserGlobalSignOut ::
  -- | 'userPoolId'
  Prelude.Text ->
  -- | 'username'
  Prelude.Text ->
  AdminUserGlobalSignOut
newAdminUserGlobalSignOut :: Text -> Text -> AdminUserGlobalSignOut
newAdminUserGlobalSignOut Text
pUserPoolId_ Text
pUsername_ =
  AdminUserGlobalSignOut'
    { $sel:userPoolId:AdminUserGlobalSignOut' :: Text
userPoolId = Text
pUserPoolId_,
      $sel:username:AdminUserGlobalSignOut' :: Sensitive Text
username = forall a. Iso' (Sensitive a) a
Data._Sensitive forall t b. AReview t b -> b -> t
Lens.# Text
pUsername_
    }

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

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

instance Core.AWSRequest AdminUserGlobalSignOut where
  type
    AWSResponse AdminUserGlobalSignOut =
      AdminUserGlobalSignOutResponse
  request :: (Service -> Service)
-> AdminUserGlobalSignOut -> Request AdminUserGlobalSignOut
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 AdminUserGlobalSignOut
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse AdminUserGlobalSignOut)))
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 -> AdminUserGlobalSignOutResponse
AdminUserGlobalSignOutResponse'
            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 AdminUserGlobalSignOut where
  hashWithSalt :: Int -> AdminUserGlobalSignOut -> Int
hashWithSalt Int
_salt AdminUserGlobalSignOut' {Text
Sensitive Text
username :: Sensitive Text
userPoolId :: Text
$sel:username:AdminUserGlobalSignOut' :: AdminUserGlobalSignOut -> Sensitive Text
$sel:userPoolId:AdminUserGlobalSignOut' :: AdminUserGlobalSignOut -> 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

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

instance Data.ToHeaders AdminUserGlobalSignOut where
  toHeaders :: AdminUserGlobalSignOut -> 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.AdminUserGlobalSignOut" ::
                          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 AdminUserGlobalSignOut where
  toJSON :: AdminUserGlobalSignOut -> Value
toJSON AdminUserGlobalSignOut' {Text
Sensitive Text
username :: Sensitive Text
userPoolId :: Text
$sel:username:AdminUserGlobalSignOut' :: AdminUserGlobalSignOut -> Sensitive Text
$sel:userPoolId:AdminUserGlobalSignOut' :: AdminUserGlobalSignOut -> 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)
          ]
      )

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

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

-- | The global sign-out response, as an administrator.
--
-- /See:/ 'newAdminUserGlobalSignOutResponse' smart constructor.
data AdminUserGlobalSignOutResponse = AdminUserGlobalSignOutResponse'
  { -- | The response's http status code.
    AdminUserGlobalSignOutResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (AdminUserGlobalSignOutResponse
-> AdminUserGlobalSignOutResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AdminUserGlobalSignOutResponse
-> AdminUserGlobalSignOutResponse -> Bool
$c/= :: AdminUserGlobalSignOutResponse
-> AdminUserGlobalSignOutResponse -> Bool
== :: AdminUserGlobalSignOutResponse
-> AdminUserGlobalSignOutResponse -> Bool
$c== :: AdminUserGlobalSignOutResponse
-> AdminUserGlobalSignOutResponse -> Bool
Prelude.Eq, ReadPrec [AdminUserGlobalSignOutResponse]
ReadPrec AdminUserGlobalSignOutResponse
Int -> ReadS AdminUserGlobalSignOutResponse
ReadS [AdminUserGlobalSignOutResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AdminUserGlobalSignOutResponse]
$creadListPrec :: ReadPrec [AdminUserGlobalSignOutResponse]
readPrec :: ReadPrec AdminUserGlobalSignOutResponse
$creadPrec :: ReadPrec AdminUserGlobalSignOutResponse
readList :: ReadS [AdminUserGlobalSignOutResponse]
$creadList :: ReadS [AdminUserGlobalSignOutResponse]
readsPrec :: Int -> ReadS AdminUserGlobalSignOutResponse
$creadsPrec :: Int -> ReadS AdminUserGlobalSignOutResponse
Prelude.Read, Int -> AdminUserGlobalSignOutResponse -> ShowS
[AdminUserGlobalSignOutResponse] -> ShowS
AdminUserGlobalSignOutResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AdminUserGlobalSignOutResponse] -> ShowS
$cshowList :: [AdminUserGlobalSignOutResponse] -> ShowS
show :: AdminUserGlobalSignOutResponse -> String
$cshow :: AdminUserGlobalSignOutResponse -> String
showsPrec :: Int -> AdminUserGlobalSignOutResponse -> ShowS
$cshowsPrec :: Int -> AdminUserGlobalSignOutResponse -> ShowS
Prelude.Show, forall x.
Rep AdminUserGlobalSignOutResponse x
-> AdminUserGlobalSignOutResponse
forall x.
AdminUserGlobalSignOutResponse
-> Rep AdminUserGlobalSignOutResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep AdminUserGlobalSignOutResponse x
-> AdminUserGlobalSignOutResponse
$cfrom :: forall x.
AdminUserGlobalSignOutResponse
-> Rep AdminUserGlobalSignOutResponse x
Prelude.Generic)

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

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

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