{-# 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.CloudHSMV2.DescribeBackups
-- 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 backups of AWS CloudHSM clusters.
--
-- This is a paginated operation, which means that each response might
-- contain only a subset of all the backups. When the response contains
-- only a subset of backups, it includes a @NextToken@ value. Use this
-- value in a subsequent @DescribeBackups@ request to get more backups.
-- When you receive a response with no @NextToken@ (or an empty or null
-- value), that means there are no more backups to get.
--
-- This operation returns paginated results.
module Amazonka.CloudHSMV2.DescribeBackups
  ( -- * Creating a Request
    DescribeBackups (..),
    newDescribeBackups,

    -- * Request Lenses
    describeBackups_filters,
    describeBackups_maxResults,
    describeBackups_nextToken,
    describeBackups_sortAscending,

    -- * Destructuring the Response
    DescribeBackupsResponse (..),
    newDescribeBackupsResponse,

    -- * Response Lenses
    describeBackupsResponse_backups,
    describeBackupsResponse_nextToken,
    describeBackupsResponse_httpStatus,
  )
where

import Amazonka.CloudHSMV2.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:/ 'newDescribeBackups' smart constructor.
data DescribeBackups = DescribeBackups'
  { -- | One or more filters to limit the items returned in the response.
    --
    -- Use the @backupIds@ filter to return only the specified backups. Specify
    -- backups by their backup identifier (ID).
    --
    -- Use the @sourceBackupIds@ filter to return only the backups created from
    -- a source backup. The @sourceBackupID@ of a source backup is returned by
    -- the CopyBackupToRegion operation.
    --
    -- Use the @clusterIds@ filter to return only the backups for the specified
    -- clusters. Specify clusters by their cluster identifier (ID).
    --
    -- Use the @states@ filter to return only backups that match the specified
    -- state.
    --
    -- Use the @neverExpires@ filter to return backups filtered by the value in
    -- the @neverExpires@ parameter. @True@ returns all backups exempt from the
    -- backup retention policy. @False@ returns all backups with a backup
    -- retention policy defined at the cluster.
    DescribeBackups -> Maybe (HashMap Text [Text])
filters :: Prelude.Maybe (Prelude.HashMap Prelude.Text [Prelude.Text]),
    -- | The maximum number of backups to return in the response. When there are
    -- more backups than the number you specify, the response contains a
    -- @NextToken@ value.
    DescribeBackups -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | The @NextToken@ value that you received in the previous response. Use
    -- this value to get more backups.
    DescribeBackups -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | Designates whether or not to sort the return backups by ascending
    -- chronological order of generation.
    DescribeBackups -> Maybe Bool
sortAscending :: Prelude.Maybe Prelude.Bool
  }
  deriving (DescribeBackups -> DescribeBackups -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeBackups -> DescribeBackups -> Bool
$c/= :: DescribeBackups -> DescribeBackups -> Bool
== :: DescribeBackups -> DescribeBackups -> Bool
$c== :: DescribeBackups -> DescribeBackups -> Bool
Prelude.Eq, ReadPrec [DescribeBackups]
ReadPrec DescribeBackups
Int -> ReadS DescribeBackups
ReadS [DescribeBackups]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeBackups]
$creadListPrec :: ReadPrec [DescribeBackups]
readPrec :: ReadPrec DescribeBackups
$creadPrec :: ReadPrec DescribeBackups
readList :: ReadS [DescribeBackups]
$creadList :: ReadS [DescribeBackups]
readsPrec :: Int -> ReadS DescribeBackups
$creadsPrec :: Int -> ReadS DescribeBackups
Prelude.Read, Int -> DescribeBackups -> ShowS
[DescribeBackups] -> ShowS
DescribeBackups -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeBackups] -> ShowS
$cshowList :: [DescribeBackups] -> ShowS
show :: DescribeBackups -> String
$cshow :: DescribeBackups -> String
showsPrec :: Int -> DescribeBackups -> ShowS
$cshowsPrec :: Int -> DescribeBackups -> ShowS
Prelude.Show, forall x. Rep DescribeBackups x -> DescribeBackups
forall x. DescribeBackups -> Rep DescribeBackups x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeBackups x -> DescribeBackups
$cfrom :: forall x. DescribeBackups -> Rep DescribeBackups x
Prelude.Generic)

