{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RecordWildCards       #-}
{-# LANGUAGE TupleSections         #-}
{-# LANGUAGE TypeFamilies          #-}
module Aws.Iam.Commands.UpdateUser
    ( UpdateUser(..)
    , UpdateUserResponse(..)
    ) where

import           Aws.Core
import           Aws.Iam.Core
import           Aws.Iam.Internal
import           Control.Applicative
import           Data.Text           (Text)
import           Data.Typeable
import           Prelude

-- | Updates the name and/or path of the specified user.
--
-- <http://docs.aws.amazon.com/IAM/latest/APIReference/API_UpdateUser.html>
data UpdateUser
    = UpdateUser {
        UpdateUser -> Text
uuUserName    :: Text
      -- ^ Name of the user to be updated.
      , UpdateUser -> Maybe Text
uuNewUserName :: Maybe Text
      -- ^ New name for the user.
      , UpdateUser -> Maybe Text
uuNewPath     :: Maybe Text
      -- ^ New path to which the user will be moved.
      }
    deriving (UpdateUser -> UpdateUser -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateUser -> UpdateUser -> Bool
$c/= :: UpdateUser -> UpdateUser -> Bool
== :: UpdateUser -> UpdateUser -> Bool
$c== :: UpdateUser -> UpdateUser -> Bool
Eq, Eq UpdateUser
UpdateUser -> UpdateUser -> Bool
UpdateUser -> UpdateUser -> Ordering
UpdateUser -> UpdateUser -> UpdateUser
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: UpdateUser -> UpdateUser -> UpdateUser
$cmin :: UpdateUser -> UpdateUser -> UpdateUser
max :: UpdateUser -> UpdateUser -> UpdateUser
$cmax :: UpdateUser -> UpdateUser -> UpdateUser
>= :: UpdateUser -> UpdateUser -> Bool
$c>= :: UpdateUser -> UpdateUser -> Bool
> :: UpdateUser -> UpdateUser -> Bool
$c> :: UpdateUser -> UpdateUser -> Bool
<= :: UpdateUser -> UpdateUser -> Bool
$c<= :: UpdateUser -> UpdateUser -> Bool
< :: UpdateUser -> UpdateUser -> Bool
$c< :: UpdateUser -> UpdateUser -> Bool
compare :: UpdateUser -> UpdateUser -> Ordering
$ccompare :: UpdateUser -> UpdateUser -> Ordering
Ord, Int -> UpdateUser -> ShowS
[UpdateUser] -> ShowS
UpdateUser -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateUser] -> ShowS
$cshowList :: [UpdateUser] -> ShowS
show :: UpdateUser -> String
$cshow :: UpdateUser -> String
showsPrec :: Int -> UpdateUser -> ShowS
$cshowsPrec :: Int -> UpdateUser -> ShowS
Show, Typeable)

instance SignQuery UpdateUser where
    type ServiceConfiguration UpdateUser = IamConfiguration
    signQuery :: forall queryType.
UpdateUser
-> ServiceConfiguration UpdateUser queryType
-> SignatureData
-> SignedQuery
signQuery UpdateUser{Maybe Text
Text
uuNewPath :: Maybe Text
uuNewUserName :: Maybe Text
uuUserName :: Text
uuNewPath :: UpdateUser -> Maybe Text
uuNewUserName :: UpdateUser -> Maybe Text
uuUserName :: UpdateUser -> Text
..}
        = forall qt.
ByteString
-> [Maybe (ByteString, Text)]
-> IamConfiguration qt
-> SignatureData
-> SignedQuery
iamAction' ByteString
"UpdateUser" [
              forall a. a -> Maybe a
Just (ByteString
"UserName", Text
uuUserName)
            , (ByteString
"NewUserName",) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Text
uuNewUserName
            , (ByteString
"NewPath",) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Text
uuNewPath
            ]

data UpdateUserResponse = UpdateUserResponse
    deriving (UpdateUserResponse -> UpdateUserResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateUserResponse -> UpdateUserResponse -> Bool
$c/= :: UpdateUserResponse -> UpdateUserResponse -> Bool
== :: UpdateUserResponse -> UpdateUserResponse -> Bool
$c== :: UpdateUserResponse -> UpdateUserResponse -> Bool
Eq, Eq UpdateUserResponse
UpdateUserResponse -> UpdateUserResponse -> Bool
UpdateUserResponse -> UpdateUserResponse -> Ordering
UpdateUserResponse -> UpdateUserResponse -> UpdateUserResponse
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: UpdateUserResponse -> UpdateUserResponse -> UpdateUserResponse
$cmin :: UpdateUserResponse -> UpdateUserResponse -> UpdateUserResponse
max :: UpdateUserResponse -> UpdateUserResponse -> UpdateUserResponse
$cmax :: UpdateUserResponse -> UpdateUserResponse -> UpdateUserResponse
>= :: UpdateUserResponse -> UpdateUserResponse -> Bool
$c>= :: UpdateUserResponse -> UpdateUserResponse -> Bool
> :: UpdateUserResponse -> UpdateUserResponse -> Bool
$c> :: UpdateUserResponse -> UpdateUserResponse -> Bool
<= :: UpdateUserResponse -> UpdateUserResponse -> Bool
$c<= :: UpdateUserResponse -> UpdateUserResponse -> Bool
< :: UpdateUserResponse -> UpdateUserResponse -> Bool
$c< :: UpdateUserResponse -> UpdateUserResponse -> Bool
compare :: UpdateUserResponse -> UpdateUserResponse -> Ordering
$ccompare :: UpdateUserResponse -> UpdateUserResponse -> Ordering
Ord, Int -> UpdateUserResponse -> ShowS
[UpdateUserResponse] -> ShowS
UpdateUserResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateUserResponse] -> ShowS
$cshowList :: [UpdateUserResponse] -> ShowS
show :: UpdateUserResponse -> String
$cshow :: UpdateUserResponse -> String
showsPrec :: Int -> UpdateUserResponse -> ShowS
$cshowsPrec :: Int -> UpdateUserResponse -> ShowS
Show, Typeable)

instance ResponseConsumer UpdateUser UpdateUserResponse where
    type ResponseMetadata UpdateUserResponse = IamMetadata
    responseConsumer :: Request
-> UpdateUser
-> IORef (ResponseMetadata UpdateUserResponse)
-> HTTPResponseConsumer UpdateUserResponse
responseConsumer Request
_ UpdateUser
_
        = forall a.
(Cursor -> Response IamMetadata a)
-> IORef IamMetadata -> HTTPResponseConsumer a
iamResponseConsumer (forall a b. a -> b -> a
const forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. Monad m => a -> m a
return UpdateUserResponse
UpdateUserResponse)

instance Transaction UpdateUser UpdateUserResponse

instance AsMemoryResponse UpdateUserResponse where
    type MemoryResponse UpdateUserResponse = UpdateUserResponse
    loadToMemory :: UpdateUserResponse
-> ResourceT IO (MemoryResponse UpdateUserResponse)
loadToMemory = forall (m :: * -> *) a. Monad m => a -> m a
return