{-# 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.UpdateServer
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Updates settings for a server.
--
-- This operation is synchronous.
module Amazonka.OpsWorksCM.UpdateServer
  ( -- * Creating a Request
    UpdateServer (..),
    newUpdateServer,

    -- * Request Lenses
    updateServer_backupRetentionCount,
    updateServer_disableAutomatedBackup,
    updateServer_preferredBackupWindow,
    updateServer_preferredMaintenanceWindow,
    updateServer_serverName,

    -- * Destructuring the Response
    UpdateServerResponse (..),
    newUpdateServerResponse,

    -- * Response Lenses
    updateServerResponse_server,
    updateServerResponse_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:/ 'newUpdateServer' smart constructor.
data UpdateServer = UpdateServer'
  { -- | Sets the number of automated backups that you want to keep.
    UpdateServer -> Maybe Int
backupRetentionCount :: Prelude.Maybe Prelude.Int,
    -- | Setting DisableAutomatedBackup to @true@ disables automated or scheduled
    -- backups. Automated backups are enabled by default.
    UpdateServer -> Maybe Bool
disableAutomatedBackup :: Prelude.Maybe Prelude.Bool,
    UpdateServer -> Maybe Text
preferredBackupWindow :: Prelude.Maybe Prelude.Text,
    UpdateServer -> Maybe Text
preferredMaintenanceWindow :: Prelude.Maybe Prelude.Text,
    -- | The name of the server to update.
    UpdateServer -> Text
serverName :: Prelude.Text
  }
  deriving (UpdateServer -> UpdateServer -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateServer -> UpdateServer -> Bool
$c/= :: UpdateServer -> UpdateServer -> Bool
== :: UpdateServer -> UpdateServer -> Bool
$c== :: UpdateServer -> UpdateServer -> Bool
Prelude.Eq, ReadPrec [UpdateServer]
ReadPrec UpdateServer
Int -> ReadS UpdateServer
ReadS [UpdateServer]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateServer]
$creadListPrec :: ReadPrec [UpdateServer]
readPrec :: ReadPrec UpdateServer
$creadPrec :: ReadPrec UpdateServer
readList :: ReadS [UpdateServer]
$creadList :: ReadS [UpdateServer]
readsPrec :: Int -> ReadS UpdateServer
$creadsPrec :: Int -> ReadS UpdateServer
Prelude.Read, Int -> UpdateServer -> ShowS
[UpdateServer] -> ShowS
UpdateServer -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateServer] -> ShowS
$cshowList :: [UpdateServer] -> ShowS
show :: UpdateServer -> String
$cshow :: UpdateServer -> String
showsPrec :: Int -> UpdateServer -> ShowS
$cshowsPrec :: Int -> UpdateServer -> ShowS
Prelude.Show, forall x. Rep UpdateServer x -> UpdateServer
forall x. UpdateServer -> Rep UpdateServer x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateServer x -> UpdateServer
$cfrom :: forall x. UpdateServer -> Rep UpdateServer x
Prelude.Generic)

-- |
-- Create a value of 'UpdateServer' 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:
--
-- 'backupRetentionCount', 'updateServer_backupRetentionCount' - Sets the number of automated backups that you want to keep.
--
-- 'disableAutomatedBackup', 'updateServer_disableAutomatedBackup' - Setting DisableAutomatedBackup to @true@ disables automated or scheduled
-- backups. Automated backups are enabled by default.
--
-- 'preferredBackupWindow', 'updateServer_preferredBackupWindow' - Undocumented member.
--
-- 'preferredMaintenanceWindow', 'updateServer_preferredMaintenanceWindow' - Undocumented member.
--
-- 'serverName', 'updateServer_serverName' - The name of the server to update.
newUpdateServer ::
  -- | 'serverName'
  Prelude.Text ->
  UpdateServer
newUpdateServer :: Text -> UpdateServer
newUpdateServer Text
pServerName_ =
  UpdateServer'
    { $sel:backupRetentionCount:UpdateServer' :: Maybe Int
backupRetentionCount =
        forall a. Maybe a
Prelude.Nothing,
      $sel:disableAutomatedBackup:UpdateServer' :: Maybe Bool
disableAutomatedBackup = forall a. Maybe a
Prelude.Nothing,
      $sel:preferredBackupWindow:UpdateServer' :: Maybe Text
preferredBackupWindow = forall a. Maybe a
Prelude.Nothing,
      $sel:preferredMaintenanceWindow:UpdateServer' :: Maybe Text
preferredMaintenanceWindow = forall a. Maybe a
Prelude.Nothing,
      $sel:serverName:UpdateServer' :: Text
serverName = Text
pServerName_
    }

-- | Sets the number of automated backups that you want to keep.
updateServer_backupRetentionCount :: Lens.Lens' UpdateServer (Prelude.Maybe Prelude.Int)
updateServer_backupRetentionCount :: Lens' UpdateServer (Maybe Int)
updateServer_backupRetentionCount = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateServer' {Maybe Int
backupRetentionCount :: Maybe Int
$sel:backupRetentionCount:UpdateServer' :: UpdateServer -> Maybe Int
backupRetentionCount} -> Maybe Int
backupRetentionCount) (\s :: UpdateServer
s@UpdateServer' {} Maybe Int
a -> UpdateServer
s {$sel:backupRetentionCount:UpdateServer' :: Maybe Int
backupRetentionCount = Maybe Int
a} :: UpdateServer)

-- | Setting DisableAutomatedBackup to @true@ disables automated or scheduled
-- backups. Automated backups are enabled by default.
updateServer_disableAutomatedBackup :: Lens.Lens' UpdateServer (Prelude.Maybe Prelude.Bool)
updateServer_disableAutomatedBackup :: Lens' UpdateServer (Maybe Bool)
updateServer_disableAutomatedBackup = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateServer' {Maybe Bool
disableAutomatedBackup :: Maybe Bool
$sel:disableAutomatedBackup:UpdateServer' :: UpdateServer -> Maybe Bool
disableAutomatedBackup} -> Maybe Bool
disableAutomatedBackup) (\s :: UpdateServer
s@UpdateServer' {} Maybe Bool
a -> UpdateServer
s {$sel:disableAutomatedBackup:UpdateServer' :: Maybe Bool
disableAutomatedBackup = Maybe Bool
a} :: UpdateServer)

-- | Undocumented member.
updateServer_preferredBackupWindow :: Lens.Lens' UpdateServer (Prelude.Maybe Prelude.Text)
updateServer_preferredBackupWindow :: Lens' UpdateServer (Maybe Text)
updateServer_preferredBackupWindow = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateServer' {Maybe Text
preferredBackupWindow :: Maybe Text
$sel:preferredBackupWindow:UpdateServer' :: UpdateServer -> Maybe Text
preferredBackupWindow} -> Maybe Text
preferredBackupWindow) (\s :: UpdateServer
s@UpdateServer' {} Maybe Text
a -> UpdateServer
s {$sel:preferredBackupWindow:UpdateServer' :: Maybe Text
preferredBackupWindow = Maybe Text
a} :: UpdateServer)

-- | Undocumented member.
updateServer_preferredMaintenanceWindow :: Lens.Lens' UpdateServer (Prelude.Maybe Prelude.Text)
updateServer_preferredMaintenanceWindow :: Lens' UpdateServer (Maybe Text)
updateServer_preferredMaintenanceWindow = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateServer' {Maybe Text
preferredMaintenanceWindow :: Maybe Text
$sel:preferredMaintenanceWindow:UpdateServer' :: UpdateServer -> Maybe Text
preferredMaintenanceWindow} -> Maybe Text
preferredMaintenanceWindow) (\s :: UpdateServer
s@UpdateServer' {} Maybe Text
a -> UpdateServer
s {$sel:preferredMaintenanceWindow:UpdateServer' :: Maybe Text
preferredMaintenanceWindow = Maybe Text
a} :: UpdateServer)

-- | The name of the server to update.
updateServer_serverName :: Lens.Lens' UpdateServer Prelude.Text
updateServer_serverName :: Lens' UpdateServer Text
updateServer_serverName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateServer' {Text
serverName :: Text
$sel:serverName:UpdateServer' :: UpdateServer -> Text
serverName} -> Text
serverName) (\s :: UpdateServer
s@UpdateServer' {} Text
a -> UpdateServer
s {$sel:serverName:UpdateServer' :: Text
serverName = Text
a} :: UpdateServer)

instance Core.AWSRequest UpdateServer where
  type AWSResponse UpdateServer = UpdateServerResponse
  request :: (Service -> Service) -> UpdateServer -> Request UpdateServer
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 UpdateServer
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse UpdateServer)))
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 Server -> Int -> UpdateServerResponse
UpdateServerResponse'
            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
"Server")
            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 UpdateServer where
  hashWithSalt :: Int -> UpdateServer -> Int
hashWithSalt Int
_salt UpdateServer' {Maybe Bool
Maybe Int
Maybe Text
Text
serverName :: Text
preferredMaintenanceWindow :: Maybe Text
preferredBackupWindow :: Maybe Text
disableAutomatedBackup :: Maybe Bool
backupRetentionCount :: Maybe Int
$sel:serverName:UpdateServer' :: UpdateServer -> Text
$sel:preferredMaintenanceWindow:UpdateServer' :: UpdateServer -> Maybe Text
$sel:preferredBackupWindow:UpdateServer' :: UpdateServer -> Maybe Text
$sel:disableAutomatedBackup:UpdateServer' :: UpdateServer -> Maybe Bool
$sel:backupRetentionCount:UpdateServer' :: UpdateServer -> Maybe Int
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
backupRetentionCount
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
disableAutomatedBackup
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
preferredBackupWindow
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
preferredMaintenanceWindow
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
serverName

instance Prelude.NFData UpdateServer where
  rnf :: UpdateServer -> ()
rnf UpdateServer' {Maybe Bool
Maybe Int
Maybe Text
Text
serverName :: Text
preferredMaintenanceWindow :: Maybe Text
preferredBackupWindow :: Maybe Text
disableAutomatedBackup :: Maybe Bool
backupRetentionCount :: Maybe Int
$sel:serverName:UpdateServer' :: UpdateServer -> Text
$sel:preferredMaintenanceWindow:UpdateServer' :: UpdateServer -> Maybe Text
$sel:preferredBackupWindow:UpdateServer' :: UpdateServer -> Maybe Text
$sel:disableAutomatedBackup:UpdateServer' :: UpdateServer -> Maybe Bool
$sel:backupRetentionCount:UpdateServer' :: UpdateServer -> Maybe Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
backupRetentionCount
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
disableAutomatedBackup
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
preferredBackupWindow
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
preferredMaintenanceWindow
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
serverName

instance Data.ToHeaders UpdateServer where
  toHeaders :: UpdateServer -> 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.UpdateServer" ::
                          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 UpdateServer where
  toJSON :: UpdateServer -> Value
toJSON UpdateServer' {Maybe Bool
Maybe Int
Maybe Text
Text
serverName :: Text
preferredMaintenanceWindow :: Maybe Text
preferredBackupWindow :: Maybe Text
disableAutomatedBackup :: Maybe Bool
backupRetentionCount :: Maybe Int
$sel:serverName:UpdateServer' :: UpdateServer -> Text
$sel:preferredMaintenanceWindow:UpdateServer' :: UpdateServer -> Maybe Text
$sel:preferredBackupWindow:UpdateServer' :: UpdateServer -> Maybe Text
$sel:disableAutomatedBackup:UpdateServer' :: UpdateServer -> Maybe Bool
$sel:backupRetentionCount:UpdateServer' :: UpdateServer -> Maybe Int
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"BackupRetentionCount" 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 Int
backupRetentionCount,
            (Key
"DisableAutomatedBackup" 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
disableAutomatedBackup,
            (Key
"PreferredBackupWindow" 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
preferredBackupWindow,
            (Key
"PreferredMaintenanceWindow" 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
preferredMaintenanceWindow,
            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 UpdateServer where
  toPath :: UpdateServer -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

-- | /See:/ 'newUpdateServerResponse' smart constructor.
data UpdateServerResponse = UpdateServerResponse'
  { -- | Contains the response to a @UpdateServer@ request.
    UpdateServerResponse -> Maybe Server
server :: Prelude.Maybe Server,
    -- | The response's http status code.
    UpdateServerResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (UpdateServerResponse -> UpdateServerResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateServerResponse -> UpdateServerResponse -> Bool
$c/= :: UpdateServerResponse -> UpdateServerResponse -> Bool
== :: UpdateServerResponse -> UpdateServerResponse -> Bool
$c== :: UpdateServerResponse -> UpdateServerResponse -> Bool
Prelude.Eq, Int -> UpdateServerResponse -> ShowS
[UpdateServerResponse] -> ShowS
UpdateServerResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateServerResponse] -> ShowS
$cshowList :: [UpdateServerResponse] -> ShowS
show :: UpdateServerResponse -> String
$cshow :: UpdateServerResponse -> String
showsPrec :: Int -> UpdateServerResponse -> ShowS
$cshowsPrec :: Int -> UpdateServerResponse -> ShowS
Prelude.Show, forall x. Rep UpdateServerResponse x -> UpdateServerResponse
forall x. UpdateServerResponse -> Rep UpdateServerResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateServerResponse x -> UpdateServerResponse
$cfrom :: forall x. UpdateServerResponse -> Rep UpdateServerResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateServerResponse' 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:
--
-- 'server', 'updateServerResponse_server' - Contains the response to a @UpdateServer@ request.
--
-- 'httpStatus', 'updateServerResponse_httpStatus' - The response's http status code.
newUpdateServerResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateServerResponse
newUpdateServerResponse :: Int -> UpdateServerResponse
newUpdateServerResponse Int
pHttpStatus_ =
  UpdateServerResponse'
    { $sel:server:UpdateServerResponse' :: Maybe Server
server = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UpdateServerResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Contains the response to a @UpdateServer@ request.
updateServerResponse_server :: Lens.Lens' UpdateServerResponse (Prelude.Maybe Server)
updateServerResponse_server :: Lens' UpdateServerResponse (Maybe Server)
updateServerResponse_server = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateServerResponse' {Maybe Server
server :: Maybe Server
$sel:server:UpdateServerResponse' :: UpdateServerResponse -> Maybe Server
server} -> Maybe Server
server) (\s :: UpdateServerResponse
s@UpdateServerResponse' {} Maybe Server
a -> UpdateServerResponse
s {$sel:server:UpdateServerResponse' :: Maybe Server
server = Maybe Server
a} :: UpdateServerResponse)

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

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