{-# 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.OpsWorksCM.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 an application-level backup of a server. While the server is in
-- the @BACKING_UP@ state, the server cannot be changed, and no additional
-- backup can be created.
--
-- Backups can be created for servers in @RUNNING@, @HEALTHY@, and
-- @UNHEALTHY@ states. By default, you can create a maximum of 50 manual
-- backups.
--
-- This operation is asynchronous.
--
-- A @LimitExceededException@ is thrown when the maximum number of manual
-- backups is reached. An @InvalidStateException@ is thrown when the server
-- is not in any of the following states: RUNNING, HEALTHY, or UNHEALTHY. A
-- @ResourceNotFoundException@ is thrown when the server is not found. A
-- @ValidationException@ is thrown when parameters of the request are not
-- valid.
module Amazonka.OpsWorksCM.CreateBackup
  ( -- * Creating a Request
    CreateBackup (..),
    newCreateBackup,

    -- * Request Lenses
    createBackup_description,
    createBackup_tags,
    createBackup_serverName,

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

-- | /See:/ 'newCreateBackup' smart constructor.
data CreateBackup = CreateBackup'
  { -- | A user-defined description of the backup.
    CreateBackup -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | A map that contains tag keys and tag values to attach to an AWS
    -- OpsWorks-CM server backup.
    --
    -- -   The key cannot be empty.
    --
    -- -   The key can be a maximum of 127 characters, and can contain only
    --     Unicode letters, numbers, or separators, or the following special
    --     characters: @+ - = . _ : \/@
    --
    -- -   The value can be a maximum 255 characters, and contain only Unicode
    --     letters, numbers, or separators, or the following special
    --     characters: @+ - = . _ : \/@
    --
    -- -   Leading and trailing white spaces are trimmed from both the key and
    --     value.
    --
    -- -   A maximum of 50 user-applied tags is allowed for tag-supported AWS
    --     OpsWorks-CM resources.
    CreateBackup -> Maybe [Tag]
tags :: Prelude.Maybe [Tag],
    -- | The name of the server that you want to back up.
    CreateBackup -> Text
serverName :: 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:
--
-- 'description', 'createBackup_description' - A user-defined description of the backup.
--
-- 'tags', 'createBackup_tags' - A map that contains tag keys and tag values to attach to an AWS
-- OpsWorks-CM server backup.
--
-- -   The key cannot be empty.
--
-- -   The key can be a maximum of 127 characters, and can contain only
--     Unicode letters, numbers, or separators, or the following special
--     characters: @+ - = . _ : \/@
--
-- -   The value can be a maximum 255 characters, and contain only Unicode
--     letters, numbers, or separators, or the following special
--     characters: @+ - = . _ : \/@
--
-- -   Leading and trailing white spaces are trimmed from both the key and
--     value.
--
-- -   A maximum of 50 user-applied tags is allowed for tag-supported AWS
--     OpsWorks-CM resources.
--
-- 'serverName', 'createBackup_serverName' - The name of the server that you want to back up.
newCreateBackup ::
  -- | 'serverName'
  Prelude.Text ->
  CreateBackup
newCreateBackup :: Text -> CreateBackup
newCreateBackup Text
pServerName_ =
  CreateBackup'
    { $sel:description:CreateBackup' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:CreateBackup' :: Maybe [Tag]
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:serverName:CreateBackup' :: Text
serverName = Text
pServerName_
    }

-- | A user-defined description of the backup.
createBackup_description :: Lens.Lens' CreateBackup (Prelude.Maybe Prelude.Text)
createBackup_description :: Lens' CreateBackup (Maybe Text)
createBackup_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateBackup' {Maybe Text
description :: Maybe Text
$sel:description:CreateBackup' :: CreateBackup -> Maybe Text
description} -> Maybe Text
description) (\s :: CreateBackup
s@CreateBackup' {} Maybe Text
a -> CreateBackup
s {$sel:description:CreateBackup' :: Maybe Text
description = Maybe Text
a} :: CreateBackup)

-- | A map that contains tag keys and tag values to attach to an AWS
-- OpsWorks-CM server backup.
--
-- -   The key cannot be empty.
--
-- -   The key can be a maximum of 127 characters, and can contain only
--     Unicode letters, numbers, or separators, or the following special
--     characters: @+ - = . _ : \/@
--
-- -   The value can be a maximum 255 characters, and contain only Unicode
--     letters, numbers, or separators, or the following special
--     characters: @+ - = . _ : \/@
--
-- -   Leading and trailing white spaces are trimmed from both the key and
--     value.
--
-- -   A maximum of 50 user-applied tags is allowed for tag-supported AWS
--     OpsWorks-CM resources.
createBackup_tags :: Lens.Lens' CreateBackup (Prelude.Maybe [Tag])
createBackup_tags :: Lens' CreateBackup (Maybe [Tag])
createBackup_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateBackup' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:CreateBackup' :: CreateBackup -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: CreateBackup
s@CreateBackup' {} Maybe [Tag]
a -> CreateBackup
s {$sel:tags:CreateBackup' :: Maybe [Tag]
tags = Maybe [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

-- | The name of the server that you want to back up.
createBackup_serverName :: Lens.Lens' CreateBackup Prelude.Text
createBackup_serverName :: Lens' CreateBackup Text
createBackup_serverName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateBackup' {Text
serverName :: Text
$sel:serverName:CreateBackup' :: CreateBackup -> Text
serverName} -> Text
serverName) (\s :: CreateBackup
s@CreateBackup' {} Text
a -> CreateBackup
s {$sel:serverName:CreateBackup' :: Text
serverName = 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 [Tag]
Maybe Text
Text
serverName :: Text
tags :: Maybe [Tag]
description :: Maybe Text
$sel:serverName:CreateBackup' :: CreateBackup -> Text
$sel:tags:CreateBackup' :: CreateBackup -> Maybe [Tag]
$sel:description:CreateBackup' :: CreateBackup -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Tag]
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
serverName

instance Prelude.NFData CreateBackup where
  rnf :: CreateBackup -> ()
rnf CreateBackup' {Maybe [Tag]
Maybe Text
Text
serverName :: Text
tags :: Maybe [Tag]
description :: Maybe Text
$sel:serverName:CreateBackup' :: CreateBackup -> Text
$sel:tags:CreateBackup' :: CreateBackup -> Maybe [Tag]
$sel:description:CreateBackup' :: CreateBackup -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Tag]
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
serverName

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
"OpsWorksCM_V2016_11_01.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 [Tag]
Maybe Text
Text
serverName :: Text
tags :: Maybe [Tag]
description :: Maybe Text
$sel:serverName:CreateBackup' :: CreateBackup -> Text
$sel:tags:CreateBackup' :: CreateBackup -> Maybe [Tag]
$sel:description:CreateBackup' :: CreateBackup -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Description" 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
description,
            (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 [Tag]
tags,
            forall a. a -> Maybe a
Prelude.Just (Key
"ServerName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
serverName)
          ]
      )

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

-- | /See:/ 'newCreateBackupResponse' smart constructor.
data CreateBackupResponse = CreateBackupResponse'
  { -- | Backup created by request.
    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' - Backup created by request.
--
-- '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_
    }

-- | Backup created by request.
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