{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RecordWildCards       #-}
{-# LANGUAGE TupleSections         #-}
{-# LANGUAGE TypeFamilies          #-}
module Aws.Iam.Commands.CreateUser
    ( CreateUser(..)
    , CreateUserResponse(..)
    , User(..)
    ) where

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

-- | Creates a new user.
--
-- <http://docs.aws.amazon.com/IAM/latest/APIReference/API_CreateUser.html>
data CreateUser
    = CreateUser {
        CreateUser -> Text
cuUserName :: Text
      -- ^ Name of the new user
      , CreateUser -> Maybe Text
cuPath     :: Maybe Text
      -- ^ Path under which the user will be created. Defaults to @/@ if
      -- omitted.
      }
    deriving (CreateUser -> CreateUser -> Bool
(CreateUser -> CreateUser -> Bool)
-> (CreateUser -> CreateUser -> Bool) -> Eq CreateUser
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CreateUser -> CreateUser -> Bool
== :: CreateUser -> CreateUser -> Bool
$c/= :: CreateUser -> CreateUser -> Bool
/= :: CreateUser -> CreateUser -> Bool
Eq, Eq CreateUser
Eq CreateUser =>
(CreateUser -> CreateUser -> Ordering)
-> (CreateUser -> CreateUser -> Bool)
-> (CreateUser -> CreateUser -> Bool)
-> (CreateUser -> CreateUser -> Bool)
-> (CreateUser -> CreateUser -> Bool)
-> (CreateUser -> CreateUser -> CreateUser)
-> (CreateUser -> CreateUser -> CreateUser)
-> Ord CreateUser
CreateUser -> CreateUser -> Bool
CreateUser -> CreateUser -> Ordering
CreateUser -> CreateUser -> CreateUser
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
$ccompare :: CreateUser -> CreateUser -> Ordering
compare :: CreateUser -> CreateUser -> Ordering
$c< :: CreateUser -> CreateUser -> Bool
< :: CreateUser -> CreateUser -> Bool
$c<= :: CreateUser -> CreateUser -> Bool
<= :: CreateUser -> CreateUser -> Bool
$c> :: CreateUser -> CreateUser -> Bool
> :: CreateUser -> CreateUser -> Bool
$c>= :: CreateUser -> CreateUser -> Bool
>= :: CreateUser -> CreateUser -> Bool
$cmax :: CreateUser -> CreateUser -> CreateUser
max :: CreateUser -> CreateUser -> CreateUser
$cmin :: CreateUser -> CreateUser -> CreateUser
min :: CreateUser -> CreateUser -> CreateUser
Ord, Int -> CreateUser -> ShowS
[CreateUser] -> ShowS
CreateUser -> String
(Int -> CreateUser -> ShowS)
-> (CreateUser -> String)
-> ([CreateUser] -> ShowS)
-> Show CreateUser
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CreateUser -> ShowS
showsPrec :: Int -> CreateUser -> ShowS
$cshow :: CreateUser -> String
show :: CreateUser -> String
$cshowList :: [CreateUser] -> ShowS
showList :: [CreateUser] -> ShowS
Show, Typeable)

instance SignQuery CreateUser where
    type ServiceConfiguration CreateUser = IamConfiguration
    signQuery :: forall queryType.
CreateUser
-> ServiceConfiguration CreateUser queryType
-> SignatureData
-> SignedQuery
signQuery CreateUser{Maybe Text
Text
cuUserName :: CreateUser -> Text
cuPath :: CreateUser -> Maybe Text
cuUserName :: Text
cuPath :: Maybe Text
..}
        = ByteString
-> [Maybe (ByteString, Text)]
-> IamConfiguration queryType
-> SignatureData
-> SignedQuery
forall qt.
ByteString
-> [Maybe (ByteString, Text)]
-> IamConfiguration qt
-> SignatureData
-> SignedQuery
iamAction' ByteString
"CreateUser" [
              (ByteString, Text) -> Maybe (ByteString, Text)
forall a. a -> Maybe a
Just (ByteString
"UserName", Text
cuUserName)
            , (ByteString
"Path",) (Text -> (ByteString, Text))
-> Maybe Text -> Maybe (ByteString, Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Text
cuPath
            ]

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

instance ResponseConsumer CreateUser CreateUserResponse where
    type ResponseMetadata CreateUserResponse = IamMetadata
    responseConsumer :: Request
-> CreateUser
-> IORef (ResponseMetadata CreateUserResponse)
-> HTTPResponseConsumer CreateUserResponse
responseConsumer Request
_ CreateUser
_
        = (Cursor -> Response IamMetadata CreateUserResponse)
-> IORef IamMetadata -> HTTPResponseConsumer CreateUserResponse
forall a.
(Cursor -> Response IamMetadata a)
-> IORef IamMetadata -> HTTPResponseConsumer a
iamResponseConsumer ((Cursor -> Response IamMetadata CreateUserResponse)
 -> IORef IamMetadata -> HTTPResponseConsumer CreateUserResponse)
-> (Cursor -> Response IamMetadata CreateUserResponse)
-> IORef IamMetadata
-> HTTPResponseConsumer CreateUserResponse
forall a b. (a -> b) -> a -> b
$
          (User -> CreateUserResponse)
-> Response IamMetadata User
-> Response IamMetadata CreateUserResponse
forall a b.
(a -> b) -> Response IamMetadata a -> Response IamMetadata b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap User -> CreateUserResponse
CreateUserResponse (Response IamMetadata User
 -> Response IamMetadata CreateUserResponse)
-> (Cursor -> Response IamMetadata User)
-> Cursor
-> Response IamMetadata CreateUserResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Cursor -> Response IamMetadata User
forall (m :: * -> *). MonadThrow m => Cursor -> m User
parseUser

instance Transaction CreateUser CreateUserResponse

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