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

    -- * Request Lenses
    adminEnableUser_userPoolId,
    adminEnableUser_username,

    -- * Destructuring the Response
    AdminEnableUserResponse (..),
    newAdminEnableUserResponse,

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

-- | Represents the request that enables the user as an administrator.
--
-- /See:/ 'newAdminEnableUser' smart constructor.
data AdminEnableUser = AdminEnableUser'
  { -- | The user pool ID for the user pool where you want to enable the user.
    AdminEnableUser -> Text
userPoolId :: Prelude.Text,
    -- | The user name of the user you want to enable.
    AdminEnableUser -> Sensitive Text
username :: Data.Sensitive Prelude.Text
  }
  deriving (AdminEnableUser -> AdminEnableUser -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AdminEnableUser -> AdminEnableUser -> Bool
$c/= :: AdminEnableUser -> AdminEnableUser -> Bool
== :: AdminEnableUser -> AdminEnableUser -> Bool
$c== :: AdminEnableUser -> AdminEnableUser -> Bool
Prelude.Eq, Int -> AdminEnableUser -> ShowS
[AdminEnableUser] -> ShowS
AdminEnableUser -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AdminEnableUser] -> ShowS
$cshowList :: [AdminEnableUser] -> ShowS
show :: AdminEnableUser -> String
$cshow :: AdminEnableUser -> String
showsPrec :: Int -> AdminEnableUser -> ShowS
$cshowsPrec :: Int -> AdminEnableUser -> ShowS
Prelude.Show, forall x. Rep AdminEnableUser x -> AdminEnableUser
forall x. AdminEnableUser -> Rep AdminEnableUser x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AdminEnableUser x -> AdminEnableUser
$cfrom :: forall x. AdminEnableUser -> Rep AdminEnableUser x
Prelude.Generic)

-- |
-- Create a value of 'AdminEnableUser' 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', 'adminEnableUser_userPoolId' - The user pool ID for the user pool where you want to enable the user.
--
-- 'username', 'adminEnableUser_username' - The user name of the user you want to enable.
newAdminEnableUser ::
  -- | 'userPoolId'
  Prelude.Text ->
  -- | 'username'
  Prelude.Text ->
  AdminEnableUser
newAdminEnableUser :: Text -> Text -> AdminEnableUser
newAdminEnableUser Text
pUserPoolId_ Text
pUsername_ =
  AdminEnableUser'
    { $sel:userPoolId:AdminEnableUser' :: Text
userPoolId = Text
pUserPoolId_,
      $sel:username:AdminEnableUser' :: 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 for the user pool where you want to enable the user.
adminEnableUser_userPoolId :: Lens.Lens' AdminEnableUser Prelude.Text
adminEnableUser_userPoolId :: Lens' AdminEnableUser Text
adminEnableUser_userPoolId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AdminEnableUser' {Text
userPoolId :: Text
$sel:userPoolId:AdminEnableUser' :: AdminEnableUser -> Text
userPoolId} -> Text
userPoolId) (\s :: AdminEnableUser
s@AdminEnableUser' {} Text
a -> AdminEnableUser
s {$sel:userPoolId:AdminEnableUser' :: Text
userPoolId = Text
a} :: AdminEnableUser)

-- | The user name of the user you want to enable.
adminEnableUser_username :: Lens.Lens' AdminEnableUser Prelude.Text
adminEnableUser_username :: Lens' AdminEnableUser Text
adminEnableUser_username = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AdminEnableUser' {Sensitive Text
username :: Sensitive Text
$sel:username:AdminEnableUser' :: AdminEnableUser -> Sensitive Text
username} -> Sensitive Text
username) (\s :: AdminEnableUser
s@AdminEnableUser' {} Sensitive Text
a -> AdminEnableUser
s {$sel:username:AdminEnableUser' :: Sensitive Text
username = Sensitive Text
a} :: AdminEnableUser) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a. Iso' (Sensitive a) a
Data._Sensitive

instance Core.AWSRequest AdminEnableUser where
  type
    AWSResponse AdminEnableUser =
      AdminEnableUserResponse
  request :: (Service -> Service) -> AdminEnableUser -> Request AdminEnableUser
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 AdminEnableUser
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse AdminEnableUser)))
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 -> AdminEnableUserResponse
AdminEnableUserResponse'
            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 AdminEnableUser where
  hashWithSalt :: Int -> AdminEnableUser -> Int
hashWithSalt Int
_salt AdminEnableUser' {Text
Sensitive Text
username :: Sensitive Text
userPoolId :: Text
$sel:username:AdminEnableUser' :: AdminEnableUser -> Sensitive Text
$sel:userPoolId:AdminEnableUser' :: AdminEnableUser -> 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 AdminEnableUser where
  rnf :: AdminEnableUser -> ()
rnf AdminEnableUser' {Text
Sensitive Text
username :: Sensitive Text
userPoolId :: Text
$sel:username:AdminEnableUser' :: AdminEnableUser -> Sensitive Text
$sel:userPoolId:AdminEnableUser' :: AdminEnableUser -> 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 AdminEnableUser where
  toHeaders :: AdminEnableUser -> 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.AdminEnableUser" ::
                          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 AdminEnableUser where
  toJSON :: AdminEnableUser -> Value
toJSON AdminEnableUser' {Text
Sensitive Text
username :: Sensitive Text
userPoolId :: Text
$sel:username:AdminEnableUser' :: AdminEnableUser -> Sensitive Text
$sel:userPoolId:AdminEnableUser' :: AdminEnableUser -> 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 AdminEnableUser where
  toPath :: AdminEnableUser -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

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

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

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

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