{-# 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.IAM.AddUserToGroup
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Adds the specified user to the specified group.
module Amazonka.IAM.AddUserToGroup
  ( -- * Creating a Request
    AddUserToGroup (..),
    newAddUserToGroup,

    -- * Request Lenses
    addUserToGroup_groupName,
    addUserToGroup_userName,

    -- * Destructuring the Response
    AddUserToGroupResponse (..),
    newAddUserToGroupResponse,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.IAM.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newAddUserToGroup' smart constructor.
data AddUserToGroup = AddUserToGroup'
  { -- | The name of the group to update.
    --
    -- This parameter allows (through its
    -- <http://wikipedia.org/wiki/regex regex pattern>) a string of characters
    -- consisting of upper and lowercase alphanumeric characters with no
    -- spaces. You can also include any of the following characters: _+=,.\@-
    AddUserToGroup -> Text
groupName :: Prelude.Text,
    -- | The name of the user to add.
    --
    -- This parameter allows (through its
    -- <http://wikipedia.org/wiki/regex regex pattern>) a string of characters
    -- consisting of upper and lowercase alphanumeric characters with no
    -- spaces. You can also include any of the following characters: _+=,.\@-
    AddUserToGroup -> Text
userName :: Prelude.Text
  }
  deriving (AddUserToGroup -> AddUserToGroup -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AddUserToGroup -> AddUserToGroup -> Bool
$c/= :: AddUserToGroup -> AddUserToGroup -> Bool
== :: AddUserToGroup -> AddUserToGroup -> Bool
$c== :: AddUserToGroup -> AddUserToGroup -> Bool
Prelude.Eq, ReadPrec [AddUserToGroup]
ReadPrec AddUserToGroup
Int -> ReadS AddUserToGroup
ReadS [AddUserToGroup]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AddUserToGroup]
$creadListPrec :: ReadPrec [AddUserToGroup]
readPrec :: ReadPrec AddUserToGroup
$creadPrec :: ReadPrec AddUserToGroup
readList :: ReadS [AddUserToGroup]
$creadList :: ReadS [AddUserToGroup]
readsPrec :: Int -> ReadS AddUserToGroup
$creadsPrec :: Int -> ReadS AddUserToGroup
Prelude.Read, Int -> AddUserToGroup -> ShowS
[AddUserToGroup] -> ShowS
AddUserToGroup -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AddUserToGroup] -> ShowS
$cshowList :: [AddUserToGroup] -> ShowS
show :: AddUserToGroup -> String
$cshow :: AddUserToGroup -> String
showsPrec :: Int -> AddUserToGroup -> ShowS
$cshowsPrec :: Int -> AddUserToGroup -> ShowS
Prelude.Show, forall x. Rep AddUserToGroup x -> AddUserToGroup
forall x. AddUserToGroup -> Rep AddUserToGroup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AddUserToGroup x -> AddUserToGroup
$cfrom :: forall x. AddUserToGroup -> Rep AddUserToGroup x
Prelude.Generic)

-- |
-- Create a value of 'AddUserToGroup' 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:
--
-- 'groupName', 'addUserToGroup_groupName' - The name of the group to update.
--
-- This parameter allows (through its
-- <http://wikipedia.org/wiki/regex regex pattern>) a string of characters
-- consisting of upper and lowercase alphanumeric characters with no
-- spaces. You can also include any of the following characters: _+=,.\@-
--
-- 'userName', 'addUserToGroup_userName' - The name of the user to add.
--
-- This parameter allows (through its
-- <http://wikipedia.org/wiki/regex regex pattern>) a string of characters
-- consisting of upper and lowercase alphanumeric characters with no
-- spaces. You can also include any of the following characters: _+=,.\@-
newAddUserToGroup ::
  -- | 'groupName'
  Prelude.Text ->
  -- | 'userName'
  Prelude.Text ->
  AddUserToGroup
newAddUserToGroup :: Text -> Text -> AddUserToGroup
newAddUserToGroup Text
pGroupName_ Text
pUserName_ =
  AddUserToGroup'
    { $sel:groupName:AddUserToGroup' :: Text
groupName = Text
pGroupName_,
      $sel:userName:AddUserToGroup' :: Text
userName = Text
pUserName_
    }

-- | The name of the group to update.
--
-- This parameter allows (through its
-- <http://wikipedia.org/wiki/regex regex pattern>) a string of characters
-- consisting of upper and lowercase alphanumeric characters with no
-- spaces. You can also include any of the following characters: _+=,.\@-
addUserToGroup_groupName :: Lens.Lens' AddUserToGroup Prelude.Text
addUserToGroup_groupName :: Lens' AddUserToGroup Text
addUserToGroup_groupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AddUserToGroup' {Text
groupName :: Text
$sel:groupName:AddUserToGroup' :: AddUserToGroup -> Text
groupName} -> Text
groupName) (\s :: AddUserToGroup
s@AddUserToGroup' {} Text
a -> AddUserToGroup
s {$sel:groupName:AddUserToGroup' :: Text
groupName = Text
a} :: AddUserToGroup)

-- | The name of the user to add.
--
-- This parameter allows (through its
-- <http://wikipedia.org/wiki/regex regex pattern>) a string of characters
-- consisting of upper and lowercase alphanumeric characters with no
-- spaces. You can also include any of the following characters: _+=,.\@-
addUserToGroup_userName :: Lens.Lens' AddUserToGroup Prelude.Text
addUserToGroup_userName :: Lens' AddUserToGroup Text
addUserToGroup_userName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AddUserToGroup' {Text
userName :: Text
$sel:userName:AddUserToGroup' :: AddUserToGroup -> Text
userName} -> Text
userName) (\s :: AddUserToGroup
s@AddUserToGroup' {} Text
a -> AddUserToGroup
s {$sel:userName:AddUserToGroup' :: Text
userName = Text
a} :: AddUserToGroup)

instance Core.AWSRequest AddUserToGroup where
  type
    AWSResponse AddUserToGroup =
      AddUserToGroupResponse
  request :: (Service -> Service) -> AddUserToGroup -> Request AddUserToGroup
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.postQuery (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy AddUserToGroup
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse AddUserToGroup)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull AddUserToGroupResponse
AddUserToGroupResponse'

instance Prelude.Hashable AddUserToGroup where
  hashWithSalt :: Int -> AddUserToGroup -> Int
hashWithSalt Int
_salt AddUserToGroup' {Text
userName :: Text
groupName :: Text
$sel:userName:AddUserToGroup' :: AddUserToGroup -> Text
$sel:groupName:AddUserToGroup' :: AddUserToGroup -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
groupName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
userName

instance Prelude.NFData AddUserToGroup where
  rnf :: AddUserToGroup -> ()
rnf AddUserToGroup' {Text
userName :: Text
groupName :: Text
$sel:userName:AddUserToGroup' :: AddUserToGroup -> Text
$sel:groupName:AddUserToGroup' :: AddUserToGroup -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
groupName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
userName

instance Data.ToHeaders AddUserToGroup where
  toHeaders :: AddUserToGroup -> [Header]
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance Data.ToQuery AddUserToGroup where
  toQuery :: AddUserToGroup -> QueryString
toQuery AddUserToGroup' {Text
userName :: Text
groupName :: Text
$sel:userName:AddUserToGroup' :: AddUserToGroup -> Text
$sel:groupName:AddUserToGroup' :: AddUserToGroup -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"AddUserToGroup" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2010-05-08" :: Prelude.ByteString),
        ByteString
"GroupName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
groupName,
        ByteString
"UserName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
userName
      ]

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

-- |
-- Create a value of 'AddUserToGroupResponse' 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.
newAddUserToGroupResponse ::
  AddUserToGroupResponse
newAddUserToGroupResponse :: AddUserToGroupResponse
newAddUserToGroupResponse = AddUserToGroupResponse
AddUserToGroupResponse'

instance Prelude.NFData AddUserToGroupResponse where
  rnf :: AddUserToGroupResponse -> ()
rnf AddUserToGroupResponse
_ = ()