{-# 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.AutoScaling.CancelInstanceRefresh
-- 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 an instance refresh operation in progress. Cancellation does not
-- roll back any replacements that have already been completed, but it
-- prevents new replacements from being started.
--
-- This operation is part of the
-- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/asg-instance-refresh.html instance refresh feature>
-- in Amazon EC2 Auto Scaling, which helps you update instances in your
-- Auto Scaling group after you make configuration changes.
module Amazonka.AutoScaling.CancelInstanceRefresh
  ( -- * Creating a Request
    CancelInstanceRefresh (..),
    newCancelInstanceRefresh,

    -- * Request Lenses
    cancelInstanceRefresh_autoScalingGroupName,

    -- * Destructuring the Response
    CancelInstanceRefreshResponse (..),
    newCancelInstanceRefreshResponse,

    -- * Response Lenses
    cancelInstanceRefreshResponse_instanceRefreshId,
    cancelInstanceRefreshResponse_httpStatus,
  )
where

import Amazonka.AutoScaling.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:/ 'newCancelInstanceRefresh' smart constructor.
data CancelInstanceRefresh = CancelInstanceRefresh'
  { -- | The name of the Auto Scaling group.
    CancelInstanceRefresh -> Text
autoScalingGroupName :: Prelude.Text
  }
  deriving (CancelInstanceRefresh -> CancelInstanceRefresh -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CancelInstanceRefresh -> CancelInstanceRefresh -> Bool
$c/= :: CancelInstanceRefresh -> CancelInstanceRefresh -> Bool
== :: CancelInstanceRefresh -> CancelInstanceRefresh -> Bool
$c== :: CancelInstanceRefresh -> CancelInstanceRefresh -> Bool
Prelude.Eq, ReadPrec [CancelInstanceRefresh]
ReadPrec CancelInstanceRefresh
Int -> ReadS CancelInstanceRefresh
ReadS [CancelInstanceRefresh]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CancelInstanceRefresh]
$creadListPrec :: ReadPrec [CancelInstanceRefresh]
readPrec :: ReadPrec CancelInstanceRefresh
$creadPrec :: ReadPrec CancelInstanceRefresh
readList :: ReadS [CancelInstanceRefresh]
$creadList :: ReadS [CancelInstanceRefresh]
readsPrec :: Int -> ReadS CancelInstanceRefresh
$creadsPrec :: Int -> ReadS CancelInstanceRefresh
Prelude.Read, Int -> CancelInstanceRefresh -> ShowS
[CancelInstanceRefresh] -> ShowS
CancelInstanceRefresh -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CancelInstanceRefresh] -> ShowS
$cshowList :: [CancelInstanceRefresh] -> ShowS
show :: CancelInstanceRefresh -> String
$cshow :: CancelInstanceRefresh -> String
showsPrec :: Int -> CancelInstanceRefresh -> ShowS
$cshowsPrec :: Int -> CancelInstanceRefresh -> ShowS
Prelude.Show, forall x. Rep CancelInstanceRefresh x -> CancelInstanceRefresh
forall x. CancelInstanceRefresh -> Rep CancelInstanceRefresh x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CancelInstanceRefresh x -> CancelInstanceRefresh
$cfrom :: forall x. CancelInstanceRefresh -> Rep CancelInstanceRefresh x
Prelude.Generic)

-- |
-- Create a value of 'CancelInstanceRefresh' 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:
--
-- 'autoScalingGroupName', 'cancelInstanceRefresh_autoScalingGroupName' - The name of the Auto Scaling group.
newCancelInstanceRefresh ::
  -- | 'autoScalingGroupName'
  Prelude.Text ->
  CancelInstanceRefresh
newCancelInstanceRefresh :: Text -> CancelInstanceRefresh
newCancelInstanceRefresh Text
pAutoScalingGroupName_ =
  CancelInstanceRefresh'
    { $sel:autoScalingGroupName:CancelInstanceRefresh' :: Text
autoScalingGroupName =
        Text
pAutoScalingGroupName_
    }

-- | The name of the Auto Scaling group.
cancelInstanceRefresh_autoScalingGroupName :: Lens.Lens' CancelInstanceRefresh Prelude.Text
cancelInstanceRefresh_autoScalingGroupName :: Lens' CancelInstanceRefresh Text
cancelInstanceRefresh_autoScalingGroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CancelInstanceRefresh' {Text
autoScalingGroupName :: Text
$sel:autoScalingGroupName:CancelInstanceRefresh' :: CancelInstanceRefresh -> Text
autoScalingGroupName} -> Text
autoScalingGroupName) (\s :: CancelInstanceRefresh
s@CancelInstanceRefresh' {} Text
a -> CancelInstanceRefresh
s {$sel:autoScalingGroupName:CancelInstanceRefresh' :: Text
autoScalingGroupName = Text
a} :: CancelInstanceRefresh)

instance Core.AWSRequest CancelInstanceRefresh where
  type
    AWSResponse CancelInstanceRefresh =
      CancelInstanceRefreshResponse
  request :: (Service -> Service)
-> CancelInstanceRefresh -> Request CancelInstanceRefresh
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.postQuery (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy CancelInstanceRefresh
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CancelInstanceRefresh)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
Text
-> (Int
    -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXMLWrapper
      Text
"CancelInstanceRefreshResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe Text -> Int -> CancelInstanceRefreshResponse
CancelInstanceRefreshResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"InstanceRefreshId")
            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 CancelInstanceRefresh where
  hashWithSalt :: Int -> CancelInstanceRefresh -> Int
hashWithSalt Int
_salt CancelInstanceRefresh' {Text
autoScalingGroupName :: Text
$sel:autoScalingGroupName:CancelInstanceRefresh' :: CancelInstanceRefresh -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
autoScalingGroupName

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

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

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

instance Data.ToQuery CancelInstanceRefresh where
  toQuery :: CancelInstanceRefresh -> QueryString
toQuery CancelInstanceRefresh' {Text
autoScalingGroupName :: Text
$sel:autoScalingGroupName:CancelInstanceRefresh' :: CancelInstanceRefresh -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"CancelInstanceRefresh" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2011-01-01" :: Prelude.ByteString),
        ByteString
"AutoScalingGroupName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
autoScalingGroupName
      ]

-- | /See:/ 'newCancelInstanceRefreshResponse' smart constructor.
data CancelInstanceRefreshResponse = CancelInstanceRefreshResponse'
  { -- | The instance refresh ID.
    CancelInstanceRefreshResponse -> Maybe Text
instanceRefreshId :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    CancelInstanceRefreshResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CancelInstanceRefreshResponse
-> CancelInstanceRefreshResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CancelInstanceRefreshResponse
-> CancelInstanceRefreshResponse -> Bool
$c/= :: CancelInstanceRefreshResponse
-> CancelInstanceRefreshResponse -> Bool
== :: CancelInstanceRefreshResponse
-> CancelInstanceRefreshResponse -> Bool
$c== :: CancelInstanceRefreshResponse
-> CancelInstanceRefreshResponse -> Bool
Prelude.Eq, ReadPrec [CancelInstanceRefreshResponse]
ReadPrec CancelInstanceRefreshResponse
Int -> ReadS CancelInstanceRefreshResponse
ReadS [CancelInstanceRefreshResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CancelInstanceRefreshResponse]
$creadListPrec :: ReadPrec [CancelInstanceRefreshResponse]
readPrec :: ReadPrec CancelInstanceRefreshResponse
$creadPrec :: ReadPrec CancelInstanceRefreshResponse
readList :: ReadS [CancelInstanceRefreshResponse]
$creadList :: ReadS [CancelInstanceRefreshResponse]
readsPrec :: Int -> ReadS CancelInstanceRefreshResponse
$creadsPrec :: Int -> ReadS CancelInstanceRefreshResponse
Prelude.Read, Int -> CancelInstanceRefreshResponse -> ShowS
[CancelInstanceRefreshResponse] -> ShowS
CancelInstanceRefreshResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CancelInstanceRefreshResponse] -> ShowS
$cshowList :: [CancelInstanceRefreshResponse] -> ShowS
show :: CancelInstanceRefreshResponse -> String
$cshow :: CancelInstanceRefreshResponse -> String
showsPrec :: Int -> CancelInstanceRefreshResponse -> ShowS
$cshowsPrec :: Int -> CancelInstanceRefreshResponse -> ShowS
Prelude.Show, forall x.
Rep CancelInstanceRefreshResponse x
-> CancelInstanceRefreshResponse
forall x.
CancelInstanceRefreshResponse
-> Rep CancelInstanceRefreshResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CancelInstanceRefreshResponse x
-> CancelInstanceRefreshResponse
$cfrom :: forall x.
CancelInstanceRefreshResponse
-> Rep CancelInstanceRefreshResponse x
Prelude.Generic)

-- |
-- Create a value of 'CancelInstanceRefreshResponse' 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:
--
-- 'instanceRefreshId', 'cancelInstanceRefreshResponse_instanceRefreshId' - The instance refresh ID.
--
-- 'httpStatus', 'cancelInstanceRefreshResponse_httpStatus' - The response's http status code.
newCancelInstanceRefreshResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CancelInstanceRefreshResponse
newCancelInstanceRefreshResponse :: Int -> CancelInstanceRefreshResponse
newCancelInstanceRefreshResponse Int
pHttpStatus_ =
  CancelInstanceRefreshResponse'
    { $sel:instanceRefreshId:CancelInstanceRefreshResponse' :: Maybe Text
instanceRefreshId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CancelInstanceRefreshResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The instance refresh ID.
cancelInstanceRefreshResponse_instanceRefreshId :: Lens.Lens' CancelInstanceRefreshResponse (Prelude.Maybe Prelude.Text)
cancelInstanceRefreshResponse_instanceRefreshId :: Lens' CancelInstanceRefreshResponse (Maybe Text)
cancelInstanceRefreshResponse_instanceRefreshId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CancelInstanceRefreshResponse' {Maybe Text
instanceRefreshId :: Maybe Text
$sel:instanceRefreshId:CancelInstanceRefreshResponse' :: CancelInstanceRefreshResponse -> Maybe Text
instanceRefreshId} -> Maybe Text
instanceRefreshId) (\s :: CancelInstanceRefreshResponse
s@CancelInstanceRefreshResponse' {} Maybe Text
a -> CancelInstanceRefreshResponse
s {$sel:instanceRefreshId:CancelInstanceRefreshResponse' :: Maybe Text
instanceRefreshId = Maybe Text
a} :: CancelInstanceRefreshResponse)

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

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