{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeFamilies #-}
module Aws.Iam.Commands.UpdateAccessKey
( UpdateAccessKey(..)
, UpdateAccessKeyResponse(..)
) where
import Aws.Core
import Aws.Iam.Core
import Aws.Iam.Internal
import Control.Applicative
import Data.Text (Text)
import Data.Typeable
import Prelude
data UpdateAccessKey
= UpdateAccessKey {
UpdateAccessKey -> Text
uakAccessKeyId :: Text
, UpdateAccessKey -> AccessKeyStatus
uakStatus :: AccessKeyStatus
, UpdateAccessKey -> Maybe Text
uakUserName :: Maybe Text
}
deriving (UpdateAccessKey -> UpdateAccessKey -> Bool
(UpdateAccessKey -> UpdateAccessKey -> Bool)
-> (UpdateAccessKey -> UpdateAccessKey -> Bool)
-> Eq UpdateAccessKey
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: UpdateAccessKey -> UpdateAccessKey -> Bool
== :: UpdateAccessKey -> UpdateAccessKey -> Bool
$c/= :: UpdateAccessKey -> UpdateAccessKey -> Bool
/= :: UpdateAccessKey -> UpdateAccessKey -> Bool
Eq, Eq UpdateAccessKey
Eq UpdateAccessKey =>
(UpdateAccessKey -> UpdateAccessKey -> Ordering)
-> (UpdateAccessKey -> UpdateAccessKey -> Bool)
-> (UpdateAccessKey -> UpdateAccessKey -> Bool)
-> (UpdateAccessKey -> UpdateAccessKey -> Bool)
-> (UpdateAccessKey -> UpdateAccessKey -> Bool)
-> (UpdateAccessKey -> UpdateAccessKey -> UpdateAccessKey)
-> (UpdateAccessKey -> UpdateAccessKey -> UpdateAccessKey)
-> Ord UpdateAccessKey
UpdateAccessKey -> UpdateAccessKey -> Bool
UpdateAccessKey -> UpdateAccessKey -> Ordering
UpdateAccessKey -> UpdateAccessKey -> UpdateAccessKey
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 :: UpdateAccessKey -> UpdateAccessKey -> Ordering
compare :: UpdateAccessKey -> UpdateAccessKey -> Ordering
$c< :: UpdateAccessKey -> UpdateAccessKey -> Bool
< :: UpdateAccessKey -> UpdateAccessKey -> Bool
$c<= :: UpdateAccessKey -> UpdateAccessKey -> Bool
<= :: UpdateAccessKey -> UpdateAccessKey -> Bool
$c> :: UpdateAccessKey -> UpdateAccessKey -> Bool
> :: UpdateAccessKey -> UpdateAccessKey -> Bool
$c>= :: UpdateAccessKey -> UpdateAccessKey -> Bool
>= :: UpdateAccessKey -> UpdateAccessKey -> Bool
$cmax :: UpdateAccessKey -> UpdateAccessKey -> UpdateAccessKey
max :: UpdateAccessKey -> UpdateAccessKey -> UpdateAccessKey
$cmin :: UpdateAccessKey -> UpdateAccessKey -> UpdateAccessKey
min :: UpdateAccessKey -> UpdateAccessKey -> UpdateAccessKey
Ord, Int -> UpdateAccessKey -> ShowS
[UpdateAccessKey] -> ShowS
UpdateAccessKey -> String
(Int -> UpdateAccessKey -> ShowS)
-> (UpdateAccessKey -> String)
-> ([UpdateAccessKey] -> ShowS)
-> Show UpdateAccessKey
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> UpdateAccessKey -> ShowS
showsPrec :: Int -> UpdateAccessKey -> ShowS
$cshow :: UpdateAccessKey -> String
show :: UpdateAccessKey -> String
$cshowList :: [UpdateAccessKey] -> ShowS
showList :: [UpdateAccessKey] -> ShowS
Show, Typeable)
instance SignQuery UpdateAccessKey where
type ServiceConfiguration UpdateAccessKey = IamConfiguration
signQuery :: forall queryType.
UpdateAccessKey
-> ServiceConfiguration UpdateAccessKey queryType
-> SignatureData
-> SignedQuery
signQuery UpdateAccessKey{Maybe Text
Text
AccessKeyStatus
uakAccessKeyId :: UpdateAccessKey -> Text
uakStatus :: UpdateAccessKey -> AccessKeyStatus
uakUserName :: UpdateAccessKey -> Maybe Text
uakAccessKeyId :: Text
uakStatus :: AccessKeyStatus
uakUserName :: Maybe Text
..}
= ByteString
-> [Maybe (ByteString, Text)]
-> IamConfiguration queryType
-> SignatureData
-> SignedQuery
forall qt.
ByteString
-> [Maybe (ByteString, Text)]
-> IamConfiguration qt
-> SignatureData
-> SignedQuery
iamAction' ByteString
"UpdateAccessKey" [
(ByteString, Text) -> Maybe (ByteString, Text)
forall a. a -> Maybe a
Just (ByteString
"AccessKeyId", Text
uakAccessKeyId)
, (ByteString, Text) -> Maybe (ByteString, Text)
forall a. a -> Maybe a
Just (ByteString
"Status", AccessKeyStatus -> Text
forall {a}. IsString a => AccessKeyStatus -> a
showStatus AccessKeyStatus
uakStatus)
, (ByteString
"UserName",) (Text -> (ByteString, Text))
-> Maybe Text -> Maybe (ByteString, Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Text
uakUserName
]
where
showStatus :: AccessKeyStatus -> a
showStatus AccessKeyStatus
AccessKeyActive = a
"Active"
showStatus AccessKeyStatus
_ = a
"Inactive"
data UpdateAccessKeyResponse = UpdateAccessKeyResponse
deriving (UpdateAccessKeyResponse -> UpdateAccessKeyResponse -> Bool
(UpdateAccessKeyResponse -> UpdateAccessKeyResponse -> Bool)
-> (UpdateAccessKeyResponse -> UpdateAccessKeyResponse -> Bool)
-> Eq UpdateAccessKeyResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: UpdateAccessKeyResponse -> UpdateAccessKeyResponse -> Bool
== :: UpdateAccessKeyResponse -> UpdateAccessKeyResponse -> Bool
$c/= :: UpdateAccessKeyResponse -> UpdateAccessKeyResponse -> Bool
/= :: UpdateAccessKeyResponse -> UpdateAccessKeyResponse -> Bool
Eq, Eq UpdateAccessKeyResponse
Eq UpdateAccessKeyResponse =>
(UpdateAccessKeyResponse -> UpdateAccessKeyResponse -> Ordering)
-> (UpdateAccessKeyResponse -> UpdateAccessKeyResponse -> Bool)
-> (UpdateAccessKeyResponse -> UpdateAccessKeyResponse -> Bool)
-> (UpdateAccessKeyResponse -> UpdateAccessKeyResponse -> Bool)
-> (UpdateAccessKeyResponse -> UpdateAccessKeyResponse -> Bool)
-> (UpdateAccessKeyResponse
-> UpdateAccessKeyResponse -> UpdateAccessKeyResponse)
-> (UpdateAccessKeyResponse
-> UpdateAccessKeyResponse -> UpdateAccessKeyResponse)
-> Ord UpdateAccessKeyResponse
UpdateAccessKeyResponse -> UpdateAccessKeyResponse -> Bool
UpdateAccessKeyResponse -> UpdateAccessKeyResponse -> Ordering
UpdateAccessKeyResponse
-> UpdateAccessKeyResponse -> UpdateAccessKeyResponse
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 :: UpdateAccessKeyResponse -> UpdateAccessKeyResponse -> Ordering
compare :: UpdateAccessKeyResponse -> UpdateAccessKeyResponse -> Ordering
$c< :: UpdateAccessKeyResponse -> UpdateAccessKeyResponse -> Bool
< :: UpdateAccessKeyResponse -> UpdateAccessKeyResponse -> Bool
$c<= :: UpdateAccessKeyResponse -> UpdateAccessKeyResponse -> Bool
<= :: UpdateAccessKeyResponse -> UpdateAccessKeyResponse -> Bool
$c> :: UpdateAccessKeyResponse -> UpdateAccessKeyResponse -> Bool
> :: UpdateAccessKeyResponse -> UpdateAccessKeyResponse -> Bool
$c>= :: UpdateAccessKeyResponse -> UpdateAccessKeyResponse -> Bool
>= :: UpdateAccessKeyResponse -> UpdateAccessKeyResponse -> Bool
$cmax :: UpdateAccessKeyResponse
-> UpdateAccessKeyResponse -> UpdateAccessKeyResponse
max :: UpdateAccessKeyResponse
-> UpdateAccessKeyResponse -> UpdateAccessKeyResponse
$cmin :: UpdateAccessKeyResponse
-> UpdateAccessKeyResponse -> UpdateAccessKeyResponse
min :: UpdateAccessKeyResponse
-> UpdateAccessKeyResponse -> UpdateAccessKeyResponse
Ord, Int -> UpdateAccessKeyResponse -> ShowS
[UpdateAccessKeyResponse] -> ShowS
UpdateAccessKeyResponse -> String
(Int -> UpdateAccessKeyResponse -> ShowS)
-> (UpdateAccessKeyResponse -> String)
-> ([UpdateAccessKeyResponse] -> ShowS)
-> Show UpdateAccessKeyResponse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> UpdateAccessKeyResponse -> ShowS
showsPrec :: Int -> UpdateAccessKeyResponse -> ShowS
$cshow :: UpdateAccessKeyResponse -> String
show :: UpdateAccessKeyResponse -> String
$cshowList :: [UpdateAccessKeyResponse] -> ShowS
showList :: [UpdateAccessKeyResponse] -> ShowS
Show, Typeable)
instance ResponseConsumer UpdateAccessKey UpdateAccessKeyResponse where
type ResponseMetadata UpdateAccessKeyResponse = IamMetadata
responseConsumer :: Request
-> UpdateAccessKey
-> IORef (ResponseMetadata UpdateAccessKeyResponse)
-> HTTPResponseConsumer UpdateAccessKeyResponse
responseConsumer Request
_ UpdateAccessKey
_
= (Cursor -> Response IamMetadata UpdateAccessKeyResponse)
-> IORef IamMetadata
-> HTTPResponseConsumer UpdateAccessKeyResponse
forall a.
(Cursor -> Response IamMetadata a)
-> IORef IamMetadata -> HTTPResponseConsumer a
iamResponseConsumer (Response IamMetadata UpdateAccessKeyResponse
-> Cursor -> Response IamMetadata UpdateAccessKeyResponse
forall a b. a -> b -> a
const (Response IamMetadata UpdateAccessKeyResponse
-> Cursor -> Response IamMetadata UpdateAccessKeyResponse)
-> Response IamMetadata UpdateAccessKeyResponse
-> Cursor
-> Response IamMetadata UpdateAccessKeyResponse
forall a b. (a -> b) -> a -> b
$ UpdateAccessKeyResponse
-> Response IamMetadata UpdateAccessKeyResponse
forall a. a -> Response IamMetadata a
forall (m :: * -> *) a. Monad m => a -> m a
return UpdateAccessKeyResponse
UpdateAccessKeyResponse)
instance Transaction UpdateAccessKey UpdateAccessKeyResponse
instance AsMemoryResponse UpdateAccessKeyResponse where
type MemoryResponse UpdateAccessKeyResponse = UpdateAccessKeyResponse
loadToMemory :: UpdateAccessKeyResponse
-> ResourceT IO (MemoryResponse UpdateAccessKeyResponse)
loadToMemory = UpdateAccessKeyResponse
-> ResourceT IO (MemoryResponse UpdateAccessKeyResponse)
UpdateAccessKeyResponse -> ResourceT IO UpdateAccessKeyResponse
forall a. a -> ResourceT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return