{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.AutoScaling.DescribeScheduledActions
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Gets information about the scheduled actions that haven\'t run or that
-- have not reached their end time.
--
-- To describe the scaling activities for scheduled actions that have
-- already run, call the DescribeScalingActivities API.
--
-- This operation returns paginated results.
module Amazonka.AutoScaling.DescribeScheduledActions
  ( -- * Creating a Request
    DescribeScheduledActions (..),
    newDescribeScheduledActions,

    -- * Request Lenses
    describeScheduledActions_autoScalingGroupName,
    describeScheduledActions_endTime,
    describeScheduledActions_maxRecords,
    describeScheduledActions_nextToken,
    describeScheduledActions_scheduledActionNames,
    describeScheduledActions_startTime,

    -- * Destructuring the Response
    DescribeScheduledActionsResponse (..),
    newDescribeScheduledActionsResponse,

    -- * Response Lenses
    describeScheduledActionsResponse_nextToken,
    describeScheduledActionsResponse_scheduledUpdateGroupActions,
    describeScheduledActionsResponse_httpStatus,
  )
where

import Amazonka.AutoScaling.Types
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newDescribeScheduledActions' smart constructor.
data DescribeScheduledActions = DescribeScheduledActions'
  { -- | The name of the Auto Scaling group.
    DescribeScheduledActions -> Maybe Text
autoScalingGroupName :: Prelude.Maybe Prelude.Text,
    -- | The latest scheduled start time to return. If scheduled action names are
    -- provided, this property is ignored.
    DescribeScheduledActions -> Maybe ISO8601
endTime :: Prelude.Maybe Data.ISO8601,
    -- | The maximum number of items to return with this call. The default value
    -- is @50@ and the maximum value is @100@.
    DescribeScheduledActions -> Maybe Int
maxRecords :: Prelude.Maybe Prelude.Int,
    -- | The token for the next set of items to return. (You received this token
    -- from a previous call.)
    DescribeScheduledActions -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The names of one or more scheduled actions. If you omit this property,
    -- all scheduled actions are described. If you specify an unknown scheduled
    -- action, it is ignored with no error.
    --
    -- Array Members: Maximum number of 50 actions.
    DescribeScheduledActions -> Maybe [Text]
scheduledActionNames :: Prelude.Maybe [Prelude.Text],
    -- | The earliest scheduled start time to return. If scheduled action names
    -- are provided, this property is ignored.
    DescribeScheduledActions -> Maybe ISO8601
startTime :: Prelude.Maybe Data.ISO8601
  }
  deriving (DescribeScheduledActions -> DescribeScheduledActions -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeScheduledActions -> DescribeScheduledActions -> Bool
$c/= :: DescribeScheduledActions -> DescribeScheduledActions -> Bool
== :: DescribeScheduledActions -> DescribeScheduledActions -> Bool
$c== :: DescribeScheduledActions -> DescribeScheduledActions -> Bool
Prelude.Eq, ReadPrec [DescribeScheduledActions]
ReadPrec DescribeScheduledActions
Int -> ReadS DescribeScheduledActions
ReadS [DescribeScheduledActions]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeScheduledActions]
$creadListPrec :: ReadPrec [DescribeScheduledActions]
readPrec :: ReadPrec DescribeScheduledActions
$creadPrec :: ReadPrec DescribeScheduledActions
readList :: ReadS [DescribeScheduledActions]
$creadList :: ReadS [DescribeScheduledActions]
readsPrec :: Int -> ReadS DescribeScheduledActions
$creadsPrec :: Int -> ReadS DescribeScheduledActions
Prelude.Read, Int -> DescribeScheduledActions -> ShowS
[DescribeScheduledActions] -> ShowS
DescribeScheduledActions -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeScheduledActions] -> ShowS
$cshowList :: [DescribeScheduledActions] -> ShowS
show :: DescribeScheduledActions -> String
$cshow :: DescribeScheduledActions -> String
showsPrec :: Int -> DescribeScheduledActions -> ShowS
$cshowsPrec :: Int -> DescribeScheduledActions -> ShowS
Prelude.Show, forall x.
Rep DescribeScheduledActions x -> DescribeScheduledActions
forall x.
DescribeScheduledActions -> Rep DescribeScheduledActions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeScheduledActions x -> DescribeScheduledActions
$cfrom :: forall x.
DescribeScheduledActions -> Rep DescribeScheduledActions x
Prelude.Generic)

