{-# 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.Redshift.DescribeSnapshotSchedules
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Returns a list of snapshot schedules.
--
-- This operation returns paginated results.
module Amazonka.Redshift.DescribeSnapshotSchedules
  ( -- * Creating a Request
    DescribeSnapshotSchedules (..),
    newDescribeSnapshotSchedules,

    -- * Request Lenses
    describeSnapshotSchedules_clusterIdentifier,
    describeSnapshotSchedules_marker,
    describeSnapshotSchedules_maxRecords,
    describeSnapshotSchedules_scheduleIdentifier,
    describeSnapshotSchedules_tagKeys,
    describeSnapshotSchedules_tagValues,

    -- * Destructuring the Response
    DescribeSnapshotSchedulesResponse (..),
    newDescribeSnapshotSchedulesResponse,

    -- * Response Lenses
    describeSnapshotSchedulesResponse_marker,
    describeSnapshotSchedulesResponse_snapshotSchedules,
    describeSnapshotSchedulesResponse_httpStatus,
  )
where

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 Amazonka.Redshift.Types
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newDescribeSnapshotSchedules' smart constructor.
data DescribeSnapshotSchedules = DescribeSnapshotSchedules'
  { -- | The unique identifier for the cluster whose snapshot schedules you want
    -- to view.
    DescribeSnapshotSchedules -> Maybe Text
clusterIdentifier :: Prelude.Maybe Prelude.Text,
    -- | A value that indicates the starting point for the next set of response
    -- records in a subsequent request. If a value is returned in a response,
    -- you can retrieve the next set of records by providing this returned
    -- marker value in the @marker@ parameter and retrying the command. If the
    -- @marker@ field is empty, all response records have been retrieved for
    -- the request.
    DescribeSnapshotSchedules -> Maybe Text
marker :: Prelude.Maybe Prelude.Text,
    -- | The maximum number or response records to return in each call. If the
    -- number of remaining response records exceeds the specified @MaxRecords@
    -- value, a value is returned in a @marker@ field of the response. You can
    -- retrieve the next set of records by retrying the command with the
    -- returned @marker@ value.
    DescribeSnapshotSchedules -> Maybe Int
maxRecords :: Prelude.Maybe Prelude.Int,
    -- | A unique identifier for a snapshot schedule.
    DescribeSnapshotSchedules -> Maybe Text
scheduleIdentifier :: Prelude.Maybe Prelude.Text,
    -- | The key value for a snapshot schedule tag.
    DescribeSnapshotSchedules -> Maybe [Text]
tagKeys :: Prelude.Maybe [Prelude.Text],
    -- | The value corresponding to the key of the snapshot schedule tag.
    DescribeSnapshotSchedules -> Maybe [Text]
tagValues :: Prelude.Maybe [Prelude.Text]
  }
  deriving (DescribeSnapshotSchedules -> DescribeSnapshotSchedules -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeSnapshotSchedules -> DescribeSnapshotSchedules -> Bool
$c/= :: DescribeSnapshotSchedules -> DescribeSnapshotSchedules -> Bool
== :: DescribeSnapshotSchedules -> DescribeSnapshotSchedules -> Bool
$c== :: DescribeSnapshotSchedules -> DescribeSnapshotSchedules -> Bool
Prelude.Eq, ReadPrec [DescribeSnapshotSchedules]
ReadPrec DescribeSnapshotSchedules
Int -> ReadS DescribeSnapshotSchedules
ReadS [DescribeSnapshotSchedules]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeSnapshotSchedules]
$creadListPrec :: ReadPrec [DescribeSnapshotSchedules]
readPrec :: ReadPrec DescribeSnapshotSchedules
$creadPrec :: ReadPrec DescribeSnapshotSchedules
readList :: ReadS [DescribeSnapshotSchedules]
$creadList :: ReadS [DescribeSnapshotSchedules]
readsPrec :: Int -> ReadS DescribeSnapshotSchedules
$creadsPrec :: Int -> ReadS DescribeSnapshotSchedules
Prelude.Read, Int -> DescribeSnapshotSchedules -> ShowS
[DescribeSnapshotSchedules] -> ShowS
DescribeSnapshotSchedules -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeSnapshotSchedules] -> ShowS
$cshowList :: [DescribeSnapshotSchedules] -> ShowS
show :: DescribeSnapshotSchedules -> String
$cshow :: DescribeSnapshotSchedules -> String
showsPrec :: Int -> DescribeSnapshotSchedules -> ShowS
$cshowsPrec :: Int -> DescribeSnapshotSchedules -> ShowS
Prelude.Show, forall x.
Rep DescribeSnapshotSchedules x -> DescribeSnapshotSchedules
forall x.
DescribeSnapshotSchedules -> Rep DescribeSnapshotSchedules x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeSnapshotSchedules x -> DescribeSnapshotSchedules
$cfrom :: forall x.
DescribeSnapshotSchedules -> Rep DescribeSnapshotSchedules x
Prelude.Generic)

-- |
-- Create a value of 'DescribeSnapshotSchedules' 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:
--
-- 'clusterIdentifier', 'describeSnapshotSchedules_clusterIdentifier' - The unique identifier for the cluster whose snapshot schedules you want
-- to view.
--
-- 'marker', 'describeSnapshotSchedules_marker' - A value that indicates the starting point for the next set of response
-- records in a subsequent request. If a value is returned in a response,
-- you can retrieve the next set of records by providing this returned
-- marker value in the @marker@ parameter and retrying the command. If the
-- @marker@ field is empty, all response records have been retrieved for
-- the request.
--
-- 'maxRecords', 'describeSnapshotSchedules_maxRecords' - The maximum number or response records to return in each call. If the
-- number of remaining response records exceeds the specified @MaxRecords@
-- value, a value is returned in a @marker@ field of the response. You can
-- retrieve the next set of records by retrying the command with the
-- returned @marker@ value.
--
-- 'scheduleIdentifier', 'describeSnapshotSchedules_scheduleIdentifier' - A unique identifier for a snapshot schedule.
--
-- 'tagKeys', 'describeSnapshotSchedules_tagKeys' - The key value for a snapshot schedule tag.
--
-- 'tagValues', 'describeSnapshotSchedules_tagValues' - The value corresponding to the key of the snapshot schedule tag.
newDescribeSnapshotSchedules ::
  DescribeSnapshotSchedules
newDescribeSnapshotSchedules :: DescribeSnapshotSchedules
newDescribeSnapshotSchedules =
  DescribeSnapshotSchedules'
    { $sel:clusterIdentifier:DescribeSnapshotSchedules' :: Maybe Text
clusterIdentifier =
        forall a. Maybe a
Prelude.Nothing,
      $sel:marker:DescribeSnapshotSchedules' :: Maybe Text
marker = forall a. Maybe a
Prelude.Nothing,
      $sel:maxRecords:DescribeSnapshotSchedules' :: Maybe Int
maxRecords = forall a. Maybe a
Prelude.Nothing,
      $sel:scheduleIdentifier:DescribeSnapshotSchedules' :: Maybe Text
scheduleIdentifier = forall a. Maybe a
Prelude.Nothing,
      $sel:tagKeys:DescribeSnapshotSchedules' :: Maybe [Text]
tagKeys = forall a. Maybe a
Prelude.Nothing,
      $sel:tagValues:DescribeSnapshotSchedules' :: Maybe [Text]
tagValues = forall a. Maybe a
Prelude.Nothing
    }

-- | The unique identifier for the cluster whose snapshot schedules you want
-- to view.
describeSnapshotSchedules_clusterIdentifier :: Lens.Lens' DescribeSnapshotSchedules (Prelude.Maybe Prelude.Text)
describeSnapshotSchedules_clusterIdentifier :: Lens' DescribeSnapshotSchedules (Maybe Text)
describeSnapshotSchedules_clusterIdentifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSnapshotSchedules' {Maybe Text
clusterIdentifier :: Maybe Text
$sel:clusterIdentifier:DescribeSnapshotSchedules' :: DescribeSnapshotSchedules -> Maybe Text
clusterIdentifier} -> Maybe Text
clusterIdentifier) (\s :: DescribeSnapshotSchedules
s@DescribeSnapshotSchedules' {} Maybe Text
a -> DescribeSnapshotSchedules
s {$sel:clusterIdentifier:DescribeSnapshotSchedules' :: Maybe Text
clusterIdentifier = Maybe Text
a} :: DescribeSnapshotSchedules)