-- |
-- Create a value of 'DescribeBackups' 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:
--
-- 'filters', 'describeBackups_filters' - One or more filters to limit the items returned in the response.
--
-- Use the @backupIds@ filter to return only the specified backups. Specify
-- backups by their backup identifier (ID).
--
-- Use the @sourceBackupIds@ filter to return only the backups created from
-- a source backup. The @sourceBackupID@ of a source backup is returned by
-- the CopyBackupToRegion operation.
--
-- Use the @clusterIds@ filter to return only the backups for the specified
-- clusters. Specify clusters by their cluster identifier (ID).
--
-- Use the @states@ filter to return only backups that match the specified
-- state.
--
-- Use the @neverExpires@ filter to return backups filtered by the value in
-- the @neverExpires@ parameter. @True@ returns all backups exempt from the
-- backup retention policy. @False@ returns all backups with a backup
-- retention policy defined at the cluster.
--
-- 'maxResults', 'describeBackups_maxResults' - The maximum number of backups to return in the response. When there are
-- more backups than the number you specify, the response contains a
-- @NextToken@ value.
--
-- 'nextToken', 'describeBackups_nextToken' - The @NextToken@ value that you received in the previous response. Use
-- this value to get more backups.
--
-- 'sortAscending', 'describeBackups_sortAscending' - Designates whether or not to sort the return backups by ascending
-- chronological order of generation.
newDescribeBackups ::
  DescribeBackups
newDescribeBackups :: DescribeBackups
newDescribeBackups =
  DescribeBackups'
    { $sel:filters:DescribeBackups' :: Maybe (HashMap Text [Text])
filters = forall a. Maybe a
Prelude.Nothing,
      $sel:maxResults:DescribeBackups' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:DescribeBackups' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:sortAscending:DescribeBackups' :: Maybe Bool
sortAscending = forall a. Maybe a
Prelude.Nothing
    }

-- | One or more filters to limit the items returned in the response.
--
-- Use the @backupIds@ filter to return only the specified backups. Specify
-- backups by their backup identifier (ID).
--
-- Use the @sourceBackupIds@ filter to return only the backups created from
-- a source backup. The @sourceBackupID@ of a source backup is returned by
-- the CopyBackupToRegion operation.
--
-- Use the @clusterIds@ filter to return only the backups for the specified
-- clusters. Specify clusters by their cluster identifier (ID).
--
-- Use the @states@ filter to return only backups that match the specified
-- state.
--
-- Use the @neverExpires@ filter to return backups filtered by the value in
-- the @neverExpires@ parameter. @True@ returns all backups exempt from the
-- backup retention policy. @False@ returns all backups with a backup
-- retention policy defined at the cluster.
describeBackups_filters :: Lens.Lens' DescribeBackups (Prelude.Maybe (Prelude.HashMap Prelude.Text [Prelude.Text]))
describeBackups_filters :: Lens' DescribeBackups (Maybe (HashMap Text [Text]))
describeBackups_filters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeBackups' {Maybe (HashMap Text [Text])
filters :: Maybe (HashMap Text [Text])
$sel:filters:DescribeBackups' :: DescribeBackups -> Maybe (HashMap Text [Text])
filters} -> Maybe (HashMap Text [Text])
filters) (\s :: DescribeBackups
s@DescribeBackups' {} Maybe (HashMap Text [Text])
a -> DescribeBackups
s {$sel:filters:DescribeBackups' :: Maybe (HashMap Text [Text])
filters = Maybe (HashMap Text [Text])
a} :: DescribeBackups) 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 maximum number of backups to return in the response. When there are
-- more backups than the number you specify, the response contains a
-- @NextToken@ value.
describeBackups_maxResults :: Lens.Lens' DescribeBackups (Prelude.Maybe Prelude.Natural)
describeBackups_maxResults :: Lens' DescribeBackups (Maybe Natural)
describeBackups_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeBackups' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:DescribeBackups' :: DescribeBackups -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: DescribeBackups
s@DescribeBackups' {} Maybe Natural
a -> DescribeBackups
s {$sel:maxResults:DescribeBackups' :: Maybe Natural
maxResults = Maybe Natural
a} :: DescribeBackups)

-- | The @NextToken@ value that you received in the previous response. Use
-- this value to get more backups.
describeBackups_nextToken :: Lens.Lens' DescribeBackups (Prelude.Maybe Prelude.Text)
describeBackups_nextToken :: Lens' DescribeBackups (Maybe Text)
describeBackups_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeBackups' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:DescribeBackups' :: DescribeBackups -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: DescribeBackups
s@DescribeBackups' {} Maybe Text
a -> DescribeBackups
s {$sel:nextToken:DescribeBackups' :: Maybe Text
nextToken = Maybe Text
a} :: DescribeBackups)

-- | Designates whether or not to sort the return backups by ascending
-- chronological order of generation.
describeBackups_sortAscending :: Lens.Lens' DescribeBackups (Prelude.Maybe Prelude.Bool)
describeBackups_sortAscending :: Lens' DescribeBackups (Maybe Bool)
describeBackups_sortAscending = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeBackups' {Maybe Bool
sortAscending :: Maybe Bool
$sel:sortAscending:DescribeBackups' :: DescribeBackups -> Maybe Bool
sortAscending} -> Maybe Bool
sortAscending) (\s :: DescribeBackups
s@DescribeBackups' {} Maybe Bool
a -> DescribeBackups
s {$sel:sortAscending:DescribeBackups' :: Maybe Bool
sortAscending = Maybe Bool
a} :: DescribeBackups)

