{-# 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.DisconnectSourceServer
-- 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 a specific Source Server from Elastic Disaster Recovery.
-- Data replication is stopped immediately. All AWS resources created by
-- Elastic Disaster Recovery for enabling the replication of the Source
-- Server will be terminated \/ deleted within 90 minutes. You cannot
-- disconnect a Source Server if it has a Recovery Instance. If the agent
-- on the Source Server has not been prevented from communicating with the
-- Elastic Disaster Recovery 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.DrS.DisconnectSourceServer
  ( -- * Creating a Request
    DisconnectSourceServer (..),
    newDisconnectSourceServer,

    -- * Request Lenses
    disconnectSourceServer_sourceServerID,

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

    -- * Response Lenses
    sourceServer_arn,
    sourceServer_dataReplicationInfo,
    sourceServer_lastLaunchResult,
    sourceServer_lifeCycle,
    sourceServer_recoveryInstanceId,
    sourceServer_replicationDirection,
    sourceServer_reversedDirectionSourceServerArn,
    sourceServer_sourceCloudProperties,
    sourceServer_sourceProperties,
    sourceServer_sourceServerID,
    sourceServer_stagingArea,
    sourceServer_tags,
  )
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:/ 'newDisconnectSourceServer' smart constructor.
data DisconnectSourceServer = DisconnectSourceServer'
  { -- | The ID of the Source Server to disconnect.
    DisconnectSourceServer -> Text
sourceServerID :: Prelude.Text
  }
  deriving (DisconnectSourceServer -> DisconnectSourceServer -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DisconnectSourceServer -> DisconnectSourceServer -> Bool
$c/= :: DisconnectSourceServer -> DisconnectSourceServer -> Bool
== :: DisconnectSourceServer -> DisconnectSourceServer -> Bool
$c== :: DisconnectSourceServer -> DisconnectSourceServer -> Bool
Prelude.Eq, ReadPrec [DisconnectSourceServer]
ReadPrec DisconnectSourceServer
Int -> ReadS DisconnectSourceServer
ReadS [DisconnectSourceServer]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DisconnectSourceServer]
$creadListPrec :: ReadPrec [DisconnectSourceServer]
readPrec :: ReadPrec DisconnectSourceServer
$creadPrec :: ReadPrec DisconnectSourceServer
readList :: ReadS [DisconnectSourceServer]
$creadList :: ReadS [DisconnectSourceServer]
readsPrec :: Int -> ReadS DisconnectSourceServer
$creadsPrec :: Int -> ReadS DisconnectSourceServer
Prelude.Read, Int -> DisconnectSourceServer -> ShowS
[DisconnectSourceServer] -> ShowS
DisconnectSourceServer -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DisconnectSourceServer] -> ShowS
$cshowList :: [DisconnectSourceServer] -> ShowS
show :: DisconnectSourceServer -> String
$cshow :: DisconnectSourceServer -> String
showsPrec :: Int -> DisconnectSourceServer -> ShowS
$cshowsPrec :: Int -> DisconnectSourceServer -> ShowS
Prelude.Show, forall x. Rep DisconnectSourceServer x -> DisconnectSourceServer
forall x. DisconnectSourceServer -> Rep DisconnectSourceServer x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DisconnectSourceServer x -> DisconnectSourceServer
$cfrom :: forall x. DisconnectSourceServer -> Rep DisconnectSourceServer x
Prelude.Generic)

-- |
-- Create a value of 'DisconnectSourceServer' 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', 'disconnectSourceServer_sourceServerID' - The ID of the Source Server to disconnect.
newDisconnectSourceServer ::
  -- | 'sourceServerID'
  Prelude.Text ->
  DisconnectSourceServer
newDisconnectSourceServer :: Text -> DisconnectSourceServer
newDisconnectSourceServer Text
pSourceServerID_ =
  DisconnectSourceServer'
    { $sel:sourceServerID:DisconnectSourceServer' :: Text
sourceServerID =
        Text
pSourceServerID_
    }

-- | The ID of the Source Server to disconnect.
disconnectSourceServer_sourceServerID :: Lens.Lens' DisconnectSourceServer Prelude.Text
disconnectSourceServer_sourceServerID :: Lens' DisconnectSourceServer Text
disconnectSourceServer_sourceServerID = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DisconnectSourceServer' {Text
sourceServerID :: Text
$sel:sourceServerID:DisconnectSourceServer' :: DisconnectSourceServer -> Text
sourceServerID} -> Text
sourceServerID) (\s :: DisconnectSourceServer
s@DisconnectSourceServer' {} Text
a -> DisconnectSourceServer
s {$sel:sourceServerID:DisconnectSourceServer' :: Text
sourceServerID = Text
a} :: DisconnectSourceServer)

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

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

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

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