-- | A value that indicates the starting point for the next set of response
-- records in a subsequent request. If a value is returned in a response,
-- you can retrieve the next set of records by providing this returned
-- marker value in the @marker@ parameter and retrying the command. If the
-- @marker@ field is empty, all response records have been retrieved for
-- the request.
describeSnapshotSchedules_marker :: Lens.Lens' DescribeSnapshotSchedules (Prelude.Maybe Prelude.Text)
describeSnapshotSchedules_marker :: Lens' DescribeSnapshotSchedules (Maybe Text)
describeSnapshotSchedules_marker = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSnapshotSchedules' {Maybe Text
marker :: Maybe Text
$sel:marker:DescribeSnapshotSchedules' :: DescribeSnapshotSchedules -> Maybe Text
marker} -> Maybe Text
marker) (\s :: DescribeSnapshotSchedules
s@DescribeSnapshotSchedules' {} Maybe Text
a -> DescribeSnapshotSchedules
s {$sel:marker:DescribeSnapshotSchedules' :: Maybe Text
marker = Maybe Text
a} :: DescribeSnapshotSchedules)

-- | The maximum number or response records to return in each call. If the
-- number of remaining response records exceeds the specified @MaxRecords@
-- value, a value is returned in a @marker@ field of the response. You can
-- retrieve the next set of records by retrying the command with the
-- returned @marker@ value.
describeSnapshotSchedules_maxRecords :: Lens.Lens' DescribeSnapshotSchedules (Prelude.Maybe Prelude.Int)
describeSnapshotSchedules_maxRecords :: Lens' DescribeSnapshotSchedules (Maybe Int)
describeSnapshotSchedules_maxRecords = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSnapshotSchedules' {Maybe Int
maxRecords :: Maybe Int
$sel:maxRecords:DescribeSnapshotSchedules' :: DescribeSnapshotSchedules -> Maybe Int
maxRecords} -> Maybe Int
maxRecords) (\s :: DescribeSnapshotSchedules
s@DescribeSnapshotSchedules' {} Maybe Int
a -> DescribeSnapshotSchedules
s {$sel:maxRecords:DescribeSnapshotSchedules' :: Maybe Int
maxRecords = Maybe Int
a} :: DescribeSnapshotSchedules)

-- | A unique identifier for a snapshot schedule.
describeSnapshotSchedules_scheduleIdentifier :: Lens.Lens' DescribeSnapshotSchedules (Prelude.Maybe Prelude.Text)
describeSnapshotSchedules_scheduleIdentifier :: Lens' DescribeSnapshotSchedules (Maybe Text)
describeSnapshotSchedules_scheduleIdentifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSnapshotSchedules' {Maybe Text
scheduleIdentifier :: Maybe Text
$sel:scheduleIdentifier:DescribeSnapshotSchedules' :: DescribeSnapshotSchedules -> Maybe Text
scheduleIdentifier} -> Maybe Text
scheduleIdentifier) (\s :: DescribeSnapshotSchedules
s@DescribeSnapshotSchedules' {} Maybe Text
a -> DescribeSnapshotSchedules
s {$sel:scheduleIdentifier:DescribeSnapshotSchedules' :: Maybe Text
scheduleIdentifier = Maybe Text
a} :: DescribeSnapshotSchedules)

