{-# 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.UpdateServerEngineAttributes
-- 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 engine-specific attributes on a specified server. The server
-- enters the @MODIFYING@ state when this operation is in progress. Only
-- one update can occur at a time. You can use this command to reset a Chef
-- server\'s public key (@CHEF_PIVOTAL_KEY@) or a Puppet server\'s admin
-- password (@PUPPET_ADMIN_PASSWORD@).
--
-- This operation is asynchronous.
--
-- This operation can only be called for servers in @HEALTHY@ or
-- @UNHEALTHY@ states. Otherwise, an @InvalidStateException@ is raised. A
-- @ResourceNotFoundException@ is thrown when the server does not exist. A
-- @ValidationException@ is raised when parameters of the request are not
-- valid.
module Amazonka.OpsWorksCM.UpdateServerEngineAttributes
  ( -- * Creating a Request
    UpdateServerEngineAttributes (..),
    newUpdateServerEngineAttributes,

    -- * Request Lenses
    updateServerEngineAttributes_attributeValue,
    updateServerEngineAttributes_serverName,
    updateServerEngineAttributes_attributeName,

    -- * Destructuring the Response
    UpdateServerEngineAttributesResponse (..),
    newUpdateServerEngineAttributesResponse,

    -- * Response Lenses
    updateServerEngineAttributesResponse_server,
    updateServerEngineAttributesResponse_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:/ 'newUpdateServerEngineAttributes' smart constructor.
data UpdateServerEngineAttributes = UpdateServerEngineAttributes'
  { -- | The value to set for the attribute.
    UpdateServerEngineAttributes -> Maybe Text
attributeValue :: Prelude.Maybe Prelude.Text,
    -- | The name of the server to update.
    UpdateServerEngineAttributes -> Text
serverName :: Prelude.Text,
    -- | The name of the engine attribute to update.
    UpdateServerEngineAttributes -> Text
attributeName :: Prelude.Text
  }
  deriving (UpdateServerEngineAttributes
-> UpdateServerEngineAttributes -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateServerEngineAttributes
-> UpdateServerEngineAttributes -> Bool
$c/= :: UpdateServerEngineAttributes
-> UpdateServerEngineAttributes -> Bool
== :: UpdateServerEngineAttributes
-> UpdateServerEngineAttributes -> Bool
$c== :: UpdateServerEngineAttributes
-> UpdateServerEngineAttributes -> Bool
Prelude.Eq, ReadPrec [UpdateServerEngineAttributes]
ReadPrec UpdateServerEngineAttributes
Int -> ReadS UpdateServerEngineAttributes
ReadS [UpdateServerEngineAttributes]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateServerEngineAttributes]
$creadListPrec :: ReadPrec [UpdateServerEngineAttributes]
readPrec :: ReadPrec UpdateServerEngineAttributes
$creadPrec :: ReadPrec UpdateServerEngineAttributes
readList :: ReadS [UpdateServerEngineAttributes]
$creadList :: ReadS [UpdateServerEngineAttributes]
readsPrec :: Int -> ReadS UpdateServerEngineAttributes
$creadsPrec :: Int -> ReadS UpdateServerEngineAttributes
Prelude.Read, Int -> UpdateServerEngineAttributes -> ShowS
[UpdateServerEngineAttributes] -> ShowS
UpdateServerEngineAttributes -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateServerEngineAttributes] -> ShowS
$cshowList :: [UpdateServerEngineAttributes] -> ShowS
show :: UpdateServerEngineAttributes -> String
$cshow :: UpdateServerEngineAttributes -> String
showsPrec :: Int -> UpdateServerEngineAttributes -> ShowS
$cshowsPrec :: Int -> UpdateServerEngineAttributes -> ShowS
Prelude.Show, forall x.
Rep UpdateServerEngineAttributes x -> UpdateServerEngineAttributes
forall x.
UpdateServerEngineAttributes -> Rep UpdateServerEngineAttributes x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateServerEngineAttributes x -> UpdateServerEngineAttributes
$cfrom :: forall x.
UpdateServerEngineAttributes -> Rep UpdateServerEngineAttributes x
Prelude.Generic)

-- |
-- Create a value of 'UpdateServerEngineAttributes' 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:
--
-- 'attributeValue', 'updateServerEngineAttributes_attributeValue' - The value to set for the attribute.
--
-- 'serverName', 'updateServerEngineAttributes_serverName' - The name of the server to update.
--
-- 'attributeName', 'updateServerEngineAttributes_attributeName' - The name of the engine attribute to update.
newUpdateServerEngineAttributes ::
  -- | 'serverName'
  Prelude.Text ->
  -- | 'attributeName'
  Prelude.Text ->
  UpdateServerEngineAttributes
newUpdateServerEngineAttributes :: Text -> Text -> UpdateServerEngineAttributes
newUpdateServerEngineAttributes
  Text
pServerName_
  Text
pAttributeName_ =
    UpdateServerEngineAttributes'
      { $sel:attributeValue:UpdateServerEngineAttributes' :: Maybe Text
attributeValue =
          forall a. Maybe a
Prelude.Nothing,
        $sel:serverName:UpdateServerEngineAttributes' :: Text
serverName = Text
pServerName_,
        $sel:attributeName:UpdateServerEngineAttributes' :: Text
attributeName = Text
pAttributeName_
      }

-- | The value to set for the attribute.
updateServerEngineAttributes_attributeValue :: Lens.Lens' UpdateServerEngineAttributes (Prelude.Maybe Prelude.Text)
updateServerEngineAttributes_attributeValue :: Lens' UpdateServerEngineAttributes (Maybe Text)
updateServerEngineAttributes_attributeValue = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateServerEngineAttributes' {Maybe Text
attributeValue :: Maybe Text
$sel:attributeValue:UpdateServerEngineAttributes' :: UpdateServerEngineAttributes -> Maybe Text
attributeValue} -> Maybe Text
attributeValue) (\s :: UpdateServerEngineAttributes
s@UpdateServerEngineAttributes' {} Maybe Text
a -> UpdateServerEngineAttributes
s {$sel:attributeValue:UpdateServerEngineAttributes' :: Maybe Text
attributeValue = Maybe Text
a} :: UpdateServerEngineAttributes)

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

-- | The name of the engine attribute to update.
updateServerEngineAttributes_attributeName :: Lens.Lens' UpdateServerEngineAttributes Prelude.Text
updateServerEngineAttributes_attributeName :: Lens' UpdateServerEngineAttributes Text
updateServerEngineAttributes_attributeName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateServerEngineAttributes' {Text
attributeName :: Text
$sel:attributeName:UpdateServerEngineAttributes' :: UpdateServerEngineAttributes -> Text
attributeName} -> Text
attributeName) (\s :: UpdateServerEngineAttributes
s@UpdateServerEngineAttributes' {} Text
a -> UpdateServerEngineAttributes
s {$sel:attributeName:UpdateServerEngineAttributes' :: Text
attributeName = Text
a} :: UpdateServerEngineAttributes)

instance Core.AWSRequest UpdateServerEngineAttributes where
  type
    AWSResponse UpdateServerEngineAttributes =
      UpdateServerEngineAttributesResponse
  request :: (Service -> Service)
-> UpdateServerEngineAttributes
-> Request UpdateServerEngineAttributes
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 UpdateServerEngineAttributes
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse UpdateServerEngineAttributes)))
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 -> UpdateServerEngineAttributesResponse
UpdateServerEngineAttributesResponse'
            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
    UpdateServerEngineAttributes
  where
  hashWithSalt :: Int -> UpdateServerEngineAttributes -> Int
hashWithSalt Int
_salt UpdateServerEngineAttributes' {Maybe Text
Text
attributeName :: Text
serverName :: Text
attributeValue :: Maybe Text
$sel:attributeName:UpdateServerEngineAttributes' :: UpdateServerEngineAttributes -> Text
$sel:serverName:UpdateServerEngineAttributes' :: UpdateServerEngineAttributes -> Text
$sel:attributeValue:UpdateServerEngineAttributes' :: UpdateServerEngineAttributes -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
attributeValue
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
serverName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
attributeName

instance Prelude.NFData UpdateServerEngineAttributes where
  rnf :: UpdateServerEngineAttributes -> ()
rnf UpdateServerEngineAttributes' {Maybe Text
Text
attributeName :: Text
serverName :: Text
attributeValue :: Maybe Text
$sel:attributeName:UpdateServerEngineAttributes' :: UpdateServerEngineAttributes -> Text
$sel:serverName:UpdateServerEngineAttributes' :: UpdateServerEngineAttributes -> Text
$sel:attributeValue:UpdateServerEngineAttributes' :: UpdateServerEngineAttributes -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
attributeValue
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
serverName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
attributeName

instance Data.ToHeaders UpdateServerEngineAttributes where
  toHeaders :: UpdateServerEngineAttributes -> 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.UpdateServerEngineAttributes" ::
                          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 UpdateServerEngineAttributes where
  toJSON :: UpdateServerEngineAttributes -> Value
toJSON UpdateServerEngineAttributes' {Maybe Text
Text
attributeName :: Text
serverName :: Text
attributeValue :: Maybe Text
$sel:attributeName:UpdateServerEngineAttributes' :: UpdateServerEngineAttributes -> Text
$sel:serverName:UpdateServerEngineAttributes' :: UpdateServerEngineAttributes -> Text
$sel:attributeValue:UpdateServerEngineAttributes' :: UpdateServerEngineAttributes -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"AttributeValue" 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
attributeValue,
            forall a. a -> Maybe a
Prelude.Just (Key
"ServerName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
serverName),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"AttributeName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
attributeName)
          ]
      )

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

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

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

-- |
-- Create a value of 'UpdateServerEngineAttributesResponse' 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', 'updateServerEngineAttributesResponse_server' - Contains the response to an @UpdateServerEngineAttributes@ request.
--
-- 'httpStatus', 'updateServerEngineAttributesResponse_httpStatus' - The response's http status code.
newUpdateServerEngineAttributesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateServerEngineAttributesResponse
newUpdateServerEngineAttributesResponse :: Int -> UpdateServerEngineAttributesResponse
newUpdateServerEngineAttributesResponse Int
pHttpStatus_ =
  UpdateServerEngineAttributesResponse'
    { $sel:server:UpdateServerEngineAttributesResponse' :: Maybe Server
server =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UpdateServerEngineAttributesResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

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

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

instance
  Prelude.NFData
    UpdateServerEngineAttributesResponse
  where
  rnf :: UpdateServerEngineAttributesResponse -> ()
rnf UpdateServerEngineAttributesResponse' {Int
Maybe Server
httpStatus :: Int
server :: Maybe Server
$sel:httpStatus:UpdateServerEngineAttributesResponse' :: UpdateServerEngineAttributesResponse -> Int
$sel:server:UpdateServerEngineAttributesResponse' :: UpdateServerEngineAttributesResponse -> 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