{-# 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.FSx.CreateBackup
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Creates a backup of an existing Amazon FSx for Windows File Server file
-- system, Amazon FSx for Lustre file system, Amazon FSx for NetApp ONTAP
-- volume, or Amazon FSx for OpenZFS file system. We recommend creating
-- regular backups so that you can restore a file system or volume from a
-- backup if an issue arises with the original file system or volume.
--
-- For Amazon FSx for Lustre file systems, you can create a backup only for
-- file systems that have the following configuration:
--
-- -   A Persistent deployment type
--
-- -   Are /not/ linked to a data repository
--
-- For more information about backups, see the following:
--
-- -   For Amazon FSx for Lustre, see
--     <https://docs.aws.amazon.com/fsx/latest/LustreGuide/using-backups-fsx.html Working with FSx for Lustre backups>.
--
-- -   For Amazon FSx for Windows, see
--     <https://docs.aws.amazon.com/fsx/latest/WindowsGuide/using-backups.html Working with FSx for Windows backups>.
--
-- -   For Amazon FSx for NetApp ONTAP, see
--     <https://docs.aws.amazon.com/fsx/latest/ONTAPGuide/using-backups.html Working with FSx for NetApp ONTAP backups>.
--
-- -   For Amazon FSx for OpenZFS, see
--     <https://docs.aws.amazon.com/fsx/latest/OpenZFSGuide/using-backups.html Working with FSx for OpenZFS backups>.
--
-- If a backup with the specified client request token exists and the
-- parameters match, this operation returns the description of the existing
-- backup. If a backup with the specified client request token exists and
-- the parameters don\'t match, this operation returns
-- @IncompatibleParameterError@. If a backup with the specified client
-- request token doesn\'t exist, @CreateBackup@ does the following:
--
-- -   Creates a new Amazon FSx backup with an assigned ID, and an initial
--     lifecycle state of @CREATING@.
--
-- -   Returns the description of the backup.
--
-- By using the idempotent operation, you can retry a @CreateBackup@
-- operation without the risk of creating an extra backup. This approach
-- can be useful when an initial call fails in a way that makes it unclear
-- whether a backup was created. If you use the same client request token
-- and the initial call created a backup, the operation returns a
-- successful result because all the parameters are the same.
--
-- The @CreateBackup@ operation returns while the backup\'s lifecycle state
-- is still @CREATING@. You can check the backup creation status by calling
-- the
-- <https://docs.aws.amazon.com/fsx/latest/APIReference/API_DescribeBackups.html DescribeBackups>
-- operation, which returns the backup state along with other information.
module Amazonka.FSx.CreateBackup
  ( -- * Creating a Request
    CreateBackup (..),
    newCreateBackup,

    -- * Request Lenses
    createBackup_clientRequestToken,
    createBackup_fileSystemId,
    createBackup_tags,
    createBackup_volumeId,

    -- * Destructuring the Response
    CreateBackupResponse (..),
    newCreateBackupResponse,

    -- * Response Lenses
    createBackupResponse_backup,
    createBackupResponse_httpStatus,
  )
where

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

-- | The request object for the @CreateBackup@ operation.
--
-- /See:/ 'newCreateBackup' smart constructor.
data CreateBackup = CreateBackup'
  { -- | (Optional) A string of up to 64 ASCII characters that Amazon FSx uses to
    -- ensure idempotent creation. This string is automatically filled on your
    -- behalf when you use the Command Line Interface (CLI) or an Amazon Web
    -- Services SDK.
    CreateBackup -> Maybe Text
clientRequestToken :: Prelude.Maybe Prelude.Text,
    -- | The ID of the file system to back up.
    CreateBackup -> Maybe Text
fileSystemId :: Prelude.Maybe Prelude.Text,
    -- | (Optional) The tags to apply to the backup at backup creation. The key
    -- value of the @Name@ tag appears in the console as the backup name. If
    -- you have set @CopyTagsToBackups@ to @true@, and you specify one or more
    -- tags using the @CreateBackup@ operation, no existing file system tags
    -- are copied from the file system to the backup.
    CreateBackup -> Maybe (NonEmpty Tag)
tags :: Prelude.Maybe (Prelude.NonEmpty Tag),
    -- | (Optional) The ID of the FSx for ONTAP volume to back up.
    CreateBackup -> Maybe Text
volumeId :: Prelude.Maybe Prelude.Text
  }
  deriving (CreateBackup -> CreateBackup -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateBackup -> CreateBackup -> Bool
$c/= :: CreateBackup -> CreateBackup -> Bool
== :: CreateBackup -> CreateBackup -> Bool
$c== :: CreateBackup -> CreateBackup -> Bool
Prelude.Eq, ReadPrec [CreateBackup]
ReadPrec CreateBackup
Int -> ReadS CreateBackup
ReadS [CreateBackup]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateBackup]
$creadListPrec :: ReadPrec [CreateBackup]
readPrec :: ReadPrec CreateBackup
$creadPrec :: ReadPrec CreateBackup
readList :: ReadS [CreateBackup]
$creadList :: ReadS [CreateBackup]
readsPrec :: Int -> ReadS CreateBackup
$creadsPrec :: Int -> ReadS CreateBackup
Prelude.Read, Int -> CreateBackup -> ShowS
[CreateBackup] -> ShowS
CreateBackup -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateBackup] -> ShowS
$cshowList :: [CreateBackup] -> ShowS
show :: CreateBackup -> String
$cshow :: CreateBackup -> String
showsPrec :: Int -> CreateBackup -> ShowS
$cshowsPrec :: Int -> CreateBackup -> ShowS
Prelude.Show, forall x. Rep CreateBackup x -> CreateBackup
forall x. CreateBackup -> Rep CreateBackup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateBackup x -> CreateBackup
$cfrom :: forall x. CreateBackup -> Rep CreateBackup x
Prelude.Generic)

