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

    -- * Request Lenses
    removeUserFromGroup_groupName,
    removeUserFromGroup_userName,

    -- * Destructuring the Response
    RemoveUserFromGroupResponse (..),
    newRemoveUserFromGroupResponse,
  )
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:/ 'newRemoveUserFromGroup' smart constructor.
data RemoveUserFromGroup = RemoveUserFromGroup'
  { -- | 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: _+=,.\@-
    RemoveUserFromGroup -> Text
groupName :: Prelude.Text,
    -- | The name of the user to remove.
    --
    -- 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: _+=,.\@-
    RemoveUserFromGroup -> Text
userName :: Prelude.Text
  }
  deriving (RemoveUserFromGroup -> RemoveUserFromGroup -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RemoveUserFromGroup -> RemoveUserFromGroup -> Bool
$c/= :: RemoveUserFromGroup -> RemoveUserFromGroup -> Bool
== :: RemoveUserFromGroup -> RemoveUserFromGroup -> Bool
$c== :: RemoveUserFromGroup -> RemoveUserFromGroup -> Bool
Prelude.Eq, ReadPrec [RemoveUserFromGroup]
ReadPrec RemoveUserFromGroup
Int -> ReadS RemoveUserFromGroup
ReadS [RemoveUserFromGroup]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RemoveUserFromGroup]
$creadListPrec :: ReadPrec [RemoveUserFromGroup]
readPrec :: ReadPrec RemoveUserFromGroup
$creadPrec :: ReadPrec RemoveUserFromGroup
readList :: ReadS [RemoveUserFromGroup]
$creadList :: ReadS [RemoveUserFromGroup]
readsPrec :: Int -> ReadS RemoveUserFromGroup
$creadsPrec :: Int -> ReadS RemoveUserFromGroup
Prelude.Read, Int -> RemoveUserFromGroup -> ShowS
[RemoveUserFromGroup] -> ShowS
RemoveUserFromGroup -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RemoveUserFromGroup] -> ShowS
$cshowList :: [RemoveUserFromGroup] -> ShowS
show :: RemoveUserFromGroup -> String
$cshow :: RemoveUserFromGroup -> String
showsPrec :: Int -> RemoveUserFromGroup -> ShowS
$cshowsPrec :: Int -> RemoveUserFromGroup -> ShowS
Prelude.Show, forall x. Rep RemoveUserFromGroup x -> RemoveUserFromGroup
forall x. RemoveUserFromGroup -> Rep RemoveUserFromGroup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RemoveUserFromGroup x -> RemoveUserFromGroup
$cfrom :: forall x. RemoveUserFromGroup -> Rep RemoveUserFromGroup x
Prelude.Generic)

-- |
-- Create a value of 'RemoveUserFromGroup' 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', 'removeUserFromGroup_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', 'removeUserFromGroup_userName' - The name of the user to remove.
--
-- 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: _+=,.\@-
newRemoveUserFromGroup ::
  -- | 'groupName'
  Prelude.Text ->
  -- | 'userName'
  Prelude.Text ->
  RemoveUserFromGroup
newRemoveUserFromGroup :: Text -> Text -> RemoveUserFromGroup
newRemoveUserFromGroup Text
pGroupName_ Text
pUserName_ =
  RemoveUserFromGroup'
    { $sel:groupName:RemoveUserFromGroup' :: Text
groupName = Text
pGroupName_,
      $sel:userName:RemoveUserFromGroup' :: 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: _+=,.\@-
removeUserFromGroup_groupName :: Lens.Lens' RemoveUserFromGroup Prelude.Text
removeUserFromGroup_groupName :: Lens' RemoveUserFromGroup Text
removeUserFromGroup_groupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RemoveUserFromGroup' {Text
groupName :: Text
$sel:groupName:RemoveUserFromGroup' :: RemoveUserFromGroup -> Text
groupName} -> Text
groupName) (\s :: RemoveUserFromGroup
s@RemoveUserFromGroup' {} Text
a -> RemoveUserFromGroup
s {$sel:groupName:RemoveUserFromGroup' :: Text
groupName = Text
a} :: RemoveUserFromGroup)

-- | The name of the user to remove.
--
-- 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: _+=,.\@-
removeUserFromGroup_userName :: Lens.Lens' RemoveUserFromGroup Prelude.Text
removeUserFromGroup_userName :: Lens' RemoveUserFromGroup Text
removeUserFromGroup_userName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RemoveUserFromGroup' {Text
userName :: Text
$sel:userName:RemoveUserFromGroup' :: RemoveUserFromGroup -> Text
userName} -> Text
userName) (\s :: RemoveUserFromGroup
s@RemoveUserFromGroup' {} Text
a -> RemoveUserFromGroup
s {$sel:userName:RemoveUserFromGroup' :: Text
userName = Text
a} :: RemoveUserFromGroup)

