{-# 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.UpdateThingGroup
(
updateThingGroup
, UpdateThingGroup
, utgExpectedVersion
, utgThingGroupName
, utgThingGroupProperties
, updateThingGroupResponse
, UpdateThingGroupResponse
, utgrsVersion
, utgrsResponseStatus
) 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 UpdateThingGroup = UpdateThingGroup'
{ _utgExpectedVersion :: !(Maybe Integer)
, _utgThingGroupName :: !Text
, _utgThingGroupProperties :: !ThingGroupProperties
} deriving (Eq, Read, Show, Data, Typeable, Generic)
updateThingGroup
:: Text
-> ThingGroupProperties
-> UpdateThingGroup
updateThingGroup pThingGroupName_ pThingGroupProperties_ =
UpdateThingGroup'
{ _utgExpectedVersion = Nothing
, _utgThingGroupName = pThingGroupName_
, _utgThingGroupProperties = pThingGroupProperties_
}
utgExpectedVersion :: Lens' UpdateThingGroup (Maybe Integer)
utgExpectedVersion = lens _utgExpectedVersion (\ s a -> s{_utgExpectedVersion = a})
utgThingGroupName :: Lens' UpdateThingGroup Text
utgThingGroupName = lens _utgThingGroupName (\ s a -> s{_utgThingGroupName = a})
utgThingGroupProperties :: Lens' UpdateThingGroup ThingGroupProperties
utgThingGroupProperties = lens _utgThingGroupProperties (\ s a -> s{_utgThingGroupProperties = a})
instance AWSRequest UpdateThingGroup where
type Rs UpdateThingGroup = UpdateThingGroupResponse
request = patchJSON ioT
response
= receiveJSON
(\ s h x ->
UpdateThingGroupResponse' <$>
(x .?> "version") <*> (pure (fromEnum s)))
instance Hashable UpdateThingGroup where
instance NFData UpdateThingGroup where
instance ToHeaders UpdateThingGroup where
toHeaders = const mempty
instance ToJSON UpdateThingGroup where
toJSON UpdateThingGroup'{..}
= object
(catMaybes
[("expectedVersion" .=) <$> _utgExpectedVersion,
Just
("thingGroupProperties" .=
_utgThingGroupProperties)])
instance ToPath UpdateThingGroup where
toPath UpdateThingGroup'{..}
= mconcat ["/thing-groups/", toBS _utgThingGroupName]
instance ToQuery UpdateThingGroup where
toQuery = const mempty
data UpdateThingGroupResponse = UpdateThingGroupResponse'
{ _utgrsVersion :: !(Maybe Integer)
, _utgrsResponseStatus :: !Int
} deriving (Eq, Read, Show, Data, Typeable, Generic)
updateThingGroupResponse
:: Int
-> UpdateThingGroupResponse
updateThingGroupResponse pResponseStatus_ =
UpdateThingGroupResponse'
{_utgrsVersion = Nothing, _utgrsResponseStatus = pResponseStatus_}
utgrsVersion :: Lens' UpdateThingGroupResponse (Maybe Integer)
utgrsVersion = lens _utgrsVersion (\ s a -> s{_utgrsVersion = a})
utgrsResponseStatus :: Lens' UpdateThingGroupResponse Int
utgrsResponseStatus = lens _utgrsResponseStatus (\ s a -> s{_utgrsResponseStatus = a})
instance NFData UpdateThingGroupResponse where