{-# 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.SSM.CancelMaintenanceWindowExecution
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Stops a maintenance window execution that is already in progress and
-- cancels any tasks in the window that haven\'t already starting running.
-- Tasks already in progress will continue to completion.
module Amazonka.SSM.CancelMaintenanceWindowExecution
  ( -- * Creating a Request
    CancelMaintenanceWindowExecution (..),
    newCancelMaintenanceWindowExecution,

    -- * Request Lenses
    cancelMaintenanceWindowExecution_windowExecutionId,

    -- * Destructuring the Response
    CancelMaintenanceWindowExecutionResponse (..),
    newCancelMaintenanceWindowExecutionResponse,

    -- * Response Lenses
    cancelMaintenanceWindowExecutionResponse_windowExecutionId,
    cancelMaintenanceWindowExecutionResponse_httpStatus,
  )
where

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
import Amazonka.SSM.Types

-- | /See:/ 'newCancelMaintenanceWindowExecution' smart constructor.
data CancelMaintenanceWindowExecution = CancelMaintenanceWindowExecution'
  { -- | The ID of the maintenance window execution to stop.
    CancelMaintenanceWindowExecution -> Text
windowExecutionId :: Prelude.Text
  }
  deriving (CancelMaintenanceWindowExecution
-> CancelMaintenanceWindowExecution -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CancelMaintenanceWindowExecution
-> CancelMaintenanceWindowExecution -> Bool
$c/= :: CancelMaintenanceWindowExecution
-> CancelMaintenanceWindowExecution -> Bool
== :: CancelMaintenanceWindowExecution
-> CancelMaintenanceWindowExecution -> Bool
$c== :: CancelMaintenanceWindowExecution
-> CancelMaintenanceWindowExecution -> Bool
Prelude.Eq, ReadPrec [CancelMaintenanceWindowExecution]
ReadPrec CancelMaintenanceWindowExecution
Int -> ReadS CancelMaintenanceWindowExecution
ReadS [CancelMaintenanceWindowExecution]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CancelMaintenanceWindowExecution]
$creadListPrec :: ReadPrec [CancelMaintenanceWindowExecution]
readPrec :: ReadPrec CancelMaintenanceWindowExecution
$creadPrec :: ReadPrec CancelMaintenanceWindowExecution
readList :: ReadS [CancelMaintenanceWindowExecution]
$creadList :: ReadS [CancelMaintenanceWindowExecution]
readsPrec :: Int -> ReadS CancelMaintenanceWindowExecution
$creadsPrec :: Int -> ReadS CancelMaintenanceWindowExecution
Prelude.Read, Int -> CancelMaintenanceWindowExecution -> ShowS
[CancelMaintenanceWindowExecution] -> ShowS
CancelMaintenanceWindowExecution -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CancelMaintenanceWindowExecution] -> ShowS
$cshowList :: [CancelMaintenanceWindowExecution] -> ShowS
show :: CancelMaintenanceWindowExecution -> String
$cshow :: CancelMaintenanceWindowExecution -> String
showsPrec :: Int -> CancelMaintenanceWindowExecution -> ShowS
$cshowsPrec :: Int -> CancelMaintenanceWindowExecution -> ShowS
Prelude.Show, forall x.
Rep CancelMaintenanceWindowExecution x
-> CancelMaintenanceWindowExecution
forall x.
CancelMaintenanceWindowExecution
-> Rep CancelMaintenanceWindowExecution x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CancelMaintenanceWindowExecution x
-> CancelMaintenanceWindowExecution
$cfrom :: forall x.
CancelMaintenanceWindowExecution
-> Rep CancelMaintenanceWindowExecution x
Prelude.Generic)

-- |
-- Create a value of 'CancelMaintenanceWindowExecution' 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:
--
-- 'windowExecutionId', 'cancelMaintenanceWindowExecution_windowExecutionId' - The ID of the maintenance window execution to stop.
newCancelMaintenanceWindowExecution ::
  -- | 'windowExecutionId'
  Prelude.Text ->
  CancelMaintenanceWindowExecution
newCancelMaintenanceWindowExecution :: Text -> CancelMaintenanceWindowExecution
newCancelMaintenanceWindowExecution
  Text
pWindowExecutionId_ =
    CancelMaintenanceWindowExecution'
      { $sel:windowExecutionId:CancelMaintenanceWindowExecution' :: Text
windowExecutionId =
          Text
pWindowExecutionId_
      }

-- | The ID of the maintenance window execution to stop.
cancelMaintenanceWindowExecution_windowExecutionId :: Lens.Lens' CancelMaintenanceWindowExecution Prelude.Text
cancelMaintenanceWindowExecution_windowExecutionId :: Lens' CancelMaintenanceWindowExecution Text
cancelMaintenanceWindowExecution_windowExecutionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CancelMaintenanceWindowExecution' {Text
windowExecutionId :: Text
$sel:windowExecutionId:CancelMaintenanceWindowExecution' :: CancelMaintenanceWindowExecution -> Text
windowExecutionId} -> Text
windowExecutionId) (\s :: CancelMaintenanceWindowExecution
s@CancelMaintenanceWindowExecution' {} Text
a -> CancelMaintenanceWindowExecution
s {$sel:windowExecutionId:CancelMaintenanceWindowExecution' :: Text
windowExecutionId = Text
a} :: CancelMaintenanceWindowExecution)

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

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

instance
  Data.ToHeaders
    CancelMaintenanceWindowExecution
  where
  toHeaders :: CancelMaintenanceWindowExecution -> 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
"AmazonSSM.CancelMaintenanceWindowExecution" ::
                          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 CancelMaintenanceWindowExecution where
  toJSON :: CancelMaintenanceWindowExecution -> Value
toJSON CancelMaintenanceWindowExecution' {Text
windowExecutionId :: Text
$sel:windowExecutionId:CancelMaintenanceWindowExecution' :: CancelMaintenanceWindowExecution -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just
              (Key
"WindowExecutionId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
windowExecutionId)
          ]
      )

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

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

-- | /See:/ 'newCancelMaintenanceWindowExecutionResponse' smart constructor.
data CancelMaintenanceWindowExecutionResponse = CancelMaintenanceWindowExecutionResponse'
  { -- | The ID of the maintenance window execution that has been stopped.
    CancelMaintenanceWindowExecutionResponse -> Maybe Text
windowExecutionId :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    CancelMaintenanceWindowExecutionResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CancelMaintenanceWindowExecutionResponse
-> CancelMaintenanceWindowExecutionResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CancelMaintenanceWindowExecutionResponse
-> CancelMaintenanceWindowExecutionResponse -> Bool
$c/= :: CancelMaintenanceWindowExecutionResponse
-> CancelMaintenanceWindowExecutionResponse -> Bool
== :: CancelMaintenanceWindowExecutionResponse
-> CancelMaintenanceWindowExecutionResponse -> Bool
$c== :: CancelMaintenanceWindowExecutionResponse
-> CancelMaintenanceWindowExecutionResponse -> Bool
Prelude.Eq, ReadPrec [CancelMaintenanceWindowExecutionResponse]
ReadPrec CancelMaintenanceWindowExecutionResponse
Int -> ReadS CancelMaintenanceWindowExecutionResponse
ReadS [CancelMaintenanceWindowExecutionResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CancelMaintenanceWindowExecutionResponse]
$creadListPrec :: ReadPrec [CancelMaintenanceWindowExecutionResponse]
readPrec :: ReadPrec CancelMaintenanceWindowExecutionResponse
$creadPrec :: ReadPrec CancelMaintenanceWindowExecutionResponse
readList :: ReadS [CancelMaintenanceWindowExecutionResponse]
$creadList :: ReadS [CancelMaintenanceWindowExecutionResponse]
readsPrec :: Int -> ReadS CancelMaintenanceWindowExecutionResponse
$creadsPrec :: Int -> ReadS CancelMaintenanceWindowExecutionResponse
Prelude.Read, Int -> CancelMaintenanceWindowExecutionResponse -> ShowS
[CancelMaintenanceWindowExecutionResponse] -> ShowS
CancelMaintenanceWindowExecutionResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CancelMaintenanceWindowExecutionResponse] -> ShowS
$cshowList :: [CancelMaintenanceWindowExecutionResponse] -> ShowS
show :: CancelMaintenanceWindowExecutionResponse -> String
$cshow :: CancelMaintenanceWindowExecutionResponse -> String
showsPrec :: Int -> CancelMaintenanceWindowExecutionResponse -> ShowS
$cshowsPrec :: Int -> CancelMaintenanceWindowExecutionResponse -> ShowS
Prelude.Show, forall x.
Rep CancelMaintenanceWindowExecutionResponse x
-> CancelMaintenanceWindowExecutionResponse
forall x.
CancelMaintenanceWindowExecutionResponse
-> Rep CancelMaintenanceWindowExecutionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CancelMaintenanceWindowExecutionResponse x
-> CancelMaintenanceWindowExecutionResponse
$cfrom :: forall x.
CancelMaintenanceWindowExecutionResponse
-> Rep CancelMaintenanceWindowExecutionResponse x
Prelude.Generic)

-- |
-- Create a value of 'CancelMaintenanceWindowExecutionResponse' 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:
--
-- 'windowExecutionId', 'cancelMaintenanceWindowExecutionResponse_windowExecutionId' - The ID of the maintenance window execution that has been stopped.
--
-- 'httpStatus', 'cancelMaintenanceWindowExecutionResponse_httpStatus' - The response's http status code.
newCancelMaintenanceWindowExecutionResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CancelMaintenanceWindowExecutionResponse
newCancelMaintenanceWindowExecutionResponse :: Int -> CancelMaintenanceWindowExecutionResponse
newCancelMaintenanceWindowExecutionResponse
  Int
pHttpStatus_ =
    CancelMaintenanceWindowExecutionResponse'
      { $sel:windowExecutionId:CancelMaintenanceWindowExecutionResponse' :: Maybe Text
windowExecutionId =
          forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:CancelMaintenanceWindowExecutionResponse' :: Int
httpStatus = Int
pHttpStatus_
      }

-- | The ID of the maintenance window execution that has been stopped.
cancelMaintenanceWindowExecutionResponse_windowExecutionId :: Lens.Lens' CancelMaintenanceWindowExecutionResponse (Prelude.Maybe Prelude.Text)
cancelMaintenanceWindowExecutionResponse_windowExecutionId :: Lens' CancelMaintenanceWindowExecutionResponse (Maybe Text)
cancelMaintenanceWindowExecutionResponse_windowExecutionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CancelMaintenanceWindowExecutionResponse' {Maybe Text
windowExecutionId :: Maybe Text
$sel:windowExecutionId:CancelMaintenanceWindowExecutionResponse' :: CancelMaintenanceWindowExecutionResponse -> Maybe Text
windowExecutionId} -> Maybe Text
windowExecutionId) (\s :: CancelMaintenanceWindowExecutionResponse
s@CancelMaintenanceWindowExecutionResponse' {} Maybe Text
a -> CancelMaintenanceWindowExecutionResponse
s {$sel:windowExecutionId:CancelMaintenanceWindowExecutionResponse' :: Maybe Text
windowExecutionId = Maybe Text
a} :: CancelMaintenanceWindowExecutionResponse)

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

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