{-# 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.MGN.FinalizeCutover
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Finalizes the cutover immediately for specific Source Servers. All AWS
-- resources created by Application Migration Service for enabling the
-- replication of these source servers will be terminated \/ deleted within
-- 90 minutes. Launched Test or Cutover instances will NOT be terminated.
-- The AWS Replication Agent will receive a command to uninstall itself
-- (within 10 minutes). The following properties of the SourceServer will
-- be changed immediately: dataReplicationInfo.dataReplicationState will be
-- changed to DISCONNECTED; The SourceServer.lifeCycle.state will be
-- changed to CUTOVER; The totalStorageBytes property fo each of
-- dataReplicationInfo.replicatedDisks will be set to zero;
-- dataReplicationInfo.lagDuration and dataReplicationInfo.lagDuration will
-- be nullified.
module Amazonka.MGN.FinalizeCutover
  ( -- * Creating a Request
    FinalizeCutover (..),
    newFinalizeCutover,

    -- * Request Lenses
    finalizeCutover_sourceServerID,

    -- * Destructuring the Response
    SourceServer (..),
    newSourceServer,

    -- * Response Lenses
    sourceServer_applicationID,
    sourceServer_arn,
    sourceServer_dataReplicationInfo,
    sourceServer_isArchived,
    sourceServer_launchedInstance,
    sourceServer_lifeCycle,
    sourceServer_replicationType,
    sourceServer_sourceProperties,
    sourceServer_sourceServerID,
    sourceServer_tags,
    sourceServer_vcenterClientID,
  )
where

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

-- | /See:/ 'newFinalizeCutover' smart constructor.
data FinalizeCutover = FinalizeCutover'
  { -- | Request to finalize Cutover by Source Server ID.
    FinalizeCutover -> Text
sourceServerID :: Prelude.Text
  }
  deriving (FinalizeCutover -> FinalizeCutover -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FinalizeCutover -> FinalizeCutover -> Bool
$c/= :: FinalizeCutover -> FinalizeCutover -> Bool
== :: FinalizeCutover -> FinalizeCutover -> Bool
$c== :: FinalizeCutover -> FinalizeCutover -> Bool
Prelude.Eq, ReadPrec [FinalizeCutover]
ReadPrec FinalizeCutover
Int -> ReadS FinalizeCutover
ReadS [FinalizeCutover]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [FinalizeCutover]
$creadListPrec :: ReadPrec [FinalizeCutover]
readPrec :: ReadPrec FinalizeCutover
$creadPrec :: ReadPrec FinalizeCutover
readList :: ReadS [FinalizeCutover]
$creadList :: ReadS [FinalizeCutover]
readsPrec :: Int -> ReadS FinalizeCutover
$creadsPrec :: Int -> ReadS FinalizeCutover
Prelude.Read, Int -> FinalizeCutover -> ShowS
[FinalizeCutover] -> ShowS
FinalizeCutover -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FinalizeCutover] -> ShowS
$cshowList :: [FinalizeCutover] -> ShowS
show :: FinalizeCutover -> String
$cshow :: FinalizeCutover -> String
showsPrec :: Int -> FinalizeCutover -> ShowS
$cshowsPrec :: Int -> FinalizeCutover -> ShowS
Prelude.Show, forall x. Rep FinalizeCutover x -> FinalizeCutover
forall x. FinalizeCutover -> Rep FinalizeCutover x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FinalizeCutover x -> FinalizeCutover
$cfrom :: forall x. FinalizeCutover -> Rep FinalizeCutover x
Prelude.Generic)

-- |
-- Create a value of 'FinalizeCutover' 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:
--
-- 'sourceServerID', 'finalizeCutover_sourceServerID' - Request to finalize Cutover by Source Server ID.
newFinalizeCutover ::
  -- | 'sourceServerID'
  Prelude.Text ->
  FinalizeCutover
newFinalizeCutover :: Text -> FinalizeCutover
newFinalizeCutover Text
pSourceServerID_ =
  FinalizeCutover' {$sel:sourceServerID:FinalizeCutover' :: Text
sourceServerID = Text
pSourceServerID_}

-- | Request to finalize Cutover by Source Server ID.
finalizeCutover_sourceServerID :: Lens.Lens' FinalizeCutover Prelude.Text
finalizeCutover_sourceServerID :: Lens' FinalizeCutover Text
finalizeCutover_sourceServerID = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FinalizeCutover' {Text
sourceServerID :: Text
$sel:sourceServerID:FinalizeCutover' :: FinalizeCutover -> Text
sourceServerID} -> Text
sourceServerID) (\s :: FinalizeCutover
s@FinalizeCutover' {} Text
a -> FinalizeCutover
s {$sel:sourceServerID:FinalizeCutover' :: Text
sourceServerID = Text
a} :: FinalizeCutover)

instance Core.AWSRequest FinalizeCutover where
  type AWSResponse FinalizeCutover = SourceServer
  request :: (Service -> Service) -> FinalizeCutover -> Request FinalizeCutover
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 FinalizeCutover
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse FinalizeCutover)))
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 -> forall a. FromJSON a => Object -> Either String a
Data.eitherParseJSON Object
x)

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

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

instance Data.ToHeaders FinalizeCutover where
  toHeaders :: FinalizeCutover -> ResponseHeaders
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 -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

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

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

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