-- | The key value for a snapshot schedule tag.
describeSnapshotSchedules_tagKeys :: Lens.Lens' DescribeSnapshotSchedules (Prelude.Maybe [Prelude.Text])
describeSnapshotSchedules_tagKeys :: Lens' DescribeSnapshotSchedules (Maybe [Text])
describeSnapshotSchedules_tagKeys = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSnapshotSchedules' {Maybe [Text]
tagKeys :: Maybe [Text]
$sel:tagKeys:DescribeSnapshotSchedules' :: DescribeSnapshotSchedules -> Maybe [Text]
tagKeys} -> Maybe [Text]
tagKeys) (\s :: DescribeSnapshotSchedules
s@DescribeSnapshotSchedules' {} Maybe [Text]
a -> DescribeSnapshotSchedules
s {$sel:tagKeys:DescribeSnapshotSchedules' :: Maybe [Text]
tagKeys = Maybe [Text]
a} :: DescribeSnapshotSchedules) 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 value corresponding to the key of the snapshot schedule tag.
describeSnapshotSchedules_tagValues :: Lens.Lens' DescribeSnapshotSchedules (Prelude.Maybe [Prelude.Text])
describeSnapshotSchedules_tagValues :: Lens' DescribeSnapshotSchedules (Maybe [Text])
describeSnapshotSchedules_tagValues = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSnapshotSchedules' {Maybe [Text]
tagValues :: Maybe [Text]
$sel:tagValues:DescribeSnapshotSchedules' :: DescribeSnapshotSchedules -> Maybe [Text]
tagValues} -> Maybe [Text]
tagValues) (\s :: DescribeSnapshotSchedules
s@DescribeSnapshotSchedules' {} Maybe [Text]
a -> DescribeSnapshotSchedules
s {$sel:tagValues:DescribeSnapshotSchedules' :: Maybe [Text]
tagValues = Maybe [Text]
a} :: DescribeSnapshotSchedules) 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

instance Core.AWSPager DescribeSnapshotSchedules where
  page :: DescribeSnapshotSchedules
-> AWSResponse DescribeSnapshotSchedules
-> Maybe DescribeSnapshotSchedules
page DescribeSnapshotSchedules
rq AWSResponse DescribeSnapshotSchedules
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse DescribeSnapshotSchedules
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' DescribeSnapshotSchedulesResponse (Maybe Text)
describeSnapshotSchedulesResponse_marker
            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 DescribeSnapshotSchedules
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' DescribeSnapshotSchedulesResponse (Maybe [SnapshotSchedule])
describeSnapshotSchedulesResponse_snapshotSchedules
            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.$ DescribeSnapshotSchedules
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' DescribeSnapshotSchedules (Maybe Text)
describeSnapshotSchedules_marker
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse DescribeSnapshotSchedules
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' DescribeSnapshotSchedulesResponse (Maybe Text)
describeSnapshotSchedulesResponse_marker
          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 DescribeSnapshotSchedules where
  type
    AWSResponse DescribeSnapshotSchedules =
      DescribeSnapshotSchedulesResponse
  request :: (Service -> Service)
-> DescribeSnapshotSchedules -> Request DescribeSnapshotSchedules
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 DescribeSnapshotSchedules
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeSnapshotSchedules)))
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
"DescribeSnapshotSchedulesResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe Text
-> Maybe [SnapshotSchedule]
-> Int
-> DescribeSnapshotSchedulesResponse
DescribeSnapshotSchedulesResponse'
            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
"Marker")
            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
"SnapshotSchedules"
                            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
"SnapshotSchedule")
                        )
            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 DescribeSnapshotSchedules where
  hashWithSalt :: Int -> DescribeSnapshotSchedules -> Int
hashWithSalt Int
_salt DescribeSnapshotSchedules' {Maybe Int
Maybe [Text]
Maybe Text
tagValues :: Maybe [Text]
tagKeys :: Maybe [Text]
scheduleIdentifier :: Maybe Text
maxRecords :: Maybe Int
marker :: Maybe Text
clusterIdentifier :: Maybe Text
$sel:tagValues:DescribeSnapshotSchedules' :: DescribeSnapshotSchedules -> Maybe [Text]
$sel:tagKeys:DescribeSnapshotSchedules' :: DescribeSnapshotSchedules -> Maybe [Text]
$sel:scheduleIdentifier:DescribeSnapshotSchedules' :: DescribeSnapshotSchedules -> Maybe Text
$sel:maxRecords:DescribeSnapshotSchedules' :: DescribeSnapshotSchedules -> Maybe Int
$sel:marker:DescribeSnapshotSchedules' :: DescribeSnapshotSchedules -> Maybe Text
$sel:clusterIdentifier:DescribeSnapshotSchedules' :: DescribeSnapshotSchedules -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
clusterIdentifier
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
marker
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
maxRecords
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
scheduleIdentifier
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
tagKeys
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
tagValues

