{-# 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.Lightsail.ImportKeyPair
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Imports a public SSH key from a specific key pair.
module Amazonka.Lightsail.ImportKeyPair
  ( -- * Creating a Request
    ImportKeyPair (..),
    newImportKeyPair,

    -- * Request Lenses
    importKeyPair_keyPairName,
    importKeyPair_publicKeyBase64,

    -- * Destructuring the Response
    ImportKeyPairResponse (..),
    newImportKeyPairResponse,

    -- * Response Lenses
    importKeyPairResponse_operation,
    importKeyPairResponse_httpStatus,
  )
where

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

-- | /See:/ 'newImportKeyPair' smart constructor.
data ImportKeyPair = ImportKeyPair'
  { -- | The name of the key pair for which you want to import the public key.
    ImportKeyPair -> Text
keyPairName :: Prelude.Text,
    -- | A base64-encoded public key of the @ssh-rsa@ type.
    ImportKeyPair -> Text
publicKeyBase64 :: Prelude.Text
  }
  deriving (ImportKeyPair -> ImportKeyPair -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ImportKeyPair -> ImportKeyPair -> Bool
$c/= :: ImportKeyPair -> ImportKeyPair -> Bool
== :: ImportKeyPair -> ImportKeyPair -> Bool
$c== :: ImportKeyPair -> ImportKeyPair -> Bool
Prelude.Eq, ReadPrec [ImportKeyPair]
ReadPrec ImportKeyPair
Int -> ReadS ImportKeyPair
ReadS [ImportKeyPair]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ImportKeyPair]
$creadListPrec :: ReadPrec [ImportKeyPair]
readPrec :: ReadPrec ImportKeyPair
$creadPrec :: ReadPrec ImportKeyPair
readList :: ReadS [ImportKeyPair]
$creadList :: ReadS [ImportKeyPair]
readsPrec :: Int -> ReadS ImportKeyPair
$creadsPrec :: Int -> ReadS ImportKeyPair
Prelude.Read, Int -> ImportKeyPair -> ShowS
[ImportKeyPair] -> ShowS
ImportKeyPair -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ImportKeyPair] -> ShowS
$cshowList :: [ImportKeyPair] -> ShowS
show :: ImportKeyPair -> String
$cshow :: ImportKeyPair -> String
showsPrec :: Int -> ImportKeyPair -> ShowS
$cshowsPrec :: Int -> ImportKeyPair -> ShowS
Prelude.Show, forall x. Rep ImportKeyPair x -> ImportKeyPair
forall x. ImportKeyPair -> Rep ImportKeyPair x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ImportKeyPair x -> ImportKeyPair
$cfrom :: forall x. ImportKeyPair -> Rep ImportKeyPair x
Prelude.Generic)

-- |
-- Create a value of 'ImportKeyPair' 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:
--
-- 'keyPairName', 'importKeyPair_keyPairName' - The name of the key pair for which you want to import the public key.
--
-- 'publicKeyBase64', 'importKeyPair_publicKeyBase64' - A base64-encoded public key of the @ssh-rsa@ type.
newImportKeyPair ::
  -- | 'keyPairName'
  Prelude.Text ->
  -- | 'publicKeyBase64'
  Prelude.Text ->
  ImportKeyPair
newImportKeyPair :: Text -> Text -> ImportKeyPair
newImportKeyPair Text
pKeyPairName_ Text
pPublicKeyBase64_ =
  ImportKeyPair'
    { $sel:keyPairName:ImportKeyPair' :: Text
keyPairName = Text
pKeyPairName_,
      $sel:publicKeyBase64:ImportKeyPair' :: Text
publicKeyBase64 = Text
pPublicKeyBase64_
    }

-- | The name of the key pair for which you want to import the public key.
importKeyPair_keyPairName :: Lens.Lens' ImportKeyPair Prelude.Text
importKeyPair_keyPairName :: Lens' ImportKeyPair Text
importKeyPair_keyPairName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImportKeyPair' {Text
keyPairName :: Text
$sel:keyPairName:ImportKeyPair' :: ImportKeyPair -> Text
keyPairName} -> Text
keyPairName) (\s :: ImportKeyPair
s@ImportKeyPair' {} Text
a -> ImportKeyPair
s {$sel:keyPairName:ImportKeyPair' :: Text
keyPairName = Text
a} :: ImportKeyPair)

-- | A base64-encoded public key of the @ssh-rsa@ type.
importKeyPair_publicKeyBase64 :: Lens.Lens' ImportKeyPair Prelude.Text
importKeyPair_publicKeyBase64 :: Lens' ImportKeyPair Text
importKeyPair_publicKeyBase64 = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImportKeyPair' {Text
publicKeyBase64 :: Text
$sel:publicKeyBase64:ImportKeyPair' :: ImportKeyPair -> Text
publicKeyBase64} -> Text
publicKeyBase64) (\s :: ImportKeyPair
s@ImportKeyPair' {} Text
a -> ImportKeyPair
s {$sel:publicKeyBase64:ImportKeyPair' :: Text
publicKeyBase64 = Text
a} :: ImportKeyPair)

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

instance Prelude.NFData ImportKeyPair where
  rnf :: ImportKeyPair -> ()
rnf ImportKeyPair' {Text
publicKeyBase64 :: Text
keyPairName :: Text
$sel:publicKeyBase64:ImportKeyPair' :: ImportKeyPair -> Text
$sel:keyPairName:ImportKeyPair' :: ImportKeyPair -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
keyPairName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
publicKeyBase64

instance Data.ToHeaders ImportKeyPair where
  toHeaders :: ImportKeyPair -> 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
"Lightsail_20161128.ImportKeyPair" ::
                          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 ImportKeyPair where
  toJSON :: ImportKeyPair -> Value
toJSON ImportKeyPair' {Text
publicKeyBase64 :: Text
keyPairName :: Text
$sel:publicKeyBase64:ImportKeyPair' :: ImportKeyPair -> Text
$sel:keyPairName:ImportKeyPair' :: ImportKeyPair -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just (Key
"keyPairName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
keyPairName),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"publicKeyBase64" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
publicKeyBase64)
          ]
      )

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

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

-- | /See:/ 'newImportKeyPairResponse' smart constructor.
data ImportKeyPairResponse = ImportKeyPairResponse'
  { -- | An array of objects that describe the result of the action, such as the
    -- status of the request, the timestamp of the request, and the resources
    -- affected by the request.
    ImportKeyPairResponse -> Maybe Operation
operation :: Prelude.Maybe Operation,
    -- | The response's http status code.
    ImportKeyPairResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ImportKeyPairResponse -> ImportKeyPairResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ImportKeyPairResponse -> ImportKeyPairResponse -> Bool
$c/= :: ImportKeyPairResponse -> ImportKeyPairResponse -> Bool
== :: ImportKeyPairResponse -> ImportKeyPairResponse -> Bool
$c== :: ImportKeyPairResponse -> ImportKeyPairResponse -> Bool
Prelude.Eq, ReadPrec [ImportKeyPairResponse]
ReadPrec ImportKeyPairResponse
Int -> ReadS ImportKeyPairResponse
ReadS [ImportKeyPairResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ImportKeyPairResponse]
$creadListPrec :: ReadPrec [ImportKeyPairResponse]
readPrec :: ReadPrec ImportKeyPairResponse
$creadPrec :: ReadPrec ImportKeyPairResponse
readList :: ReadS [ImportKeyPairResponse]
$creadList :: ReadS [ImportKeyPairResponse]
readsPrec :: Int -> ReadS ImportKeyPairResponse
$creadsPrec :: Int -> ReadS ImportKeyPairResponse
Prelude.Read, Int -> ImportKeyPairResponse -> ShowS
[ImportKeyPairResponse] -> ShowS
ImportKeyPairResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ImportKeyPairResponse] -> ShowS
$cshowList :: [ImportKeyPairResponse] -> ShowS
show :: ImportKeyPairResponse -> String
$cshow :: ImportKeyPairResponse -> String
showsPrec :: Int -> ImportKeyPairResponse -> ShowS
$cshowsPrec :: Int -> ImportKeyPairResponse -> ShowS
Prelude.Show, forall x. Rep ImportKeyPairResponse x -> ImportKeyPairResponse
forall x. ImportKeyPairResponse -> Rep ImportKeyPairResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ImportKeyPairResponse x -> ImportKeyPairResponse
$cfrom :: forall x. ImportKeyPairResponse -> Rep ImportKeyPairResponse x
Prelude.Generic)

-- |
-- Create a value of 'ImportKeyPairResponse' 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:
--
-- 'operation', 'importKeyPairResponse_operation' - An array of objects that describe the result of the action, such as the
-- status of the request, the timestamp of the request, and the resources
-- affected by the request.
--
-- 'httpStatus', 'importKeyPairResponse_httpStatus' - The response's http status code.
newImportKeyPairResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ImportKeyPairResponse
newImportKeyPairResponse :: Int -> ImportKeyPairResponse
newImportKeyPairResponse Int
pHttpStatus_ =
  ImportKeyPairResponse'
    { $sel:operation:ImportKeyPairResponse' :: Maybe Operation
operation = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ImportKeyPairResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | An array of objects that describe the result of the action, such as the
-- status of the request, the timestamp of the request, and the resources
-- affected by the request.
importKeyPairResponse_operation :: Lens.Lens' ImportKeyPairResponse (Prelude.Maybe Operation)
importKeyPairResponse_operation :: Lens' ImportKeyPairResponse (Maybe Operation)
importKeyPairResponse_operation = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ImportKeyPairResponse' {Maybe Operation
operation :: Maybe Operation
$sel:operation:ImportKeyPairResponse' :: ImportKeyPairResponse -> Maybe Operation
operation} -> Maybe Operation
operation) (\s :: ImportKeyPairResponse
s@ImportKeyPairResponse' {} Maybe Operation
a -> ImportKeyPairResponse
s {$sel:operation:ImportKeyPairResponse' :: Maybe Operation
operation = Maybe Operation
a} :: ImportKeyPairResponse)

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

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