{-# 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.Transfer.ImportHostKey
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Adds a host key to the server that\'s specified by the @ServerId@
-- parameter.
module Amazonka.Transfer.ImportHostKey
  ( -- * Creating a Request
    ImportHostKey (..),
    newImportHostKey,

    -- * Request Lenses
    importHostKey_description,
    importHostKey_tags,
    importHostKey_serverId,
    importHostKey_hostKeyBody,

    -- * Destructuring the Response
    ImportHostKeyResponse (..),
    newImportHostKeyResponse,

    -- * Response Lenses
    importHostKeyResponse_httpStatus,
    importHostKeyResponse_serverId,
    importHostKeyResponse_hostKeyId,
  )
where

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

-- | /See:/ 'newImportHostKey' smart constructor.
data ImportHostKey = ImportHostKey'
  { -- | The text description that identifies this host key.
    ImportHostKey -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | Key-value pairs that can be used to group and search for host keys.
    ImportHostKey -> Maybe (NonEmpty Tag)
tags :: Prelude.Maybe (Prelude.NonEmpty Tag),
    -- | The identifier of the server that contains the host key that you are
    -- importing.
    ImportHostKey -> Text
serverId :: Prelude.Text,
    -- | The public key portion of an SSH key pair.
    --
    -- Transfer Family accepts RSA, ECDSA, and ED25519 keys.
    ImportHostKey -> Sensitive Text
hostKeyBody :: Data.Sensitive Prelude.Text
  }
  deriving (ImportHostKey -> ImportHostKey -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ImportHostKey -> ImportHostKey -> Bool
$c/= :: ImportHostKey -> ImportHostKey -> Bool
== :: ImportHostKey -> ImportHostKey -> Bool
$c== :: ImportHostKey -> ImportHostKey -> Bool
Prelude.Eq, Int -> ImportHostKey -> ShowS
[ImportHostKey] -> ShowS
ImportHostKey -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ImportHostKey] -> ShowS
$cshowList :: [ImportHostKey] -> ShowS
show :: ImportHostKey -> String
$cshow :: ImportHostKey -> String
showsPrec :: Int -> ImportHostKey -> ShowS
$cshowsPrec :: Int -> ImportHostKey -> ShowS
Prelude.Show, forall x. Rep ImportHostKey x -> ImportHostKey
forall x. ImportHostKey -> Rep ImportHostKey x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ImportHostKey x -> ImportHostKey
$cfrom :: forall x. ImportHostKey -> Rep ImportHostKey x
Prelude.Generic)

-- |
-- Create a value of 'ImportHostKey' 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:
--
-- 'description', 'importHostKey_description' - The text description that identifies this host key.
--
-- 'tags', 'importHostKey_tags' - Key-value pairs that can be used to group and search for host keys.
--
-- 'serverId', 'importHostKey_serverId' - The identifier of the server that contains the host key that you are
-- importing.
--
-- 'hostKeyBody', 'importHostKey_hostKeyBody' - The public key portion of an SSH key pair.
--
-- Transfer Family accepts RSA, ECDSA, and ED25519 keys.
newImportHostKey ::
  -- | 'serverId'
  Prelude.Text ->
  -- | 'hostKeyBody'
  Prelude.Text ->
  ImportHostKey
newImportHostKey :: Text -> Text -> ImportHostKey
newImportHostKey Text
pServerId_ Text
pHostKeyBody_ =
  ImportHostKey'
    { $sel:description:ImportHostKey' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:ImportHostKey' :: Maybe (NonEmpty Tag)
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:serverId:ImportHostKey' :: Text
serverId = Text
pServerId_,
      $sel:hostKeyBody:ImportHostKey' :: Sensitive Text
hostKeyBody = forall a. Iso' (Sensitive a) a
Data._Sensitive forall t b. AReview t b -> b -> t
Lens.# Text
pHostKeyBody_
    }

