{-# 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.MQ.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 an ActiveMQ user.
module Amazonka.MQ.CreateUser
  ( -- * Creating a Request
    CreateUser (..),
    newCreateUser,

    -- * Request Lenses
    createUser_consoleAccess,
    createUser_groups,
    createUser_username,
    createUser_brokerId,
    createUser_password,

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

    -- * Response Lenses
    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.MQ.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | Creates a new ActiveMQ user.
--
-- /See:/ 'newCreateUser' smart constructor.
data CreateUser = CreateUser'
  { -- | Enables access to the ActiveMQ Web Console for the ActiveMQ user.
    CreateUser -> Maybe Bool
consoleAccess :: Prelude.Maybe Prelude.Bool,
    -- | The list of groups (20 maximum) to which the ActiveMQ user belongs. This
    -- value can contain only alphanumeric characters, dashes, periods,
    -- underscores, and tildes (- . _ ~). This value must be 2-100 characters
    -- long.
    CreateUser -> Maybe [Text]
groups :: Prelude.Maybe [Prelude.Text],
    -- | The username of the ActiveMQ user. This value can contain only
    -- alphanumeric characters, dashes, periods, underscores, and tildes (- . _
    -- ~). This value must be 2-100 characters long.
    CreateUser -> Text
username :: Prelude.Text,
    -- | The unique ID that Amazon MQ generates for the broker.
    CreateUser -> Text
brokerId :: Prelude.Text,
    -- | Required. The password of the user. This value must be at least 12
    -- characters long, must contain at least 4 unique characters, and must not
    -- contain commas, colons, or equal signs (,:=).
    CreateUser -> Text
password :: 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:
--
-- 'consoleAccess', 'createUser_consoleAccess' - Enables access to the ActiveMQ Web Console for the ActiveMQ user.
--
-- 'groups', 'createUser_groups' - The list of groups (20 maximum) to which the ActiveMQ user belongs. This
-- value can contain only alphanumeric characters, dashes, periods,
-- underscores, and tildes (- . _ ~). This value must be 2-100 characters
-- long.
--
-- 'username', 'createUser_username' - The username of the ActiveMQ user. This value can contain only
-- alphanumeric characters, dashes, periods, underscores, and tildes (- . _
-- ~). This value must be 2-100 characters long.
--
-- 'brokerId', 'createUser_brokerId' - The unique ID that Amazon MQ generates for the broker.
--
-- 'password', 'createUser_password' - Required. The password of the user. This value must be at least 12
-- characters long, must contain at least 4 unique characters, and must not
-- contain commas, colons, or equal signs (,:=).
newCreateUser ::
  -- | 'username'
  Prelude.Text ->
  -- | 'brokerId'
  Prelude.Text ->
  -- | 'password'
  Prelude.Text ->
  CreateUser
newCreateUser :: Text -> Text -> Text -> CreateUser
newCreateUser Text
pUsername_ Text
pBrokerId_ Text
pPassword_ =
  CreateUser'
    { $sel:consoleAccess:CreateUser' :: Maybe Bool
consoleAccess = forall a. Maybe a
Prelude.Nothing,
      $sel:groups:CreateUser' :: Maybe [Text]
groups = forall a. Maybe a
Prelude.Nothing,
      $sel:username:CreateUser' :: Text
username = Text
pUsername_,
      $sel:brokerId:CreateUser' :: Text
brokerId = Text
pBrokerId_,
      $sel:password:CreateUser' :: Text
password = Text
pPassword_
    }

-- | Enables access to the ActiveMQ Web Console for the ActiveMQ user.
createUser_consoleAccess :: Lens.Lens' CreateUser (Prelude.Maybe Prelude.Bool)
createUser_consoleAccess :: Lens' CreateUser (Maybe Bool)
createUser_consoleAccess = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateUser' {Maybe Bool
consoleAccess :: Maybe Bool
$sel:consoleAccess:CreateUser' :: CreateUser -> Maybe Bool
consoleAccess} -> Maybe Bool
consoleAccess) (\s :: CreateUser
s@CreateUser' {} Maybe Bool
a -> CreateUser
s {$sel:consoleAccess:CreateUser' :: Maybe Bool
consoleAccess = Maybe Bool
a} :: CreateUser)

-- | The list of groups (20 maximum) to which the ActiveMQ user belongs. This
-- value can contain only alphanumeric characters, dashes, periods,
-- underscores, and tildes (- . _ ~). This value must be 2-100 characters
-- long.
createUser_groups :: Lens.Lens' CreateUser (Prelude.Maybe [Prelude.Text])
createUser_groups :: Lens' CreateUser (Maybe [Text])
createUser_groups = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateUser' {Maybe [Text]
groups :: Maybe [Text]
$sel:groups:CreateUser' :: CreateUser -> Maybe [Text]
groups} -> Maybe [Text]
groups) (\s :: CreateUser
s@CreateUser' {} Maybe [Text]
a -> CreateUser
s {$sel:groups:CreateUser' :: Maybe [Text]
groups = Maybe [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 username of the ActiveMQ user. This value can contain only
-- alphanumeric characters, dashes, periods, underscores, and tildes (- . _
-- ~). This value must be 2-100 characters long.
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 unique ID that Amazon MQ generates for the broker.
createUser_brokerId :: Lens.Lens' CreateUser Prelude.Text
createUser_brokerId :: Lens' CreateUser Text
createUser_brokerId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateUser' {Text
brokerId :: Text
$sel:brokerId:CreateUser' :: CreateUser -> Text
brokerId} -> Text
brokerId) (\s :: CreateUser
s@CreateUser' {} Text
a -> CreateUser
s {$sel:brokerId:CreateUser' :: Text
brokerId = Text
a} :: CreateUser)

-- | Required. The password of the user. This value must be at least 12
-- characters long, must contain at least 4 unique characters, and must not
-- contain commas, colons, or equal signs (,:=).
createUser_password :: Lens.Lens' CreateUser Prelude.Text
createUser_password :: Lens' CreateUser Text
createUser_password = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateUser' {Text
password :: Text
$sel:password:CreateUser' :: CreateUser -> Text
password} -> Text
password) (\s :: CreateUser
s@CreateUser' {} Text
a -> CreateUser
s {$sel:password:CreateUser' :: Text
password = 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 -> () -> 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 Bool
Maybe [Text]
Text
password :: Text
brokerId :: Text
username :: Text
groups :: Maybe [Text]
consoleAccess :: Maybe Bool
$sel:password:CreateUser' :: CreateUser -> Text
$sel:brokerId:CreateUser' :: CreateUser -> Text
$sel:username:CreateUser' :: CreateUser -> Text
$sel:groups:CreateUser' :: CreateUser -> Maybe [Text]
$sel:consoleAccess:CreateUser' :: CreateUser -> Maybe Bool
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
consoleAccess
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
groups
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
username
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
brokerId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
password

instance Prelude.NFData CreateUser where
  rnf :: CreateUser -> ()
rnf CreateUser' {Maybe Bool
Maybe [Text]
Text
password :: Text
brokerId :: Text
username :: Text
groups :: Maybe [Text]
consoleAccess :: Maybe Bool
$sel:password:CreateUser' :: CreateUser -> Text
$sel:brokerId:CreateUser' :: CreateUser -> Text
$sel:username:CreateUser' :: CreateUser -> Text
$sel:groups:CreateUser' :: CreateUser -> Maybe [Text]
$sel:consoleAccess:CreateUser' :: CreateUser -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
consoleAccess
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
groups
      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 Text
brokerId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
password

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 Bool
Maybe [Text]
Text
password :: Text
brokerId :: Text
username :: Text
groups :: Maybe [Text]
consoleAccess :: Maybe Bool
$sel:password:CreateUser' :: CreateUser -> Text
$sel:brokerId:CreateUser' :: CreateUser -> Text
$sel:username:CreateUser' :: CreateUser -> Text
$sel:groups:CreateUser' :: CreateUser -> Maybe [Text]
$sel:consoleAccess:CreateUser' :: CreateUser -> Maybe Bool
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"consoleAccess" 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 Bool
consoleAccess,
            (Key
"groups" 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]
groups,
            forall a. a -> Maybe a
Prelude.Just (Key
"password" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
password)
          ]
      )

instance Data.ToPath CreateUser where
  toPath :: CreateUser -> ByteString
toPath CreateUser' {Maybe Bool
Maybe [Text]
Text
password :: Text
brokerId :: Text
username :: Text
groups :: Maybe [Text]
consoleAccess :: Maybe Bool
$sel:password:CreateUser' :: CreateUser -> Text
$sel:brokerId:CreateUser' :: CreateUser -> Text
$sel:username:CreateUser' :: CreateUser -> Text
$sel:groups:CreateUser' :: CreateUser -> Maybe [Text]
$sel:consoleAccess:CreateUser' :: CreateUser -> Maybe Bool
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/v1/brokers/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
brokerId,
        ByteString
"/users/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
username
      ]

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