-- |
-- Create a value of 'DescribeScheduledActions' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'autoScalingGroupName', 'describeScheduledActions_autoScalingGroupName' - The name of the Auto Scaling group.
--
-- 'endTime', 'describeScheduledActions_endTime' - The latest scheduled start time to return. If scheduled action names are
-- provided, this property is ignored.
--
-- 'maxRecords', 'describeScheduledActions_maxRecords' - The maximum number of items to return with this call. The default value
-- is @50@ and the maximum value is @100@.
--
-- 'nextToken', 'describeScheduledActions_nextToken' - The token for the next set of items to return. (You received this token
-- from a previous call.)
--
-- 'scheduledActionNames', 'describeScheduledActions_scheduledActionNames' - The names of one or more scheduled actions. If you omit this property,
-- all scheduled actions are described. If you specify an unknown scheduled
-- action, it is ignored with no error.
--
-- Array Members: Maximum number of 50 actions.
--
-- 'startTime', 'describeScheduledActions_startTime' - The earliest scheduled start time to return. If scheduled action names
-- are provided, this property is ignored.
newDescribeScheduledActions ::
  DescribeScheduledActions
newDescribeScheduledActions :: DescribeScheduledActions
newDescribeScheduledActions =
  DescribeScheduledActions'
    { $sel:autoScalingGroupName:DescribeScheduledActions' :: Maybe Text
autoScalingGroupName =
        forall a. Maybe a
Prelude.Nothing,
      $sel:endTime:DescribeScheduledActions' :: Maybe ISO8601
endTime = forall a. Maybe a
Prelude.Nothing,
      $sel:maxRecords:DescribeScheduledActions' :: Maybe Int
maxRecords = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:DescribeScheduledActions' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:scheduledActionNames:DescribeScheduledActions' :: Maybe [Text]
scheduledActionNames = forall a. Maybe a
Prelude.Nothing,
      $sel:startTime:DescribeScheduledActions' :: Maybe ISO8601
startTime = forall a. Maybe a
Prelude.Nothing
    }

-- | The name of the Auto Scaling group.
describeScheduledActions_autoScalingGroupName :: Lens.Lens' DescribeScheduledActions (Prelude.Maybe Prelude.Text)
describeScheduledActions_autoScalingGroupName :: Lens' DescribeScheduledActions (Maybe Text)
describeScheduledActions_autoScalingGroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeScheduledActions' {Maybe Text
autoScalingGroupName :: Maybe Text
$sel:autoScalingGroupName:DescribeScheduledActions' :: DescribeScheduledActions -> Maybe Text
autoScalingGroupName} -> Maybe Text
autoScalingGroupName) (\s :: DescribeScheduledActions
s@DescribeScheduledActions' {} Maybe Text
a -> DescribeScheduledActions
s {$sel:autoScalingGroupName:DescribeScheduledActions' :: Maybe Text
autoScalingGroupName = Maybe Text
a} :: DescribeScheduledActions)

-- | The latest scheduled start time to return. If scheduled action names are
-- provided, this property is ignored.
describeScheduledActions_endTime :: Lens.Lens' DescribeScheduledActions (Prelude.Maybe Prelude.UTCTime)
describeScheduledActions_endTime :: Lens' DescribeScheduledActions (Maybe UTCTime)
describeScheduledActions_endTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeScheduledActions' {Maybe ISO8601
endTime :: Maybe ISO8601
$sel:endTime:DescribeScheduledActions' :: DescribeScheduledActions -> Maybe ISO8601
endTime} -> Maybe ISO8601
endTime) (\s :: DescribeScheduledActions
s@DescribeScheduledActions' {} Maybe ISO8601
a -> DescribeScheduledActions
s {$sel:endTime:DescribeScheduledActions' :: Maybe ISO8601
endTime = Maybe ISO8601
a} :: DescribeScheduledActions) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The maximum number of items to return with this call. The default value
-- is @50@ and the maximum value is @100@.
describeScheduledActions_maxRecords :: Lens.Lens' DescribeScheduledActions (Prelude.Maybe Prelude.Int)
describeScheduledActions_maxRecords :: Lens' DescribeScheduledActions (Maybe Int)
describeScheduledActions_maxRecords = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeScheduledActions' {Maybe Int
maxRecords :: Maybe Int
$sel:maxRecords:DescribeScheduledActions' :: DescribeScheduledActions -> Maybe Int
maxRecords} -> Maybe Int
maxRecords) (\s :: DescribeScheduledActions
s@DescribeScheduledActions' {} Maybe Int
a -> DescribeScheduledActions
s {$sel:maxRecords:DescribeScheduledActions' :: Maybe Int
maxRecords = Maybe Int
a} :: DescribeScheduledActions)

