{-# 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.AutoScaling.PutScheduledUpdateGroupAction
    (
    
      putScheduledUpdateGroupAction
    , PutScheduledUpdateGroupAction
    
    , psugaStartTime
    , psugaTime
    , psugaMaxSize
    , psugaRecurrence
    , psugaDesiredCapacity
    , psugaMinSize
    , psugaEndTime
    , psugaAutoScalingGroupName
    , psugaScheduledActionName
    
    , putScheduledUpdateGroupActionResponse
    , PutScheduledUpdateGroupActionResponse
    ) where
import           Network.AWS.AutoScaling.Types
import           Network.AWS.AutoScaling.Types.Product
import           Network.AWS.Lens
import           Network.AWS.Prelude
import           Network.AWS.Request
import           Network.AWS.Response
data PutScheduledUpdateGroupAction = PutScheduledUpdateGroupAction'
    { _psugaStartTime            :: !(Maybe ISO8601)
    , _psugaTime                 :: !(Maybe ISO8601)
    , _psugaMaxSize              :: !(Maybe Int)
    , _psugaRecurrence           :: !(Maybe Text)
    , _psugaDesiredCapacity      :: !(Maybe Int)
    , _psugaMinSize              :: !(Maybe Int)
    , _psugaEndTime              :: !(Maybe ISO8601)
    , _psugaAutoScalingGroupName :: !Text
    , _psugaScheduledActionName  :: !Text
    } deriving (Eq,Read,Show,Data,Typeable,Generic)
putScheduledUpdateGroupAction
    :: Text 
    -> Text 
    -> PutScheduledUpdateGroupAction
putScheduledUpdateGroupAction pAutoScalingGroupName_ pScheduledActionName_ =
    PutScheduledUpdateGroupAction'
    { _psugaStartTime = Nothing
    , _psugaTime = Nothing
    , _psugaMaxSize = Nothing
    , _psugaRecurrence = Nothing
    , _psugaDesiredCapacity = Nothing
    , _psugaMinSize = Nothing
    , _psugaEndTime = Nothing
    , _psugaAutoScalingGroupName = pAutoScalingGroupName_
    , _psugaScheduledActionName = pScheduledActionName_
    }
psugaStartTime :: Lens' PutScheduledUpdateGroupAction (Maybe UTCTime)
psugaStartTime = lens _psugaStartTime (\ s a -> s{_psugaStartTime = a}) . mapping _Time;
psugaTime :: Lens' PutScheduledUpdateGroupAction (Maybe UTCTime)
psugaTime = lens _psugaTime (\ s a -> s{_psugaTime = a}) . mapping _Time;
psugaMaxSize :: Lens' PutScheduledUpdateGroupAction (Maybe Int)
psugaMaxSize = lens _psugaMaxSize (\ s a -> s{_psugaMaxSize = a});
psugaRecurrence :: Lens' PutScheduledUpdateGroupAction (Maybe Text)
psugaRecurrence = lens _psugaRecurrence (\ s a -> s{_psugaRecurrence = a});
psugaDesiredCapacity :: Lens' PutScheduledUpdateGroupAction (Maybe Int)
psugaDesiredCapacity = lens _psugaDesiredCapacity (\ s a -> s{_psugaDesiredCapacity = a});
psugaMinSize :: Lens' PutScheduledUpdateGroupAction (Maybe Int)
psugaMinSize = lens _psugaMinSize (\ s a -> s{_psugaMinSize = a});
psugaEndTime :: Lens' PutScheduledUpdateGroupAction (Maybe UTCTime)
psugaEndTime = lens _psugaEndTime (\ s a -> s{_psugaEndTime = a}) . mapping _Time;
psugaAutoScalingGroupName :: Lens' PutScheduledUpdateGroupAction Text
psugaAutoScalingGroupName = lens _psugaAutoScalingGroupName (\ s a -> s{_psugaAutoScalingGroupName = a});
psugaScheduledActionName :: Lens' PutScheduledUpdateGroupAction Text
psugaScheduledActionName = lens _psugaScheduledActionName (\ s a -> s{_psugaScheduledActionName = a});
instance AWSRequest PutScheduledUpdateGroupAction
         where
        type Rs PutScheduledUpdateGroupAction =
             PutScheduledUpdateGroupActionResponse
        request = postQuery autoScaling
        response
          = receiveNull PutScheduledUpdateGroupActionResponse'
instance Hashable PutScheduledUpdateGroupAction
instance NFData PutScheduledUpdateGroupAction
instance ToHeaders PutScheduledUpdateGroupAction
         where
        toHeaders = const mempty
instance ToPath PutScheduledUpdateGroupAction where
        toPath = const "/"
instance ToQuery PutScheduledUpdateGroupAction where
        toQuery PutScheduledUpdateGroupAction'{..}
          = mconcat
              ["Action" =:
                 ("PutScheduledUpdateGroupAction" :: ByteString),
               "Version" =: ("2011-01-01" :: ByteString),
               "StartTime" =: _psugaStartTime, "Time" =: _psugaTime,
               "MaxSize" =: _psugaMaxSize,
               "Recurrence" =: _psugaRecurrence,
               "DesiredCapacity" =: _psugaDesiredCapacity,
               "MinSize" =: _psugaMinSize,
               "EndTime" =: _psugaEndTime,
               "AutoScalingGroupName" =: _psugaAutoScalingGroupName,
               "ScheduledActionName" =: _psugaScheduledActionName]
data PutScheduledUpdateGroupActionResponse =
    PutScheduledUpdateGroupActionResponse'
    deriving (Eq,Read,Show,Data,Typeable,Generic)
putScheduledUpdateGroupActionResponse
    :: PutScheduledUpdateGroupActionResponse
putScheduledUpdateGroupActionResponse = PutScheduledUpdateGroupActionResponse'
instance NFData PutScheduledUpdateGroupActionResponse