module Aws.Iam.Commands.ListUserPolicies
( ListUserPolicies(..)
, ListUserPoliciesResponse(..)
) where
import Aws.Core
import Aws.Iam.Core
import Aws.Iam.Internal
import Data.Text (Text)
import Data.Typeable
import Text.XML.Cursor (content, laxElement, ($//), (&/))
data ListUserPolicies
= ListUserPolicies {
lupUserName :: Text
, lupMarker :: Maybe Text
, lupMaxItems :: Maybe Integer
}
deriving (Eq, Ord, Show, Typeable)
instance SignQuery ListUserPolicies where
type ServiceConfiguration ListUserPolicies = IamConfiguration
signQuery ListUserPolicies{..}
= iamAction' "ListUserPolicies" $ [
Just ("UserName", lupUserName)
] <> markedIter lupMarker lupMaxItems
data ListUserPoliciesResponse
= ListUserPoliciesResponse {
luprPolicyNames :: [Text]
, luprIsTruncated :: Bool
, luprMarker :: Maybe Text
}
deriving (Eq, Ord, Show, Typeable)
instance ResponseConsumer ListUserPolicies ListUserPoliciesResponse where
type ResponseMetadata ListUserPoliciesResponse = IamMetadata
responseConsumer _
= iamResponseConsumer $ \cursor -> do
(luprIsTruncated, luprMarker) <- markedIterResponse cursor
let luprPolicyNames = cursor $// laxElement "member" &/ content
return ListUserPoliciesResponse{..}
instance Transaction ListUserPolicies ListUserPoliciesResponse
instance IteratedTransaction ListUserPolicies ListUserPoliciesResponse where
nextIteratedRequest request response
= case luprMarker response of
Nothing -> Nothing
Just marker -> Just $ request { lupMarker = Just marker }
instance AsMemoryResponse ListUserPoliciesResponse where
type MemoryResponse ListUserPoliciesResponse = ListUserPoliciesResponse
loadToMemory = return