-- | The token for the next set of items to return. (You received this token
-- from a previous call.)
describeScheduledActions_nextToken :: Lens.Lens' DescribeScheduledActions (Prelude.Maybe Prelude.Text)
describeScheduledActions_nextToken :: Lens' DescribeScheduledActions (Maybe Text)
describeScheduledActions_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeScheduledActions' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:DescribeScheduledActions' :: DescribeScheduledActions -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: DescribeScheduledActions
s@DescribeScheduledActions' {} Maybe Text
a -> DescribeScheduledActions
s {$sel:nextToken:DescribeScheduledActions' :: Maybe Text
nextToken = Maybe Text
a} :: DescribeScheduledActions)

-- | The names of one or more scheduled actions. If you omit this property,
-- all scheduled actions are described. If you specify an unknown scheduled
-- action, it is ignored with no error.
--
-- Array Members: Maximum number of 50 actions.
describeScheduledActions_scheduledActionNames :: Lens.Lens' DescribeScheduledActions (Prelude.Maybe [Prelude.Text])
describeScheduledActions_scheduledActionNames :: Lens' DescribeScheduledActions (Maybe [Text])
describeScheduledActions_scheduledActionNames = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeScheduledActions' {Maybe [Text]
scheduledActionNames :: Maybe [Text]
$sel:scheduledActionNames:DescribeScheduledActions' :: DescribeScheduledActions -> Maybe [Text]
scheduledActionNames} -> Maybe [Text]
scheduledActionNames) (\s :: DescribeScheduledActions
s@DescribeScheduledActions' {} Maybe [Text]
a -> DescribeScheduledActions
s {$sel:scheduledActionNames:DescribeScheduledActions' :: Maybe [Text]
scheduledActionNames = Maybe [Text]
a} :: DescribeScheduledActions) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The earliest scheduled start time to return. If scheduled action names
-- are provided, this property is ignored.
describeScheduledActions_startTime :: Lens.Lens' DescribeScheduledActions (Prelude.Maybe Prelude.UTCTime)
describeScheduledActions_startTime :: Lens' DescribeScheduledActions (Maybe UTCTime)
describeScheduledActions_startTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeScheduledActions' {Maybe ISO8601
startTime :: Maybe ISO8601
$sel:startTime:DescribeScheduledActions' :: DescribeScheduledActions -> Maybe ISO8601
startTime} -> Maybe ISO8601
startTime) (\s :: DescribeScheduledActions
s@DescribeScheduledActions' {} Maybe ISO8601
a -> DescribeScheduledActions
s {$sel:startTime:DescribeScheduledActions' :: Maybe ISO8601
startTime = Maybe ISO8601
a} :: DescribeScheduledActions) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

instance Core.AWSPager DescribeScheduledActions where
  page :: DescribeScheduledActions
-> AWSResponse DescribeScheduledActions
-> Maybe DescribeScheduledActions
page DescribeScheduledActions
rq AWSResponse DescribeScheduledActions
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse DescribeScheduledActions
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' DescribeScheduledActionsResponse (Maybe Text)
describeScheduledActionsResponse_nextToken
            forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
        ) =
        forall a. Maybe a
Prelude.Nothing
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse DescribeScheduledActions
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens'
  DescribeScheduledActionsResponse
  (Maybe [ScheduledUpdateGroupAction])
describeScheduledActionsResponse_scheduledUpdateGroupActions
            forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
        ) =
        forall a. Maybe a
Prelude.Nothing
    | Bool
Prelude.otherwise =
        forall a. a -> Maybe a
Prelude.Just
          forall a b. (a -> b) -> a -> b
Prelude.$ DescribeScheduledActions
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' DescribeScheduledActions (Maybe Text)
describeScheduledActions_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse DescribeScheduledActions
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' DescribeScheduledActionsResponse (Maybe Text)
describeScheduledActionsResponse_nextToken
          forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just

instance Core.AWSRequest DescribeScheduledActions where
  type
    AWSResponse DescribeScheduledActions =
      DescribeScheduledActionsResponse
  request :: (Service -> Service)
-> DescribeScheduledActions -> Request DescribeScheduledActions
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.postQuery (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DescribeScheduledActions
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeScheduledActions)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
Text
-> (Int
    -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXMLWrapper
      Text
"DescribeScheduledActionsResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe Text
-> Maybe [ScheduledUpdateGroupAction]
-> Int
-> DescribeScheduledActionsResponse
DescribeScheduledActionsResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"NextToken")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( [Node]
x
                            forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"ScheduledUpdateGroupActions"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                            forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"member")
                        )
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable DescribeScheduledActions where
  hashWithSalt :: Int -> DescribeScheduledActions -> Int
hashWithSalt Int
_salt DescribeScheduledActions' {Maybe Int
Maybe [Text]
Maybe Text
Maybe ISO8601
startTime :: Maybe ISO8601
scheduledActionNames :: Maybe [Text]
nextToken :: Maybe Text
maxRecords :: Maybe Int
endTime :: Maybe ISO8601
autoScalingGroupName :: Maybe Text
$sel:startTime:DescribeScheduledActions' :: DescribeScheduledActions -> Maybe ISO8601
$sel:scheduledActionNames:DescribeScheduledActions' :: DescribeScheduledActions -> Maybe [Text]
$sel:nextToken:DescribeScheduledActions' :: DescribeScheduledActions -> Maybe Text
$sel:maxRecords:DescribeScheduledActions' :: DescribeScheduledActions -> Maybe Int
$sel:endTime:DescribeScheduledActions' :: DescribeScheduledActions -> Maybe ISO8601
$sel:autoScalingGroupName:DescribeScheduledActions' :: DescribeScheduledActions -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
autoScalingGroupName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ISO8601
endTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
maxRecords
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
scheduledActionNames
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ISO8601
startTime

instance Prelude.NFData DescribeScheduledActions where
  rnf :: DescribeScheduledActions -> ()
rnf DescribeScheduledActions' {Maybe Int
Maybe [Text]
Maybe Text
Maybe ISO8601
startTime :: Maybe ISO8601
scheduledActionNames :: Maybe [Text]
nextToken :: Maybe Text
maxRecords :: Maybe Int
endTime :: Maybe ISO8601
autoScalingGroupName :: Maybe Text
$sel:startTime:DescribeScheduledActions' :: DescribeScheduledActions -> Maybe ISO8601
$sel:scheduledActionNames:DescribeScheduledActions' :: DescribeScheduledActions -> Maybe [Text]
$sel:nextToken:DescribeScheduledActions' :: DescribeScheduledActions -> Maybe Text
$sel:maxRecords:DescribeScheduledActions' :: DescribeScheduledActions -> Maybe Int
$sel:endTime:DescribeScheduledActions' :: DescribeScheduledActions -> Maybe ISO8601
$sel:autoScalingGroupName:DescribeScheduledActions' :: DescribeScheduledActions -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
autoScalingGroupName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ISO8601
endTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
maxRecords
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
scheduledActionNames
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ISO8601
startTime

instance Data.ToHeaders DescribeScheduledActions where
  toHeaders :: DescribeScheduledActions -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

instance Data.ToPath DescribeScheduledActions where
  toPath :: DescribeScheduledActions -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

instance Data.ToQuery DescribeScheduledActions where
  toQuery :: DescribeScheduledActions -> QueryString
toQuery DescribeScheduledActions' {Maybe Int
Maybe [Text]
Maybe Text
Maybe ISO8601
startTime :: Maybe ISO8601
scheduledActionNames :: Maybe [Text]
nextToken :: Maybe Text
maxRecords :: Maybe Int
endTime :: Maybe ISO8601
autoScalingGroupName :: Maybe Text
$sel:startTime:DescribeScheduledActions' :: DescribeScheduledActions -> Maybe ISO8601
$sel:scheduledActionNames:DescribeScheduledActions' :: DescribeScheduledActions -> Maybe [Text]
$sel:nextToken:DescribeScheduledActions' :: DescribeScheduledActions -> Maybe Text
$sel:maxRecords:DescribeScheduledActions' :: DescribeScheduledActions -> Maybe Int
$sel:endTime:DescribeScheduledActions' :: DescribeScheduledActions -> Maybe ISO8601
$sel:autoScalingGroupName:DescribeScheduledActions' :: DescribeScheduledActions -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"DescribeScheduledActions" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2011-01-01" :: Prelude.ByteString),
        ByteString
