{-# 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.CreateExtendedSourceServer
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Create an extended source server in the target Account based on the
-- source server in staging account.
module Amazonka.DrS.CreateExtendedSourceServer
  ( -- * Creating a Request
    CreateExtendedSourceServer (..),
    newCreateExtendedSourceServer,

    -- * Request Lenses
    createExtendedSourceServer_tags,
    createExtendedSourceServer_sourceServerArn,

    -- * Destructuring the Response
    CreateExtendedSourceServerResponse (..),
    newCreateExtendedSourceServerResponse,

    -- * Response Lenses
    createExtendedSourceServerResponse_sourceServer,
    createExtendedSourceServerResponse_httpStatus,
  )
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:/ 'newCreateExtendedSourceServer' smart constructor.
data CreateExtendedSourceServer = CreateExtendedSourceServer'
  { -- | A list of tags associated with the extended source server.
    CreateExtendedSourceServer -> Maybe (Sensitive (HashMap Text Text))
tags :: Prelude.Maybe (Data.Sensitive (Prelude.HashMap Prelude.Text Prelude.Text)),
    -- | This defines the ARN of the source server in staging Account based on
    -- which you want to create an extended source server.
    CreateExtendedSourceServer -> Text
sourceServerArn :: Prelude.Text
  }
  deriving (CreateExtendedSourceServer -> CreateExtendedSourceServer -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateExtendedSourceServer -> CreateExtendedSourceServer -> Bool
$c/= :: CreateExtendedSourceServer -> CreateExtendedSourceServer -> Bool
== :: CreateExtendedSourceServer -> CreateExtendedSourceServer -> Bool
$c== :: CreateExtendedSourceServer -> CreateExtendedSourceServer -> Bool
Prelude.Eq, Int -> CreateExtendedSourceServer -> ShowS
[CreateExtendedSourceServer] -> ShowS
CreateExtendedSourceServer -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateExtendedSourceServer] -> ShowS
$cshowList :: [CreateExtendedSourceServer] -> ShowS
show :: CreateExtendedSourceServer -> String
$cshow :: CreateExtendedSourceServer -> String
showsPrec :: Int -> CreateExtendedSourceServer -> ShowS
$cshowsPrec :: Int -> CreateExtendedSourceServer -> ShowS
Prelude.Show, forall x.
Rep CreateExtendedSourceServer x -> CreateExtendedSourceServer
forall x.
CreateExtendedSourceServer -> Rep CreateExtendedSourceServer x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateExtendedSourceServer x -> CreateExtendedSourceServer
$cfrom :: forall x.
CreateExtendedSourceServer -> Rep CreateExtendedSourceServer x
Prelude.Generic)

-- |
-- Create a value of 'CreateExtendedSourceServer' 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:
--
-- 'tags', 'createExtendedSourceServer_tags' - A list of tags associated with the extended source server.
--
-- 'sourceServerArn', 'createExtendedSourceServer_sourceServerArn' - This defines the ARN of the source server in staging Account based on
-- which you want to create an extended source server.
newCreateExtendedSourceServer ::
  -- | 'sourceServerArn'
  Prelude.Text ->
  CreateExtendedSourceServer
newCreateExtendedSourceServer :: Text -> CreateExtendedSourceServer
newCreateExtendedSourceServer Text
pSourceServerArn_ =
  CreateExtendedSourceServer'
    { $sel:tags:CreateExtendedSourceServer' :: Maybe (Sensitive (HashMap Text Text))
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:sourceServerArn:CreateExtendedSourceServer' :: Text
sourceServerArn = Text
pSourceServerArn_
    }

-- | A list of tags associated with the extended source server.
createExtendedSourceServer_tags :: Lens.Lens' CreateExtendedSourceServer (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
createExtendedSourceServer_tags :: Lens' CreateExtendedSourceServer (Maybe (HashMap Text Text))
createExtendedSourceServer_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateExtendedSourceServer' {Maybe (Sensitive (HashMap Text Text))
tags :: Maybe (Sensitive (HashMap Text Text))
$sel:tags:CreateExtendedSourceServer' :: CreateExtendedSourceServer -> Maybe (Sensitive (HashMap Text Text))
tags} -> Maybe (Sensitive (HashMap Text Text))
tags) (\s :: CreateExtendedSourceServer
s@CreateExtendedSourceServer' {} Maybe (Sensitive (HashMap Text Text))
a -> CreateExtendedSourceServer
s {$sel:tags:CreateExtendedSourceServer' :: Maybe (Sensitive (HashMap Text Text))
tags = Maybe (Sensitive (HashMap Text Text))
a} :: CreateExtendedSourceServer) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping (forall a. Iso' (Sensitive a) a
Data._Sensitive forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced)

-- | This defines the ARN of the source server in staging Account based on
-- which you want to create an extended source server.
createExtendedSourceServer_sourceServerArn :: Lens.Lens' CreateExtendedSourceServer Prelude.Text
createExtendedSourceServer_sourceServerArn :: Lens' CreateExtendedSourceServer Text
createExtendedSourceServer_sourceServerArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateExtendedSourceServer' {Text
sourceServerArn :: Text
$sel:sourceServerArn:CreateExtendedSourceServer' :: CreateExtendedSourceServer -> Text
sourceServerArn} -> Text
sourceServerArn) (\s :: CreateExtendedSourceServer
s@CreateExtendedSourceServer' {} Text
a -> CreateExtendedSourceServer
s {$sel:sourceServerArn:CreateExtendedSourceServer' :: Text
sourceServerArn = Text
a} :: CreateExtendedSourceServer)

instance Core.AWSRequest CreateExtendedSourceServer where
  type
    AWSResponse CreateExtendedSourceServer =
      CreateExtendedSourceServerResponse
  request :: (Service -> Service)
-> CreateExtendedSourceServer -> Request CreateExtendedSourceServer
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 CreateExtendedSourceServer
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CreateExtendedSourceServer)))
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 ->
          Maybe SourceServer -> Int -> CreateExtendedSourceServerResponse
CreateExtendedSourceServerResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"sourceServer")
            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 CreateExtendedSourceServer where
  hashWithSalt :: Int -> CreateExtendedSourceServer -> Int
hashWithSalt Int
_salt CreateExtendedSourceServer' {Maybe (Sensitive (HashMap Text Text))
Text
sourceServerArn :: Text
tags :: Maybe (Sensitive (HashMap Text Text))
$sel:sourceServerArn:CreateExtendedSourceServer' :: CreateExtendedSourceServer -> Text
$sel:tags:CreateExtendedSourceServer' :: CreateExtendedSourceServer -> Maybe (Sensitive (HashMap Text Text))
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (Sensitive (HashMap Text Text))
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
sourceServerArn

instance Prelude.NFData CreateExtendedSourceServer where
  rnf :: CreateExtendedSourceServer -> ()
rnf CreateExtendedSourceServer' {Maybe (Sensitive (HashMap Text Text))
Text
sourceServerArn :: Text
tags :: Maybe (Sensitive (HashMap Text Text))
$sel:sourceServerArn:CreateExtendedSourceServer' :: CreateExtendedSourceServer -> Text
$sel:tags:CreateExtendedSourceServer' :: CreateExtendedSourceServer -> Maybe (Sensitive (HashMap Text Text))
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe (Sensitive (HashMap Text Text))
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
sourceServerArn

instance Data.ToHeaders CreateExtendedSourceServer where
  toHeaders :: CreateExtendedSourceServer -> 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 CreateExtendedSourceServer where
  toJSON :: CreateExtendedSourceServer -> Value
toJSON CreateExtendedSourceServer' {Maybe (Sensitive (HashMap Text Text))
Text
sourceServerArn :: Text
tags :: Maybe (Sensitive (HashMap Text Text))
$sel:sourceServerArn:CreateExtendedSourceServer' :: CreateExtendedSourceServer -> Text
$sel:tags:CreateExtendedSourceServer' :: CreateExtendedSourceServer -> Maybe (Sensitive (HashMap Text Text))
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"tags" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Sensitive (HashMap Text Text))
tags,
            forall a. a -> Maybe a
Prelude.Just
              (Key
"sourceServerArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
sourceServerArn)
          ]
      )

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

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

-- | /See:/ 'newCreateExtendedSourceServerResponse' smart constructor.
data CreateExtendedSourceServerResponse = CreateExtendedSourceServerResponse'
  { -- | Created extended source server.
    CreateExtendedSourceServerResponse -> Maybe SourceServer
sourceServer :: Prelude.Maybe SourceServer,
    -- | The response's http status code.
    CreateExtendedSourceServerResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateExtendedSourceServerResponse
-> CreateExtendedSourceServerResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateExtendedSourceServerResponse
-> CreateExtendedSourceServerResponse -> Bool
$c/= :: CreateExtendedSourceServerResponse
-> CreateExtendedSourceServerResponse -> Bool
== :: CreateExtendedSourceServerResponse
-> CreateExtendedSourceServerResponse -> Bool
$c== :: CreateExtendedSourceServerResponse
-> CreateExtendedSourceServerResponse -> Bool
Prelude.Eq, Int -> CreateExtendedSourceServerResponse -> ShowS
[CreateExtendedSourceServerResponse] -> ShowS
CreateExtendedSourceServerResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateExtendedSourceServerResponse] -> ShowS
$cshowList :: [CreateExtendedSourceServerResponse] -> ShowS
show :: CreateExtendedSourceServerResponse -> String
$cshow :: CreateExtendedSourceServerResponse -> String
showsPrec :: Int -> CreateExtendedSourceServerResponse -> ShowS
$cshowsPrec :: Int -> CreateExtendedSourceServerResponse -> ShowS
Prelude.Show, forall x.
Rep CreateExtendedSourceServerResponse x
-> CreateExtendedSourceServerResponse
forall x.
CreateExtendedSourceServerResponse
-> Rep CreateExtendedSourceServerResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateExtendedSourceServerResponse x
-> CreateExtendedSourceServerResponse
$cfrom :: forall x.
CreateExtendedSourceServerResponse
-> Rep CreateExtendedSourceServerResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateExtendedSourceServerResponse' 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:
--
-- 'sourceServer', 'createExtendedSourceServerResponse_sourceServer' - Created extended source server.
--
-- 'httpStatus', 'createExtendedSourceServerResponse_httpStatus' - The response's http status code.
newCreateExtendedSourceServerResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateExtendedSourceServerResponse
newCreateExtendedSourceServerResponse :: Int -> CreateExtendedSourceServerResponse
newCreateExtendedSourceServerResponse Int
pHttpStatus_ =
  CreateExtendedSourceServerResponse'
    { $sel:sourceServer:CreateExtendedSourceServerResponse' :: Maybe SourceServer
sourceServer =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateExtendedSourceServerResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Created extended source server.
createExtendedSourceServerResponse_sourceServer :: Lens.Lens' CreateExtendedSourceServerResponse (Prelude.Maybe SourceServer)
createExtendedSourceServerResponse_sourceServer :: Lens' CreateExtendedSourceServerResponse (Maybe SourceServer)
createExtendedSourceServerResponse_sourceServer = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateExtendedSourceServerResponse' {Maybe SourceServer
sourceServer :: Maybe SourceServer
$sel:sourceServer:CreateExtendedSourceServerResponse' :: CreateExtendedSourceServerResponse -> Maybe SourceServer
sourceServer} -> Maybe SourceServer
sourceServer) (\s :: CreateExtendedSourceServerResponse
s@CreateExtendedSourceServerResponse' {} Maybe SourceServer
a -> CreateExtendedSourceServerResponse
s {$sel:sourceServer:CreateExtendedSourceServerResponse' :: Maybe SourceServer
sourceServer = Maybe SourceServer
a} :: CreateExtendedSourceServerResponse)

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

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