{-# 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.Chime.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 under the specified Amazon Chime account.
module Amazonka.Chime.CreateUser
  ( -- * Creating a Request
    CreateUser (..),
    newCreateUser,

    -- * Request Lenses
    createUser_email,
    createUser_userType,
    createUser_username,
    createUser_accountId,

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

    -- * Response Lenses
    createUserResponse_user,
    createUserResponse_httpStatus,
  )
where

import Amazonka.Chime.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 user\'s email address.
    CreateUser -> Maybe (Sensitive Text)
email :: Prelude.Maybe (Data.Sensitive Prelude.Text),
    -- | The user type.
    CreateUser -> Maybe UserType
userType :: Prelude.Maybe UserType,
    -- | The user name.
    CreateUser -> Maybe Text
username :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Chime account ID.
    CreateUser -> Text
accountId :: 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, 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:
--
-- 'email', 'createUser_email' - The user\'s email address.
--
-- 'userType', 'createUser_userType' - The user type.
--
-- 'username', 'createUser_username' - The user name.
--
-- 'accountId', 'createUser_accountId' - The Amazon Chime account ID.
newCreateUser ::
  -- | 'accountId'
  Prelude.Text ->
  CreateUser
newCreateUser :: Text -> CreateUser
newCreateUser Text
pAccountId_ =
  CreateUser'
    { $sel:email:CreateUser' :: Maybe (Sensitive Text)
email = forall a. Maybe a
Prelude.Nothing,
      $sel:userType:CreateUser' :: Maybe UserType
userType = forall a. Maybe a
Prelude.Nothing,
      $sel:username:CreateUser' :: Maybe Text
username = forall a. Maybe a
Prelude.Nothing,
      $sel:accountId:CreateUser' :: Text
accountId = Text
pAccountId_
    }

-- | The user\'s email address.
createUser_email :: Lens.Lens' CreateUser (Prelude.Maybe Prelude.Text)
createUser_email :: Lens' CreateUser (Maybe Text)
createUser_email = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateUser' {Maybe (Sensitive Text)
email :: Maybe (Sensitive Text)
$sel:email:CreateUser' :: CreateUser -> Maybe (Sensitive Text)
email} -> Maybe (Sensitive Text)
email) (\s :: CreateUser
s@CreateUser' {} Maybe (Sensitive Text)
a -> CreateUser
s {$sel:email:CreateUser' :: Maybe (Sensitive Text)
email = 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 user type.
createUser_userType :: Lens.Lens' CreateUser (Prelude.Maybe UserType)
createUser_userType :: Lens' CreateUser (Maybe UserType)
createUser_userType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateUser' {Maybe UserType
userType :: Maybe UserType
$sel:userType:CreateUser' :: CreateUser -> Maybe UserType
userType} -> Maybe UserType
userType) (\s :: CreateUser
s@CreateUser' {} Maybe UserType
a -> CreateUser
s {$sel:userType:CreateUser' :: Maybe UserType
userType = Maybe UserType
a} :: CreateUser)

-- | The user name.
createUser_username :: Lens.Lens' CreateUser (Prelude.Maybe Prelude.Text)
createUser_username :: Lens' CreateUser (Maybe Text)
createUser_username = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateUser' {Maybe Text
username :: Maybe Text
$sel:username:CreateUser' :: CreateUser -> Maybe Text
username} -> Maybe Text
username) (\s :: CreateUser
s@CreateUser' {} Maybe Text
a -> CreateUser
s {$sel:username:CreateUser' :: Maybe Text
username = Maybe Text
a} :: CreateUser)

-- | The Amazon Chime account ID.
createUser_accountId :: Lens.Lens' CreateUser Prelude.Text
createUser_accountId :: Lens' CreateUser Text
createUser_accountId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateUser' {Text
accountId :: Text
$sel:accountId:CreateUser' :: CreateUser -> Text
accountId} -> Text
accountId) (\s :: CreateUser
s@CreateUser' {} Text
a -> CreateUser
s {$sel:accountId:CreateUser' :: Text
accountId = 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.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 -> 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 User -> 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
"User")
            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 (Sensitive Text)
Maybe UserType
Text
accountId :: Text
username :: Maybe Text
userType :: Maybe UserType
email :: Maybe (Sensitive Text)
$sel:accountId:CreateUser' :: CreateUser -> Text
$sel:username:CreateUser' :: CreateUser -> Maybe Text
$sel:userType:CreateUser' :: CreateUser -> Maybe UserType
$sel:email:CreateUser' :: CreateUser -> Maybe (Sensitive Text)
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (Sensitive Text)
email
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe UserType
userType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
username
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
accountId

instance Prelude.NFData CreateUser where
  rnf :: CreateUser -> ()
rnf CreateUser' {Maybe Text
Maybe (Sensitive Text)
Maybe UserType
Text
accountId :: Text
username :: Maybe Text
userType :: Maybe UserType
email :: Maybe (Sensitive Text)
$sel:accountId:CreateUser' :: CreateUser -> Text
$sel:username:CreateUser' :: CreateUser -> Maybe Text
$sel:userType:CreateUser' :: CreateUser -> Maybe UserType
$sel:email:CreateUser' :: CreateUser -> Maybe (Sensitive Text)
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe (Sensitive Text)
email
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe UserType
userType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
username
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
accountId

instance Data.ToHeaders CreateUser where
  toHeaders :: CreateUser -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

instance Data.ToJSON CreateUser where
  toJSON :: CreateUser -> Value
toJSON CreateUser' {Maybe Text
Maybe (Sensitive Text)
Maybe UserType
Text
accountId :: Text
username :: Maybe Text
userType :: Maybe UserType
email :: Maybe (Sensitive Text)
$sel:accountId:CreateUser' :: CreateUser -> Text
$sel:username:CreateUser' :: CreateUser -> Maybe Text
$sel:userType:CreateUser' :: CreateUser -> Maybe UserType
$sel:email:CreateUser' :: CreateUser -> Maybe (Sensitive Text)
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Email" 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)
email,
            (Key
"UserType" 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 UserType
userType,
            (Key
"Username" 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
username
          ]
      )

instance Data.ToPath CreateUser where
  toPath :: CreateUser -> ByteString
toPath CreateUser' {Maybe Text
Maybe (Sensitive Text)
Maybe UserType
Text
accountId :: Text
username :: Maybe Text
userType :: Maybe UserType
email :: Maybe (Sensitive Text)
$sel:accountId:CreateUser' :: CreateUser -> Text
$sel:username:CreateUser' :: CreateUser -> Maybe Text
$sel:userType:CreateUser' :: CreateUser -> Maybe UserType
$sel:email:CreateUser' :: CreateUser -> Maybe (Sensitive Text)
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/accounts/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
accountId, ByteString
"/users"]

instance Data.ToQuery CreateUser where
  toQuery :: CreateUser -> QueryString
toQuery =
    forall a b. a -> b -> a
Prelude.const
      (forall a. Monoid a => [a] -> a
Prelude.mconcat [QueryString
"operation=create"])

-- | /See:/ 'newCreateUserResponse' smart constructor.
data CreateUserResponse = CreateUserResponse'
  { CreateUserResponse -> Maybe User
user :: Prelude.Maybe User,
    -- | 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, 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:
--
-- 'user', 'createUserResponse_user' - Undocumented member.
--
-- 'httpStatus', 'createUserResponse_httpStatus' - The response's http status code.
newCreateUserResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateUserResponse
newCreateUserResponse :: Int -> CreateUserResponse
newCreateUserResponse Int
pHttpStatus_ =
  CreateUserResponse'
    { $sel:user:CreateUserResponse' :: Maybe User
user = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateUserResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Undocumented member.
createUserResponse_user :: Lens.Lens' CreateUserResponse (Prelude.Maybe User)
createUserResponse_user :: Lens' CreateUserResponse (Maybe User)
createUserResponse_user = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateUserResponse' {Maybe User
user :: Maybe User
$sel:user:CreateUserResponse' :: CreateUserResponse -> Maybe User
user} -> Maybe User
user) (\s :: CreateUserResponse
s@CreateUserResponse' {} Maybe User
a -> CreateUserResponse
s {$sel:user:CreateUserResponse' :: Maybe User
user = Maybe User
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 User
httpStatus :: Int
user :: Maybe User
$sel:httpStatus:CreateUserResponse' :: CreateUserResponse -> Int
$sel:user:CreateUserResponse' :: CreateUserResponse -> Maybe User
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe User
user
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus