{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE RecordWildCards #-}
module Aws.Iam.Commands.ListMfaDevices
( ListMfaDevices(..)
, ListMfaDevicesResponse(..)
) 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 ListMfaDevices = ListMfaDevices
{ ListMfaDevices -> Maybe Text
lmfaUserName :: Maybe Text
, ListMfaDevices -> Maybe Text
lmfaMarker :: Maybe Text
, ListMfaDevices -> Maybe Integer
lmfaMaxItems :: Maybe Integer
} deriving (ListMfaDevices -> ListMfaDevices -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListMfaDevices -> ListMfaDevices -> Bool
$c/= :: ListMfaDevices -> ListMfaDevices -> Bool
== :: ListMfaDevices -> ListMfaDevices -> Bool
$c== :: ListMfaDevices -> ListMfaDevices -> Bool
Eq, Eq ListMfaDevices
ListMfaDevices -> ListMfaDevices -> Bool
ListMfaDevices -> ListMfaDevices -> Ordering
ListMfaDevices -> ListMfaDevices -> ListMfaDevices
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
min :: ListMfaDevices -> ListMfaDevices -> ListMfaDevices
$cmin :: ListMfaDevices -> ListMfaDevices -> ListMfaDevices
max :: ListMfaDevices -> ListMfaDevices -> ListMfaDevices
$cmax :: ListMfaDevices -> ListMfaDevices -> ListMfaDevices
>= :: ListMfaDevices -> ListMfaDevices -> Bool
$c>= :: ListMfaDevices -> ListMfaDevices -> Bool
> :: ListMfaDevices -> ListMfaDevices -> Bool
$c> :: ListMfaDevices -> ListMfaDevices -> Bool
<= :: ListMfaDevices -> ListMfaDevices -> Bool
$c<= :: ListMfaDevices -> ListMfaDevices -> Bool
< :: ListMfaDevices -> ListMfaDevices -> Bool
$c< :: ListMfaDevices -> ListMfaDevices -> Bool
compare :: ListMfaDevices -> ListMfaDevices -> Ordering
$ccompare :: ListMfaDevices -> ListMfaDevices -> Ordering
Ord, Int -> ListMfaDevices -> ShowS
[ListMfaDevices] -> ShowS
ListMfaDevices -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListMfaDevices] -> ShowS
$cshowList :: [ListMfaDevices] -> ShowS
show :: ListMfaDevices -> String
$cshow :: ListMfaDevices -> String
showsPrec :: Int -> ListMfaDevices -> ShowS
$cshowsPrec :: Int -> ListMfaDevices -> ShowS
Show, Typeable)
instance SignQuery ListMfaDevices where
type ServiceConfiguration ListMfaDevices = IamConfiguration
signQuery :: forall queryType.
ListMfaDevices
-> ServiceConfiguration ListMfaDevices queryType
-> SignatureData
-> SignedQuery
signQuery ListMfaDevices{Maybe Integer
Maybe Text
lmfaMaxItems :: Maybe Integer
lmfaMarker :: Maybe Text
lmfaUserName :: Maybe Text
lmfaMaxItems :: ListMfaDevices -> Maybe Integer
lmfaMarker :: ListMfaDevices -> Maybe Text
lmfaUserName :: ListMfaDevices -> Maybe Text
..} = forall qt.
ByteString
-> [Maybe (ByteString, Text)]
-> IamConfiguration qt
-> SignatureData
-> SignedQuery
iamAction' ByteString
"ListMFADevices"
([ (ByteString
"UserName",) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Text
lmfaUserName ]
forall a. Semigroup a => a -> a -> a
<> Maybe Text -> Maybe Integer -> [Maybe (ByteString, Text)]
markedIter Maybe Text
lmfaMarker Maybe Integer
lmfaMaxItems)
data ListMfaDevicesResponse = ListMfaDevicesResponse
{ ListMfaDevicesResponse -> [MfaDevice]
lmfarMfaDevices :: [MfaDevice]
, ListMfaDevicesResponse -> Bool
lmfarIsTruncated :: Bool
, ListMfaDevicesResponse -> Maybe Text
lmfarMarker :: Maybe Text
} deriving (ListMfaDevicesResponse -> ListMfaDevicesResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListMfaDevicesResponse -> ListMfaDevicesResponse -> Bool
$c/= :: ListMfaDevicesResponse -> ListMfaDevicesResponse -> Bool
== :: ListMfaDevicesResponse -> ListMfaDevicesResponse -> Bool
$c== :: ListMfaDevicesResponse -> ListMfaDevicesResponse -> Bool
Eq, Eq ListMfaDevicesResponse
ListMfaDevicesResponse -> ListMfaDevicesResponse -> Bool
ListMfaDevicesResponse -> ListMfaDevicesResponse -> Ordering
ListMfaDevicesResponse
-> ListMfaDevicesResponse -> ListMfaDevicesResponse
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
min :: ListMfaDevicesResponse
-> ListMfaDevicesResponse -> ListMfaDevicesResponse
$cmin :: ListMfaDevicesResponse
-> ListMfaDevicesResponse -> ListMfaDevicesResponse
max :: ListMfaDevicesResponse
-> ListMfaDevicesResponse -> ListMfaDevicesResponse
$cmax :: ListMfaDevicesResponse
-> ListMfaDevicesResponse -> ListMfaDevicesResponse
>= :: ListMfaDevicesResponse -> ListMfaDevicesResponse -> Bool
$c>= :: ListMfaDevicesResponse -> ListMfaDevicesResponse -> Bool
> :: ListMfaDevicesResponse -> ListMfaDevicesResponse -> Bool
$c> :: ListMfaDevicesResponse -> ListMfaDevicesResponse -> Bool
<= :: ListMfaDevicesResponse -> ListMfaDevicesResponse -> Bool
$c<= :: ListMfaDevicesResponse -> ListMfaDevicesResponse -> Bool
< :: ListMfaDevicesResponse -> ListMfaDevicesResponse -> Bool
$c< :: ListMfaDevicesResponse -> ListMfaDevicesResponse -> Bool
compare :: ListMfaDevicesResponse -> ListMfaDevicesResponse -> Ordering
$ccompare :: ListMfaDevicesResponse -> ListMfaDevicesResponse -> Ordering
Ord, Int -> ListMfaDevicesResponse -> ShowS
[ListMfaDevicesResponse] -> ShowS
ListMfaDevicesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListMfaDevicesResponse] -> ShowS
$cshowList :: [ListMfaDevicesResponse] -> ShowS
show :: ListMfaDevicesResponse -> String
$cshow :: ListMfaDevicesResponse -> String
showsPrec :: Int -> ListMfaDevicesResponse -> ShowS
$cshowsPrec :: Int -> ListMfaDevicesResponse -> ShowS
Show, Typeable)
instance ResponseConsumer ListMfaDevices ListMfaDevicesResponse where
type ResponseMetadata ListMfaDevicesResponse = IamMetadata
responseConsumer :: Request
-> ListMfaDevices
-> IORef (ResponseMetadata ListMfaDevicesResponse)
-> HTTPResponseConsumer ListMfaDevicesResponse
responseConsumer Request
_ ListMfaDevices
_req =
forall a.
(Cursor -> Response IamMetadata a)
-> IORef IamMetadata -> HTTPResponseConsumer a
iamResponseConsumer forall a b. (a -> b) -> a -> b
$ \ Cursor
cursor -> do
(Bool
lmfarIsTruncated, Maybe Text
lmfarMarker) <- forall (m :: * -> *).
MonadThrow m =>
Cursor -> m (Bool, Maybe Text)
markedIterResponse Cursor
cursor
[MfaDevice]
lmfarMfaDevices <-
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence forall a b. (a -> b) -> a -> b
$ Cursor
cursor forall node a. Cursor node -> (Cursor node -> [a]) -> [a]
$// Text -> Axis
laxElement Text
"member" forall node a b.
(Cursor node -> [a]) -> (a -> b) -> Cursor node -> [b]
&| forall (m :: * -> *). MonadThrow m => Cursor -> m MfaDevice
parseMfaDevice
forall (m :: * -> *) a. Monad m => a -> m a
return ListMfaDevicesResponse{Bool
[MfaDevice]
Maybe Text
lmfarMfaDevices :: [MfaDevice]
lmfarMarker :: Maybe Text
lmfarIsTruncated :: Bool
lmfarMarker :: Maybe Text
lmfarIsTruncated :: Bool
lmfarMfaDevices :: [MfaDevice]
..}
instance Transaction ListMfaDevices ListMfaDevicesResponse
instance IteratedTransaction ListMfaDevices ListMfaDevicesResponse where
nextIteratedRequest :: ListMfaDevices -> ListMfaDevicesResponse -> Maybe ListMfaDevices
nextIteratedRequest ListMfaDevices
request ListMfaDevicesResponse
response
= case ListMfaDevicesResponse -> Maybe Text
lmfarMarker ListMfaDevicesResponse
response of
Maybe Text
Nothing -> forall a. Maybe a
Nothing
Just Text
marker -> forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ ListMfaDevices
request { lmfaMarker :: Maybe Text
lmfaMarker = forall a. a -> Maybe a
Just Text
marker }
instance AsMemoryResponse ListMfaDevicesResponse where
type MemoryResponse ListMfaDevicesResponse = ListMfaDevicesResponse
loadToMemory :: ListMfaDevicesResponse
-> ResourceT IO (MemoryResponse ListMfaDevicesResponse)
loadToMemory = forall (m :: * -> *) a. Monad m => a -> m a
return