"AutoScalingGroupName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
autoScalingGroupName,
        ByteString
"EndTime" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe ISO8601
endTime,
        ByteString
"MaxRecords" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Int
maxRecords,
        ByteString
"NextToken" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
nextToken,
        ByteString
"ScheduledActionNames"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: forall a. ToQuery a => a -> QueryString
Data.toQuery
            ( forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"member"
                forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Text]
scheduledActionNames
            ),
        ByteString
"StartTime" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe ISO8601
startTime
      ]

-- | /See:/ 'newDescribeScheduledActionsResponse' smart constructor.
data DescribeScheduledActionsResponse = DescribeScheduledActionsResponse'
  { -- | A string that indicates that the response contains more items than can
    -- be returned in a single response. To receive additional items, specify
    -- this string for the @NextToken@ value when requesting the next set of
    -- items. This value is null when there are no more items to return.
    DescribeScheduledActionsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The scheduled actions.
    DescribeScheduledActionsResponse
-> Maybe [ScheduledUpdateGroupAction]
scheduledUpdateGroupActions :: Prelude.Maybe [ScheduledUpdateGroupAction],
    -- | The response's http status code.
    DescribeScheduledActionsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeScheduledActionsResponse
-> DescribeScheduledActionsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeScheduledActionsResponse
-> DescribeScheduledActionsResponse -> Bool
$c/= :: DescribeScheduledActionsResponse
-> DescribeScheduledActionsResponse -> Bool
== :: DescribeScheduledActionsResponse
-> DescribeScheduledActionsResponse -> Bool
$c== :: DescribeScheduledActionsResponse
-> DescribeScheduledActionsResponse -> Bool
Prelude.Eq, ReadPrec [DescribeScheduledActionsResponse]
ReadPrec DescribeScheduledActionsResponse
Int -> ReadS DescribeScheduledActionsResponse
ReadS [DescribeScheduledActionsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeScheduledActionsResponse]
$creadListPrec :: ReadPrec [DescribeScheduledActionsResponse]
readPrec :: ReadPrec DescribeScheduledActionsResponse
$creadPrec :: ReadPrec DescribeScheduledActionsResponse
readList :: ReadS [DescribeScheduledActionsResponse]
$creadList :: ReadS [DescribeScheduledActionsResponse]
readsPrec :: Int -> ReadS DescribeScheduledActionsResponse
$creadsPrec :: Int -> ReadS DescribeScheduledActionsResponse
Prelude.Read, Int -> DescribeScheduledActionsResponse -> ShowS
[DescribeScheduledActionsResponse] -> ShowS
DescribeScheduledActionsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeScheduledActionsResponse] -> ShowS
$cshowList :: [DescribeScheduledActionsResponse] -> ShowS
show :: DescribeScheduledActionsResponse -> String
$cshow :: DescribeScheduledActionsResponse -> String
showsPrec :: Int -> DescribeScheduledActionsResponse -> ShowS
$cshowsPrec :: Int -> DescribeScheduledActionsResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeScheduledActionsResponse x
-> DescribeScheduledActionsResponse
forall x.
DescribeScheduledActionsResponse
-> Rep DescribeScheduledActionsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeScheduledActionsResponse x
-> DescribeScheduledActionsResponse
$cfrom :: forall x.
DescribeScheduledActionsResponse
-> Rep DescribeScheduledActionsResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeScheduledActionsResponse' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'nextToken', 'describeScheduledActionsResponse_nextToken' - A string that indicates that the response contains more items than can
-- be returned in a single response. To receive additional items, specify
-- this string for the @NextToken@ value when requesting the next set of
-- items. This value is null when there are no more items to return.
--
-- 'scheduledUpdateGroupActions', 'describeScheduledActionsResponse_scheduledUpdateGroupActions' - The scheduled actions.
--
-- 'httpStatus', 'describeScheduledActionsResponse_httpStatus' - The response's http status code.
newDescribeScheduledActionsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeScheduledActionsResponse
newDescribeScheduledActionsResponse :: Int -> DescribeScheduledActionsResponse
newDescribeScheduledActionsResponse Int
pHttpStatus_ =
  DescribeScheduledActionsResponse'
    { $sel:nextToken:DescribeScheduledActionsResponse' :: Maybe Text
nextToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:scheduledUpdateGroupActions:DescribeScheduledActionsResponse' :: Maybe [ScheduledUpdateGroupAction]
scheduledUpdateGroupActions =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeScheduledActionsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A string that indicates that the response contains more items than can
-- be returned in a single response. To receive additional items, specify
-- this string for the @NextToken@ value when requesting the next set of
-- items. This value is null when there are no more items to return.
describeScheduledActionsResponse_nextToken :: Lens.Lens' DescribeScheduledActionsResponse (Prelude.Maybe Prelude.Text)
describeScheduledActionsResponse_nextToken :: Lens' DescribeScheduledActionsResponse (Maybe Text)
describeScheduledActionsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeScheduledActionsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:DescribeScheduledActionsResponse' :: DescribeScheduledActionsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: DescribeScheduledActionsResponse
s@DescribeScheduledActionsResponse' {} Maybe Text
a -> DescribeScheduledActionsResponse
s {$sel:nextToken:DescribeScheduledActionsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: DescribeScheduledActionsResponse)

-- | The scheduled actions.
describeScheduledActionsResponse_scheduledUpdateGroupActions :: Lens.Lens' DescribeScheduledActionsResponse (Prelude.Maybe [ScheduledUpdateGroupAction])
describeScheduledActionsResponse_scheduledUpdateGroupActions :: Lens'
  DescribeScheduledActionsResponse
  (Maybe [ScheduledUpdateGroupAction])
describeScheduledActionsResponse_scheduledUpdateGroupActions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeScheduledActionsResponse' {Maybe [ScheduledUpdateGroupAction]
scheduledUpdateGroupActions :: Maybe [ScheduledUpdateGroupAction]
$sel:scheduledUpdateGroupActions:DescribeScheduledActionsResponse' :: DescribeScheduledActionsResponse
-> Maybe [ScheduledUpdateGroupAction]
scheduledUpdateGroupActions} -> Maybe [ScheduledUpdateGroupAction]
scheduledUpdateGroupActions) (\s :: DescribeScheduledActionsResponse
s@DescribeScheduledActionsResponse' {} Maybe [ScheduledUpdateGroupAction]
a -> DescribeScheduledActionsResponse
s {$sel:scheduledUpdateGroupActions:DescribeScheduledActionsResponse' :: Maybe [ScheduledUpdateGroupAction]
scheduledUpdateGroupActions = Maybe [ScheduledUpdateGroupAction]
a} :: DescribeScheduledActionsResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The response's http status code.
describeScheduledActionsResponse_httpStatus :: Lens.Lens' DescribeScheduledActionsResponse Prelude.Int
describeScheduledActionsResponse_httpStatus :: Lens' DescribeScheduledActionsResponse Int
describeScheduledActionsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeScheduledActionsResponse' {Int
httpStatus :: Int
$sel:httpStatus:DescribeScheduledActionsResponse' :: DescribeScheduledActionsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: DescribeScheduledActionsResponse
s@DescribeScheduledActionsResponse' {} Int
a -> DescribeScheduledActionsResponse
s {$sel:httpStatus:DescribeScheduledActionsResponse' :: Int
httpStatus = Int
a} :: DescribeScheduledActionsResponse)

instance
  Prelude.NFData
    DescribeScheduledActionsResponse
  where
  rnf :: DescribeScheduledActionsResponse -> ()
rnf DescribeScheduledActionsResponse' {Int
Maybe [ScheduledUpdateGroupAction]
Maybe Text
httpStatus :: Int
scheduledUpdateGroupActions :: Maybe [ScheduledUpdateGroupAction]
nextToken :: Maybe Text
$sel:httpStatus:DescribeScheduledActionsResponse' :: DescribeScheduledActionsResponse -> Int
$sel:scheduledUpdateGroupActions:DescribeScheduledActionsResponse' :: DescribeScheduledActionsResponse
-> Maybe [ScheduledUpdateGroupAction]
$sel:nextToken:DescribeScheduledActionsResponse' :: DescribeScheduledActionsResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [ScheduledUpdateGroupAction]
scheduledUpdateGroupActions
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus