{-# 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 {
        uakAccessKeyId :: Text
      
      , uakStatus      :: AccessKeyStatus
      
      , uakUserName    :: Maybe Text
      
      
      
      }
    deriving (Eq, Ord, Show, Typeable)
instance SignQuery UpdateAccessKey where
    type ServiceConfiguration UpdateAccessKey = IamConfiguration
    signQuery UpdateAccessKey{..}
        = iamAction' "UpdateAccessKey" [
              Just ("AccessKeyId", uakAccessKeyId)
            , Just ("Status", showStatus uakStatus)
            , ("UserName",) <$> uakUserName
            ]
        where
          showStatus AccessKeyActive = "Active"
          showStatus _               = "Inactive"
data UpdateAccessKeyResponse = UpdateAccessKeyResponse
    deriving (Eq, Ord, Show, Typeable)
instance ResponseConsumer UpdateAccessKey UpdateAccessKeyResponse where
    type ResponseMetadata UpdateAccessKeyResponse = IamMetadata
    responseConsumer _ _
        = iamResponseConsumer (const $ return UpdateAccessKeyResponse)
instance Transaction UpdateAccessKey UpdateAccessKeyResponse
instance AsMemoryResponse UpdateAccessKeyResponse where
    type MemoryResponse UpdateAccessKeyResponse = UpdateAccessKeyResponse
    loadToMemory = return