instance Core.AWSRequest RemoveUserFromGroup where
  type
    AWSResponse RemoveUserFromGroup =
      RemoveUserFromGroupResponse
  request :: (Service -> Service)
-> RemoveUserFromGroup -> Request RemoveUserFromGroup
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 RemoveUserFromGroup
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse RemoveUserFromGroup)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull RemoveUserFromGroupResponse
RemoveUserFromGroupResponse'

instance Prelude.Hashable RemoveUserFromGroup where
  hashWithSalt :: Int -> RemoveUserFromGroup -> Int
hashWithSalt Int
_salt RemoveUserFromGroup' {Text
userName :: Text
groupName :: Text
$sel:userName:RemoveUserFromGroup' :: RemoveUserFromGroup -> Text
$sel:groupName:RemoveUserFromGroup' :: RemoveUserFromGroup -> 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 RemoveUserFromGroup where
  rnf :: RemoveUserFromGroup -> ()
rnf RemoveUserFromGroup' {Text
userName :: Text
groupName :: Text
$sel:userName:RemoveUserFromGroup' :: RemoveUserFromGroup -> Text
$sel:groupName:RemoveUserFromGroup' :: RemoveUserFromGroup -> 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 RemoveUserFromGroup where
  toHeaders :: RemoveUserFromGroup -> [Header]
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance Data.ToQuery RemoveUserFromGroup where
  toQuery :: RemoveUserFromGroup -> QueryString
toQuery RemoveUserFromGroup' {Text
userName :: Text
groupName :: Text
$sel:userName:RemoveUserFromGroup' :: RemoveUserFromGroup -> Text
$sel:groupName:RemoveUserFromGroup' :: RemoveUserFromGroup -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"RemoveUserFromGroup" :: 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:/ 'newRemoveUserFromGroupResponse' smart constructor.
data RemoveUserFromGroupResponse = RemoveUserFromGroupResponse'
  {
  }
  deriving (RemoveUserFromGroupResponse -> RemoveUserFromGroupResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RemoveUserFromGroupResponse -> RemoveUserFromGroupResponse -> Bool
$c/= :: RemoveUserFromGroupResponse -> RemoveUserFromGroupResponse -> Bool
== :: RemoveUserFromGroupResponse -> RemoveUserFromGroupResponse -> Bool
$c== :: RemoveUserFromGroupResponse -> RemoveUserFromGroupResponse -> Bool
Prelude.Eq, ReadPrec [RemoveUserFromGroupResponse]
ReadPrec RemoveUserFromGroupResponse
Int -> ReadS RemoveUserFromGroupResponse
ReadS [RemoveUserFromGroupResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RemoveUserFromGroupResponse]
$creadListPrec :: ReadPrec [RemoveUserFromGroupResponse]
readPrec :: ReadPrec RemoveUserFromGroupResponse
$creadPrec :: ReadPrec RemoveUserFromGroupResponse
readList :: ReadS [RemoveUserFromGroupResponse]
$creadList :: ReadS [RemoveUserFromGroupResponse]
readsPrec :: Int -> ReadS RemoveUserFromGroupResponse
$creadsPrec :: Int -> ReadS RemoveUserFromGroupResponse
Prelude.Read, Int -> RemoveUserFromGroupResponse -> ShowS
[RemoveUserFromGroupResponse] -> ShowS
RemoveUserFromGroupResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RemoveUserFromGroupResponse] -> ShowS
$cshowList :: [RemoveUserFromGroupResponse] -> ShowS
show :: RemoveUserFromGroupResponse -> String
$cshow :: RemoveUserFromGroupResponse -> String
showsPrec :: Int -> RemoveUserFromGroupResponse -> ShowS
$cshowsPrec :: Int -> RemoveUserFromGroupResponse -> ShowS
Prelude.Show, forall x.
Rep RemoveUserFromGroupResponse x -> RemoveUserFromGroupResponse
forall x.
RemoveUserFromGroupResponse -> Rep RemoveUserFromGroupResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep RemoveUserFromGroupResponse x -> RemoveUserFromGroupResponse
$cfrom :: forall x.
RemoveUserFromGroupResponse -> Rep RemoveUserFromGroupResponse x
Prelude.Generic)

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

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