{-# 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.AdminSetUserSettings
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- /This action is no longer supported./ You can use it to configure only
-- SMS MFA. You can\'t use it to configure time-based one-time password
-- (TOTP) software token MFA. To configure either type of MFA, use
-- <https://docs.aws.amazon.com/cognito-user-identity-pools/latest/APIReference/API_AdminSetUserMFAPreference.html AdminSetUserMFAPreference>
-- instead.
module Amazonka.CognitoIdentityProvider.AdminSetUserSettings
  ( -- * Creating a Request
    AdminSetUserSettings (..),
    newAdminSetUserSettings,

    -- * Request Lenses
    adminSetUserSettings_userPoolId,
    adminSetUserSettings_username,
    adminSetUserSettings_mfaOptions,

    -- * Destructuring the Response
    AdminSetUserSettingsResponse (..),
    newAdminSetUserSettingsResponse,

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

-- | You can use this parameter to set an MFA configuration that uses the SMS
-- delivery medium.
--
-- /See:/ 'newAdminSetUserSettings' smart constructor.
data AdminSetUserSettings = AdminSetUserSettings'
  { -- | The ID of the user pool that contains the user whose options you\'re
    -- setting.
    AdminSetUserSettings -> Text
userPoolId :: Prelude.Text,
    -- | The user name of the user whose options you\'re setting.
    AdminSetUserSettings -> Sensitive Text
username :: Data.Sensitive Prelude.Text,
    -- | You can use this parameter only to set an SMS configuration that uses
    -- SMS for delivery.
    AdminSetUserSettings -> [MFAOptionType]
mfaOptions :: [MFAOptionType]
  }
  deriving (AdminSetUserSettings -> AdminSetUserSettings -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AdminSetUserSettings -> AdminSetUserSettings -> Bool
$c/= :: AdminSetUserSettings -> AdminSetUserSettings -> Bool
== :: AdminSetUserSettings -> AdminSetUserSettings -> Bool
$c== :: AdminSetUserSettings -> AdminSetUserSettings -> Bool
Prelude.Eq, Int -> AdminSetUserSettings -> ShowS
[AdminSetUserSettings] -> ShowS
AdminSetUserSettings -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AdminSetUserSettings] -> ShowS
$cshowList :: [AdminSetUserSettings] -> ShowS
show :: AdminSetUserSettings -> String
$cshow :: AdminSetUserSettings -> String
showsPrec :: Int -> AdminSetUserSettings -> ShowS
$cshowsPrec :: Int -> AdminSetUserSettings -> ShowS
Prelude.Show, forall x. Rep AdminSetUserSettings x -> AdminSetUserSettings
forall x. AdminSetUserSettings -> Rep AdminSetUserSettings x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AdminSetUserSettings x -> AdminSetUserSettings
$cfrom :: forall x. AdminSetUserSettings -> Rep AdminSetUserSettings x
Prelude.Generic)

-- |
-- Create a value of 'AdminSetUserSettings' 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', 'adminSetUserSettings_userPoolId' - The ID of the user pool that contains the user whose options you\'re
-- setting.
--
-- 'username', 'adminSetUserSettings_username' - The user name of the user whose options you\'re setting.
--
-- 'mfaOptions', 'adminSetUserSettings_mfaOptions' - You can use this parameter only to set an SMS configuration that uses
-- SMS for delivery.
newAdminSetUserSettings ::
  -- | 'userPoolId'
  Prelude.Text ->
  -- | 'username'
  Prelude.Text ->
  AdminSetUserSettings
newAdminSetUserSettings :: Text -> Text -> AdminSetUserSettings
newAdminSetUserSettings Text
pUserPoolId_ Text
pUsername_ =
  AdminSetUserSettings'
    { $sel:userPoolId:AdminSetUserSettings' :: Text
userPoolId = Text
pUserPoolId_,
      $sel:username:AdminSetUserSettings' :: Sensitive Text
username = forall a. Iso' (Sensitive a) a
Data._Sensitive forall t b. AReview t b -> b -> t
Lens.# Text
pUsername_,
      $sel:mfaOptions:AdminSetUserSettings' :: [MFAOptionType]
mfaOptions = forall a. Monoid a => a
Prelude.mempty
    }

-- | The ID of the user pool that contains the user whose options you\'re
-- setting.
adminSetUserSettings_userPoolId :: Lens.Lens' AdminSetUserSettings Prelude.Text
adminSetUserSettings_userPoolId :: Lens' AdminSetUserSettings Text
adminSetUserSettings_userPoolId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AdminSetUserSettings' {Text
userPoolId :: Text
$sel:userPoolId:AdminSetUserSettings' :: AdminSetUserSettings -> Text
userPoolId} -> Text
userPoolId) (\s :: AdminSetUserSettings
s@AdminSetUserSettings' {} Text
a -> AdminSetUserSettings
s {$sel:userPoolId:AdminSetUserSettings' :: Text
userPoolId = Text
a} :: AdminSetUserSettings)

-- | The user name of the user whose options you\'re setting.
adminSetUserSettings_username :: Lens.Lens' AdminSetUserSettings Prelude.Text
adminSetUserSettings_username :: Lens' AdminSetUserSettings Text
adminSetUserSettings_username = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AdminSetUserSettings' {Sensitive Text
username :: Sensitive Text
$sel:username:AdminSetUserSettings' :: AdminSetUserSettings -> Sensitive Text
username} -> Sensitive Text
username) (\s :: AdminSetUserSettings
s@AdminSetUserSettings' {} Sensitive Text
a -> AdminSetUserSettings
s {$sel:username:AdminSetUserSettings' :: Sensitive Text
username = Sensitive Text
a} :: AdminSetUserSettings) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a. Iso' (Sensitive a) a
Data._Sensitive

-- | You can use this parameter only to set an SMS configuration that uses
-- SMS for delivery.
adminSetUserSettings_mfaOptions :: Lens.Lens' AdminSetUserSettings [MFAOptionType]
adminSetUserSettings_mfaOptions :: Lens' AdminSetUserSettings [MFAOptionType]
adminSetUserSettings_mfaOptions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AdminSetUserSettings' {[MFAOptionType]
mfaOptions :: [MFAOptionType]
$sel:mfaOptions:AdminSetUserSettings' :: AdminSetUserSettings -> [MFAOptionType]
mfaOptions} -> [MFAOptionType]
mfaOptions) (\s :: AdminSetUserSettings
s@AdminSetUserSettings' {} [MFAOptionType]
a -> AdminSetUserSettings
s {$sel:mfaOptions:AdminSetUserSettings' :: [MFAOptionType]
mfaOptions = [MFAOptionType]
a} :: AdminSetUserSettings) 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 AdminSetUserSettings where
  type
    AWSResponse AdminSetUserSettings =
      AdminSetUserSettingsResponse
  request :: (Service -> Service)
-> AdminSetUserSettings -> Request AdminSetUserSettings
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 AdminSetUserSettings
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse AdminSetUserSettings)))
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 -> AdminSetUserSettingsResponse
AdminSetUserSettingsResponse'
            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 AdminSetUserSettings where
  hashWithSalt :: Int -> AdminSetUserSettings -> Int
hashWithSalt Int
_salt AdminSetUserSettings' {[MFAOptionType]
Text
Sensitive Text
mfaOptions :: [MFAOptionType]
username :: Sensitive Text
userPoolId :: Text
$sel:mfaOptions:AdminSetUserSettings' :: AdminSetUserSettings -> [MFAOptionType]
$sel:username:AdminSetUserSettings' :: AdminSetUserSettings -> Sensitive Text
$sel:userPoolId:AdminSetUserSettings' :: AdminSetUserSettings -> 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` [MFAOptionType]
mfaOptions

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

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

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

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

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

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

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

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