{-# 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.SWF.GetWorkflowExecutionHistory
(
getWorkflowExecutionHistory
, GetWorkflowExecutionHistory
, gwehNextPageToken
, gwehReverseOrder
, gwehMaximumPageSize
, gwehDomain
, gwehExecution
, getWorkflowExecutionHistoryResponse
, GetWorkflowExecutionHistoryResponse
, gwehrsNextPageToken
, gwehrsResponseStatus
, gwehrsEvents
) where
import Network.AWS.Lens
import Network.AWS.Pager
import Network.AWS.Prelude
import Network.AWS.Request
import Network.AWS.Response
import Network.AWS.SWF.Types
import Network.AWS.SWF.Types.Product
data GetWorkflowExecutionHistory = GetWorkflowExecutionHistory'
{ _gwehNextPageToken :: !(Maybe Text)
, _gwehReverseOrder :: !(Maybe Bool)
, _gwehMaximumPageSize :: !(Maybe Nat)
, _gwehDomain :: !Text
, _gwehExecution :: !WorkflowExecution
} deriving (Eq,Read,Show,Data,Typeable,Generic)
getWorkflowExecutionHistory
:: Text
-> WorkflowExecution
-> GetWorkflowExecutionHistory
getWorkflowExecutionHistory pDomain_ pExecution_ =
GetWorkflowExecutionHistory'
{ _gwehNextPageToken = Nothing
, _gwehReverseOrder = Nothing
, _gwehMaximumPageSize = Nothing
, _gwehDomain = pDomain_
, _gwehExecution = pExecution_
}
gwehNextPageToken :: Lens' GetWorkflowExecutionHistory (Maybe Text)
gwehNextPageToken = lens _gwehNextPageToken (\ s a -> s{_gwehNextPageToken = a});
gwehReverseOrder :: Lens' GetWorkflowExecutionHistory (Maybe Bool)
gwehReverseOrder = lens _gwehReverseOrder (\ s a -> s{_gwehReverseOrder = a});
gwehMaximumPageSize :: Lens' GetWorkflowExecutionHistory (Maybe Natural)
gwehMaximumPageSize = lens _gwehMaximumPageSize (\ s a -> s{_gwehMaximumPageSize = a}) . mapping _Nat;
gwehDomain :: Lens' GetWorkflowExecutionHistory Text
gwehDomain = lens _gwehDomain (\ s a -> s{_gwehDomain = a});
gwehExecution :: Lens' GetWorkflowExecutionHistory WorkflowExecution
gwehExecution = lens _gwehExecution (\ s a -> s{_gwehExecution = a});
instance AWSPager GetWorkflowExecutionHistory where
page rq rs
| stop (rs ^. gwehrsNextPageToken) = Nothing
| stop (rs ^. gwehrsEvents) = Nothing
| otherwise =
Just $ rq &
gwehNextPageToken .~ rs ^. gwehrsNextPageToken
instance AWSRequest GetWorkflowExecutionHistory where
type Rs GetWorkflowExecutionHistory =
GetWorkflowExecutionHistoryResponse
request = postJSON swf
response
= receiveJSON
(\ s h x ->
GetWorkflowExecutionHistoryResponse' <$>
(x .?> "nextPageToken") <*> (pure (fromEnum s)) <*>
(x .?> "events" .!@ mempty))
instance Hashable GetWorkflowExecutionHistory
instance NFData GetWorkflowExecutionHistory
instance ToHeaders GetWorkflowExecutionHistory where
toHeaders
= const
(mconcat
["X-Amz-Target" =#
("SimpleWorkflowService.GetWorkflowExecutionHistory"
:: ByteString),
"Content-Type" =#
("application/x-amz-json-1.0" :: ByteString)])
instance ToJSON GetWorkflowExecutionHistory where
toJSON GetWorkflowExecutionHistory'{..}
= object
(catMaybes
[("nextPageToken" .=) <$> _gwehNextPageToken,
("reverseOrder" .=) <$> _gwehReverseOrder,
("maximumPageSize" .=) <$> _gwehMaximumPageSize,
Just ("domain" .= _gwehDomain),
Just ("execution" .= _gwehExecution)])
instance ToPath GetWorkflowExecutionHistory where
toPath = const "/"
instance ToQuery GetWorkflowExecutionHistory where
toQuery = const mempty
data GetWorkflowExecutionHistoryResponse = GetWorkflowExecutionHistoryResponse'
{ _gwehrsNextPageToken :: !(Maybe Text)
, _gwehrsResponseStatus :: !Int
, _gwehrsEvents :: ![HistoryEvent]
} deriving (Eq,Read,Show,Data,Typeable,Generic)
getWorkflowExecutionHistoryResponse
:: Int
-> GetWorkflowExecutionHistoryResponse
getWorkflowExecutionHistoryResponse pResponseStatus_ =
GetWorkflowExecutionHistoryResponse'
{ _gwehrsNextPageToken = Nothing
, _gwehrsResponseStatus = pResponseStatus_
, _gwehrsEvents = mempty
}
gwehrsNextPageToken :: Lens' GetWorkflowExecutionHistoryResponse (Maybe Text)
gwehrsNextPageToken = lens _gwehrsNextPageToken (\ s a -> s{_gwehrsNextPageToken = a});
gwehrsResponseStatus :: Lens' GetWorkflowExecutionHistoryResponse Int
gwehrsResponseStatus = lens _gwehrsResponseStatus (\ s a -> s{_gwehrsResponseStatus = a});
gwehrsEvents :: Lens' GetWorkflowExecutionHistoryResponse [HistoryEvent]
gwehrsEvents = lens _gwehrsEvents (\ s a -> s{_gwehrsEvents = a}) . _Coerce;
instance NFData GetWorkflowExecutionHistoryResponse