{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TupleSections #-}
module Aws.Iam.Internal
( iamAction
, iamAction'
, markedIter
, markedIterResponse
, (<>)
) where
import Aws.Core
import Aws.Iam.Core
import Control.Applicative
import Control.Arrow (second)
import Control.Monad
import Control.Monad.Trans.Resource (MonadThrow)
import Data.ByteString (ByteString)
import Data.Maybe
import Data.Monoid
import Prelude
import Data.Text (Text)
import qualified Data.Text as Text
import qualified Data.Text.Encoding as Text
import Text.XML.Cursor (($//))
import qualified Text.XML.Cursor as Cu
iamAction
:: ByteString
-> [(ByteString, Text)]
-> IamConfiguration qt
-> SignatureData
-> SignedQuery
iamAction :: forall qt.
ByteString
-> [(ByteString, Text)]
-> IamConfiguration qt
-> SignatureData
-> SignedQuery
iamAction ByteString
action = forall qt.
[(ByteString, ByteString)]
-> IamConfiguration qt -> SignatureData -> SignedQuery
iamSignQuery
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (:) (ByteString
"Action", ByteString
action)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map (forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (d, b) (d, c)
second Text -> ByteString
Text.encodeUtf8)
iamAction'
:: ByteString
-> [Maybe (ByteString, Text)]
-> IamConfiguration qt
-> SignatureData
-> SignedQuery
iamAction' :: forall qt.
ByteString
-> [Maybe (ByteString, Text)]
-> IamConfiguration qt
-> SignatureData
-> SignedQuery
iamAction' ByteString
action = forall qt.
ByteString
-> [(ByteString, Text)]
-> IamConfiguration qt
-> SignatureData
-> SignedQuery
iamAction ByteString
action forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [Maybe a] -> [a]
catMaybes
markedIter :: Maybe Text -> Maybe Integer -> [Maybe (ByteString, Text)]
markedIter :: Maybe Text -> Maybe Integer -> [Maybe (ByteString, Text)]
markedIter Maybe Text
marker Maybe Integer
maxItems
= [ (ByteString
"Marker" ,) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Text
marker
, (ByteString
"MaxItems",) forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Text
encodeInteger forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Integer
maxItems
]
where
encodeInteger :: Integer -> Text
encodeInteger = String -> Text
Text.pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show
markedIterResponse
:: MonadThrow m
=> Cu.Cursor
-> m (Bool, Maybe Text)
markedIterResponse :: forall (m :: * -> *).
MonadThrow m =>
Cursor -> m (Bool, Maybe Text)
markedIterResponse Cursor
cursor = do
Bool
isTruncated <- (Text -> Text
Text.toCaseFold Text
"true" forall a. Eq a => a -> a -> Bool
==) forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
`liftM` Text -> m Text
attr Text
"IsTruncated"
Maybe Text
marker <- if Bool
isTruncated
then forall a. a -> Maybe a
Just forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
`liftM` Text -> m Text
attr Text
"Marker"
else forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
isTruncated, Maybe Text
marker)
where
attr :: Text -> m Text
attr Text
name = forall (m :: * -> *) a. MonadThrow m => String -> [a] -> m a
force (String
"Missing " forall a. [a] -> [a] -> [a]
++ Text -> String
Text.unpack Text
name) forall a b. (a -> b) -> a -> b
$
Cursor
cursor forall node a. Cursor node -> (Cursor node -> [a]) -> [a]
$// Text -> Cursor -> [Text]
elContent Text
name