{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TypeFamilies #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}
module Network.AWS.Athena.ListQueryExecutions
(
listQueryExecutions
, ListQueryExecutions
, lqeNextToken
, lqeMaxResults
, listQueryExecutionsResponse
, ListQueryExecutionsResponse
, lqersQueryExecutionIds
, lqersNextToken
, lqersResponseStatus
) where
import Network.AWS.Athena.Types
import Network.AWS.Athena.Types.Product
import Network.AWS.Lens
import Network.AWS.Pager
import Network.AWS.Prelude
import Network.AWS.Request
import Network.AWS.Response
data ListQueryExecutions = ListQueryExecutions'
{ _lqeNextToken :: !(Maybe Text)
, _lqeMaxResults :: !(Maybe Nat)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
listQueryExecutions
:: ListQueryExecutions
listQueryExecutions =
ListQueryExecutions' {_lqeNextToken = Nothing, _lqeMaxResults = Nothing}
lqeNextToken :: Lens' ListQueryExecutions (Maybe Text)
lqeNextToken = lens _lqeNextToken (\ s a -> s{_lqeNextToken = a})
lqeMaxResults :: Lens' ListQueryExecutions (Maybe Natural)
lqeMaxResults = lens _lqeMaxResults (\ s a -> s{_lqeMaxResults = a}) . mapping _Nat
instance AWSPager ListQueryExecutions where
page rq rs
| stop (rs ^. lqersNextToken) = Nothing
| stop (rs ^. lqersQueryExecutionIds) = Nothing
| otherwise =
Just $ rq & lqeNextToken .~ rs ^. lqersNextToken
instance AWSRequest ListQueryExecutions where
type Rs ListQueryExecutions =
ListQueryExecutionsResponse
request = postJSON athena
response
= receiveJSON
(\ s h x ->
ListQueryExecutionsResponse' <$>
(x .?> "QueryExecutionIds") <*> (x .?> "NextToken")
<*> (pure (fromEnum s)))
instance Hashable ListQueryExecutions where
instance NFData ListQueryExecutions where
instance ToHeaders ListQueryExecutions where
toHeaders
= const
(mconcat
["X-Amz-Target" =#
("AmazonAthena.ListQueryExecutions" :: ByteString),
"Content-Type" =#
("application/x-amz-json-1.1" :: ByteString)])
instance ToJSON ListQueryExecutions where
toJSON ListQueryExecutions'{..}
= object
(catMaybes
[("NextToken" .=) <$> _lqeNextToken,
("MaxResults" .=) <$> _lqeMaxResults])
instance ToPath ListQueryExecutions where
toPath = const "/"
instance ToQuery ListQueryExecutions where
toQuery = const mempty
data ListQueryExecutionsResponse = ListQueryExecutionsResponse'
{ _lqersQueryExecutionIds :: !(Maybe (List1 Text))
, _lqersNextToken :: !(Maybe Text)
, _lqersResponseStatus :: !Int
} deriving (Eq, Read, Show, Data, Typeable, Generic)
listQueryExecutionsResponse
:: Int
-> ListQueryExecutionsResponse
listQueryExecutionsResponse pResponseStatus_ =
ListQueryExecutionsResponse'
{ _lqersQueryExecutionIds = Nothing
, _lqersNextToken = Nothing
, _lqersResponseStatus = pResponseStatus_
}
lqersQueryExecutionIds :: Lens' ListQueryExecutionsResponse (Maybe (NonEmpty Text))
lqersQueryExecutionIds = lens _lqersQueryExecutionIds (\ s a -> s{_lqersQueryExecutionIds = a}) . mapping _List1
lqersNextToken :: Lens' ListQueryExecutionsResponse (Maybe Text)
lqersNextToken = lens _lqersNextToken (\ s a -> s{_lqersNextToken = a})
lqersResponseStatus :: Lens' ListQueryExecutionsResponse Int
lqersResponseStatus = lens _lqersResponseStatus (\ s a -> s{_lqersResponseStatus = a})
instance NFData ListQueryExecutionsResponse where