{-# 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.CodeCommit.ListBranches
(
listBranches
, ListBranches
, lbNextToken
, lbRepositoryName
, listBranchesResponse
, ListBranchesResponse
, lbrsBranches
, lbrsNextToken
, lbrsResponseStatus
) where
import Network.AWS.CodeCommit.Types
import Network.AWS.CodeCommit.Types.Product
import Network.AWS.Lens
import Network.AWS.Pager
import Network.AWS.Prelude
import Network.AWS.Request
import Network.AWS.Response
data ListBranches = ListBranches'
{ _lbNextToken :: !(Maybe Text)
, _lbRepositoryName :: !Text
} deriving (Eq,Read,Show,Data,Typeable,Generic)
listBranches
:: Text
-> ListBranches
listBranches pRepositoryName_ =
ListBranches'
{ _lbNextToken = Nothing
, _lbRepositoryName = pRepositoryName_
}
lbNextToken :: Lens' ListBranches (Maybe Text)
lbNextToken = lens _lbNextToken (\ s a -> s{_lbNextToken = a});
lbRepositoryName :: Lens' ListBranches Text
lbRepositoryName = lens _lbRepositoryName (\ s a -> s{_lbRepositoryName = a});
instance AWSPager ListBranches where
page rq rs
| stop (rs ^. lbrsNextToken) = Nothing
| stop (rs ^. lbrsBranches) = Nothing
| otherwise =
Just $ rq & lbNextToken .~ rs ^. lbrsNextToken
instance AWSRequest ListBranches where
type Rs ListBranches = ListBranchesResponse
request = postJSON codeCommit
response
= receiveJSON
(\ s h x ->
ListBranchesResponse' <$>
(x .?> "branches" .!@ mempty) <*> (x .?> "nextToken")
<*> (pure (fromEnum s)))
instance Hashable ListBranches
instance NFData ListBranches
instance ToHeaders ListBranches where
toHeaders
= const
(mconcat
["X-Amz-Target" =#
("CodeCommit_20150413.ListBranches" :: ByteString),
"Content-Type" =#
("application/x-amz-json-1.1" :: ByteString)])
instance ToJSON ListBranches where
toJSON ListBranches'{..}
= object
(catMaybes
[("nextToken" .=) <$> _lbNextToken,
Just ("repositoryName" .= _lbRepositoryName)])
instance ToPath ListBranches where
toPath = const "/"
instance ToQuery ListBranches where
toQuery = const mempty
data ListBranchesResponse = ListBranchesResponse'
{ _lbrsBranches :: !(Maybe [Text])
, _lbrsNextToken :: !(Maybe Text)
, _lbrsResponseStatus :: !Int
} deriving (Eq,Read,Show,Data,Typeable,Generic)
listBranchesResponse
:: Int
-> ListBranchesResponse
listBranchesResponse pResponseStatus_ =
ListBranchesResponse'
{ _lbrsBranches = Nothing
, _lbrsNextToken = Nothing
, _lbrsResponseStatus = pResponseStatus_
}
lbrsBranches :: Lens' ListBranchesResponse [Text]
lbrsBranches = lens _lbrsBranches (\ s a -> s{_lbrsBranches = a}) . _Default . _Coerce;
lbrsNextToken :: Lens' ListBranchesResponse (Maybe Text)
lbrsNextToken = lens _lbrsNextToken (\ s a -> s{_lbrsNextToken = a});
lbrsResponseStatus :: Lens' ListBranchesResponse Int
lbrsResponseStatus = lens _lbrsResponseStatus (\ s a -> s{_lbrsResponseStatus = a});
instance NFData ListBranchesResponse