{-# 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.Backup.GetBackupSelection
-- 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 selection metadata and a document in JSON format that specifies
-- a list of resources that are associated with a backup plan.
module Amazonka.Backup.GetBackupSelection
  ( -- * Creating a Request
    GetBackupSelection (..),
    newGetBackupSelection,

    -- * Request Lenses
    getBackupSelection_backupPlanId,
    getBackupSelection_selectionId,

    -- * Destructuring the Response
    GetBackupSelectionResponse (..),
    newGetBackupSelectionResponse,

    -- * Response Lenses
    getBackupSelectionResponse_backupPlanId,
    getBackupSelectionResponse_backupSelection,
    getBackupSelectionResponse_creationDate,
    getBackupSelectionResponse_creatorRequestId,
    getBackupSelectionResponse_selectionId,
    getBackupSelectionResponse_httpStatus,
  )
where

import Amazonka.Backup.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:/ 'newGetBackupSelection' smart constructor.
data GetBackupSelection = GetBackupSelection'
  { -- | Uniquely identifies a backup plan.
    GetBackupSelection -> Text
backupPlanId :: Prelude.Text,
    -- | Uniquely identifies the body of a request to assign a set of resources
    -- to a backup plan.
    GetBackupSelection -> Text
selectionId :: Prelude.Text
  }
  deriving (GetBackupSelection -> GetBackupSelection -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetBackupSelection -> GetBackupSelection -> Bool
$c/= :: GetBackupSelection -> GetBackupSelection -> Bool
== :: GetBackupSelection -> GetBackupSelection -> Bool
$c== :: GetBackupSelection -> GetBackupSelection -> Bool
Prelude.Eq, ReadPrec [GetBackupSelection]
ReadPrec GetBackupSelection
Int -> ReadS GetBackupSelection
ReadS [GetBackupSelection]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetBackupSelection]
$creadListPrec :: ReadPrec [GetBackupSelection]
readPrec :: ReadPrec GetBackupSelection
$creadPrec :: ReadPrec GetBackupSelection
readList :: ReadS [GetBackupSelection]
$creadList :: ReadS [GetBackupSelection]
readsPrec :: Int -> ReadS GetBackupSelection
$creadsPrec :: Int -> ReadS GetBackupSelection
Prelude.Read, Int -> GetBackupSelection -> ShowS
[GetBackupSelection] -> ShowS
GetBackupSelection -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetBackupSelection] -> ShowS
$cshowList :: [GetBackupSelection] -> ShowS
show :: GetBackupSelection -> String
$cshow :: GetBackupSelection -> String
showsPrec :: Int -> GetBackupSelection -> ShowS
$cshowsPrec :: Int -> GetBackupSelection -> ShowS
Prelude.Show, forall x. Rep GetBackupSelection x -> GetBackupSelection
forall x. GetBackupSelection -> Rep GetBackupSelection x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetBackupSelection x -> GetBackupSelection
$cfrom :: forall x. GetBackupSelection -> Rep GetBackupSelection x
Prelude.Generic)

-- |
-- Create a value of 'GetBackupSelection' 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:
--
-- 'backupPlanId', 'getBackupSelection_backupPlanId' - Uniquely identifies a backup plan.
--
-- 'selectionId', 'getBackupSelection_selectionId' - Uniquely identifies the body of a request to assign a set of resources
-- to a backup plan.
newGetBackupSelection ::
  -- | 'backupPlanId'
  Prelude.Text ->
  -- | 'selectionId'
  Prelude.Text ->
  GetBackupSelection
newGetBackupSelection :: Text -> Text -> GetBackupSelection
newGetBackupSelection Text
pBackupPlanId_ Text
pSelectionId_ =
  GetBackupSelection'
    { $sel:backupPlanId:GetBackupSelection' :: Text
backupPlanId = Text
pBackupPlanId_,
      $sel:selectionId:GetBackupSelection' :: Text
selectionId = Text
pSelectionId_
    }

-- | Uniquely identifies a backup plan.
getBackupSelection_backupPlanId :: Lens.Lens' GetBackupSelection Prelude.Text
getBackupSelection_backupPlanId :: Lens' GetBackupSelection Text
getBackupSelection_backupPlanId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBackupSelection' {Text
backupPlanId :: Text
$sel:backupPlanId:GetBackupSelection' :: GetBackupSelection -> Text
backupPlanId} -> Text
backupPlanId) (\s :: GetBackupSelection
s@GetBackupSelection' {} Text
a -> GetBackupSelection
s {$sel:backupPlanId:GetBackupSelection' :: Text
backupPlanId = Text
a} :: GetBackupSelection)

-- | Uniquely identifies the body of a request to assign a set of resources
-- to a backup plan.
getBackupSelection_selectionId :: Lens.Lens' GetBackupSelection Prelude.Text
getBackupSelection_selectionId :: Lens' GetBackupSelection Text
getBackupSelection_selectionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBackupSelection' {Text
selectionId :: Text
$sel:selectionId:GetBackupSelection' :: GetBackupSelection -> Text
selectionId} -> Text
selectionId) (\s :: GetBackupSelection
s@GetBackupSelection' {} Text
a -> GetBackupSelection
s {$sel:selectionId:GetBackupSelection' :: Text
selectionId = Text
a} :: GetBackupSelection)

instance Core.AWSRequest GetBackupSelection where
  type
    AWSResponse GetBackupSelection =
      GetBackupSelectionResponse
  request :: (Service -> Service)
-> GetBackupSelection -> Request GetBackupSelection
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.get (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy GetBackupSelection
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetBackupSelection)))
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 Text
-> Maybe BackupSelection
-> Maybe POSIX
-> Maybe Text
-> Maybe Text
-> Int
-> GetBackupSelectionResponse
GetBackupSelectionResponse'
            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
"BackupPlanId")
            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
"BackupSelection")
            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
"CreationDate")
            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
"CreatorRequestId")
            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
"SelectionId")
            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 GetBackupSelection where
  hashWithSalt :: Int -> GetBackupSelection -> Int
hashWithSalt Int
_salt GetBackupSelection' {Text
selectionId :: Text
backupPlanId :: Text
$sel:selectionId:GetBackupSelection' :: GetBackupSelection -> Text
$sel:backupPlanId:GetBackupSelection' :: GetBackupSelection -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
backupPlanId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
selectionId

instance Prelude.NFData GetBackupSelection where
  rnf :: GetBackupSelection -> ()
rnf GetBackupSelection' {Text
selectionId :: Text
backupPlanId :: Text
$sel:selectionId:GetBackupSelection' :: GetBackupSelection -> Text
$sel:backupPlanId:GetBackupSelection' :: GetBackupSelection -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
backupPlanId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
selectionId

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

instance Data.ToPath GetBackupSelection where
  toPath :: GetBackupSelection -> ByteString
toPath GetBackupSelection' {Text
selectionId :: Text
backupPlanId :: Text
$sel:selectionId:GetBackupSelection' :: GetBackupSelection -> Text
$sel:backupPlanId:GetBackupSelection' :: GetBackupSelection -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/backup/plans/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
backupPlanId,
        ByteString
"/selections/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
selectionId
      ]

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

-- | /See:/ 'newGetBackupSelectionResponse' smart constructor.
data GetBackupSelectionResponse = GetBackupSelectionResponse'
  { -- | Uniquely identifies a backup plan.
    GetBackupSelectionResponse -> Maybe Text
backupPlanId :: Prelude.Maybe Prelude.Text,
    -- | Specifies the body of a request to assign a set of resources to a backup
    -- plan.
    GetBackupSelectionResponse -> Maybe BackupSelection
backupSelection :: Prelude.Maybe BackupSelection,
    -- | The date and time a backup selection is created, in Unix format and
    -- Coordinated Universal Time (UTC). The value of @CreationDate@ is
    -- accurate to milliseconds. For example, the value 1516925490.087
    -- represents Friday, January 26, 2018 12:11:30.087 AM.
    GetBackupSelectionResponse -> Maybe POSIX
creationDate :: Prelude.Maybe Data.POSIX,
    -- | A unique string that identifies the request and allows failed requests
    -- to be retried without the risk of running the operation twice.
    GetBackupSelectionResponse -> Maybe Text
creatorRequestId :: Prelude.Maybe Prelude.Text,
    -- | Uniquely identifies the body of a request to assign a set of resources
    -- to a backup plan.
    GetBackupSelectionResponse -> Maybe Text
selectionId :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    GetBackupSelectionResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetBackupSelectionResponse -> GetBackupSelectionResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetBackupSelectionResponse -> GetBackupSelectionResponse -> Bool
$c/= :: GetBackupSelectionResponse -> GetBackupSelectionResponse -> Bool
== :: GetBackupSelectionResponse -> GetBackupSelectionResponse -> Bool
$c== :: GetBackupSelectionResponse -> GetBackupSelectionResponse -> Bool
Prelude.Eq, ReadPrec [GetBackupSelectionResponse]
ReadPrec GetBackupSelectionResponse
Int -> ReadS GetBackupSelectionResponse
ReadS [GetBackupSelectionResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetBackupSelectionResponse]
$creadListPrec :: ReadPrec [GetBackupSelectionResponse]
readPrec :: ReadPrec GetBackupSelectionResponse
$creadPrec :: ReadPrec GetBackupSelectionResponse
readList :: ReadS [GetBackupSelectionResponse]
$creadList :: ReadS [GetBackupSelectionResponse]
readsPrec :: Int -> ReadS GetBackupSelectionResponse
$creadsPrec :: Int -> ReadS GetBackupSelectionResponse
Prelude.Read, Int -> GetBackupSelectionResponse -> ShowS
[GetBackupSelectionResponse] -> ShowS
GetBackupSelectionResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetBackupSelectionResponse] -> ShowS
$cshowList :: [GetBackupSelectionResponse] -> ShowS
show :: GetBackupSelectionResponse -> String
$cshow :: GetBackupSelectionResponse -> String
showsPrec :: Int -> GetBackupSelectionResponse -> ShowS
$cshowsPrec :: Int -> GetBackupSelectionResponse -> ShowS
Prelude.Show, forall x.
Rep GetBackupSelectionResponse x -> GetBackupSelectionResponse
forall x.
GetBackupSelectionResponse -> Rep GetBackupSelectionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetBackupSelectionResponse x -> GetBackupSelectionResponse
$cfrom :: forall x.
GetBackupSelectionResponse -> Rep GetBackupSelectionResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetBackupSelectionResponse' 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:
--
-- 'backupPlanId', 'getBackupSelectionResponse_backupPlanId' - Uniquely identifies a backup plan.
--
-- 'backupSelection', 'getBackupSelectionResponse_backupSelection' - Specifies the body of a request to assign a set of resources to a backup
-- plan.
--
-- 'creationDate', 'getBackupSelectionResponse_creationDate' - The date and time a backup selection is created, in Unix format and
-- Coordinated Universal Time (UTC). The value of @CreationDate@ is
-- accurate to milliseconds. For example, the value 1516925490.087
-- represents Friday, January 26, 2018 12:11:30.087 AM.
--
-- 'creatorRequestId', 'getBackupSelectionResponse_creatorRequestId' - A unique string that identifies the request and allows failed requests
-- to be retried without the risk of running the operation twice.
--
-- 'selectionId', 'getBackupSelectionResponse_selectionId' - Uniquely identifies the body of a request to assign a set of resources
-- to a backup plan.
--
-- 'httpStatus', 'getBackupSelectionResponse_httpStatus' - The response's http status code.
newGetBackupSelectionResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetBackupSelectionResponse
newGetBackupSelectionResponse :: Int -> GetBackupSelectionResponse
newGetBackupSelectionResponse Int
pHttpStatus_ =
  GetBackupSelectionResponse'
    { $sel:backupPlanId:GetBackupSelectionResponse' :: Maybe Text
backupPlanId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:backupSelection:GetBackupSelectionResponse' :: Maybe BackupSelection
backupSelection = forall a. Maybe a
Prelude.Nothing,
      $sel:creationDate:GetBackupSelectionResponse' :: Maybe POSIX
creationDate = forall a. Maybe a
Prelude.Nothing,
      $sel:creatorRequestId:GetBackupSelectionResponse' :: Maybe Text
creatorRequestId = forall a. Maybe a
Prelude.Nothing,
      $sel:selectionId:GetBackupSelectionResponse' :: Maybe Text
selectionId = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetBackupSelectionResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Uniquely identifies a backup plan.
getBackupSelectionResponse_backupPlanId :: Lens.Lens' GetBackupSelectionResponse (Prelude.Maybe Prelude.Text)
getBackupSelectionResponse_backupPlanId :: Lens' GetBackupSelectionResponse (Maybe Text)
getBackupSelectionResponse_backupPlanId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBackupSelectionResponse' {Maybe Text
backupPlanId :: Maybe Text
$sel:backupPlanId:GetBackupSelectionResponse' :: GetBackupSelectionResponse -> Maybe Text
backupPlanId} -> Maybe Text
backupPlanId) (\s :: GetBackupSelectionResponse
s@GetBackupSelectionResponse' {} Maybe Text
a -> GetBackupSelectionResponse
s {$sel:backupPlanId:GetBackupSelectionResponse' :: Maybe Text
backupPlanId = Maybe Text
a} :: GetBackupSelectionResponse)

-- | Specifies the body of a request to assign a set of resources to a backup
-- plan.
getBackupSelectionResponse_backupSelection :: Lens.Lens' GetBackupSelectionResponse (Prelude.Maybe BackupSelection)
getBackupSelectionResponse_backupSelection :: Lens' GetBackupSelectionResponse (Maybe BackupSelection)
getBackupSelectionResponse_backupSelection = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBackupSelectionResponse' {Maybe BackupSelection
backupSelection :: Maybe BackupSelection
$sel:backupSelection:GetBackupSelectionResponse' :: GetBackupSelectionResponse -> Maybe BackupSelection
backupSelection} -> Maybe BackupSelection
backupSelection) (\s :: GetBackupSelectionResponse
s@GetBackupSelectionResponse' {} Maybe BackupSelection
a -> GetBackupSelectionResponse
s {$sel:backupSelection:GetBackupSelectionResponse' :: Maybe BackupSelection
backupSelection = Maybe BackupSelection
a} :: GetBackupSelectionResponse)

-- | The date and time a backup selection is created, in Unix format and
-- Coordinated Universal Time (UTC). The value of @CreationDate@ is
-- accurate to milliseconds. For example, the value 1516925490.087
-- represents Friday, January 26, 2018 12:11:30.087 AM.
getBackupSelectionResponse_creationDate :: Lens.Lens' GetBackupSelectionResponse (Prelude.Maybe Prelude.UTCTime)
getBackupSelectionResponse_creationDate :: Lens' GetBackupSelectionResponse (Maybe UTCTime)
getBackupSelectionResponse_creationDate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBackupSelectionResponse' {Maybe POSIX
creationDate :: Maybe POSIX
$sel:creationDate:GetBackupSelectionResponse' :: GetBackupSelectionResponse -> Maybe POSIX
creationDate} -> Maybe POSIX
creationDate) (\s :: GetBackupSelectionResponse
s@GetBackupSelectionResponse' {} Maybe POSIX
a -> GetBackupSelectionResponse
s {$sel:creationDate:GetBackupSelectionResponse' :: Maybe POSIX
creationDate = Maybe POSIX
a} :: GetBackupSelectionResponse) 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

-- | A unique string that identifies the request and allows failed requests
-- to be retried without the risk of running the operation twice.
getBackupSelectionResponse_creatorRequestId :: Lens.Lens' GetBackupSelectionResponse (Prelude.Maybe Prelude.Text)
getBackupSelectionResponse_creatorRequestId :: Lens' GetBackupSelectionResponse (Maybe Text)
getBackupSelectionResponse_creatorRequestId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBackupSelectionResponse' {Maybe Text
creatorRequestId :: Maybe Text
$sel:creatorRequestId:GetBackupSelectionResponse' :: GetBackupSelectionResponse -> Maybe Text
creatorRequestId} -> Maybe Text
creatorRequestId) (\s :: GetBackupSelectionResponse
s@GetBackupSelectionResponse' {} Maybe Text
a -> GetBackupSelectionResponse
s {$sel:creatorRequestId:GetBackupSelectionResponse' :: Maybe Text
creatorRequestId = Maybe Text
a} :: GetBackupSelectionResponse)

-- | Uniquely identifies the body of a request to assign a set of resources
-- to a backup plan.
getBackupSelectionResponse_selectionId :: Lens.Lens' GetBackupSelectionResponse (Prelude.Maybe Prelude.Text)
getBackupSelectionResponse_selectionId :: Lens' GetBackupSelectionResponse (Maybe Text)
getBackupSelectionResponse_selectionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBackupSelectionResponse' {Maybe Text
selectionId :: Maybe Text
$sel:selectionId:GetBackupSelectionResponse' :: GetBackupSelectionResponse -> Maybe Text
selectionId} -> Maybe Text
selectionId) (\s :: GetBackupSelectionResponse
s@GetBackupSelectionResponse' {} Maybe Text
a -> GetBackupSelectionResponse
s {$sel:selectionId:GetBackupSelectionResponse' :: Maybe Text
selectionId = Maybe Text
a} :: GetBackupSelectionResponse)

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

instance Prelude.NFData GetBackupSelectionResponse where
  rnf :: GetBackupSelectionResponse -> ()
rnf GetBackupSelectionResponse' {Int
Maybe Text
Maybe POSIX
Maybe BackupSelection
httpStatus :: Int
selectionId :: Maybe Text
creatorRequestId :: Maybe Text
creationDate :: Maybe POSIX
backupSelection :: Maybe BackupSelection
backupPlanId :: Maybe Text
$sel:httpStatus:GetBackupSelectionResponse' :: GetBackupSelectionResponse -> Int
$sel:selectionId:GetBackupSelectionResponse' :: GetBackupSelectionResponse -> Maybe Text
$sel:creatorRequestId:GetBackupSelectionResponse' :: GetBackupSelectionResponse -> Maybe Text
$sel:creationDate:GetBackupSelectionResponse' :: GetBackupSelectionResponse -> Maybe POSIX
$sel:backupSelection:GetBackupSelectionResponse' :: GetBackupSelectionResponse -> Maybe BackupSelection
$sel:backupPlanId:GetBackupSelectionResponse' :: GetBackupSelectionResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
backupPlanId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe BackupSelection
backupSelection
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
creationDate
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
creatorRequestId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
selectionId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus