{-# 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.MemoryDb.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 MemoryDB user. For more information, see
-- <https://docs.aws.amazon.com/MemoryDB/latest/devguide/clusters.acls.html Authenticating users with Access Contol Lists (ACLs)>.
module Amazonka.MemoryDb.CreateUser
  ( -- * Creating a Request
    CreateUser (..),
    newCreateUser,

    -- * Request Lenses
    createUser_tags,
    createUser_userName,
    createUser_authenticationMode,
    createUser_accessString,

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

    -- * Response Lenses
    createUserResponse_user,
    createUserResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.MemoryDb.Types
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'
  { -- | A list of tags to be added to this resource. A tag is a key-value pair.
    -- A tag key must be accompanied by a tag value, although null is accepted.
    CreateUser -> Maybe [Tag]
tags :: Prelude.Maybe [Tag],
    -- | The name of the user. This value must be unique as it also serves as the
    -- user identifier.
    CreateUser -> Text
userName :: Prelude.Text,
    -- | Denotes the user\'s authentication properties, such as whether it
    -- requires a password to authenticate.
    CreateUser -> AuthenticationMode
authenticationMode :: AuthenticationMode,
    -- | Access permissions string used for this user.
    CreateUser -> Text
accessString :: 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:
--
-- 'tags', 'createUser_tags' - A list of tags to be added to this resource. A tag is a key-value pair.
-- A tag key must be accompanied by a tag value, although null is accepted.
--
-- 'userName', 'createUser_userName' - The name of the user. This value must be unique as it also serves as the
-- user identifier.
--
-- 'authenticationMode', 'createUser_authenticationMode' - Denotes the user\'s authentication properties, such as whether it
-- requires a password to authenticate.
--
-- 'accessString', 'createUser_accessString' - Access permissions string used for this user.
newCreateUser ::
  -- | 'userName'
  Prelude.Text ->
  -- | 'authenticationMode'
  AuthenticationMode ->
  -- | 'accessString'
  Prelude.Text ->
  CreateUser
newCreateUser :: Text -> AuthenticationMode -> Text -> CreateUser
newCreateUser
  Text
pUserName_
  AuthenticationMode
pAuthenticationMode_
  Text
pAccessString_ =
    CreateUser'
      { $sel:tags:CreateUser' :: Maybe [Tag]
tags = forall a. Maybe a
Prelude.Nothing,
        $sel:userName:CreateUser' :: Text
userName = Text
pUserName_,
        $sel:authenticationMode:CreateUser' :: AuthenticationMode
authenticationMode = AuthenticationMode
pAuthenticationMode_,
        $sel:accessString:CreateUser' :: Text
accessString = Text
pAccessString_
      }

-- | A list of tags to be added to this resource. A tag is a key-value pair.
-- A tag key must be accompanied by a tag value, although null is accepted.
createUser_tags :: Lens.Lens' CreateUser (Prelude.Maybe [Tag])
createUser_tags :: Lens' CreateUser (Maybe [Tag])
createUser_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateUser' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:CreateUser' :: CreateUser -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: CreateUser
s@CreateUser' {} Maybe [Tag]
a -> CreateUser
s {$sel:tags:CreateUser' :: Maybe [Tag]
tags = Maybe [Tag]
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 name of the user. This value must be unique as it also serves as the
-- user identifier.
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)

-- | Denotes the user\'s authentication properties, such as whether it
-- requires a password to authenticate.
createUser_authenticationMode :: Lens.Lens' CreateUser AuthenticationMode
createUser_authenticationMode :: Lens' CreateUser AuthenticationMode
createUser_authenticationMode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateUser' {AuthenticationMode
authenticationMode :: AuthenticationMode
$sel:authenticationMode:CreateUser' :: CreateUser -> AuthenticationMode
authenticationMode} -> AuthenticationMode
authenticationMode) (\s :: CreateUser
s@CreateUser' {} AuthenticationMode
a -> CreateUser
s {$sel:authenticationMode:CreateUser' :: AuthenticationMode
authenticationMode = AuthenticationMode
a} :: CreateUser)

-- | Access permissions string used for this user.
createUser_accessString :: Lens.Lens' CreateUser Prelude.Text
createUser_accessString :: Lens' CreateUser Text
createUser_accessString = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateUser' {Text
accessString :: Text
$sel:accessString:CreateUser' :: CreateUser -> Text
accessString} -> Text
accessString) (\s :: CreateUser
s@CreateUser' {} Text
a -> CreateUser
s {$sel:accessString:CreateUser' :: Text
accessString = 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 [Tag]
Text
AuthenticationMode
accessString :: Text
authenticationMode :: AuthenticationMode
userName :: Text
tags :: Maybe [Tag]
$sel:accessString:CreateUser' :: CreateUser -> Text
$sel:authenticationMode:CreateUser' :: CreateUser -> AuthenticationMode
$sel:userName:CreateUser' :: CreateUser -> Text
$sel:tags:CreateUser' :: CreateUser -> Maybe [Tag]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Tag]
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
userName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` AuthenticationMode
authenticationMode
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
accessString

instance Prelude.NFData CreateUser where
  rnf :: CreateUser -> ()
rnf CreateUser' {Maybe [Tag]
Text
AuthenticationMode
accessString :: Text
authenticationMode :: AuthenticationMode
userName :: Text
tags :: Maybe [Tag]
$sel:accessString:CreateUser' :: CreateUser -> Text
$sel:authenticationMode:CreateUser' :: CreateUser -> AuthenticationMode
$sel:userName:CreateUser' :: CreateUser -> Text
$sel:tags:CreateUser' :: CreateUser -> Maybe [Tag]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Tag]
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 AuthenticationMode
authenticationMode
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
accessString

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
"AmazonMemoryDB.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 [Tag]
Text
AuthenticationMode
accessString :: Text
authenticationMode :: AuthenticationMode
userName :: Text
tags :: Maybe [Tag]
$sel:accessString:CreateUser' :: CreateUser -> Text
$sel:authenticationMode:CreateUser' :: CreateUser -> AuthenticationMode
$sel:userName:CreateUser' :: CreateUser -> Text
$sel:tags:CreateUser' :: CreateUser -> Maybe [Tag]
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (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 [Tag]
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
"AuthenticationMode" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= AuthenticationMode
authenticationMode),
            forall a. a -> Maybe a
Prelude.Just (Key
"AccessString" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
accessString)
          ]
      )

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 newly-created user.
    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, 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:
--
-- 'user', 'createUserResponse_user' - The newly-created user.
--
-- '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_
    }

-- | The newly-created user.
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