{-# 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.Connect.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 user account for the specified Amazon Connect instance.
--
-- For information about how to create user accounts using the Amazon
-- Connect console, see
-- <https://docs.aws.amazon.com/connect/latest/adminguide/user-management.html Add Users>
-- in the /Amazon Connect Administrator Guide/.
module Amazonka.Connect.CreateUser
  ( -- * Creating a Request
    CreateUser (..),
    newCreateUser,

    -- * Request Lenses
    createUser_directoryUserId,
    createUser_hierarchyGroupId,
    createUser_identityInfo,
    createUser_password,
    createUser_tags,
    createUser_username,
    createUser_phoneConfig,
    createUser_securityProfileIds,
    createUser_routingProfileId,
    createUser_instanceId,

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

    -- * Response Lenses
    createUserResponse_userArn,
    createUserResponse_userId,
    createUserResponse_httpStatus,
  )
where

import Amazonka.Connect.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 identifier of the user account in the directory used for identity
    -- management. If Amazon Connect cannot access the directory, you can
    -- specify this identifier to authenticate users. If you include the
    -- identifier, we assume that Amazon Connect cannot access the directory.
    -- Otherwise, the identity information is used to authenticate users from
    -- your directory.
    --
    -- This parameter is required if you are using an existing directory for
    -- identity management in Amazon Connect when Amazon Connect cannot access
    -- your directory to authenticate users. If you are using SAML for identity
    -- management and include this parameter, an error is returned.
    CreateUser -> Maybe Text
directoryUserId :: Prelude.Maybe Prelude.Text,
    -- | The identifier of the hierarchy group for the user.
    CreateUser -> Maybe Text
hierarchyGroupId :: Prelude.Maybe Prelude.Text,
    -- | The information about the identity of the user.
    CreateUser -> Maybe UserIdentityInfo
identityInfo :: Prelude.Maybe UserIdentityInfo,
    -- | The password for the user account. A password is required if you are
    -- using Amazon Connect for identity management. Otherwise, it is an error
    -- to include a password.
    CreateUser -> Maybe Text
password :: Prelude.Maybe Prelude.Text,
    -- | The tags used to organize, track, or control access for this resource.
    -- For example, { \"tags\": {\"key1\":\"value1\", \"key2\":\"value2\"} }.
    CreateUser -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The user name for the account. For instances not using SAML for identity
    -- management, the user name can include up to 20 characters. If you are
    -- using SAML for identity management, the user name can include up to 64
    -- characters from [a-zA-Z0-9_-.\\\@]+.
    CreateUser -> Text
username :: Prelude.Text,
    -- | The phone settings for the user.
    CreateUser -> UserPhoneConfig
phoneConfig :: UserPhoneConfig,
    -- | The identifier of the security profile for the user.
    CreateUser -> NonEmpty Text
securityProfileIds :: Prelude.NonEmpty Prelude.Text,
    -- | The identifier of the routing profile for the user.
    CreateUser -> Text
routingProfileId :: Prelude.Text,
    -- | The identifier of the Amazon Connect instance. You can find the
    -- instanceId in the ARN of the instance.
    CreateUser -> Text
instanceId :: Prelude.Text
  }
  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, ReadPrec [CreateUser]
ReadPrec CreateUser
Int -> ReadS CreateUser
ReadS [CreateUser]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateUser]
$creadListPrec :: ReadPrec [CreateUser]
readPrec :: ReadPrec CreateUser
$creadPrec :: ReadPrec CreateUser
readList :: ReadS [CreateUser]
$creadList :: ReadS [CreateUser]
readsPrec :: Int -> ReadS CreateUser
$creadsPrec :: Int -> ReadS CreateUser
Prelude.Read, 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:
--
-- 'directoryUserId', 'createUser_directoryUserId' - The identifier of the user account in the directory used for identity
-- management. If Amazon Connect cannot access the directory, you can
-- specify this identifier to authenticate users. If you include the
-- identifier, we assume that Amazon Connect cannot access the directory.
-- Otherwise, the identity information is used to authenticate users from
-- your directory.
--
-- This parameter is required if you are using an existing directory for
-- identity management in Amazon Connect when Amazon Connect cannot access
-- your directory to authenticate users. If you are using SAML for identity
-- management and include this parameter, an error is returned.
--
-- 'hierarchyGroupId', 'createUser_hierarchyGroupId' - The identifier of the hierarchy group for the user.
--
-- 'identityInfo', 'createUser_identityInfo' - The information about the identity of the user.
--
-- 'password', 'createUser_password' - The password for the user account. A password is required if you are
-- using Amazon Connect for identity management. Otherwise, it is an error
-- to include a password.
--
-- 'tags', 'createUser_tags' - The tags used to organize, track, or control access for this resource.
-- For example, { \"tags\": {\"key1\":\"value1\", \"key2\":\"value2\"} }.
--
-- 'username', 'createUser_username' - The user name for the account. For instances not using SAML for identity
-- management, the user name can include up to 20 characters. If you are
-- using SAML for identity management, the user name can include up to 64
-- characters from [a-zA-Z0-9_-.\\\@]+.
--
-- 'phoneConfig', 'createUser_phoneConfig' - The phone settings for the user.
--
-- 'securityProfileIds', 'createUser_securityProfileIds' - The identifier of the security profile for the user.
--
-- 'routingProfileId', 'createUser_routingProfileId' - The identifier of the routing profile for the user.
--
-- 'instanceId', 'createUser_instanceId' - The identifier of the Amazon Connect instance. You can find the
-- instanceId in the ARN of the instance.
newCreateUser ::
  -- | 'username'
  Prelude.Text ->
  -- | 'phoneConfig'
  UserPhoneConfig ->
  -- | 'securityProfileIds'
  Prelude.NonEmpty Prelude.Text ->
  -- | 'routingProfileId'
  Prelude.Text ->
  -- | 'instanceId'
  Prelude.Text ->
  CreateUser
newCreateUser :: Text
-> UserPhoneConfig -> NonEmpty Text -> Text -> Text -> CreateUser
newCreateUser
  Text
pUsername_
  UserPhoneConfig
pPhoneConfig_
  NonEmpty Text
pSecurityProfileIds_
  Text
pRoutingProfileId_
  Text
pInstanceId_ =
    CreateUser'
      { $sel:directoryUserId:CreateUser' :: Maybe Text
directoryUserId = forall a. Maybe a
Prelude.Nothing,
        $sel:hierarchyGroupId:CreateUser' :: Maybe Text
hierarchyGroupId = forall a. Maybe a
Prelude.Nothing,
        $sel:identityInfo:CreateUser' :: Maybe UserIdentityInfo
identityInfo = forall a. Maybe a
Prelude.Nothing,
        $sel:password:CreateUser' :: Maybe Text
password = forall a. Maybe a
Prelude.Nothing,
        $sel:tags:CreateUser' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
        $sel:username:CreateUser' :: Text
username = Text
pUsername_,
        $sel:phoneConfig:CreateUser' :: UserPhoneConfig
phoneConfig = UserPhoneConfig
pPhoneConfig_,
        $sel:securityProfileIds:CreateUser' :: NonEmpty Text
securityProfileIds =
          forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced forall t b. AReview t b -> b -> t
Lens.# NonEmpty Text
pSecurityProfileIds_,
        $sel:routingProfileId:CreateUser' :: Text
routingProfileId = Text
pRoutingProfileId_,
        $sel:instanceId:CreateUser' :: Text
instanceId = Text
pInstanceId_
      }

-- | The identifier of the user account in the directory used for identity
-- management. If Amazon Connect cannot access the directory, you can
-- specify this identifier to authenticate users. If you include the
-- identifier, we assume that Amazon Connect cannot access the directory.
-- Otherwise, the identity information is used to authenticate users from
-- your directory.
--
-- This parameter is required if you are using an existing directory for
-- identity management in Amazon Connect when Amazon Connect cannot access
-- your directory to authenticate users. If you are using SAML for identity
-- management and include this parameter, an error is returned.
createUser_directoryUserId :: Lens.Lens' CreateUser (Prelude.Maybe Prelude.Text)
createUser_directoryUserId :: Lens' CreateUser (Maybe Text)
createUser_directoryUserId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateUser' {Maybe Text
directoryUserId :: Maybe Text
$sel:directoryUserId:CreateUser' :: CreateUser -> Maybe Text
directoryUserId} -> Maybe Text
directoryUserId) (\s :: CreateUser
s@CreateUser' {} Maybe Text
a -> CreateUser
s {$sel:directoryUserId:CreateUser' :: Maybe Text
directoryUserId = Maybe Text
a} :: CreateUser)

-- | The identifier of the hierarchy group for the user.
createUser_hierarchyGroupId :: Lens.Lens' CreateUser (Prelude.Maybe Prelude.Text)
createUser_hierarchyGroupId :: Lens' CreateUser (Maybe Text)
createUser_hierarchyGroupId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateUser' {Maybe Text
hierarchyGroupId :: Maybe Text
$sel:hierarchyGroupId:CreateUser' :: CreateUser -> Maybe Text
hierarchyGroupId} -> Maybe Text
hierarchyGroupId) (\s :: CreateUser
s@CreateUser' {} Maybe Text
a -> CreateUser
s {$sel:hierarchyGroupId:CreateUser' :: Maybe Text
hierarchyGroupId = Maybe Text
a} :: CreateUser)

-- | The information about the identity of the user.
createUser_identityInfo :: Lens.Lens' CreateUser (Prelude.Maybe UserIdentityInfo)
createUser_identityInfo :: Lens' CreateUser (Maybe UserIdentityInfo)
createUser_identityInfo = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateUser' {Maybe UserIdentityInfo
identityInfo :: Maybe UserIdentityInfo
$sel:identityInfo:CreateUser' :: CreateUser -> Maybe UserIdentityInfo
identityInfo} -> Maybe UserIdentityInfo
identityInfo) (\s :: CreateUser
s@CreateUser' {} Maybe UserIdentityInfo
a -> CreateUser
s {$sel:identityInfo:CreateUser' :: Maybe UserIdentityInfo
identityInfo = Maybe UserIdentityInfo
a} :: CreateUser)

-- | The password for the user account. A password is required if you are
-- using Amazon Connect for identity management. Otherwise, it is an error
-- to include a password.
createUser_password :: Lens.Lens' CreateUser (Prelude.Maybe Prelude.Text)
createUser_password :: Lens' CreateUser (Maybe Text)
createUser_password = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateUser' {Maybe Text
password :: Maybe Text
$sel:password:CreateUser' :: CreateUser -> Maybe Text
password} -> Maybe Text
password) (\s :: CreateUser
s@CreateUser' {} Maybe Text
a -> CreateUser
s {$sel:password:CreateUser' :: Maybe Text
password = Maybe Text
a} :: CreateUser)

-- | The tags used to organize, track, or control access for this resource.
-- For example, { \"tags\": {\"key1\":\"value1\", \"key2\":\"value2\"} }.
createUser_tags :: Lens.Lens' CreateUser (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
createUser_tags :: Lens' CreateUser (Maybe (HashMap Text Text))
createUser_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateUser' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:CreateUser' :: CreateUser -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: CreateUser
s@CreateUser' {} Maybe (HashMap Text Text)
a -> CreateUser
s {$sel:tags:CreateUser' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text 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 s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The user name for the account. For instances not using SAML for identity
-- management, the user name can include up to 20 characters. If you are
-- using SAML for identity management, the user name can include up to 64
-- characters from [a-zA-Z0-9_-.\\\@]+.
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' {Text
username :: Text
$sel:username:CreateUser' :: CreateUser -> Text
username} -> Text
username) (\s :: CreateUser
s@CreateUser' {} Text
a -> CreateUser
s {$sel:username:CreateUser' :: Text
username = Text
a} :: CreateUser)

-- | The phone settings for the user.
createUser_phoneConfig :: Lens.Lens' CreateUser UserPhoneConfig
createUser_phoneConfig :: Lens' CreateUser UserPhoneConfig
createUser_phoneConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateUser' {UserPhoneConfig
phoneConfig :: UserPhoneConfig
$sel:phoneConfig:CreateUser' :: CreateUser -> UserPhoneConfig
phoneConfig} -> UserPhoneConfig
phoneConfig) (\s :: CreateUser
s@CreateUser' {} UserPhoneConfig
a -> CreateUser
s {$sel:phoneConfig:CreateUser' :: UserPhoneConfig
phoneConfig = UserPhoneConfig
a} :: CreateUser)

-- | The identifier of the security profile for the user.
createUser_securityProfileIds :: Lens.Lens' CreateUser (Prelude.NonEmpty Prelude.Text)
createUser_securityProfileIds :: Lens' CreateUser (NonEmpty Text)
createUser_securityProfileIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateUser' {NonEmpty Text
securityProfileIds :: NonEmpty Text
$sel:securityProfileIds:CreateUser' :: CreateUser -> NonEmpty Text
securityProfileIds} -> NonEmpty Text
securityProfileIds) (\s :: CreateUser
s@CreateUser' {} NonEmpty Text
a -> CreateUser
s {$sel:securityProfileIds:CreateUser' :: NonEmpty Text
securityProfileIds = NonEmpty Text
a} :: CreateUser) 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

-- | The identifier of the routing profile for the user.
createUser_routingProfileId :: Lens.Lens' CreateUser Prelude.Text
createUser_routingProfileId :: Lens' CreateUser Text
createUser_routingProfileId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateUser' {Text
routingProfileId :: Text
$sel:routingProfileId:CreateUser' :: CreateUser -> Text
routingProfileId} -> Text
routingProfileId) (\s :: CreateUser
s@CreateUser' {} Text
a -> CreateUser
s {$sel:routingProfileId:CreateUser' :: Text
routingProfileId = Text
a} :: CreateUser)

-- | The identifier of the Amazon Connect instance. You can find the
-- instanceId in the ARN of the instance.
createUser_instanceId :: Lens.Lens' CreateUser Prelude.Text
createUser_instanceId :: Lens' CreateUser Text
createUser_instanceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateUser' {Text
instanceId :: Text
$sel:instanceId:CreateUser' :: CreateUser -> Text
instanceId} -> Text
instanceId) (\s :: CreateUser
s@CreateUser' {} Text
a -> CreateUser
s {$sel:instanceId:CreateUser' :: Text
instanceId = Text
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.putJSON (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 -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe Text -> Maybe Text -> Int -> CreateUserResponse
CreateUserResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"UserArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"UserId")
            forall (f :: * -> *) a b. Applicative f => 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 Text
Maybe (HashMap Text Text)
Maybe UserIdentityInfo
NonEmpty Text
Text
UserPhoneConfig
instanceId :: Text
routingProfileId :: Text
securityProfileIds :: NonEmpty Text
phoneConfig :: UserPhoneConfig
username :: Text
tags :: Maybe (HashMap Text Text)
password :: Maybe Text
identityInfo :: Maybe UserIdentityInfo
hierarchyGroupId :: Maybe Text
directoryUserId :: Maybe Text
$sel:instanceId:CreateUser' :: CreateUser -> Text
$sel:routingProfileId:CreateUser' :: CreateUser -> Text
$sel:securityProfileIds:CreateUser' :: CreateUser -> NonEmpty Text
$sel:phoneConfig:CreateUser' :: CreateUser -> UserPhoneConfig
$sel:username:CreateUser' :: CreateUser -> Text
$sel:tags:CreateUser' :: CreateUser -> Maybe (HashMap Text Text)
$sel:password:CreateUser' :: CreateUser -> Maybe Text
$sel:identityInfo:CreateUser' :: CreateUser -> Maybe UserIdentityInfo
$sel:hierarchyGroupId:CreateUser' :: CreateUser -> Maybe Text
$sel:directoryUserId:CreateUser' :: CreateUser -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
directoryUserId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
hierarchyGroupId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe UserIdentityInfo
identityInfo
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
password
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
username
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` UserPhoneConfig
phoneConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` NonEmpty Text
securityProfileIds
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
routingProfileId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
instanceId

instance Prelude.NFData CreateUser where
  rnf :: CreateUser -> ()
rnf CreateUser' {Maybe Text
Maybe (HashMap Text Text)
Maybe UserIdentityInfo
NonEmpty Text
Text
UserPhoneConfig
instanceId :: Text
routingProfileId :: Text
securityProfileIds :: NonEmpty Text
phoneConfig :: UserPhoneConfig
username :: Text
tags :: Maybe (HashMap Text Text)
password :: Maybe Text
identityInfo :: Maybe UserIdentityInfo
hierarchyGroupId :: Maybe Text
directoryUserId :: Maybe Text
$sel:instanceId:CreateUser' :: CreateUser -> Text
$sel:routingProfileId:CreateUser' :: CreateUser -> Text
$sel:securityProfileIds:CreateUser' :: CreateUser -> NonEmpty Text
$sel:phoneConfig:CreateUser' :: CreateUser -> UserPhoneConfig
$sel:username:CreateUser' :: CreateUser -> Text
$sel:tags:CreateUser' :: CreateUser -> Maybe (HashMap Text Text)
$sel:password:CreateUser' :: CreateUser -> Maybe Text
$sel:identityInfo:CreateUser' :: CreateUser -> Maybe UserIdentityInfo
$sel:hierarchyGroupId:CreateUser' :: CreateUser -> Maybe Text
$sel:directoryUserId:CreateUser' :: CreateUser -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
directoryUserId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
hierarchyGroupId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe UserIdentityInfo
identityInfo
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
password
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
username
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf UserPhoneConfig
phoneConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf NonEmpty Text
securityProfileIds
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
routingProfileId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
instanceId

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
"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 Text
Maybe (HashMap Text Text)
Maybe UserIdentityInfo
NonEmpty Text
Text
UserPhoneConfig
instanceId :: Text
routingProfileId :: Text
securityProfileIds :: NonEmpty Text
phoneConfig :: UserPhoneConfig
username :: Text
tags :: Maybe (HashMap Text Text)
password :: Maybe Text
identityInfo :: Maybe UserIdentityInfo
hierarchyGroupId :: Maybe Text
directoryUserId :: Maybe Text
$sel:instanceId:CreateUser' :: CreateUser -> Text
$sel:routingProfileId:CreateUser' :: CreateUser -> Text
$sel:securityProfileIds:CreateUser' :: CreateUser -> NonEmpty Text
$sel:phoneConfig:CreateUser' :: CreateUser -> UserPhoneConfig
$sel:username:CreateUser' :: CreateUser -> Text
$sel:tags:CreateUser' :: CreateUser -> Maybe (HashMap Text Text)
$sel:password:CreateUser' :: CreateUser -> Maybe Text
$sel:identityInfo:CreateUser' :: CreateUser -> Maybe UserIdentityInfo
$sel:hierarchyGroupId:CreateUser' :: CreateUser -> Maybe Text
$sel:directoryUserId:CreateUser' :: CreateUser -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"DirectoryUserId" 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 Text
directoryUserId,
            (Key
"HierarchyGroupId" 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 Text
hierarchyGroupId,
            (Key
"IdentityInfo" 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 UserIdentityInfo
identityInfo,
            (Key
"Password" 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 Text
password,
            (Key
"Tags" 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 (HashMap Text Text)
tags,
            forall a. a -> Maybe a
Prelude.Just (Key
"Username" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
username),
            forall a. a -> Maybe a
Prelude.Just (Key
"PhoneConfig" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= UserPhoneConfig
phoneConfig),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"SecurityProfileIds" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= NonEmpty Text
securityProfileIds),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"RoutingProfileId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
routingProfileId)
          ]
      )

instance Data.ToPath CreateUser where
  toPath :: CreateUser -> ByteString
toPath CreateUser' {Maybe Text
Maybe (HashMap Text Text)
Maybe UserIdentityInfo
NonEmpty Text
Text
UserPhoneConfig
instanceId :: Text
routingProfileId :: Text
securityProfileIds :: NonEmpty Text
phoneConfig :: UserPhoneConfig
username :: Text
tags :: Maybe (HashMap Text Text)
password :: Maybe Text
identityInfo :: Maybe UserIdentityInfo
hierarchyGroupId :: Maybe Text
directoryUserId :: Maybe Text
$sel:instanceId:CreateUser' :: CreateUser -> Text
$sel:routingProfileId:CreateUser' :: CreateUser -> Text
$sel:securityProfileIds:CreateUser' :: CreateUser -> NonEmpty Text
$sel:phoneConfig:CreateUser' :: CreateUser -> UserPhoneConfig
$sel:username:CreateUser' :: CreateUser -> Text
$sel:tags:CreateUser' :: CreateUser -> Maybe (HashMap Text Text)
$sel:password:CreateUser' :: CreateUser -> Maybe Text
$sel:identityInfo:CreateUser' :: CreateUser -> Maybe UserIdentityInfo
$sel:hierarchyGroupId:CreateUser' :: CreateUser -> Maybe Text
$sel:directoryUserId:CreateUser' :: CreateUser -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat [ByteString
"/users/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
instanceId]

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 Amazon Resource Name (ARN) of the user account.
    CreateUserResponse -> Maybe Text
userArn :: Prelude.Maybe Prelude.Text,
    -- | The identifier of the user account.
    CreateUserResponse -> Maybe Text
userId :: Prelude.Maybe Prelude.Text,
    -- | 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:
--
-- 'userArn', 'createUserResponse_userArn' - The Amazon Resource Name (ARN) of the user account.
--
-- 'userId', 'createUserResponse_userId' - The identifier of the user account.
--
-- 'httpStatus', 'createUserResponse_httpStatus' - The response's http status code.
newCreateUserResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateUserResponse
newCreateUserResponse :: Int -> CreateUserResponse
newCreateUserResponse Int
pHttpStatus_ =
  CreateUserResponse'
    { $sel:userArn:CreateUserResponse' :: Maybe Text
userArn = forall a. Maybe a
Prelude.Nothing,
      $sel:userId:CreateUserResponse' :: Maybe Text
userId = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateUserResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The Amazon Resource Name (ARN) of the user account.
createUserResponse_userArn :: Lens.Lens' CreateUserResponse (Prelude.Maybe Prelude.Text)
createUserResponse_userArn :: Lens' CreateUserResponse (Maybe Text)
createUserResponse_userArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateUserResponse' {Maybe Text
userArn :: Maybe Text
$sel:userArn:CreateUserResponse' :: CreateUserResponse -> Maybe Text
userArn} -> Maybe Text
userArn) (\s :: CreateUserResponse
s@CreateUserResponse' {} Maybe Text
a -> CreateUserResponse
s {$sel:userArn:CreateUserResponse' :: Maybe Text
userArn = Maybe Text
a} :: CreateUserResponse)

-- | The identifier of the user account.
createUserResponse_userId :: Lens.Lens' CreateUserResponse (Prelude.Maybe Prelude.Text)
createUserResponse_userId :: Lens' CreateUserResponse (Maybe Text)
createUserResponse_userId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateUserResponse' {Maybe Text
userId :: Maybe Text
$sel:userId:CreateUserResponse' :: CreateUserResponse -> Maybe Text
userId} -> Maybe Text
userId) (\s :: CreateUserResponse
s@CreateUserResponse' {} Maybe Text
a -> CreateUserResponse
s {$sel:userId:CreateUserResponse' :: Maybe Text
userId = Maybe Text
a} :: CreateUserResponse)

-- | 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
Maybe Text
httpStatus :: Int
userId :: Maybe Text
userArn :: Maybe Text
$sel:httpStatus:CreateUserResponse' :: CreateUserResponse -> Int
$sel:userId:CreateUserResponse' :: CreateUserResponse -> Maybe Text
$sel:userArn:CreateUserResponse' :: CreateUserResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
userArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
userId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus