{-# 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.OpenSearch.CancelServiceSoftwareUpdate
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Cancels a scheduled service software update for an Amazon OpenSearch
-- Service domain. You can only perform this operation before the
-- @AutomatedUpdateDate@ and when the domain\'s @UpdateStatus@ is
-- @PENDING_UPDATE@. For more information, see
-- <https://docs.aws.amazon.com/opensearch-service/latest/developerguide/service-software.html Service software updates in Amazon OpenSearch Service>.
module Amazonka.OpenSearch.CancelServiceSoftwareUpdate
  ( -- * Creating a Request
    CancelServiceSoftwareUpdate (..),
    newCancelServiceSoftwareUpdate,

    -- * Request Lenses
    cancelServiceSoftwareUpdate_domainName,

    -- * Destructuring the Response
    CancelServiceSoftwareUpdateResponse (..),
    newCancelServiceSoftwareUpdateResponse,

    -- * Response Lenses
    cancelServiceSoftwareUpdateResponse_serviceSoftwareOptions,
    cancelServiceSoftwareUpdateResponse_httpStatus,
  )
where

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

-- | Container for the request parameters to cancel a service software
-- update.
--
-- /See:/ 'newCancelServiceSoftwareUpdate' smart constructor.
data CancelServiceSoftwareUpdate = CancelServiceSoftwareUpdate'
  { -- | Name of the OpenSearch Service domain that you want to cancel the
    -- service software update on.
    CancelServiceSoftwareUpdate -> Text
domainName :: Prelude.Text
  }
  deriving (CancelServiceSoftwareUpdate -> CancelServiceSoftwareUpdate -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CancelServiceSoftwareUpdate -> CancelServiceSoftwareUpdate -> Bool
$c/= :: CancelServiceSoftwareUpdate -> CancelServiceSoftwareUpdate -> Bool
== :: CancelServiceSoftwareUpdate -> CancelServiceSoftwareUpdate -> Bool
$c== :: CancelServiceSoftwareUpdate -> CancelServiceSoftwareUpdate -> Bool
Prelude.Eq, ReadPrec [CancelServiceSoftwareUpdate]
ReadPrec CancelServiceSoftwareUpdate
Int -> ReadS CancelServiceSoftwareUpdate
ReadS [CancelServiceSoftwareUpdate]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CancelServiceSoftwareUpdate]
$creadListPrec :: ReadPrec [CancelServiceSoftwareUpdate]
readPrec :: ReadPrec CancelServiceSoftwareUpdate
$creadPrec :: ReadPrec CancelServiceSoftwareUpdate
readList :: ReadS [CancelServiceSoftwareUpdate]
$creadList :: ReadS [CancelServiceSoftwareUpdate]
readsPrec :: Int -> ReadS CancelServiceSoftwareUpdate
$creadsPrec :: Int -> ReadS CancelServiceSoftwareUpdate
Prelude.Read, Int -> CancelServiceSoftwareUpdate -> ShowS
[CancelServiceSoftwareUpdate] -> ShowS
CancelServiceSoftwareUpdate -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CancelServiceSoftwareUpdate] -> ShowS
$cshowList :: [CancelServiceSoftwareUpdate] -> ShowS
show :: CancelServiceSoftwareUpdate -> String
$cshow :: CancelServiceSoftwareUpdate -> String
showsPrec :: Int -> CancelServiceSoftwareUpdate -> ShowS
$cshowsPrec :: Int -> CancelServiceSoftwareUpdate -> ShowS
Prelude.Show, forall x.
Rep CancelServiceSoftwareUpdate x -> CancelServiceSoftwareUpdate
forall x.
CancelServiceSoftwareUpdate -> Rep CancelServiceSoftwareUpdate x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CancelServiceSoftwareUpdate x -> CancelServiceSoftwareUpdate
$cfrom :: forall x.
CancelServiceSoftwareUpdate -> Rep CancelServiceSoftwareUpdate x
Prelude.Generic)

-- |
-- Create a value of 'CancelServiceSoftwareUpdate' 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:
--
-- 'domainName', 'cancelServiceSoftwareUpdate_domainName' - Name of the OpenSearch Service domain that you want to cancel the
-- service software update on.
newCancelServiceSoftwareUpdate ::
  -- | 'domainName'
  Prelude.Text ->
  CancelServiceSoftwareUpdate
newCancelServiceSoftwareUpdate :: Text -> CancelServiceSoftwareUpdate
newCancelServiceSoftwareUpdate Text
pDomainName_ =
  CancelServiceSoftwareUpdate'
    { $sel:domainName:CancelServiceSoftwareUpdate' :: Text
domainName =
        Text
pDomainName_
    }

-- | Name of the OpenSearch Service domain that you want to cancel the
-- service software update on.
cancelServiceSoftwareUpdate_domainName :: Lens.Lens' CancelServiceSoftwareUpdate Prelude.Text
cancelServiceSoftwareUpdate_domainName :: Lens' CancelServiceSoftwareUpdate Text
cancelServiceSoftwareUpdate_domainName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CancelServiceSoftwareUpdate' {Text
domainName :: Text
$sel:domainName:CancelServiceSoftwareUpdate' :: CancelServiceSoftwareUpdate -> Text
domainName} -> Text
domainName) (\s :: CancelServiceSoftwareUpdate
s@CancelServiceSoftwareUpdate' {} Text
a -> CancelServiceSoftwareUpdate
s {$sel:domainName:CancelServiceSoftwareUpdate' :: Text
domainName = Text
a} :: CancelServiceSoftwareUpdate)

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

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

instance Data.ToHeaders CancelServiceSoftwareUpdate where
  toHeaders :: CancelServiceSoftwareUpdate -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance Data.ToPath CancelServiceSoftwareUpdate where
  toPath :: CancelServiceSoftwareUpdate -> ByteString
toPath =
    forall a b. a -> b -> a
Prelude.const
      ByteString
"/2021-01-01/opensearch/serviceSoftwareUpdate/cancel"

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

-- | Container for the response to a @CancelServiceSoftwareUpdate@ operation.
-- Contains the status of the update.
--
-- /See:/ 'newCancelServiceSoftwareUpdateResponse' smart constructor.
data CancelServiceSoftwareUpdateResponse = CancelServiceSoftwareUpdateResponse'
  { -- | Container for the state of your domain relative to the latest service
    -- software.
    CancelServiceSoftwareUpdateResponse -> Maybe ServiceSoftwareOptions
serviceSoftwareOptions :: Prelude.Maybe ServiceSoftwareOptions,
    -- | The response's http status code.
    CancelServiceSoftwareUpdateResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CancelServiceSoftwareUpdateResponse
-> CancelServiceSoftwareUpdateResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CancelServiceSoftwareUpdateResponse
-> CancelServiceSoftwareUpdateResponse -> Bool
$c/= :: CancelServiceSoftwareUpdateResponse
-> CancelServiceSoftwareUpdateResponse -> Bool
== :: CancelServiceSoftwareUpdateResponse
-> CancelServiceSoftwareUpdateResponse -> Bool
$c== :: CancelServiceSoftwareUpdateResponse
-> CancelServiceSoftwareUpdateResponse -> Bool
Prelude.Eq, ReadPrec [CancelServiceSoftwareUpdateResponse]
ReadPrec CancelServiceSoftwareUpdateResponse
Int -> ReadS CancelServiceSoftwareUpdateResponse
ReadS [CancelServiceSoftwareUpdateResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CancelServiceSoftwareUpdateResponse]
$creadListPrec :: ReadPrec [CancelServiceSoftwareUpdateResponse]
readPrec :: ReadPrec CancelServiceSoftwareUpdateResponse
$creadPrec :: ReadPrec CancelServiceSoftwareUpdateResponse
readList :: ReadS [CancelServiceSoftwareUpdateResponse]
$creadList :: ReadS [CancelServiceSoftwareUpdateResponse]
readsPrec :: Int -> ReadS CancelServiceSoftwareUpdateResponse
$creadsPrec :: Int -> ReadS CancelServiceSoftwareUpdateResponse
Prelude.Read, Int -> CancelServiceSoftwareUpdateResponse -> ShowS
[CancelServiceSoftwareUpdateResponse] -> ShowS
CancelServiceSoftwareUpdateResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CancelServiceSoftwareUpdateResponse] -> ShowS
$cshowList :: [CancelServiceSoftwareUpdateResponse] -> ShowS
show :: CancelServiceSoftwareUpdateResponse -> String
$cshow :: CancelServiceSoftwareUpdateResponse -> String
showsPrec :: Int -> CancelServiceSoftwareUpdateResponse -> ShowS
$cshowsPrec :: Int -> CancelServiceSoftwareUpdateResponse -> ShowS
Prelude.Show, forall x.
Rep CancelServiceSoftwareUpdateResponse x
-> CancelServiceSoftwareUpdateResponse
forall x.
CancelServiceSoftwareUpdateResponse
-> Rep CancelServiceSoftwareUpdateResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CancelServiceSoftwareUpdateResponse x
-> CancelServiceSoftwareUpdateResponse
$cfrom :: forall x.
CancelServiceSoftwareUpdateResponse
-> Rep CancelServiceSoftwareUpdateResponse x
Prelude.Generic)

-- |
-- Create a value of 'CancelServiceSoftwareUpdateResponse' 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:
--
-- 'serviceSoftwareOptions', 'cancelServiceSoftwareUpdateResponse_serviceSoftwareOptions' - Container for the state of your domain relative to the latest service
-- software.
--
-- 'httpStatus', 'cancelServiceSoftwareUpdateResponse_httpStatus' - The response's http status code.
newCancelServiceSoftwareUpdateResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CancelServiceSoftwareUpdateResponse
newCancelServiceSoftwareUpdateResponse :: Int -> CancelServiceSoftwareUpdateResponse
newCancelServiceSoftwareUpdateResponse Int
pHttpStatus_ =
  CancelServiceSoftwareUpdateResponse'
    { $sel:serviceSoftwareOptions:CancelServiceSoftwareUpdateResponse' :: Maybe ServiceSoftwareOptions
serviceSoftwareOptions =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CancelServiceSoftwareUpdateResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Container for the state of your domain relative to the latest service
-- software.
cancelServiceSoftwareUpdateResponse_serviceSoftwareOptions :: Lens.Lens' CancelServiceSoftwareUpdateResponse (Prelude.Maybe ServiceSoftwareOptions)
cancelServiceSoftwareUpdateResponse_serviceSoftwareOptions :: Lens'
  CancelServiceSoftwareUpdateResponse (Maybe ServiceSoftwareOptions)
cancelServiceSoftwareUpdateResponse_serviceSoftwareOptions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CancelServiceSoftwareUpdateResponse' {Maybe ServiceSoftwareOptions
serviceSoftwareOptions :: Maybe ServiceSoftwareOptions
$sel:serviceSoftwareOptions:CancelServiceSoftwareUpdateResponse' :: CancelServiceSoftwareUpdateResponse -> Maybe ServiceSoftwareOptions
serviceSoftwareOptions} -> Maybe ServiceSoftwareOptions
serviceSoftwareOptions) (\s :: CancelServiceSoftwareUpdateResponse
s@CancelServiceSoftwareUpdateResponse' {} Maybe ServiceSoftwareOptions
a -> CancelServiceSoftwareUpdateResponse
s {$sel:serviceSoftwareOptions:CancelServiceSoftwareUpdateResponse' :: Maybe ServiceSoftwareOptions
serviceSoftwareOptions = Maybe ServiceSoftwareOptions
a} :: CancelServiceSoftwareUpdateResponse)

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

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