-- |
-- Create a value of 'CreateBackup' 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:
--
-- 'clientRequestToken', 'createBackup_clientRequestToken' - (Optional) A string of up to 64 ASCII characters that Amazon FSx uses to
-- ensure idempotent creation. This string is automatically filled on your
-- behalf when you use the Command Line Interface (CLI) or an Amazon Web
-- Services SDK.
--
-- 'fileSystemId', 'createBackup_fileSystemId' - The ID of the file system to back up.
--
-- 'tags', 'createBackup_tags' - (Optional) The tags to apply to the backup at backup creation. The key
-- value of the @Name@ tag appears in the console as the backup name. If
-- you have set @CopyTagsToBackups@ to @true@, and you specify one or more
-- tags using the @CreateBackup@ operation, no existing file system tags
-- are copied from the file system to the backup.
--
-- 'volumeId', 'createBackup_volumeId' - (Optional) The ID of the FSx for ONTAP volume to back up.
newCreateBackup ::
  CreateBackup
newCreateBackup :: CreateBackup
newCreateBackup =
  CreateBackup'
    { $sel:clientRequestToken:CreateBackup' :: Maybe Text
clientRequestToken = forall a. Maybe a
Prelude.Nothing,
      $sel:fileSystemId:CreateBackup' :: Maybe Text
fileSystemId = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:CreateBackup' :: Maybe (NonEmpty Tag)
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:volumeId:CreateBackup' :: Maybe Text
volumeId = forall a. Maybe a
Prelude.Nothing
    }

-- | (Optional) A string of up to 64 ASCII characters that Amazon FSx uses to
-- ensure idempotent creation. This string is automatically filled on your
-- behalf when you use the Command Line Interface (CLI) or an Amazon Web
-- Services SDK.
createBackup_clientRequestToken :: Lens.Lens' CreateBackup (Prelude.Maybe Prelude.Text)
createBackup_clientRequestToken :: Lens' CreateBackup (Maybe Text)
createBackup_clientRequestToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateBackup' {Maybe Text
clientRequestToken :: Maybe Text
$sel:clientRequestToken:CreateBackup' :: CreateBackup -> Maybe Text
clientRequestToken} -> Maybe Text
clientRequestToken) (\s :: CreateBackup
s@CreateBackup' {} Maybe Text
a -> CreateBackup
s {$sel:clientRequestToken:CreateBackup' :: Maybe Text
clientRequestToken = Maybe Text
a} :: CreateBackup)

-- | The ID of the file system to back up.
createBackup_fileSystemId :: Lens.Lens' CreateBackup (Prelude.Maybe Prelude.Text)
createBackup_fileSystemId :: Lens' CreateBackup (Maybe Text)
createBackup_fileSystemId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateBackup' {Maybe Text
fileSystemId :: Maybe Text
$sel:fileSystemId:CreateBackup' :: CreateBackup -> Maybe Text
fileSystemId} -> Maybe Text
fileSystemId) (\s :: CreateBackup
s@CreateBackup' {} Maybe Text
a -> CreateBackup
s {$sel:fileSystemId:CreateBackup' :: Maybe Text
fileSystemId = Maybe Text
a} :: CreateBackup)

