{-# 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.DrS.StopFailback
-- 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 the failback process for a specified Recovery Instance. This
-- changes the Failback State of the Recovery Instance back to
-- FAILBACK_NOT_STARTED.
module Amazonka.DrS.StopFailback
  ( -- * Creating a Request
    StopFailback (..),
    newStopFailback,

    -- * Request Lenses
    stopFailback_recoveryInstanceID,

    -- * Destructuring the Response
    StopFailbackResponse (..),
    newStopFailbackResponse,
  )
where

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

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

-- |
-- Create a value of 'StopFailback' 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:
--
-- 'recoveryInstanceID', 'stopFailback_recoveryInstanceID' - The ID of the Recovery Instance we want to stop failback for.
newStopFailback ::
  -- | 'recoveryInstanceID'
  Prelude.Text ->
  StopFailback
newStopFailback :: Text -> StopFailback
newStopFailback Text
pRecoveryInstanceID_ =
  StopFailback'
    { $sel:recoveryInstanceID:StopFailback' :: Text
recoveryInstanceID =
        Text
pRecoveryInstanceID_
    }

-- | The ID of the Recovery Instance we want to stop failback for.
stopFailback_recoveryInstanceID :: Lens.Lens' StopFailback Prelude.Text
stopFailback_recoveryInstanceID :: Lens' StopFailback Text
stopFailback_recoveryInstanceID = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StopFailback' {Text
recoveryInstanceID :: Text
$sel:recoveryInstanceID:StopFailback' :: StopFailback -> Text
recoveryInstanceID} -> Text
recoveryInstanceID) (\s :: StopFailback
s@StopFailback' {} Text
a -> StopFailback
s {$sel:recoveryInstanceID:StopFailback' :: Text
recoveryInstanceID = Text
a} :: StopFailback)

instance Core.AWSRequest StopFailback where
  type AWSResponse StopFailback = StopFailbackResponse
  request :: (Service -> Service) -> StopFailback -> Request StopFailback
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 StopFailback
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse StopFailback)))
response = forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull StopFailbackResponse
StopFailbackResponse'

instance Prelude.Hashable StopFailback where
  hashWithSalt :: Int -> StopFailback -> Int
hashWithSalt Int
_salt StopFailback' {Text
recoveryInstanceID :: Text
$sel:recoveryInstanceID:StopFailback' :: StopFailback -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
recoveryInstanceID

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

instance Data.ToHeaders StopFailback where
  toHeaders :: StopFailback -> [Header]
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> [Header]
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

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

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

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

-- | /See:/ 'newStopFailbackResponse' smart constructor.
data StopFailbackResponse = StopFailbackResponse'
  {
  }
  deriving (StopFailbackResponse -> StopFailbackResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StopFailbackResponse -> StopFailbackResponse -> Bool
$c/= :: StopFailbackResponse -> StopFailbackResponse -> Bool
== :: StopFailbackResponse -> StopFailbackResponse -> Bool
$c== :: StopFailbackResponse -> StopFailbackResponse -> Bool
Prelude.Eq, ReadPrec [StopFailbackResponse]
ReadPrec StopFailbackResponse
Int -> ReadS StopFailbackResponse
ReadS [StopFailbackResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StopFailbackResponse]
$creadListPrec :: ReadPrec [StopFailbackResponse]
readPrec :: ReadPrec StopFailbackResponse
$creadPrec :: ReadPrec StopFailbackResponse
readList :: ReadS [StopFailbackResponse]
$creadList :: ReadS [StopFailbackResponse]
readsPrec :: Int -> ReadS StopFailbackResponse
$creadsPrec :: Int -> ReadS StopFailbackResponse
Prelude.Read, Int -> StopFailbackResponse -> ShowS
[StopFailbackResponse] -> ShowS
StopFailbackResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StopFailbackResponse] -> ShowS
$cshowList :: [StopFailbackResponse] -> ShowS
show :: StopFailbackResponse -> String
$cshow :: StopFailbackResponse -> String
showsPrec :: Int -> StopFailbackResponse -> ShowS
$cshowsPrec :: Int -> StopFailbackResponse -> ShowS
Prelude.Show, forall x. Rep StopFailbackResponse x -> StopFailbackResponse
forall x. StopFailbackResponse -> Rep StopFailbackResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StopFailbackResponse x -> StopFailbackResponse
$cfrom :: forall x. StopFailbackResponse -> Rep StopFailbackResponse x
Prelude.Generic)

-- |
-- Create a value of 'StopFailbackResponse' 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.
newStopFailbackResponse ::
  StopFailbackResponse
newStopFailbackResponse :: StopFailbackResponse
newStopFailbackResponse = StopFailbackResponse
StopFailbackResponse'

instance Prelude.NFData StopFailbackResponse where
  rnf :: StopFailbackResponse -> ()
rnf StopFailbackResponse
_ = ()