-- | The text description that identifies this host key.
importHostKey_description :: Lens.Lens' ImportHostKey (Prelude.Maybe Prelude.Text)
importHostKey_description :: Lens' ImportHostKey (Maybe Text)
importHostKey_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImportHostKey' {Maybe Text
description :: Maybe Text
$sel:description:ImportHostKey' :: ImportHostKey -> Maybe Text
description} -> Maybe Text
description) (\s :: ImportHostKey
s@ImportHostKey' {} Maybe Text
a -> ImportHostKey
s {$sel:description:ImportHostKey' :: Maybe Text
description = Maybe Text
a} :: ImportHostKey)

-- | Key-value pairs that can be used to group and search for host keys.
importHostKey_tags :: Lens.Lens' ImportHostKey (Prelude.Maybe (Prelude.NonEmpty Tag))
importHostKey_tags :: Lens' ImportHostKey (Maybe (NonEmpty Tag))
importHostKey_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImportHostKey' {Maybe (NonEmpty Tag)
tags :: Maybe (NonEmpty Tag)
$sel:tags:ImportHostKey' :: ImportHostKey -> Maybe (NonEmpty Tag)
tags} -> Maybe (NonEmpty Tag)
tags) (\s :: ImportHostKey
s@ImportHostKey' {} Maybe (NonEmpty Tag)
a -> ImportHostKey
s {$sel:tags:ImportHostKey' :: Maybe (NonEmpty Tag)
tags = Maybe (NonEmpty Tag)
a} :: ImportHostKey) 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 s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The identifier of the server that contains the host key that you are
-- importing.
importHostKey_serverId :: Lens.Lens' ImportHostKey Prelude.Text
importHostKey_serverId :: Lens' ImportHostKey Text
importHostKey_serverId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImportHostKey' {Text
serverId :: Text
$sel:serverId:ImportHostKey' :: ImportHostKey -> Text
serverId} -> Text
serverId) (\s :: ImportHostKey
s@ImportHostKey' {} Text
a -> ImportHostKey
s {$sel:serverId:ImportHostKey' :: Text
serverId = Text
a} :: ImportHostKey)

-- | The public key portion of an SSH key pair.
--
-- Transfer Family accepts RSA, ECDSA, and ED25519 keys.
importHostKey_hostKeyBody :: Lens.Lens' ImportHostKey Prelude.Text
importHostKey_hostKeyBody :: Lens' ImportHostKey Text
importHostKey_hostKeyBody = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImportHostKey' {Sensitive Text
hostKeyBody :: Sensitive Text
$sel:hostKeyBody:ImportHostKey' :: ImportHostKey -> Sensitive Text
hostKeyBody} -> Sensitive Text
hostKeyBody) (\s :: ImportHostKey
s@ImportHostKey' {} Sensitive Text
a -> ImportHostKey
s {$sel:hostKeyBody:ImportHostKey' :: Sensitive Text
hostKeyBody = Sensitive Text
a} :: ImportHostKey) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a. Iso' (Sensitive a) a
Data._Sensitive

instance Core.AWSRequest ImportHostKey where
  type
    AWSResponse ImportHostKey =
      ImportHostKeyResponse
  request :: (Service -> Service) -> ImportHostKey -> Request ImportHostKey
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 ImportHostKey
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ImportHostKey)))
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 ->
          Int -> Text -> Text -> ImportHostKeyResponse
ImportHostKeyResponse'
            forall (f :: * -> *) a b. Functor 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))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"ServerId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"HostKeyId")
      )

instance Prelude.Hashable ImportHostKey where
  hashWithSalt :: Int -> ImportHostKey -> Int
hashWithSalt Int
_salt ImportHostKey' {Maybe (NonEmpty Tag)
Maybe Text
Text
Sensitive Text
hostKeyBody :: Sensitive Text
serverId :: Text
tags :: Maybe (NonEmpty Tag)
description :: Maybe Text
$sel:hostKeyBody:ImportHostKey' :: ImportHostKey -> Sensitive Text
$sel:serverId:ImportHostKey' :: ImportHostKey -> Text
$sel:tags:ImportHostKey' :: ImportHostKey -> Maybe (NonEmpty Tag)
$sel:description:ImportHostKey' :: ImportHostKey -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (NonEmpty Tag)
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
serverId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Sensitive Text
hostKeyBody

instance Prelude.NFData ImportHostKey where
  rnf :: ImportHostKey -> ()
rnf ImportHostKey' {Maybe (NonEmpty Tag)
Maybe Text
Text
Sensitive Text
hostKeyBody :: Sensitive Text
serverId :: Text
tags :: Maybe (NonEmpty Tag)
description :: Maybe Text
$sel:hostKeyBody:ImportHostKey' :: ImportHostKey -> Sensitive Text
$sel:serverId:ImportHostKey' :: ImportHostKey -> Text
$sel:tags:ImportHostKey' :: ImportHostKey -> Maybe (NonEmpty Tag)
$sel:description:ImportHostKey' :: ImportHostKey -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty Tag)
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
serverId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Sensitive Text
hostKeyBody

instance Data.ToHeaders ImportHostKey where
  toHeaders :: ImportHostKey -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"TransferService.ImportHostKey" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON ImportHostKey where
  toJSON :: ImportHostKey -> Value
toJSON ImportHostKey' {Maybe (NonEmpty Tag)
Maybe Text
Text
Sensitive Text
hostKeyBody :: Sensitive Text
serverId :: Text
tags :: Maybe (NonEmpty Tag)
description :: Maybe Text
$sel:hostKeyBody:ImportHostKey' :: ImportHostKey -> Sensitive Text
$sel:serverId:ImportHostKey' :: ImportHostKey -> Text
$sel:tags:ImportHostKey' :: ImportHostKey -> Maybe (NonEmpty Tag)
$sel:description:ImportHostKey' :: ImportHostKey -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Description" 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 Text
description,
            (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 (NonEmpty Tag)
tags,
            forall a. a -> Maybe a
Prelude.Just (Key
"ServerId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
serverId),
            forall a. a -> Maybe a
Prelude.Just (Key
"HostKeyBody" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Sensitive Text
hostKeyBody)
          ]
      )

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

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

-- | /See:/ 'newImportHostKeyResponse' smart constructor.
data ImportHostKeyResponse = ImportHostKeyResponse'
  { -- | The response's http status code.
    ImportHostKeyResponse -> Int
httpStatus :: Prelude.Int,
    -- | Returns the server identifier that contains the imported key.
    ImportHostKeyResponse -> Text
serverId :: Prelude.Text,
    -- | Returns the host key identifier for the imported key.
    ImportHostKeyResponse -> Text
hostKeyId :: Prelude.Text
  }
  deriving (ImportHostKeyResponse -> ImportHostKeyResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ImportHostKeyResponse -> ImportHostKeyResponse -> Bool
$c/= :: ImportHostKeyResponse -> ImportHostKeyResponse -> Bool
== :: ImportHostKeyResponse -> ImportHostKeyResponse -> Bool
$c== :: ImportHostKeyResponse -> ImportHostKeyResponse -> Bool
Prelude.Eq, ReadPrec [ImportHostKeyResponse]
ReadPrec ImportHostKeyResponse
Int -> ReadS ImportHostKeyResponse
ReadS [ImportHostKeyResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ImportHostKeyResponse]
$creadListPrec :: ReadPrec [ImportHostKeyResponse]
readPrec :: ReadPrec ImportHostKeyResponse
$creadPrec :: ReadPrec ImportHostKeyResponse
readList :: ReadS [ImportHostKeyResponse]
$creadList :: ReadS [ImportHostKeyResponse]
readsPrec :: Int -> ReadS ImportHostKeyResponse
$creadsPrec :: Int -> ReadS ImportHostKeyResponse
Prelude.Read, Int -> ImportHostKeyResponse -> ShowS
[ImportHostKeyResponse] -> ShowS
ImportHostKeyResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ImportHostKeyResponse] -> ShowS
$cshowList :: [ImportHostKeyResponse] -> ShowS
show :: ImportHostKeyResponse -> String
$cshow :: ImportHostKeyResponse -> String
showsPrec :: Int -> ImportHostKeyResponse -> ShowS
$cshowsPrec :: Int -> ImportHostKeyResponse -> ShowS
Prelude.Show, forall x. Rep ImportHostKeyResponse x -> ImportHostKeyResponse
forall x. ImportHostKeyResponse -> Rep ImportHostKeyResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ImportHostKeyResponse x -> ImportHostKeyResponse
$cfrom :: forall x. ImportHostKeyResponse -> Rep ImportHostKeyResponse x
Prelude.Generic)

-- |
-- Create a value of 'ImportHostKeyResponse' 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:
--
-- 'httpStatus', 'importHostKeyResponse_httpStatus' - The response's http status code.
--
-- 'serverId', 'importHostKeyResponse_serverId' - Returns the server identifier that contains the imported key.
--
-- 'hostKeyId', 'importHostKeyResponse_hostKeyId' - Returns the host key identifier for the imported key.
newImportHostKeyResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'serverId'
  Prelude.Text ->
  -- | 'hostKeyId'
  Prelude.Text ->
  ImportHostKeyResponse
newImportHostKeyResponse :: Int -> Text -> Text -> ImportHostKeyResponse
newImportHostKeyResponse
  Int
pHttpStatus_
  Text
pServerId_
  Text
pHostKeyId_ =
    ImportHostKeyResponse'
      { $sel:httpStatus:ImportHostKeyResponse' :: Int
httpStatus = Int
pHttpStatus_,
        $sel:serverId:ImportHostKeyResponse' :: Text
serverId = Text
pServerId_,
        $sel:hostKeyId:ImportHostKeyResponse' :: Text
hostKeyId = Text
pHostKeyId_
      }

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

-- | Returns the server identifier that contains the imported key.
importHostKeyResponse_serverId :: Lens.Lens' ImportHostKeyResponse Prelude.Text
importHostKeyResponse_serverId :: Lens' ImportHostKeyResponse Text
importHostKeyResponse_serverId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImportHostKeyResponse' {Text
serverId :: Text
$sel:serverId:ImportHostKeyResponse' :: ImportHostKeyResponse -> Text
serverId} -> Text
serverId) (\s :: ImportHostKeyResponse
s@ImportHostKeyResponse' {} Text
a -> ImportHostKeyResponse
s {$sel:serverId:ImportHostKeyResponse' :: Text
serverId = Text
a} :: ImportHostKeyResponse)

-- | Returns the host key identifier for the imported key.
importHostKeyResponse_hostKeyId :: Lens.Lens' ImportHostKeyResponse Prelude.Text
importHostKeyResponse_hostKeyId :: Lens' ImportHostKeyResponse Text
importHostKeyResponse_hostKeyId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImportHostKeyResponse' {Text
hostKeyId :: Text
$sel:hostKeyId:ImportHostKeyResponse' :: ImportHostKeyResponse -> Text
hostKeyId} -> Text
hostKeyId) (\s :: ImportHostKeyResponse
s@ImportHostKeyResponse' {} Text
a -> ImportHostKeyResponse
s {$sel:hostKeyId:ImportHostKeyResponse' :: Text
hostKeyId = Text
a} :: ImportHostKeyResponse)

instance Prelude.NFData ImportHostKeyResponse where
  rnf :: ImportHostKeyResponse -> ()
rnf ImportHostKeyResponse' {Int
Text
hostKeyId :: Text
serverId :: Text
httpStatus :: Int
$sel:hostKeyId:ImportHostKeyResponse' :: ImportHostKeyResponse -> Text
$sel:serverId:ImportHostKeyResponse' :: ImportHostKeyResponse -> Text
$sel:httpStatus:ImportHostKeyResponse' :: ImportHostKeyResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
serverId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
hostKeyId