{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeFamilies #-}
module Aws.Iam.Commands.ListGroups
( ListGroups(..)
, ListGroupsResponse(..)
, Group(..)
) where
import Aws.Core
import Aws.Iam.Core
import Aws.Iam.Internal
import Control.Applicative
import Data.Text (Text)
import Data.Typeable
import Prelude
import Text.XML.Cursor (laxElement, ($//), (&|))
data ListGroups
= ListGroups {
lgPathPrefix :: Maybe Text
, lgMarker :: Maybe Text
, lgMaxItems :: Maybe Integer
}
deriving (Eq, Ord, Show, Typeable)
instance SignQuery ListGroups where
type ServiceConfiguration ListGroups = IamConfiguration
signQuery ListGroups{..}
= iamAction' "ListGroups" $ [
("PathPrefix",) <$> lgPathPrefix
] <> markedIter lgMarker lgMaxItems
data ListGroupsResponse
= ListGroupsResponse {
lgrGroups :: [Group]
, lgrIsTruncated :: Bool
, lgrMarker :: Maybe Text
}
deriving (Eq, Ord, Show, Typeable)
instance ResponseConsumer ListGroups ListGroupsResponse where
type ResponseMetadata ListGroupsResponse = IamMetadata
responseConsumer _ _
= iamResponseConsumer $ \cursor -> do
(lgrIsTruncated, lgrMarker) <- markedIterResponse cursor
lgrGroups <- sequence $
cursor $// laxElement "member" &| parseGroup
return ListGroupsResponse{..}
instance Transaction ListGroups ListGroupsResponse
instance IteratedTransaction ListGroups ListGroupsResponse where
nextIteratedRequest request response
= case lgrMarker response of
Nothing -> Nothing
Just marker -> Just $ request { lgMarker = Just marker }
instance AsMemoryResponse ListGroupsResponse where
type MemoryResponse ListGroupsResponse = ListGroupsResponse
loadToMemory = return