{-# 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.BackupGateway.UpdateGatewaySoftwareNow
-- 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 the gateway virtual machine (VM) software. The request
-- immediately triggers the software update.
--
-- When you make this request, you get a @200 OK@ success response
-- immediately. However, it might take some time for the update to
-- complete.
module Amazonka.BackupGateway.UpdateGatewaySoftwareNow
  ( -- * Creating a Request
    UpdateGatewaySoftwareNow (..),
    newUpdateGatewaySoftwareNow,

    -- * Request Lenses
    updateGatewaySoftwareNow_gatewayArn,

    -- * Destructuring the Response
    UpdateGatewaySoftwareNowResponse (..),
    newUpdateGatewaySoftwareNowResponse,

    -- * Response Lenses
    updateGatewaySoftwareNowResponse_gatewayArn,
    updateGatewaySoftwareNowResponse_httpStatus,
  )
where

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

-- | /See:/ 'newUpdateGatewaySoftwareNow' smart constructor.
data UpdateGatewaySoftwareNow = UpdateGatewaySoftwareNow'
  { -- | The Amazon Resource Name (ARN) of the gateway to be updated.
    UpdateGatewaySoftwareNow -> Text
gatewayArn :: Prelude.Text
  }
  deriving (UpdateGatewaySoftwareNow -> UpdateGatewaySoftwareNow -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateGatewaySoftwareNow -> UpdateGatewaySoftwareNow -> Bool
$c/= :: UpdateGatewaySoftwareNow -> UpdateGatewaySoftwareNow -> Bool
== :: UpdateGatewaySoftwareNow -> UpdateGatewaySoftwareNow -> Bool
$c== :: UpdateGatewaySoftwareNow -> UpdateGatewaySoftwareNow -> Bool
Prelude.Eq, ReadPrec [UpdateGatewaySoftwareNow]
ReadPrec UpdateGatewaySoftwareNow
Int -> ReadS UpdateGatewaySoftwareNow
ReadS [UpdateGatewaySoftwareNow]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateGatewaySoftwareNow]
$creadListPrec :: ReadPrec [UpdateGatewaySoftwareNow]
readPrec :: ReadPrec UpdateGatewaySoftwareNow
$creadPrec :: ReadPrec UpdateGatewaySoftwareNow
readList :: ReadS [UpdateGatewaySoftwareNow]
$creadList :: ReadS [UpdateGatewaySoftwareNow]
readsPrec :: Int -> ReadS UpdateGatewaySoftwareNow
$creadsPrec :: Int -> ReadS UpdateGatewaySoftwareNow
Prelude.Read, Int -> UpdateGatewaySoftwareNow -> ShowS
[UpdateGatewaySoftwareNow] -> ShowS
UpdateGatewaySoftwareNow -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateGatewaySoftwareNow] -> ShowS
$cshowList :: [UpdateGatewaySoftwareNow] -> ShowS
show :: UpdateGatewaySoftwareNow -> String
$cshow :: UpdateGatewaySoftwareNow -> String
showsPrec :: Int -> UpdateGatewaySoftwareNow -> ShowS
$cshowsPrec :: Int -> UpdateGatewaySoftwareNow -> ShowS
Prelude.Show, forall x.
Rep UpdateGatewaySoftwareNow x -> UpdateGatewaySoftwareNow
forall x.
UpdateGatewaySoftwareNow -> Rep UpdateGatewaySoftwareNow x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateGatewaySoftwareNow x -> UpdateGatewaySoftwareNow
$cfrom :: forall x.
UpdateGatewaySoftwareNow -> Rep UpdateGatewaySoftwareNow x
Prelude.Generic)

-- |
-- Create a value of 'UpdateGatewaySoftwareNow' 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:
--
-- 'gatewayArn', 'updateGatewaySoftwareNow_gatewayArn' - The Amazon Resource Name (ARN) of the gateway to be updated.
newUpdateGatewaySoftwareNow ::
  -- | 'gatewayArn'
  Prelude.Text ->
  UpdateGatewaySoftwareNow
