{-# 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.AppStream.CreateUser
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Creates a new user in the user pool.
module Amazonka.AppStream.CreateUser
  ( -- * Creating a Request
    CreateUser (..),
    newCreateUser,

    -- * Request Lenses
    createUser_firstName,
    createUser_lastName,
    createUser_messageAction,
    createUser_userName,
    createUser_authenticationType,

    -- * Destructuring the Response
    CreateUserResponse (..),
    newCreateUserResponse,

    -- * Response Lenses
    createUserResponse_httpStatus,
  )
where

import Amazonka.AppStream.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

-- | /See:/ 'newCreateUser' smart constructor.
data CreateUser = CreateUser'
  { -- | The first name, or given name, of the user.
    CreateUser -> Maybe (Sensitive Text)
firstName :: Prelude.Maybe (Data.Sensitive Prelude.Text),
    -- | The last name, or surname, of the user.
    CreateUser -> Maybe (Sensitive Text)
lastName :: Prelude.Maybe (Data.Sensitive Prelude.Text),
    -- | The action to take for the welcome email that is sent to a user after
    -- the user is created in the user pool. If you specify SUPPRESS, no email
    -- is sent. If you specify RESEND, do not specify the first name or last
    -- name of the user. If the value is null, the email is sent.
    --
    -- The temporary password in the welcome email is valid for only 7 days. If
    -- users don’t set their passwords within 7 days, you must send them a new
    -- welcome email.
    CreateUser -> Maybe MessageAction
messageAction :: Prelude.Maybe MessageAction,
    -- | The email address of the user.
    --
    -- Users\' email addresses are case-sensitive. During login, if they
    -- specify an email address that doesn\'t use the same capitalization as
    -- the email address specified when their user pool account was created, a
    -- \"user does not exist\" error message displays.
    CreateUser -> Sensitive Text
userName :: Data.Sensitive Prelude.Text,
    -- | The authentication type for the user. You must specify USERPOOL.
    CreateUser -> AuthenticationType
authenticationType :: AuthenticationType
  }
  deriving (CreateUser -> CreateUser -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateUser -> CreateUser -> Bool
$c/= :: CreateUser -> CreateUser -> Bool
== :: CreateUser -> CreateUser -> Bool
$c== :: CreateUser -> CreateUser -> Bool
Prelude.Eq, Int -> CreateUser -> ShowS
[CreateUser] -> ShowS
CreateUser -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateUser] -> ShowS
$cshowList :: [CreateUser] -> ShowS
show :: CreateUser -> String
$cshow :: CreateUser -> String
showsPrec :: Int -> CreateUser -> ShowS
$cshowsPrec :: Int -> CreateUser -> ShowS
Prelude.Show, forall x. Rep CreateUser x -> CreateUser
forall x. CreateUser -> Rep CreateUser x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateUser x -> CreateUser
$cfrom :: forall x. CreateUser -> Rep CreateUser x
Prelude.Generic)

-- |
-- Create a value of 'CreateUser' 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:
--
-- 'firstName', 'createUser_firstName' - The first name, or given name, of the user.
--
-- 'lastName', 'createUser_lastName' - The last name, or surname, of the user.
--
-- 'messageAction', 'createUser_messageAction' - The action to take for the welcome email that is sent to a user after
-- the user is created in the user pool. If you specify SUPPRESS, no email
-- is sent. If you specify RESEND, do not specify the first name or last
-- name of the user. If the value is null, the email is sent.
--
-- The temporary password in the welcome email is valid for only 7 days. If
-- users don’t set their passwords within 7 days, you must send them a new
-- welcome email.
--
-- 'userName', 'createUser_userName' - The email address of the user.
--
-- Users\' email addresses are case-sensitive. During login, if they
-- specify an email address that doesn\'t use the same capitalization as
-- the email address specified when their user pool account was created, a
-- \"user does not exist\" error message displays.
--
-- 'authenticationType', 'createUser_authenticationType' - The authentication type for the user. You must specify USERPOOL.
newCreateUser ::
  -- | 'userName'
  Prelude.Text ->
  -- | 'authenticationType'
  AuthenticationType ->
  CreateUser
