{-# 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.StartMaintenance
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Manually starts server maintenance. This command can be useful if an
-- earlier maintenance attempt failed, and the underlying cause of
-- maintenance failure has been resolved. The server is in an
-- @UNDER_MAINTENANCE@ state while maintenance is in progress.
--
-- Maintenance can only be started on servers in @HEALTHY@ and @UNHEALTHY@
-- states. Otherwise, an @InvalidStateException@ is thrown. 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.StartMaintenance
  ( -- * Creating a Request
    StartMaintenance (..),
    newStartMaintenance,

    -- * Request Lenses
    startMaintenance_engineAttributes,
    startMaintenance_serverName,

    -- * Destructuring the Response
    StartMaintenanceResponse (..),
    newStartMaintenanceResponse,

    -- * Response Lenses
    startMaintenanceResponse_server,
    startMaintenanceResponse_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:/ 'newStartMaintenance' smart constructor.
data StartMaintenance = StartMaintenance'
  { -- | Engine attributes that are specific to the server on which you want to
    -- run maintenance.
    --
    -- __Attributes accepted in a StartMaintenance request for Chef__
    --
    -- -   @CHEF_MAJOR_UPGRADE@: If a Chef Automate server is eligible for
    --     upgrade to Chef Automate 2, add this engine attribute to a
    --     @StartMaintenance@ request and set the value to @true@ to upgrade
    --     the server to Chef Automate 2. For more information, see
    --     <https://docs.aws.amazon.com/opsworks/latest/userguide/opscm-a2upgrade.html Upgrade an AWS OpsWorks for Chef Automate Server to Chef Automate 2>.
    StartMaintenance -> Maybe [EngineAttribute]
engineAttributes :: Prelude.Maybe [EngineAttribute],
    -- | The name of the server on which to run maintenance.
    StartMaintenance -> Text
serverName :: Prelude.Text
  }
  deriving (StartMaintenance -> StartMaintenance -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StartMaintenance -> StartMaintenance -> Bool
$c/= :: StartMaintenance -> StartMaintenance -> Bool
== :: StartMaintenance -> StartMaintenance -> Bool
$c== :: StartMaintenance -> StartMaintenance -> Bool
Prelude.Eq, Int -> StartMaintenance -> ShowS
[StartMaintenance] -> ShowS
StartMaintenance -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StartMaintenance] -> ShowS
$cshowList :: [StartMaintenance] -> ShowS
show :: StartMaintenance -> String
$cshow :: StartMaintenance -> String
showsPrec :: Int -> StartMaintenance -> ShowS
$cshowsPrec :: Int -> StartMaintenance -> ShowS
Prelude.Show, forall x. Rep StartMaintenance x -> StartMaintenance
forall x. StartMaintenance -> Rep StartMaintenance x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StartMaintenance x -> StartMaintenance
$cfrom :: forall x. StartMaintenance -> Rep StartMaintenance x
Prelude.Generic)

-- |
-- Create a value of 'StartMaintenance' 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:
--
-- 'engineAttributes', 'startMaintenance_engineAttributes' - Engine attributes that are specific to the server on which you want to
-- run maintenance.
--
-- __Attributes accepted in a StartMaintenance request for Chef__
--
-- -   @CHEF_MAJOR_UPGRADE@: If a Chef Automate server is eligible for
--     upgrade to Chef Automate 2, add this engine attribute to a
--     @StartMaintenance@ request and set the value to @true@ to upgrade
--     the server to Chef Automate 2. For more information, see
--     <https://docs.aws.amazon.com/opsworks/latest/userguide/opscm-a2upgrade.html Upgrade an AWS OpsWorks for Chef Automate Server to Chef Automate 2>.
--
-- 'serverName', 'startMaintenance_serverName' - The name of the server on which to run maintenance.
newStartMaintenance ::
  -- | 'serverName'
  Prelude.Text ->
  StartMaintenance
newStartMaintenance :: Text -> StartMaintenance
newStartMaintenance Text
pServerName_ =
  StartMaintenance'
    { $sel:engineAttributes:StartMaintenance' :: Maybe [EngineAttribute]
engineAttributes =
        forall a. Maybe a
Prelude.Nothing,
      $sel:serverName:StartMaintenance' :: Text
serverName = Text
pServerName_
    }

-- | Engine attributes that are specific to the server on which you want to
-- run maintenance.
--
-- __Attributes accepted in a StartMaintenance request for Chef__
--
-- -   @CHEF_MAJOR_UPGRADE@: If a Chef Automate server is eligible for
--     upgrade to Chef Automate 2, add this engine attribute to a
--     @StartMaintenance@ request and set the value to @true@ to upgrade
--     the server to Chef Automate 2. For more information, see
--     <https://docs.aws.amazon.com/opsworks/latest/userguide/opscm-a2upgrade.html Upgrade an AWS OpsWorks for Chef Automate Server to Chef Automate 2>.
startMaintenance_engineAttributes :: Lens.Lens' StartMaintenance (Prelude.Maybe [EngineAttribute])
startMaintenance_engineAttributes :: Lens' StartMaintenance (Maybe [EngineAttribute])
startMaintenance_engineAttributes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartMaintenance' {Maybe [EngineAttribute]
engineAttributes :: Maybe [EngineAttribute]
$sel:engineAttributes:StartMaintenance' :: StartMaintenance -> Maybe [EngineAttribute]
engineAttributes} -> Maybe [EngineAttribute]
engineAttributes) (\s :: StartMaintenance
s@StartMaintenance' {} Maybe [EngineAttribute]
a -> StartMaintenance
s {$sel:engineAttributes:StartMaintenance' :: Maybe [EngineAttribute]
engineAttributes = Maybe [EngineAttribute]
a} :: StartMaintenance) 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 on which to run maintenance.
startMaintenance_serverName :: Lens.Lens' StartMaintenance Prelude.Text
startMaintenance_serverName :: Lens' StartMaintenance Text
startMaintenance_serverName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartMaintenance' {Text
serverName :: Text
$sel:serverName:StartMaintenance' :: StartMaintenance -> Text
serverName} -> Text
serverName) (\s :: StartMaintenance
s@StartMaintenance' {} Text
a -> StartMaintenance
s {$sel:serverName:StartMaintenance' :: Text
serverName = Text
a} :: StartMaintenance)

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

instance Prelude.NFData StartMaintenance where
  rnf :: StartMaintenance -> ()
rnf StartMaintenance' {Maybe [EngineAttribute]
Text
serverName :: Text
engineAttributes :: Maybe [EngineAttribute]
$sel:serverName:StartMaintenance' :: StartMaintenance -> Text
$sel:engineAttributes:StartMaintenance' :: StartMaintenance -> Maybe [EngineAttribute]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [EngineAttribute]
engineAttributes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
serverName

instance Data.ToHeaders StartMaintenance where
  toHeaders :: StartMaintenance -> 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.StartMaintenance" ::
                          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 StartMaintenance where
  toJSON :: StartMaintenance -> Value
toJSON StartMaintenance' {Maybe [EngineAttribute]
Text
serverName :: Text
engineAttributes :: Maybe [EngineAttribute]
$sel:serverName:StartMaintenance' :: StartMaintenance -> Text
$sel:engineAttributes:StartMaintenance' :: StartMaintenance -> Maybe [EngineAttribute]
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"EngineAttributes" 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 [EngineAttribute]
engineAttributes,
            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 StartMaintenance where
  toPath :: StartMaintenance -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

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

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

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

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

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