{-# 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.IoT.ListThingGroups
(
listThingGroups
, ListThingGroups
, ltgNamePrefixFilter
, ltgParentGroup
, ltgNextToken
, ltgRecursive
, ltgMaxResults
, listThingGroupsResponse
, ListThingGroupsResponse
, ltgrsThingGroups
, ltgrsNextToken
, ltgrsResponseStatus
) where
import Network.AWS.IoT.Types
import Network.AWS.IoT.Types.Product
import Network.AWS.Lens
import Network.AWS.Prelude
import Network.AWS.Request
import Network.AWS.Response
data ListThingGroups = ListThingGroups'
{ _ltgNamePrefixFilter :: !(Maybe Text)
, _ltgParentGroup :: !(Maybe Text)
, _ltgNextToken :: !(Maybe Text)
, _ltgRecursive :: !(Maybe Bool)
, _ltgMaxResults :: !(Maybe Nat)
} deriving (Eq, Read, Show, Data, Typeable, Generic)
listThingGroups
:: ListThingGroups
listThingGroups =
ListThingGroups'
{ _ltgNamePrefixFilter = Nothing
, _ltgParentGroup = Nothing
, _ltgNextToken = Nothing
, _ltgRecursive = Nothing
, _ltgMaxResults = Nothing
}
ltgNamePrefixFilter :: Lens' ListThingGroups (Maybe Text)
ltgNamePrefixFilter = lens _ltgNamePrefixFilter (\ s a -> s{_ltgNamePrefixFilter = a})
ltgParentGroup :: Lens' ListThingGroups (Maybe Text)
ltgParentGroup = lens _ltgParentGroup (\ s a -> s{_ltgParentGroup = a})
ltgNextToken :: Lens' ListThingGroups (Maybe Text)
ltgNextToken = lens _ltgNextToken (\ s a -> s{_ltgNextToken = a})
ltgRecursive :: Lens' ListThingGroups (Maybe Bool)
ltgRecursive = lens _ltgRecursive (\ s a -> s{_ltgRecursive = a})
ltgMaxResults :: Lens' ListThingGroups (Maybe Natural)
ltgMaxResults = lens _ltgMaxResults (\ s a -> s{_ltgMaxResults = a}) . mapping _Nat
instance AWSRequest ListThingGroups where
type Rs ListThingGroups = ListThingGroupsResponse
request = get ioT
response
= receiveJSON
(\ s h x ->
ListThingGroupsResponse' <$>
(x .?> "thingGroups" .!@ mempty) <*>
(x .?> "nextToken")
<*> (pure (fromEnum s)))
instance Hashable ListThingGroups where
instance NFData ListThingGroups where
instance ToHeaders ListThingGroups where
toHeaders = const mempty
instance ToPath ListThingGroups where
toPath = const "/thing-groups"
instance ToQuery ListThingGroups where
toQuery ListThingGroups'{..}
= mconcat
["namePrefixFilter" =: _ltgNamePrefixFilter,
"parentGroup" =: _ltgParentGroup,
"nextToken" =: _ltgNextToken,
"recursive" =: _ltgRecursive,
"maxResults" =: _ltgMaxResults]
data ListThingGroupsResponse = ListThingGroupsResponse'
{ _ltgrsThingGroups :: !(Maybe [GroupNameAndARN])
, _ltgrsNextToken :: !(Maybe Text)
, _ltgrsResponseStatus :: !Int
} deriving (Eq, Read, Show, Data, Typeable, Generic)
listThingGroupsResponse
:: Int
-> ListThingGroupsResponse
listThingGroupsResponse pResponseStatus_ =
ListThingGroupsResponse'
{ _ltgrsThingGroups = Nothing
, _ltgrsNextToken = Nothing
, _ltgrsResponseStatus = pResponseStatus_
}
ltgrsThingGroups :: Lens' ListThingGroupsResponse [GroupNameAndARN]
ltgrsThingGroups = lens _ltgrsThingGroups (\ s a -> s{_ltgrsThingGroups = a}) . _Default . _Coerce
ltgrsNextToken :: Lens' ListThingGroupsResponse (Maybe Text)
ltgrsNextToken = lens _ltgrsNextToken (\ s a -> s{_ltgrsNextToken = a})
ltgrsResponseStatus :: Lens' ListThingGroupsResponse Int
ltgrsResponseStatus = lens _ltgrsResponseStatus (\ s a -> s{_ltgrsResponseStatus = a})
instance NFData ListThingGroupsResponse where