newCreateUser :: Text -> AuthenticationType -> CreateUser
newCreateUser Text
pUserName_ AuthenticationType
pAuthenticationType_ =
  CreateUser'
    { $sel:firstName:CreateUser' :: Maybe (Sensitive Text)
firstName = forall a. Maybe a
Prelude.Nothing,
      $sel:lastName:CreateUser' :: Maybe (Sensitive Text)
lastName = forall a. Maybe a
Prelude.Nothing,
      $sel:messageAction:CreateUser' :: Maybe MessageAction
messageAction = forall a. Maybe a
Prelude.Nothing,
      $sel:userName:CreateUser' :: Sensitive Text
userName = forall a. Iso' (Sensitive a) a
Data._Sensitive forall t b. AReview t b -> b -> t
Lens.# Text
pUserName_,
      $sel:authenticationType:CreateUser' :: AuthenticationType
authenticationType = AuthenticationType
pAuthenticationType_
    }

-- | The first name, or given name, of the user.
createUser_firstName :: Lens.Lens' CreateUser (Prelude.Maybe Prelude.Text)
createUser_firstName :: Lens' CreateUser (Maybe Text)
createUser_firstName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateUser' {Maybe (Sensitive Text)
firstName :: Maybe (Sensitive Text)
$sel:firstName:CreateUser' :: CreateUser -> Maybe (Sensitive Text)
firstName} -> Maybe (Sensitive Text)
firstName) (\s :: CreateUser
s@CreateUser' {} Maybe (Sensitive Text)
a -> CreateUser
s {$sel:firstName:CreateUser' :: Maybe (Sensitive Text)
firstName = Maybe (Sensitive Text)
a} :: CreateUser) 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 last name, or surname, of the user.
createUser_lastName :: Lens.Lens' CreateUser (Prelude.Maybe Prelude.Text)
createUser_lastName :: Lens' CreateUser (Maybe Text)
createUser_lastName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateUser' {Maybe (Sensitive Text)
lastName :: Maybe (Sensitive Text)
$sel:lastName:CreateUser' :: CreateUser -> Maybe (Sensitive Text)
lastName} -> Maybe (Sensitive Text)
lastName) (\s :: CreateUser
s@CreateUser' {} Maybe (Sensitive Text)
a -> CreateUser
s {$sel:lastName:CreateUser' :: Maybe (Sensitive Text)
lastName = Maybe (Sensitive Text)
a} :: CreateUser) 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 action to take for the welcome email that is sent to a user after
-- the user is created in the user pool. If you specify SUPPRESS, no email
-- is sent. If you specify RESEND, do not specify the first name or last
-- name of the user. If the value is null, the email is sent.
--
-- The temporary password in the welcome email is valid for only 7 days. If
-- users don’t set their passwords within 7 days, you must send them a new
-- welcome email.
createUser_messageAction :: Lens.Lens' CreateUser (Prelude.Maybe MessageAction)
createUser_messageAction :: Lens' CreateUser (Maybe MessageAction)
createUser_messageAction = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateUser' {Maybe MessageAction
messageAction :: Maybe MessageAction
$sel:messageAction:CreateUser' :: CreateUser -> Maybe MessageAction
messageAction} -> Maybe MessageAction
messageAction) (\s :: CreateUser
s@CreateUser' {} Maybe MessageAction
a -> CreateUser
s {$sel:messageAction:CreateUser' :: Maybe MessageAction
messageAction = Maybe MessageAction
a} :: CreateUser)

-- | The email address of the user.
--
-- Users\' email addresses are case-sensitive. During login, if they
-- specify an email address that doesn\'t use the same capitalization as
-- the email address specified when their user pool account was created, a
-- \"user does not exist\" error message displays.
createUser_userName :: Lens.Lens' CreateUser Prelude.Text
createUser_userName :: Lens' CreateUser Text
createUser_userName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateUser' {Sensitive Text
userName :: Sensitive Text
$sel:userName:CreateUser' :: CreateUser -> Sensitive Text
userName} -> Sensitive Text
userName) (\s :: CreateUser
s@CreateUser' {} Sensitive Text
a -> CreateUser
s {$sel:userName:CreateUser' :: Sensitive Text
userName = Sensitive Text
a} :: CreateUser) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a. Iso' (Sensitive a) a
Data._Sensitive

-- | The authentication type for the user. You must specify USERPOOL.
createUser_authenticationType :: Lens.Lens' CreateUser AuthenticationType
createUser_authenticationType :: Lens' CreateUser AuthenticationType
createUser_authenticationType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateUser' {AuthenticationType
authenticationType :: AuthenticationType
$sel:authenticationType:CreateUser' :: CreateUser -> AuthenticationType
authenticationType} -> AuthenticationType
authenticationType) (\s :: CreateUser
s@CreateUser' {} AuthenticationType
a -> CreateUser
s {$sel:authenticationType:CreateUser' :: AuthenticationType
authenticationType = AuthenticationType
a} :: CreateUser)

instance Core.AWSRequest CreateUser where
  type AWSResponse CreateUser = CreateUserResponse
  request :: (Service -> Service) -> CreateUser -> Request CreateUser
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 CreateUser
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse CreateUser)))
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 -> CreateUserResponse
CreateUserResponse'
            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 CreateUser where
  hashWithSalt :: Int -> CreateUser -> Int
hashWithSalt Int
_salt CreateUser' {Maybe (Sensitive Text)
Maybe MessageAction
Sensitive Text
AuthenticationType
authenticationType :: AuthenticationType
userName :: Sensitive Text
messageAction :: Maybe MessageAction
lastName :: Maybe (Sensitive Text)
firstName :: Maybe (Sensitive Text)
$sel:authenticationType:CreateUser' :: CreateUser -> AuthenticationType
$sel:userName:CreateUser' :: CreateUser -> Sensitive Text
$sel:messageAction:CreateUser' :: CreateUser -> Maybe MessageAction
$sel:lastName:CreateUser' :: CreateUser -> Maybe (Sensitive Text)
$sel:firstName:CreateUser' :: CreateUser -> Maybe (Sensitive Text)
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (Sensitive Text)
firstName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (Sensitive Text)
lastName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe MessageAction
messageAction
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Sensitive Text
userName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` AuthenticationType
authenticationType

instance Prelude.NFData CreateUser where
  rnf :: CreateUser -> ()
rnf CreateUser' {Maybe (Sensitive Text)
Maybe MessageAction
Sensitive Text
AuthenticationType
authenticationType :: AuthenticationType
userName :: Sensitive Text
messageAction :: Maybe MessageAction
lastName :: Maybe (Sensitive Text)
firstName :: Maybe (Sensitive Text)
$sel:authenticationType:CreateUser' :: CreateUser -> AuthenticationType
$sel:userName:CreateUser' :: CreateUser -> Sensitive Text
$sel:messageAction:CreateUser' :: CreateUser -> Maybe MessageAction
$sel:lastName:CreateUser' :: CreateUser -> Maybe (Sensitive Text)
$sel:firstName:CreateUser' :: CreateUser -> Maybe (Sensitive Text)
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe (Sensitive Text)
firstName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (Sensitive Text)
lastName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe MessageAction
messageAction
      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 AuthenticationType
authenticationType

instance Data.ToHeaders CreateUser where
  toHeaders :: CreateUser -> 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
"PhotonAdminProxyService.CreateUser" ::
                          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 CreateUser where
  toJSON :: CreateUser -> Value
toJSON CreateUser' {Maybe (Sensitive Text)
Maybe MessageAction
Sensitive Text
AuthenticationType
authenticationType :: AuthenticationType
userName :: Sensitive Text
messageAction :: Maybe MessageAction
lastName :: Maybe (Sensitive Text)
firstName :: Maybe (Sensitive Text)
$sel:authenticationType:CreateUser' :: CreateUser -> AuthenticationType
$sel:userName:CreateUser' :: CreateUser -> Sensitive Text
$sel:messageAction:CreateUser' :: CreateUser -> Maybe MessageAction
$sel:lastName:CreateUser' :: CreateUser -> Maybe (Sensitive Text)
$sel:firstName:CreateUser' :: CreateUser -> Maybe (Sensitive Text)
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"FirstName" 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)
firstName,
            (Key
"LastName" 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)
lastName,
            (Key
"MessageAction" 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 MessageAction
messageAction,
            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
"AuthenticationType" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= AuthenticationType
authenticationType)
          ]
      )

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

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

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

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

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

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