{-# 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.DeleteKeyPair
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Deletes the specified key pair by removing the public key from Amazon
-- Lightsail.
--
-- You can delete key pairs that were created using the
-- <https://docs.aws.amazon.com/lightsail/2016-11-28/api-reference/API_ImportKeyPair.html ImportKeyPair>
-- and
-- <https://docs.aws.amazon.com/lightsail/2016-11-28/api-reference/API_CreateKeyPair.html CreateKeyPair>
-- actions, as well as the Lightsail default key pair. A new default key
-- pair will not be created unless you launch an instance without
-- specifying a custom key pair, or you call the
-- <https://docs.aws.amazon.com/lightsail/2016-11-28/api-reference/API_DownloadDefaultKeyPair.html DownloadDefaultKeyPair>
-- API.
--
-- The @delete key pair@ operation supports tag-based access control via
-- resource tags applied to the resource identified by @key pair name@. For
-- more information, see the
-- <https://lightsail.aws.amazon.com/ls/docs/en_us/articles/amazon-lightsail-controlling-access-using-tags Amazon Lightsail Developer Guide>.
module Amazonka.Lightsail.DeleteKeyPair
  ( -- * Creating a Request
    DeleteKeyPair (..),
    newDeleteKeyPair,

    -- * Request Lenses
    deleteKeyPair_expectedFingerprint,
    deleteKeyPair_keyPairName,

    -- * Destructuring the Response
    DeleteKeyPairResponse (..),
    newDeleteKeyPairResponse,

    -- * Response Lenses
    deleteKeyPairResponse_operation,
    deleteKeyPairResponse_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:/ 'newDeleteKeyPair' smart constructor.
data DeleteKeyPair = DeleteKeyPair'
  { -- | The RSA fingerprint of the Lightsail default key pair to delete.
    --
    -- The @expectedFingerprint@ parameter is required only when specifying to
    -- delete a Lightsail default key pair.
    DeleteKeyPair -> Maybe Text
expectedFingerprint :: Prelude.Maybe Prelude.Text,
    -- | The name of the key pair to delete.
    DeleteKeyPair -> Text
keyPairName :: Prelude.Text
  }
  deriving (DeleteKeyPair -> DeleteKeyPair -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteKeyPair -> DeleteKeyPair -> Bool
$c/= :: DeleteKeyPair -> DeleteKeyPair -> Bool
== :: DeleteKeyPair -> DeleteKeyPair -> Bool
$c== :: DeleteKeyPair -> DeleteKeyPair -> Bool
Prelude.Eq, ReadPrec [DeleteKeyPair]
ReadPrec DeleteKeyPair
Int -> ReadS DeleteKeyPair
ReadS [DeleteKeyPair]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteKeyPair]
$creadListPrec :: ReadPrec [DeleteKeyPair]
readPrec :: ReadPrec DeleteKeyPair
$creadPrec :: ReadPrec DeleteKeyPair
readList :: ReadS [DeleteKeyPair]
$creadList :: ReadS [DeleteKeyPair]
readsPrec :: Int -> ReadS DeleteKeyPair
$creadsPrec :: Int -> ReadS DeleteKeyPair
Prelude.Read, Int -> DeleteKeyPair -> ShowS
[DeleteKeyPair] -> ShowS
DeleteKeyPair -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteKeyPair] -> ShowS
$cshowList :: [DeleteKeyPair] -> ShowS
show :: DeleteKeyPair -> String
$cshow :: DeleteKeyPair -> String
showsPrec :: Int -> DeleteKeyPair -> ShowS
$cshowsPrec :: Int -> DeleteKeyPair -> ShowS
Prelude.Show, forall x. Rep DeleteKeyPair x -> DeleteKeyPair
forall x. DeleteKeyPair -> Rep DeleteKeyPair x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteKeyPair x -> DeleteKeyPair
$cfrom :: forall x. DeleteKeyPair -> Rep DeleteKeyPair x
Prelude.Generic)

-- |
-- Create a value of 'DeleteKeyPair' 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:
--
-- 'expectedFingerprint', 'deleteKeyPair_expectedFingerprint' - The RSA fingerprint of the Lightsail default key pair to delete.
--
-- The @expectedFingerprint@ parameter is required only when specifying to
-- delete a Lightsail default key pair.
--
-- 'keyPairName', 'deleteKeyPair_keyPairName' - The name of the key pair to delete.
newDeleteKeyPair ::
  -- | 'keyPairName'
  Prelude.Text ->
  DeleteKeyPair
newDeleteKeyPair :: Text -> DeleteKeyPair
newDeleteKeyPair Text
pKeyPairName_ =
  DeleteKeyPair'
    { $sel:expectedFingerprint:DeleteKeyPair' :: Maybe Text
expectedFingerprint =
        forall a. Maybe a
Prelude.Nothing,
      $sel:keyPairName:DeleteKeyPair' :: Text
keyPairName = Text
pKeyPairName_
    }

-- | The RSA fingerprint of the Lightsail default key pair to delete.
--
-- The @expectedFingerprint@ parameter is required only when specifying to
-- delete a Lightsail default key pair.
deleteKeyPair_expectedFingerprint :: Lens.Lens' DeleteKeyPair (Prelude.Maybe Prelude.Text)
deleteKeyPair_expectedFingerprint :: Lens' DeleteKeyPair (Maybe Text)
deleteKeyPair_expectedFingerprint = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteKeyPair' {Maybe Text
expectedFingerprint :: Maybe Text
$sel:expectedFingerprint:DeleteKeyPair' :: DeleteKeyPair -> Maybe Text
expectedFingerprint} -> Maybe Text
expectedFingerprint) (\s :: DeleteKeyPair
s@DeleteKeyPair' {} Maybe Text
a -> DeleteKeyPair
s {$sel:expectedFingerprint:DeleteKeyPair' :: Maybe Text
expectedFingerprint = Maybe Text
a} :: DeleteKeyPair)

-- | The name of the key pair to delete.
deleteKeyPair_keyPairName :: Lens.Lens' DeleteKeyPair Prelude.Text
deleteKeyPair_keyPairName :: Lens' DeleteKeyPair Text
deleteKeyPair_keyPairName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteKeyPair' {Text
keyPairName :: Text
$sel:keyPairName:DeleteKeyPair' :: DeleteKeyPair -> Text
keyPairName} -> Text
keyPairName) (\s :: DeleteKeyPair
s@DeleteKeyPair' {} Text
a -> DeleteKeyPair
s {$sel:keyPairName:DeleteKeyPair' :: Text
keyPairName = Text
a} :: DeleteKeyPair)

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

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

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

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

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

-- | /See:/ 'newDeleteKeyPairResponse' smart constructor.
data DeleteKeyPairResponse = DeleteKeyPairResponse'
  { -- | 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.
    DeleteKeyPairResponse -> Maybe Operation
operation :: Prelude.Maybe Operation,
    -- | The response's http status code.
    DeleteKeyPairResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DeleteKeyPairResponse -> DeleteKeyPairResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteKeyPairResponse -> DeleteKeyPairResponse -> Bool
$c/= :: DeleteKeyPairResponse -> DeleteKeyPairResponse -> Bool
== :: DeleteKeyPairResponse -> DeleteKeyPairResponse -> Bool
$c== :: DeleteKeyPairResponse -> DeleteKeyPairResponse -> Bool
Prelude.Eq, ReadPrec [DeleteKeyPairResponse]
ReadPrec DeleteKeyPairResponse
Int -> ReadS DeleteKeyPairResponse
ReadS [DeleteKeyPairResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteKeyPairResponse]
$creadListPrec :: ReadPrec [DeleteKeyPairResponse]
readPrec :: ReadPrec DeleteKeyPairResponse
$creadPrec :: ReadPrec DeleteKeyPairResponse
readList :: ReadS [DeleteKeyPairResponse]
$creadList :: ReadS [DeleteKeyPairResponse]
readsPrec :: Int -> ReadS DeleteKeyPairResponse
$creadsPrec :: Int -> ReadS DeleteKeyPairResponse
Prelude.Read, Int -> DeleteKeyPairResponse -> ShowS
[DeleteKeyPairResponse] -> ShowS
DeleteKeyPairResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteKeyPairResponse] -> ShowS
$cshowList :: [DeleteKeyPairResponse] -> ShowS
show :: DeleteKeyPairResponse -> String
$cshow :: DeleteKeyPairResponse -> String
showsPrec :: Int -> DeleteKeyPairResponse -> ShowS
$cshowsPrec :: Int -> DeleteKeyPairResponse -> ShowS
Prelude.Show, forall x. Rep DeleteKeyPairResponse x -> DeleteKeyPairResponse
forall x. DeleteKeyPairResponse -> Rep DeleteKeyPairResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteKeyPairResponse x -> DeleteKeyPairResponse
$cfrom :: forall x. DeleteKeyPairResponse -> Rep DeleteKeyPairResponse x
Prelude.Generic)

-- |
-- Create a value of 'DeleteKeyPairResponse' 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', 'deleteKeyPairResponse_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', 'deleteKeyPairResponse_httpStatus' - The response's http status code.
newDeleteKeyPairResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DeleteKeyPairResponse
newDeleteKeyPairResponse :: Int -> DeleteKeyPairResponse
newDeleteKeyPairResponse Int
pHttpStatus_ =
  DeleteKeyPairResponse'
    { $sel:operation:DeleteKeyPairResponse' :: Maybe Operation
operation = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DeleteKeyPairResponse' :: 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.
deleteKeyPairResponse_operation :: Lens.Lens' DeleteKeyPairResponse (Prelude.Maybe Operation)
deleteKeyPairResponse_operation :: Lens' DeleteKeyPairResponse (Maybe Operation)
deleteKeyPairResponse_operation = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteKeyPairResponse' {Maybe Operation
operation :: Maybe Operation
$sel:operation:DeleteKeyPairResponse' :: DeleteKeyPairResponse -> Maybe Operation
operation} -> Maybe Operation
operation) (\s :: DeleteKeyPairResponse
s@DeleteKeyPairResponse' {} Maybe Operation
a -> DeleteKeyPairResponse
s {$sel:operation:DeleteKeyPairResponse' :: Maybe Operation
operation = Maybe Operation
a} :: DeleteKeyPairResponse)

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

instance Prelude.NFData DeleteKeyPairResponse where
  rnf :: DeleteKeyPairResponse -> ()
rnf DeleteKeyPairResponse' {Int
Maybe Operation
httpStatus :: Int
operation :: Maybe Operation
$sel:httpStatus:DeleteKeyPairResponse' :: DeleteKeyPairResponse -> Int
$sel:operation:DeleteKeyPairResponse' :: DeleteKeyPairResponse -> 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