-- | (Optional) The tags to apply to the backup at backup creation. The key
-- value of the @Name@ tag appears in the console as the backup name. If
-- you have set @CopyTagsToBackups@ to @true@, and you specify one or more
-- tags using the @CreateBackup@ operation, no existing file system tags
-- are copied from the file system to the backup.
createBackup_tags :: Lens.Lens' CreateBackup (Prelude.Maybe (Prelude.NonEmpty Tag))
createBackup_tags :: Lens' CreateBackup (Maybe (NonEmpty Tag))
createBackup_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateBackup' {Maybe (NonEmpty Tag)
tags :: Maybe (NonEmpty Tag)
$sel:tags:CreateBackup' :: CreateBackup -> Maybe (NonEmpty Tag)
tags} -> Maybe (NonEmpty Tag)
tags) (\s :: CreateBackup
s@CreateBackup' {} Maybe (NonEmpty Tag)
a -> CreateBackup
s {$sel:tags:CreateBackup' :: Maybe (NonEmpty Tag)
tags = Maybe (NonEmpty Tag)
a} :: CreateBackup) 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

-- | (Optional) The ID of the FSx for ONTAP volume to back up.
createBackup_volumeId :: Lens.Lens' CreateBackup (Prelude.Maybe Prelude.Text)
createBackup_volumeId :: Lens' CreateBackup (Maybe Text)
createBackup_volumeId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateBackup' {Maybe Text
volumeId :: Maybe Text
$sel:volumeId:CreateBackup' :: CreateBackup -> Maybe Text
volumeId} -> Maybe Text
volumeId) (\s :: CreateBackup
s@CreateBackup' {} Maybe Text
a -> CreateBackup
s {$sel:volumeId:CreateBackup' :: Maybe Text
volumeId = Maybe Text
a} :: CreateBackup)

instance Core.AWSRequest CreateBackup where
  type AWSResponse CreateBackup = CreateBackupResponse
  request :: (Service -> Service) -> CreateBackup -> Request CreateBackup
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 CreateBackup
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse CreateBackup)))
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 -> Int -> CreateBackupResponse
CreateBackupResponse'
            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
"Backup")
            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 CreateBackup where
  hashWithSalt :: Int -> CreateBackup -> Int
hashWithSalt Int
_salt CreateBackup' {Maybe (NonEmpty Tag)
Maybe Text
volumeId :: Maybe Text
tags :: Maybe (NonEmpty Tag)
fileSystemId :: Maybe Text
clientRequestToken :: Maybe Text
$sel:volumeId:CreateBackup' :: CreateBackup -> Maybe Text
$sel:tags:CreateBackup' :: CreateBackup -> Maybe (NonEmpty Tag)
$sel:fileSystemId:CreateBackup' :: CreateBackup -> Maybe Text
$sel:clientRequestToken:CreateBackup' :: CreateBackup -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
clientRequestToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
fileSystemId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (NonEmpty Tag)
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
volumeId

instance Prelude.NFData CreateBackup where
  rnf :: CreateBackup -> ()
rnf CreateBackup' {Maybe (NonEmpty Tag)
Maybe Text
volumeId :: Maybe Text
tags :: Maybe (NonEmpty Tag)
fileSystemId :: Maybe Text
clientRequestToken :: Maybe Text
$sel:volumeId:CreateBackup' :: CreateBackup -> Maybe Text
$sel:tags:CreateBackup' :: CreateBackup -> Maybe (NonEmpty Tag)
$sel:fileSystemId:CreateBackup' :: CreateBackup -> Maybe Text
$sel:clientRequestToken:CreateBackup' :: CreateBackup -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
clientRequestToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
fileSystemId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty Tag)
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
volumeId

instance Data.ToHeaders CreateBackup where
  toHeaders :: CreateBackup -> 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
"AWSSimbaAPIService_v20180301.CreateBackup" ::
                          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 CreateBackup where
  toJSON :: CreateBackup -> Value
toJSON CreateBackup' {Maybe (NonEmpty Tag)
Maybe Text
volumeId :: Maybe Text
tags :: Maybe (NonEmpty Tag)
fileSystemId :: Maybe Text
clientRequestToken :: Maybe Text
$sel:volumeId:CreateBackup' :: CreateBackup -> Maybe Text
$sel:tags:CreateBackup' :: CreateBackup -> Maybe (NonEmpty Tag)
$sel:fileSystemId:CreateBackup' :: CreateBackup -> Maybe Text
$sel:clientRequestToken:CreateBackup' :: CreateBackup -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"ClientRequestToken" 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
clientRequestToken,
            (Key
"FileSystemId" 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
fileSystemId,
            (Key
"Tags" 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 (NonEmpty Tag)
tags,
            (Key
"VolumeId" 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
volumeId
          ]
      )

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

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

-- | The response object for the @CreateBackup@ operation.
--
-- /See:/ 'newCreateBackupResponse' smart constructor.
data CreateBackupResponse = CreateBackupResponse'
  { -- | A description of the backup.
    CreateBackupResponse -> Maybe Backup
backup :: Prelude.Maybe Backup,
    -- | The response's http status code.
    CreateBackupResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateBackupResponse -> CreateBackupResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateBackupResponse -> CreateBackupResponse -> Bool
$c/= :: CreateBackupResponse -> CreateBackupResponse -> Bool
== :: CreateBackupResponse -> CreateBackupResponse -> Bool
$c== :: CreateBackupResponse -> CreateBackupResponse -> Bool
Prelude.Eq, ReadPrec [CreateBackupResponse]
ReadPrec CreateBackupResponse
Int -> ReadS CreateBackupResponse
ReadS [CreateBackupResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateBackupResponse]
$creadListPrec :: ReadPrec [CreateBackupResponse]
readPrec :: ReadPrec CreateBackupResponse
$creadPrec :: ReadPrec CreateBackupResponse
readList :: ReadS [CreateBackupResponse]
$creadList :: ReadS [CreateBackupResponse]
readsPrec :: Int -> ReadS CreateBackupResponse
$creadsPrec :: Int -> ReadS CreateBackupResponse
Prelude.Read, Int -> CreateBackupResponse -> ShowS
[CreateBackupResponse] -> ShowS
CreateBackupResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateBackupResponse] -> ShowS
$cshowList :: [CreateBackupResponse] -> ShowS
show :: CreateBackupResponse -> String
$cshow :: CreateBackupResponse -> String
showsPrec :: Int -> CreateBackupResponse -> ShowS
$cshowsPrec :: Int -> CreateBackupResponse -> ShowS
Prelude.Show, forall x. Rep CreateBackupResponse x -> CreateBackupResponse
forall x. CreateBackupResponse -> Rep CreateBackupResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateBackupResponse x -> CreateBackupResponse
$cfrom :: forall x. CreateBackupResponse -> Rep CreateBackupResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateBackupResponse' 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:
--
-- 'backup', 'createBackupResponse_backup' - A description of the backup.
--
-- 'httpStatus', 'createBackupResponse_httpStatus' - The response's http status code.
newCreateBackupResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateBackupResponse
newCreateBackupResponse :: Int -> CreateBackupResponse
newCreateBackupResponse Int
pHttpStatus_ =
  CreateBackupResponse'
    { $sel:backup:CreateBackupResponse' :: Maybe Backup
backup = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateBackupResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A description of the backup.
createBackupResponse_backup :: Lens.Lens' CreateBackupResponse (Prelude.Maybe Backup)
createBackupResponse_backup :: Lens' CreateBackupResponse (Maybe Backup)
createBackupResponse_backup = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateBackupResponse' {Maybe Backup
backup :: Maybe Backup
$sel:backup:CreateBackupResponse' :: CreateBackupResponse -> Maybe Backup
backup} -> Maybe Backup
backup) (\s :: CreateBackupResponse
s@CreateBackupResponse' {} Maybe Backup
a -> CreateBackupResponse
s {$sel:backup:CreateBackupResponse' :: Maybe Backup
backup = Maybe Backup
a} :: CreateBackupResponse)

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

instance Prelude.NFData CreateBackupResponse where
  rnf :: CreateBackupResponse -> ()
rnf CreateBackupResponse' {Int
Maybe Backup
httpStatus :: Int
backup :: Maybe Backup
$sel:httpStatus:CreateBackupResponse' :: CreateBackupResponse -> Int
$sel:backup:CreateBackupResponse' :: CreateBackupResponse -> Maybe Backup
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Backup
backup
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus