{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeFamilies #-}
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 {
ListUserPolicies -> Text
lupUserName :: Text
, ListUserPolicies -> Maybe Text
lupMarker :: Maybe Text
, ListUserPolicies -> Maybe Integer
lupMaxItems :: Maybe Integer
}
deriving (ListUserPolicies -> ListUserPolicies -> Bool
(ListUserPolicies -> ListUserPolicies -> Bool)
-> (ListUserPolicies -> ListUserPolicies -> Bool)
-> Eq ListUserPolicies
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ListUserPolicies -> ListUserPolicies -> Bool
== :: ListUserPolicies -> ListUserPolicies -> Bool
$c/= :: ListUserPolicies -> ListUserPolicies -> Bool
/= :: ListUserPolicies -> ListUserPolicies -> Bool
Eq, Eq ListUserPolicies
Eq ListUserPolicies =>
(ListUserPolicies -> ListUserPolicies -> Ordering)
-> (ListUserPolicies -> ListUserPolicies -> Bool)
-> (ListUserPolicies -> ListUserPolicies -> Bool)
-> (ListUserPolicies -> ListUserPolicies -> Bool)
-> (ListUserPolicies -> ListUserPolicies -> Bool)
-> (ListUserPolicies -> ListUserPolicies -> ListUserPolicies)
-> (ListUserPolicies -> ListUserPolicies -> ListUserPolicies)
-> Ord ListUserPolicies
ListUserPolicies -> ListUserPolicies -> Bool
ListUserPolicies -> ListUserPolicies -> Ordering
ListUserPolicies -> ListUserPolicies -> ListUserPolicies
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 :: ListUserPolicies -> ListUserPolicies -> Ordering
compare :: ListUserPolicies -> ListUserPolicies -> Ordering
$c< :: ListUserPolicies -> ListUserPolicies -> Bool
< :: ListUserPolicies -> ListUserPolicies -> Bool
$c<= :: ListUserPolicies -> ListUserPolicies -> Bool
<= :: ListUserPolicies -> ListUserPolicies -> Bool
$c> :: ListUserPolicies -> ListUserPolicies -> Bool
> :: ListUserPolicies -> ListUserPolicies -> Bool
$c>= :: ListUserPolicies -> ListUserPolicies -> Bool
>= :: ListUserPolicies -> ListUserPolicies -> Bool
$cmax :: ListUserPolicies -> ListUserPolicies -> ListUserPolicies
max :: ListUserPolicies -> ListUserPolicies -> ListUserPolicies
$cmin :: ListUserPolicies -> ListUserPolicies -> ListUserPolicies
min :: ListUserPolicies -> ListUserPolicies -> ListUserPolicies
Ord, Int -> ListUserPolicies -> ShowS
[ListUserPolicies] -> ShowS
ListUserPolicies -> String
(Int -> ListUserPolicies -> ShowS)
-> (ListUserPolicies -> String)
-> ([ListUserPolicies] -> ShowS)
-> Show ListUserPolicies
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ListUserPolicies -> ShowS
showsPrec :: Int -> ListUserPolicies -> ShowS
$cshow :: ListUserPolicies -> String
show :: ListUserPolicies -> String
$cshowList :: [ListUserPolicies] -> ShowS
showList :: [ListUserPolicies] -> ShowS
Show, Typeable)
instance SignQuery ListUserPolicies where
type ServiceConfiguration ListUserPolicies = IamConfiguration
signQuery :: forall queryType.
ListUserPolicies
-> ServiceConfiguration ListUserPolicies queryType
-> SignatureData
-> SignedQuery
signQuery ListUserPolicies{Maybe Integer
Maybe Text
Text
lupUserName :: ListUserPolicies -> Text
lupMarker :: ListUserPolicies -> Maybe Text
lupMaxItems :: ListUserPolicies -> Maybe Integer
lupUserName :: Text
lupMarker :: Maybe Text
lupMaxItems :: Maybe Integer
..}
= ByteString
-> [Maybe (ByteString, Text)]
-> IamConfiguration queryType
-> SignatureData
-> SignedQuery
forall qt.
ByteString
-> [Maybe (ByteString, Text)]
-> IamConfiguration qt
-> SignatureData
-> SignedQuery
iamAction' ByteString
"ListUserPolicies" ([Maybe (ByteString, Text)]
-> IamConfiguration queryType -> SignatureData -> SignedQuery)
-> [Maybe (ByteString, Text)]
-> IamConfiguration queryType
-> SignatureData
-> SignedQuery
forall a b. (a -> b) -> a -> b
$ [
(ByteString, Text) -> Maybe (ByteString, Text)
forall a. a -> Maybe a
Just (ByteString
"UserName", Text
lupUserName)
] [Maybe (ByteString, Text)]
-> [Maybe (ByteString, Text)] -> [Maybe (ByteString, Text)]
forall a. Semigroup a => a -> a -> a
<> Maybe Text -> Maybe Integer -> [Maybe (ByteString, Text)]
markedIter Maybe Text
lupMarker Maybe Integer
lupMaxItems
data ListUserPoliciesResponse
= ListUserPoliciesResponse {
ListUserPoliciesResponse -> [Text]
luprPolicyNames :: [Text]
, ListUserPoliciesResponse -> Bool
luprIsTruncated :: Bool
, ListUserPoliciesResponse -> Maybe Text
luprMarker :: Maybe Text
}
deriving (ListUserPoliciesResponse -> ListUserPoliciesResponse -> Bool
(ListUserPoliciesResponse -> ListUserPoliciesResponse -> Bool)
-> (ListUserPoliciesResponse -> ListUserPoliciesResponse -> Bool)
-> Eq ListUserPoliciesResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ListUserPoliciesResponse -> ListUserPoliciesResponse -> Bool
== :: ListUserPoliciesResponse -> ListUserPoliciesResponse -> Bool
$c/= :: ListUserPoliciesResponse -> ListUserPoliciesResponse -> Bool
/= :: ListUserPoliciesResponse -> ListUserPoliciesResponse -> Bool
Eq, Eq ListUserPoliciesResponse
Eq ListUserPoliciesResponse =>
(ListUserPoliciesResponse -> ListUserPoliciesResponse -> Ordering)
-> (ListUserPoliciesResponse -> ListUserPoliciesResponse -> Bool)
-> (ListUserPoliciesResponse -> ListUserPoliciesResponse -> Bool)
-> (ListUserPoliciesResponse -> ListUserPoliciesResponse -> Bool)
-> (ListUserPoliciesResponse -> ListUserPoliciesResponse -> Bool)
-> (ListUserPoliciesResponse
-> ListUserPoliciesResponse -> ListUserPoliciesResponse)
-> (ListUserPoliciesResponse
-> ListUserPoliciesResponse -> ListUserPoliciesResponse)
-> Ord ListUserPoliciesResponse
ListUserPoliciesResponse -> ListUserPoliciesResponse -> Bool
ListUserPoliciesResponse -> ListUserPoliciesResponse -> Ordering
ListUserPoliciesResponse
-> ListUserPoliciesResponse -> ListUserPoliciesResponse
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 :: ListUserPoliciesResponse -> ListUserPoliciesResponse -> Ordering
compare :: ListUserPoliciesResponse -> ListUserPoliciesResponse -> Ordering
$c< :: ListUserPoliciesResponse -> ListUserPoliciesResponse -> Bool
< :: ListUserPoliciesResponse -> ListUserPoliciesResponse -> Bool
$c<= :: ListUserPoliciesResponse -> ListUserPoliciesResponse -> Bool
<= :: ListUserPoliciesResponse -> ListUserPoliciesResponse -> Bool
$c> :: ListUserPoliciesResponse -> ListUserPoliciesResponse -> Bool
> :: ListUserPoliciesResponse -> ListUserPoliciesResponse -> Bool
$c>= :: ListUserPoliciesResponse -> ListUserPoliciesResponse -> Bool
>= :: ListUserPoliciesResponse -> ListUserPoliciesResponse -> Bool
$cmax :: ListUserPoliciesResponse
-> ListUserPoliciesResponse -> ListUserPoliciesResponse
max :: ListUserPoliciesResponse
-> ListUserPoliciesResponse -> ListUserPoliciesResponse
$cmin :: ListUserPoliciesResponse
-> ListUserPoliciesResponse -> ListUserPoliciesResponse
min :: ListUserPoliciesResponse
-> ListUserPoliciesResponse -> ListUserPoliciesResponse
Ord, Int -> ListUserPoliciesResponse -> ShowS
[ListUserPoliciesResponse] -> ShowS
ListUserPoliciesResponse -> String
(Int -> ListUserPoliciesResponse -> ShowS)
-> (ListUserPoliciesResponse -> String)
-> ([ListUserPoliciesResponse] -> ShowS)
-> Show ListUserPoliciesResponse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ListUserPoliciesResponse -> ShowS
showsPrec :: Int -> ListUserPoliciesResponse -> ShowS
$cshow :: ListUserPoliciesResponse -> String
show :: ListUserPoliciesResponse -> String
$cshowList :: [ListUserPoliciesResponse] -> ShowS
showList :: [ListUserPoliciesResponse] -> ShowS
Show, Typeable)
instance ResponseConsumer ListUserPolicies ListUserPoliciesResponse where
type ResponseMetadata ListUserPoliciesResponse = IamMetadata
responseConsumer :: Request
-> ListUserPolicies
-> IORef (ResponseMetadata ListUserPoliciesResponse)
-> HTTPResponseConsumer ListUserPoliciesResponse
responseConsumer Request
_ ListUserPolicies
_
= (Cursor -> Response IamMetadata ListUserPoliciesResponse)
-> IORef IamMetadata
-> HTTPResponseConsumer ListUserPoliciesResponse
forall a.
(Cursor -> Response IamMetadata a)
-> IORef IamMetadata -> HTTPResponseConsumer a
iamResponseConsumer ((Cursor -> Response IamMetadata ListUserPoliciesResponse)
-> IORef IamMetadata
-> HTTPResponseConsumer ListUserPoliciesResponse)
-> (Cursor -> Response IamMetadata ListUserPoliciesResponse)
-> IORef IamMetadata
-> HTTPResponseConsumer ListUserPoliciesResponse
forall a b. (a -> b) -> a -> b
$ \Cursor
cursor -> do
(Bool
luprIsTruncated, Maybe Text
luprMarker) <- Cursor -> Response IamMetadata (Bool, Maybe Text)
forall (m :: * -> *).
MonadThrow m =>
Cursor -> m (Bool, Maybe Text)
markedIterResponse Cursor
cursor
let luprPolicyNames :: [Text]
luprPolicyNames = Cursor
cursor Cursor -> (Cursor -> [Text]) -> [Text]
forall node a. Cursor node -> (Cursor node -> [a]) -> [a]
$// Text -> Axis
laxElement Text
"member" Axis -> (Cursor -> [Text]) -> Cursor -> [Text]
forall node a.
Axis node -> (Cursor node -> [a]) -> Cursor node -> [a]
&/ Cursor -> [Text]
content
ListUserPoliciesResponse
-> Response IamMetadata ListUserPoliciesResponse
forall a. a -> Response IamMetadata a
forall (m :: * -> *) a. Monad m => a -> m a
return ListUserPoliciesResponse{Bool
[Text]
Maybe Text
luprPolicyNames :: [Text]
luprIsTruncated :: Bool
luprMarker :: Maybe Text
luprIsTruncated :: Bool
luprMarker :: Maybe Text
luprPolicyNames :: [Text]
..}
instance Transaction ListUserPolicies ListUserPoliciesResponse
instance IteratedTransaction ListUserPolicies ListUserPoliciesResponse where
nextIteratedRequest :: ListUserPolicies
-> ListUserPoliciesResponse -> Maybe ListUserPolicies
nextIteratedRequest ListUserPolicies
request ListUserPoliciesResponse
response
= case ListUserPoliciesResponse -> Maybe Text
luprMarker ListUserPoliciesResponse
response of
Maybe Text
Nothing -> Maybe ListUserPolicies
forall a. Maybe a
Nothing
Just Text
marker -> ListUserPolicies -> Maybe ListUserPolicies
forall a. a -> Maybe a
Just (ListUserPolicies -> Maybe ListUserPolicies)
-> ListUserPolicies -> Maybe ListUserPolicies
forall a b. (a -> b) -> a -> b
$ ListUserPolicies
request { lupMarker = Just marker }
instance AsMemoryResponse ListUserPoliciesResponse where
type MemoryResponse ListUserPoliciesResponse = ListUserPoliciesResponse
loadToMemory :: ListUserPoliciesResponse
-> ResourceT IO (MemoryResponse ListUserPoliciesResponse)
loadToMemory = ListUserPoliciesResponse
-> ResourceT IO (MemoryResponse ListUserPoliciesResponse)
ListUserPoliciesResponse -> ResourceT IO ListUserPoliciesResponse
forall a. a -> ResourceT IO a
forall (m :: * -> *) a. Monad m => a -> m a
return