instance Prelude.NFData DescribeSnapshotSchedules where
  rnf :: DescribeSnapshotSchedules -> ()
rnf DescribeSnapshotSchedules' {Maybe Int
Maybe [Text]
Maybe Text
tagValues :: Maybe [Text]
tagKeys :: Maybe [Text]
scheduleIdentifier :: Maybe Text
maxRecords :: Maybe Int
marker :: Maybe Text
clusterIdentifier :: Maybe Text
$sel:tagValues:DescribeSnapshotSchedules' :: DescribeSnapshotSchedules -> Maybe [Text]
$sel:tagKeys:DescribeSnapshotSchedules' :: DescribeSnapshotSchedules -> Maybe [Text]
$sel:scheduleIdentifier:DescribeSnapshotSchedules' :: DescribeSnapshotSchedules -> Maybe Text
$sel:maxRecords:DescribeSnapshotSchedules' :: DescribeSnapshotSchedules -> Maybe Int
$sel:marker:DescribeSnapshotSchedules' :: DescribeSnapshotSchedules -> Maybe Text
$sel:clusterIdentifier:DescribeSnapshotSchedules' :: DescribeSnapshotSchedules -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
clusterIdentifier
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
marker
      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
scheduleIdentifier
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
tagKeys
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
tagValues

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

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

instance Data.ToQuery DescribeSnapshotSchedules where
  toQuery :: DescribeSnapshotSchedules -> QueryString
toQuery DescribeSnapshotSchedules' {Maybe Int
Maybe [Text]
Maybe Text
tagValues :: Maybe [Text]
tagKeys :: Maybe [Text]
scheduleIdentifier :: Maybe Text
maxRecords :: Maybe Int
marker :: Maybe Text
clusterIdentifier :: Maybe Text
$sel:tagValues:DescribeSnapshotSchedules' :: DescribeSnapshotSchedules -> Maybe [Text]
$sel:tagKeys:DescribeSnapshotSchedules' :: DescribeSnapshotSchedules -> Maybe [Text]
$sel:scheduleIdentifier:DescribeSnapshotSchedules' :: DescribeSnapshotSchedules -> Maybe Text
$sel:maxRecords:DescribeSnapshotSchedules' :: DescribeSnapshotSchedules -> Maybe Int
$sel:marker:DescribeSnapshotSchedules' :: DescribeSnapshotSchedules -> Maybe Text
$sel:clusterIdentifier:DescribeSnapshotSchedules' :: DescribeSnapshotSchedules -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"DescribeSnapshotSchedules" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2012-12-01" :: Prelude.ByteString),
        ByteString
"ClusterIdentifier" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
clusterIdentifier,
        ByteString
"Marker" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
marker,
        ByteString
"MaxRecords" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Int
maxRecords,
        ByteString
"ScheduleIdentifier" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
scheduleIdentifier,
        ByteString
"TagKeys"
          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
"TagKey" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Text]
tagKeys),
        ByteString
"TagValues"
          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
"TagValue" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Text]
tagValues)
      ]

-- | /See:/ 'newDescribeSnapshotSchedulesResponse' smart constructor.
data DescribeSnapshotSchedulesResponse = DescribeSnapshotSchedulesResponse'
  { -- | A value that indicates the starting point for the next set of response
    -- records in a subsequent request. If a value is returned in a response,
    -- you can retrieve the next set of records by providing this returned
    -- marker value in the @marker@ parameter and retrying the command. If the
    -- @marker@ field is empty, all response records have been retrieved for
    -- the request.
    DescribeSnapshotSchedulesResponse -> Maybe Text
marker :: Prelude.Maybe Prelude.Text,
    -- | A list of SnapshotSchedules.
    DescribeSnapshotSchedulesResponse -> Maybe [SnapshotSchedule]
snapshotSchedules :: Prelude.Maybe [SnapshotSchedule],
    -- | The response's http status code.
    DescribeSnapshotSchedulesResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeSnapshotSchedulesResponse
-> DescribeSnapshotSchedulesResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeSnapshotSchedulesResponse
-> DescribeSnapshotSchedulesResponse -> Bool
$c/= :: DescribeSnapshotSchedulesResponse
-> DescribeSnapshotSchedulesResponse -> Bool
== :: DescribeSnapshotSchedulesResponse
-> DescribeSnapshotSchedulesResponse -> Bool
$c== :: DescribeSnapshotSchedulesResponse
-> DescribeSnapshotSchedulesResponse -> Bool
Prelude.Eq, ReadPrec [DescribeSnapshotSchedulesResponse]
ReadPrec DescribeSnapshotSchedulesResponse
Int -> ReadS DescribeSnapshotSchedulesResponse
ReadS [DescribeSnapshotSchedulesResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeSnapshotSchedulesResponse]
$creadListPrec :: ReadPrec [DescribeSnapshotSchedulesResponse]
readPrec :: ReadPrec DescribeSnapshotSchedulesResponse
$creadPrec :: ReadPrec DescribeSnapshotSchedulesResponse
readList :: ReadS [DescribeSnapshotSchedulesResponse]
$creadList :: ReadS [DescribeSnapshotSchedulesResponse]
readsPrec :: Int -> ReadS DescribeSnapshotSchedulesResponse
$creadsPrec :: Int -> ReadS DescribeSnapshotSchedulesResponse
Prelude.Read, Int -> DescribeSnapshotSchedulesResponse -> ShowS
[DescribeSnapshotSchedulesResponse] -> ShowS
DescribeSnapshotSchedulesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeSnapshotSchedulesResponse] -> ShowS
$cshowList :: [DescribeSnapshotSchedulesResponse] -> ShowS
show :: DescribeSnapshotSchedulesResponse -> String
$cshow :: DescribeSnapshotSchedulesResponse -> String
showsPrec :: Int -> DescribeSnapshotSchedulesResponse -> ShowS
$cshowsPrec :: Int -> DescribeSnapshotSchedulesResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeSnapshotSchedulesResponse x
-> DescribeSnapshotSchedulesResponse
forall x.
DescribeSnapshotSchedulesResponse
-> Rep DescribeSnapshotSchedulesResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeSnapshotSchedulesResponse x
-> DescribeSnapshotSchedulesResponse
$cfrom :: forall x.
DescribeSnapshotSchedulesResponse
-> Rep DescribeSnapshotSchedulesResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeSnapshotSchedulesResponse' 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:
--
-- 'marker', 'describeSnapshotSchedulesResponse_marker' - A value that indicates the starting point for the next set of response
-- records in a subsequent request. If a value is returned in a response,
-- you can retrieve the next set of records by providing this returned
-- marker value in the @marker@ parameter and retrying the command. If the
-- @marker@ field is empty, all response records have been retrieved for
-- the request.
--
-- 'snapshotSchedules', 'describeSnapshotSchedulesResponse_snapshotSchedules' - A list of SnapshotSchedules.
--
-- 'httpStatus', 'describeSnapshotSchedulesResponse_httpStatus' - The response's http status code.
newDescribeSnapshotSchedulesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeSnapshotSchedulesResponse
newDescribeSnapshotSchedulesResponse :: Int -> DescribeSnapshotSchedulesResponse
newDescribeSnapshotSchedulesResponse Int
pHttpStatus_ =
  DescribeSnapshotSchedulesResponse'
    { $sel:marker:DescribeSnapshotSchedulesResponse' :: Maybe Text
marker =
        forall a. Maybe a
Prelude.Nothing,
      $sel:snapshotSchedules:DescribeSnapshotSchedulesResponse' :: Maybe [SnapshotSchedule]
snapshotSchedules = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeSnapshotSchedulesResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A value that indicates the starting point for the next set of response
-- records in a subsequent request. If a value is returned in a response,
-- you can retrieve the next set of records by providing this returned
-- marker value in the @marker@ parameter and retrying the command. If the
-- @marker@ field is empty, all response records have been retrieved for
-- the request.
describeSnapshotSchedulesResponse_marker :: Lens.Lens' DescribeSnapshotSchedulesResponse (Prelude.Maybe Prelude.Text)
describeSnapshotSchedulesResponse_marker :: Lens' DescribeSnapshotSchedulesResponse (Maybe Text)
describeSnapshotSchedulesResponse_marker = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSnapshotSchedulesResponse' {Maybe Text
marker :: Maybe Text
$sel:marker:DescribeSnapshotSchedulesResponse' :: DescribeSnapshotSchedulesResponse -> Maybe Text
marker} -> Maybe Text
marker) (\s :: DescribeSnapshotSchedulesResponse
s@DescribeSnapshotSchedulesResponse' {} Maybe Text
a -> DescribeSnapshotSchedulesResponse
s {$sel:marker:DescribeSnapshotSchedulesResponse' :: Maybe Text
marker = Maybe Text
a} :: DescribeSnapshotSchedulesResponse)

-- | A list of SnapshotSchedules.
describeSnapshotSchedulesResponse_snapshotSchedules :: Lens.Lens' DescribeSnapshotSchedulesResponse (Prelude.Maybe [SnapshotSchedule])
describeSnapshotSchedulesResponse_snapshotSchedules :: Lens' DescribeSnapshotSchedulesResponse (Maybe [SnapshotSchedule])
describeSnapshotSchedulesResponse_snapshotSchedules = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSnapshotSchedulesResponse' {Maybe [SnapshotSchedule]
snapshotSchedules :: Maybe [SnapshotSchedule]
$sel:snapshotSchedules:DescribeSnapshotSchedulesResponse' :: DescribeSnapshotSchedulesResponse -> Maybe [SnapshotSchedule]
snapshotSchedules} -> Maybe [SnapshotSchedule]
snapshotSchedules) (\s :: DescribeSnapshotSchedulesResponse
s@DescribeSnapshotSchedulesResponse' {} Maybe [SnapshotSchedule]
a -> DescribeSnapshotSchedulesResponse
s {$sel:snapshotSchedules:DescribeSnapshotSchedulesResponse' :: Maybe [SnapshotSchedule]
snapshotSchedules = Maybe [SnapshotSchedule]
a} :: DescribeSnapshotSchedulesResponse) 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.
describeSnapshotSchedulesResponse_httpStatus :: Lens.Lens' DescribeSnapshotSchedulesResponse Prelude.Int
describeSnapshotSchedulesResponse_httpStatus :: Lens' DescribeSnapshotSchedulesResponse Int
describeSnapshotSchedulesResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeSnapshotSchedulesResponse' {Int
httpStatus :: Int
$sel:httpStatus:DescribeSnapshotSchedulesResponse' :: DescribeSnapshotSchedulesResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: DescribeSnapshotSchedulesResponse
s@DescribeSnapshotSchedulesResponse' {} Int
a -> DescribeSnapshotSchedulesResponse
s {$sel:httpStatus:DescribeSnapshotSchedulesResponse' :: Int
httpStatus = Int
a} :: DescribeSnapshotSchedulesResponse)

instance
  Prelude.NFData
    DescribeSnapshotSchedulesResponse
  where
  rnf :: DescribeSnapshotSchedulesResponse -> ()
rnf DescribeSnapshotSchedulesResponse' {Int
Maybe [SnapshotSchedule]
Maybe Text
httpStatus :: Int
snapshotSchedules :: Maybe [SnapshotSchedule]
marker :: Maybe Text
$sel:httpStatus:DescribeSnapshotSchedulesResponse' :: DescribeSnapshotSchedulesResponse -> Int
$sel:snapshotSchedules:DescribeSnapshotSchedulesResponse' :: DescribeSnapshotSchedulesResponse -> Maybe [SnapshotSchedule]
$sel:marker:DescribeSnapshotSchedulesResponse' :: DescribeSnapshotSchedulesResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
marker
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [SnapshotSchedule]
snapshotSchedules
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus