{-# 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.DisconnectFromService
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Disconnects specific Source Servers from Application Migration Service.
-- Data replication is stopped immediately. 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. If the agent on the
-- source server has not been prevented from communicating with the
-- Application Migration Service service, then it will receive a command to
-- uninstall itself (within approximately 10 minutes). The following
-- properties of the SourceServer will be changed immediately:
-- dataReplicationInfo.dataReplicationState will be set to DISCONNECTED;
-- The totalStorageBytes property for each of
-- dataReplicationInfo.replicatedDisks will be set to zero;
-- dataReplicationInfo.lagDuration and dataReplicationInfo.lagDuration will
-- be nullified.
module Amazonka.MGN.DisconnectFromService
  ( -- * Creating a Request
    DisconnectFromService (..),
    newDisconnectFromService,

    -- * Request Lenses
    disconnectFromService_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:/ 'newDisconnectFromService' smart constructor.
data DisconnectFromService = DisconnectFromService'
  { -- | Request to disconnect Source Server from service by Server ID.
    DisconnectFromService -> Text
sourceServerID :: Prelude.Text
  }
  deriving (DisconnectFromService -> DisconnectFromService -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DisconnectFromService -> DisconnectFromService -> Bool
$c/= :: DisconnectFromService -> DisconnectFromService -> Bool
== :: DisconnectFromService -> DisconnectFromService -> Bool
$c== :: DisconnectFromService -> DisconnectFromService -> Bool
Prelude.Eq, ReadPrec [DisconnectFromService]
ReadPrec DisconnectFromService
Int -> ReadS DisconnectFromService
ReadS [DisconnectFromService]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DisconnectFromService]
$creadListPrec :: ReadPrec [DisconnectFromService]
readPrec :: ReadPrec DisconnectFromService
$creadPrec :: ReadPrec DisconnectFromService
readList :: ReadS [DisconnectFromService]
$creadList :: ReadS [DisconnectFromService]
readsPrec :: Int -> ReadS DisconnectFromService
$creadsPrec :: Int -> ReadS DisconnectFromService
Prelude.Read, Int -> DisconnectFromService -> ShowS
[DisconnectFromService] -> ShowS
DisconnectFromService -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DisconnectFromService] -> ShowS
$cshowList :: [DisconnectFromService] -> ShowS
show :: DisconnectFromService -> String
$cshow :: DisconnectFromService -> String
showsPrec :: Int -> DisconnectFromService -> ShowS
$cshowsPrec :: Int -> DisconnectFromService -> ShowS
Prelude.Show, forall x. Rep DisconnectFromService x -> DisconnectFromService
forall x. DisconnectFromService -> Rep DisconnectFromService x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DisconnectFromService x -> DisconnectFromService
$cfrom :: forall x. DisconnectFromService -> Rep DisconnectFromService x
Prelude.Generic)

-- |
-- Create a value of 'DisconnectFromService' 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', 'disconnectFromService_sourceServerID' - Request to disconnect Source Server from service by Server ID.
newDisconnectFromService ::
  -- | 'sourceServerID'
  Prelude.Text ->
  DisconnectFromService
newDisconnectFromService :: Text -> DisconnectFromService
newDisconnectFromService Text
pSourceServerID_ =
  DisconnectFromService'
    { $sel:sourceServerID:DisconnectFromService' :: Text
sourceServerID =
        Text
pSourceServerID_
    }

-- | Request to disconnect Source Server from service by Server ID.
disconnectFromService_sourceServerID :: Lens.Lens' DisconnectFromService Prelude.Text
disconnectFromService_sourceServerID :: Lens' DisconnectFromService Text
disconnectFromService_sourceServerID = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DisconnectFromService' {Text
sourceServerID :: Text
$sel:sourceServerID:DisconnectFromService' :: DisconnectFromService -> Text
sourceServerID} -> Text
sourceServerID) (\s :: DisconnectFromService
s@DisconnectFromService' {} Text
a -> DisconnectFromService
s {$sel:sourceServerID:DisconnectFromService' :: Text
sourceServerID = Text
a} :: DisconnectFromService)

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

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

instance Data.ToHeaders DisconnectFromService where
  toHeaders :: DisconnectFromService -> 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 DisconnectFromService where
  toJSON :: DisconnectFromService -> Value
toJSON DisconnectFromService' {Text
sourceServerID :: Text
$sel:sourceServerID:DisconnectFromService' :: DisconnectFromService -> 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 DisconnectFromService where
  toPath :: DisconnectFromService -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/DisconnectFromService"

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