newUpdateGatewaySoftwareNow :: Text -> UpdateGatewaySoftwareNow
newUpdateGatewaySoftwareNow Text
pGatewayArn_ =
  UpdateGatewaySoftwareNow'
    { $sel:gatewayArn:UpdateGatewaySoftwareNow' :: Text
gatewayArn =
        Text
pGatewayArn_
    }

-- | The Amazon Resource Name (ARN) of the gateway to be updated.
updateGatewaySoftwareNow_gatewayArn :: Lens.Lens' UpdateGatewaySoftwareNow Prelude.Text
updateGatewaySoftwareNow_gatewayArn :: Lens' UpdateGatewaySoftwareNow Text
updateGatewaySoftwareNow_gatewayArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateGatewaySoftwareNow' {Text
gatewayArn :: Text
$sel:gatewayArn:UpdateGatewaySoftwareNow' :: UpdateGatewaySoftwareNow -> Text
gatewayArn} -> Text
gatewayArn) (\s :: UpdateGatewaySoftwareNow
s@UpdateGatewaySoftwareNow' {} Text
a -> UpdateGatewaySoftwareNow
s {$sel:gatewayArn:UpdateGatewaySoftwareNow' :: Text
gatewayArn = Text
a} :: UpdateGatewaySoftwareNow)

instance Core.AWSRequest UpdateGatewaySoftwareNow where
  type
    AWSResponse UpdateGatewaySoftwareNow =
      UpdateGatewaySoftwareNowResponse
  request :: (Service -> Service)
-> UpdateGatewaySoftwareNow -> Request UpdateGatewaySoftwareNow
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 UpdateGatewaySoftwareNow
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse UpdateGatewaySoftwareNow)))
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 Text -> Int -> UpdateGatewaySoftwareNowResponse
UpdateGatewaySoftwareNowResponse'
            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
"GatewayArn")
            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 UpdateGatewaySoftwareNow where
  hashWithSalt :: Int -> UpdateGatewaySoftwareNow -> Int
hashWithSalt Int
_salt UpdateGatewaySoftwareNow' {Text
gatewayArn :: Text
$sel:gatewayArn:UpdateGatewaySoftwareNow' :: UpdateGatewaySoftwareNow -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
gatewayArn

instance Prelude.NFData UpdateGatewaySoftwareNow where
  rnf :: UpdateGatewaySoftwareNow -> ()
rnf UpdateGatewaySoftwareNow' {Text
gatewayArn :: Text
$sel:gatewayArn:UpdateGatewaySoftwareNow' :: UpdateGatewaySoftwareNow -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
gatewayArn

instance Data.ToHeaders UpdateGatewaySoftwareNow where
  toHeaders :: UpdateGatewaySoftwareNow -> 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
"BackupOnPremises_v20210101.UpdateGatewaySoftwareNow" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.0" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON UpdateGatewaySoftwareNow where
  toJSON :: UpdateGatewaySoftwareNow -> Value
toJSON UpdateGatewaySoftwareNow' {Text
gatewayArn :: Text
$sel:gatewayArn:UpdateGatewaySoftwareNow' :: UpdateGatewaySoftwareNow -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [forall a. a -> Maybe a
Prelude.Just (Key
"GatewayArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
gatewayArn)]
      )

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

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

-- | /See:/ 'newUpdateGatewaySoftwareNowResponse' smart constructor.
data UpdateGatewaySoftwareNowResponse = UpdateGatewaySoftwareNowResponse'
  { -- | The Amazon Resource Name (ARN) of the gateway you updated.
    UpdateGatewaySoftwareNowResponse -> Maybe Text
gatewayArn :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    UpdateGatewaySoftwareNowResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (UpdateGatewaySoftwareNowResponse
-> UpdateGatewaySoftwareNowResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateGatewaySoftwareNowResponse
-> UpdateGatewaySoftwareNowResponse -> Bool
$c/= :: UpdateGatewaySoftwareNowResponse
-> UpdateGatewaySoftwareNowResponse -> Bool
== :: UpdateGatewaySoftwareNowResponse
-> UpdateGatewaySoftwareNowResponse -> Bool
$c== :: UpdateGatewaySoftwareNowResponse
-> UpdateGatewaySoftwareNowResponse -> Bool
Prelude.Eq, ReadPrec [UpdateGatewaySoftwareNowResponse]
ReadPrec UpdateGatewaySoftwareNowResponse
Int -> ReadS UpdateGatewaySoftwareNowResponse
ReadS [UpdateGatewaySoftwareNowResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateGatewaySoftwareNowResponse]
$creadListPrec :: ReadPrec [UpdateGatewaySoftwareNowResponse]
readPrec :: ReadPrec UpdateGatewaySoftwareNowResponse
$creadPrec :: ReadPrec UpdateGatewaySoftwareNowResponse
readList :: ReadS [UpdateGatewaySoftwareNowResponse]
$creadList :: ReadS [UpdateGatewaySoftwareNowResponse]
readsPrec :: Int -> ReadS UpdateGatewaySoftwareNowResponse
$creadsPrec :: Int -> ReadS UpdateGatewaySoftwareNowResponse
Prelude.Read, Int -> UpdateGatewaySoftwareNowResponse -> ShowS
[UpdateGatewaySoftwareNowResponse] -> ShowS
UpdateGatewaySoftwareNowResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateGatewaySoftwareNowResponse] -> ShowS
$cshowList :: [UpdateGatewaySoftwareNowResponse] -> ShowS
show :: UpdateGatewaySoftwareNowResponse -> String
$cshow :: UpdateGatewaySoftwareNowResponse -> String
showsPrec :: Int -> UpdateGatewaySoftwareNowResponse -> ShowS
$cshowsPrec :: Int -> UpdateGatewaySoftwareNowResponse -> ShowS
Prelude.Show, forall x.
Rep UpdateGatewaySoftwareNowResponse x
-> UpdateGatewaySoftwareNowResponse
forall x.
UpdateGatewaySoftwareNowResponse
-> Rep UpdateGatewaySoftwareNowResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateGatewaySoftwareNowResponse x
-> UpdateGatewaySoftwareNowResponse
$cfrom :: forall x.
UpdateGatewaySoftwareNowResponse
-> Rep UpdateGatewaySoftwareNowResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateGatewaySoftwareNowResponse' 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:
--
-- 'gatewayArn', 'updateGatewaySoftwareNowResponse_gatewayArn' - The Amazon Resource Name (ARN) of the gateway you updated.
--
-- 'httpStatus', 'updateGatewaySoftwareNowResponse_httpStatus' - The response's http status code.
newUpdateGatewaySoftwareNowResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateGatewaySoftwareNowResponse
newUpdateGatewaySoftwareNowResponse :: Int -> UpdateGatewaySoftwareNowResponse
newUpdateGatewaySoftwareNowResponse Int
pHttpStatus_ =
  UpdateGatewaySoftwareNowResponse'
    { $sel:gatewayArn:UpdateGatewaySoftwareNowResponse' :: Maybe Text
gatewayArn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UpdateGatewaySoftwareNowResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The Amazon Resource Name (ARN) of the gateway you updated.
updateGatewaySoftwareNowResponse_gatewayArn :: Lens.Lens' UpdateGatewaySoftwareNowResponse (Prelude.Maybe Prelude.Text)
updateGatewaySoftwareNowResponse_gatewayArn :: Lens' UpdateGatewaySoftwareNowResponse (Maybe Text)
updateGatewaySoftwareNowResponse_gatewayArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateGatewaySoftwareNowResponse' {Maybe Text
gatewayArn :: Maybe Text
$sel:gatewayArn:UpdateGatewaySoftwareNowResponse' :: UpdateGatewaySoftwareNowResponse -> Maybe Text
gatewayArn} -> Maybe Text
gatewayArn) (\s :: UpdateGatewaySoftwareNowResponse
s@UpdateGatewaySoftwareNowResponse' {} Maybe Text
a -> UpdateGatewaySoftwareNowResponse
s {$sel:gatewayArn:UpdateGatewaySoftwareNowResponse' :: Maybe Text
gatewayArn = Maybe Text
a} :: UpdateGatewaySoftwareNowResponse)

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

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