instance Core.AWSPager DescribeBackups where
  page :: DescribeBackups
-> AWSResponse DescribeBackups -> Maybe DescribeBackups
page DescribeBackups
rq AWSResponse DescribeBackups
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse DescribeBackups
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' DescribeBackupsResponse (Maybe Text)
describeBackupsResponse_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 DescribeBackups
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' DescribeBackupsResponse (Maybe [Backup])
describeBackupsResponse_backups
            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.$ DescribeBackups
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' DescribeBackups (Maybe Text)
describeBackups_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse DescribeBackups
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' DescribeBackupsResponse (Maybe Text)
describeBackupsResponse_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 DescribeBackups where
  type
    AWSResponse DescribeBackups =
      DescribeBackupsResponse
  request :: (Service -> Service) -> DescribeBackups -> Request DescribeBackups
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DescribeBackups
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DescribeBackups)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe [Backup] -> Maybe Text -> Int -> DescribeBackupsResponse
DescribeBackupsResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"Backups" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"NextToken")
            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 DescribeBackups where
  hashWithSalt :: Int -> DescribeBackups -> Int
hashWithSalt Int
_salt DescribeBackups' {Maybe Bool
Maybe Natural
Maybe Text
Maybe (HashMap Text [Text])
sortAscending :: Maybe Bool
nextToken :: Maybe Text
maxResults :: Maybe Natural
filters :: Maybe (HashMap Text [Text])
$sel:sortAscending:DescribeBackups' :: DescribeBackups -> Maybe Bool
$sel:nextToken:DescribeBackups' :: DescribeBackups -> Maybe Text
$sel:maxResults:DescribeBackups' :: DescribeBackups -> Maybe Natural
$sel:filters:DescribeBackups' :: DescribeBackups -> Maybe (HashMap Text [Text])
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text [Text])
filters
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maxResults
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
sortAscending

instance Prelude.NFData DescribeBackups where
  rnf :: DescribeBackups -> ()
rnf DescribeBackups' {Maybe Bool
Maybe Natural
Maybe Text
Maybe (HashMap Text [Text])
sortAscending :: Maybe Bool
nextToken :: Maybe Text
maxResults :: Maybe Natural
filters :: Maybe (HashMap Text [Text])
$sel:sortAscending:DescribeBackups' :: DescribeBackups -> Maybe Bool
$sel:nextToken:DescribeBackups' :: DescribeBackups -> Maybe Text
$sel:maxResults:DescribeBackups' :: DescribeBackups -> Maybe Natural
$sel:filters:DescribeBackups' :: DescribeBackups -> Maybe (HashMap Text [Text])
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text [Text])
filters
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
maxResults
      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 Bool
sortAscending

instance Data.ToHeaders DescribeBackups where
  toHeaders :: DescribeBackups -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"BaldrApiService.DescribeBackups" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON DescribeBackups where
  toJSON :: DescribeBackups -> Value
toJSON DescribeBackups' {Maybe Bool
Maybe Natural
Maybe Text
Maybe (HashMap Text [Text])
sortAscending :: Maybe Bool
nextToken :: Maybe Text
maxResults :: Maybe Natural
filters :: Maybe (HashMap Text [Text])
$sel:sortAscending:DescribeBackups' :: DescribeBackups -> Maybe Bool
$sel:nextToken:DescribeBackups' :: DescribeBackups -> Maybe Text
$sel:maxResults:DescribeBackups' :: DescribeBackups -> Maybe Natural
$sel:filters:DescribeBackups' :: DescribeBackups -> Maybe (HashMap Text [Text])
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Filters" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (HashMap Text [Text])
filters,
            (Key
"MaxResults" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Natural
maxResults,
            (Key
"NextToken" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
nextToken,
            (Key
"SortAscending" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Bool
sortAscending
          ]
      )

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

instance Data.ToQuery DescribeBackups where
  toQuery :: DescribeBackups -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | /See:/ 'newDescribeBackupsResponse' smart constructor.
data DescribeBackupsResponse = DescribeBackupsResponse'
  { -- | A list of backups.
    DescribeBackupsResponse -> Maybe [Backup]
backups :: Prelude.Maybe [Backup],
    -- | An opaque string that indicates that the response contains only a subset
    -- of backups. Use this value in a subsequent @DescribeBackups@ request to
    -- get more backups.
    DescribeBackupsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    DescribeBackupsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeBackupsResponse -> DescribeBackupsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeBackupsResponse -> DescribeBackupsResponse -> Bool
$c/= :: DescribeBackupsResponse -> DescribeBackupsResponse -> Bool
== :: DescribeBackupsResponse -> DescribeBackupsResponse -> Bool
$c== :: DescribeBackupsResponse -> DescribeBackupsResponse -> Bool
Prelude.Eq, ReadPrec [DescribeBackupsResponse]
ReadPrec DescribeBackupsResponse
Int -> ReadS DescribeBackupsResponse
ReadS [DescribeBackupsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeBackupsResponse]
$creadListPrec :: ReadPrec [DescribeBackupsResponse]
readPrec :: ReadPrec DescribeBackupsResponse
$creadPrec :: ReadPrec DescribeBackupsResponse
readList :: ReadS [DescribeBackupsResponse]
$creadList :: ReadS [DescribeBackupsResponse]
readsPrec :: Int -> ReadS DescribeBackupsResponse
$creadsPrec :: Int -> ReadS DescribeBackupsResponse
Prelude.Read, Int -> DescribeBackupsResponse -> ShowS
[DescribeBackupsResponse] -> ShowS
DescribeBackupsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeBackupsResponse] -> ShowS
$cshowList :: [DescribeBackupsResponse] -> ShowS
show :: DescribeBackupsResponse -> String
$cshow :: DescribeBackupsResponse -> String
showsPrec :: Int -> DescribeBackupsResponse -> ShowS
$cshowsPrec :: Int -> DescribeBackupsResponse -> ShowS
Prelude.Show, forall x. Rep DescribeBackupsResponse x -> DescribeBackupsResponse
forall x. DescribeBackupsResponse -> Rep DescribeBackupsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeBackupsResponse x -> DescribeBackupsResponse
$cfrom :: forall x. DescribeBackupsResponse -> Rep DescribeBackupsResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeBackupsResponse' 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:
--
-- 'backups', 'describeBackupsResponse_backups' - A list of backups.
--
-- 'nextToken', 'describeBackupsResponse_nextToken' - An opaque string that indicates that the response contains only a subset
-- of backups. Use this value in a subsequent @DescribeBackups@ request to
-- get more backups.
--
-- 'httpStatus', 'describeBackupsResponse_httpStatus' - The response's http status code.
newDescribeBackupsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeBackupsResponse
newDescribeBackupsResponse :: Int -> DescribeBackupsResponse
newDescribeBackupsResponse Int
pHttpStatus_ =
  DescribeBackupsResponse'
    { $sel:backups:DescribeBackupsResponse' :: Maybe [Backup]
backups = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:DescribeBackupsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeBackupsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A list of backups.
describeBackupsResponse_backups :: Lens.Lens' DescribeBackupsResponse (Prelude.Maybe [Backup])
describeBackupsResponse_backups :: Lens' DescribeBackupsResponse (Maybe [Backup])
describeBackupsResponse_backups = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeBackupsResponse' {Maybe [Backup]
backups :: Maybe [Backup]
$sel:backups:DescribeBackupsResponse' :: DescribeBackupsResponse -> Maybe [Backup]
backups} -> Maybe [Backup]
backups) (\s :: DescribeBackupsResponse
s@DescribeBackupsResponse' {} Maybe [Backup]
a -> DescribeBackupsResponse
s {$sel:backups:DescribeBackupsResponse' :: Maybe [Backup]
backups = Maybe [Backup]
a} :: DescribeBackupsResponse) 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

-- | An opaque string that indicates that the response contains only a subset
-- of backups. Use this value in a subsequent @DescribeBackups@ request to
-- get more backups.
describeBackupsResponse_nextToken :: Lens.Lens' DescribeBackupsResponse (Prelude.Maybe Prelude.Text)
describeBackupsResponse_nextToken :: Lens' DescribeBackupsResponse (Maybe Text)
describeBackupsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeBackupsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:DescribeBackupsResponse' :: DescribeBackupsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: DescribeBackupsResponse
s@DescribeBackupsResponse' {} Maybe Text
a -> DescribeBackupsResponse
s {$sel:nextToken:DescribeBackupsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: DescribeBackupsResponse)

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

instance Prelude.NFData DescribeBackupsResponse where
  rnf :: DescribeBackupsResponse -> ()
rnf DescribeBackupsResponse' {Int
Maybe [Backup]
Maybe Text
httpStatus :: Int
nextToken :: Maybe Text
backups :: Maybe [Backup]
$sel:httpStatus:DescribeBackupsResponse' :: DescribeBackupsResponse -> Int
$sel:nextToken:DescribeBackupsResponse' :: DescribeBackupsResponse -> Maybe Text
$sel:backups:DescribeBackupsResponse' :: DescribeBackupsResponse -> Maybe [Backup]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Backup]
backups
      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 Int
httpStatus