{-# 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.DeleteSshPublicKey
-- 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 a user\'s Secure Shell (SSH) public key.
module Amazonka.Transfer.DeleteSshPublicKey
  ( -- * Creating a Request
    DeleteSshPublicKey (..),
    newDeleteSshPublicKey,

    -- * Request Lenses
    deleteSshPublicKey_serverId,
    deleteSshPublicKey_sshPublicKeyId,
    deleteSshPublicKey_userName,

    -- * Destructuring the Response
    DeleteSshPublicKeyResponse (..),
    newDeleteSshPublicKeyResponse,
  )
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:/ 'newDeleteSshPublicKey' smart constructor.
data DeleteSshPublicKey = DeleteSshPublicKey'
  { -- | A system-assigned unique identifier for a file transfer protocol-enabled
    -- server instance that has the user assigned to it.
    DeleteSshPublicKey -> Text
serverId :: Prelude.Text,
    -- | A unique identifier used to reference your user\'s specific SSH key.
    DeleteSshPublicKey -> Text
sshPublicKeyId :: Prelude.Text,
    -- | A unique string that identifies a user whose public key is being
    -- deleted.
    DeleteSshPublicKey -> Text
userName :: Prelude.Text
  }
  deriving (DeleteSshPublicKey -> DeleteSshPublicKey -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteSshPublicKey -> DeleteSshPublicKey -> Bool
$c/= :: DeleteSshPublicKey -> DeleteSshPublicKey -> Bool
== :: DeleteSshPublicKey -> DeleteSshPublicKey -> Bool
$c== :: DeleteSshPublicKey -> DeleteSshPublicKey -> Bool
Prelude.Eq, ReadPrec [DeleteSshPublicKey]
ReadPrec DeleteSshPublicKey
Int -> ReadS DeleteSshPublicKey
ReadS [DeleteSshPublicKey]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteSshPublicKey]
$creadListPrec :: ReadPrec [DeleteSshPublicKey]
readPrec :: ReadPrec DeleteSshPublicKey
$creadPrec :: ReadPrec DeleteSshPublicKey
readList :: ReadS [DeleteSshPublicKey]
$creadList :: ReadS [DeleteSshPublicKey]
readsPrec :: Int -> ReadS DeleteSshPublicKey
$creadsPrec :: Int -> ReadS DeleteSshPublicKey
Prelude.Read, Int -> DeleteSshPublicKey -> ShowS
[DeleteSshPublicKey] -> ShowS
DeleteSshPublicKey -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteSshPublicKey] -> ShowS
$cshowList :: [DeleteSshPublicKey] -> ShowS
show :: DeleteSshPublicKey -> String
$cshow :: DeleteSshPublicKey -> String
showsPrec :: Int -> DeleteSshPublicKey -> ShowS
$cshowsPrec :: Int -> DeleteSshPublicKey -> ShowS
Prelude.Show, forall x. Rep DeleteSshPublicKey x -> DeleteSshPublicKey
forall x. DeleteSshPublicKey -> Rep DeleteSshPublicKey x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteSshPublicKey x -> DeleteSshPublicKey
$cfrom :: forall x. DeleteSshPublicKey -> Rep DeleteSshPublicKey x
Prelude.Generic)

-- |
-- Create a value of 'DeleteSshPublicKey' 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:
--
-- 'serverId', 'deleteSshPublicKey_serverId' - A system-assigned unique identifier for a file transfer protocol-enabled
-- server instance that has the user assigned to it.
--
-- 'sshPublicKeyId', 'deleteSshPublicKey_sshPublicKeyId' - A unique identifier used to reference your user\'s specific SSH key.
--
-- 'userName', 'deleteSshPublicKey_userName' - A unique string that identifies a user whose public key is being
-- deleted.
newDeleteSshPublicKey ::
  -- | 'serverId'
  Prelude.Text ->
  -- | 'sshPublicKeyId'
  Prelude.Text ->
  -- | 'userName'
  Prelude.Text ->
  DeleteSshPublicKey
newDeleteSshPublicKey :: Text -> Text -> Text -> DeleteSshPublicKey
newDeleteSshPublicKey
  Text
pServerId_
  Text
pSshPublicKeyId_
  Text
pUserName_ =
    DeleteSshPublicKey'
      { $sel:serverId:DeleteSshPublicKey' :: Text
serverId = Text
pServerId_,
        $sel:sshPublicKeyId:DeleteSshPublicKey' :: Text
sshPublicKeyId = Text
pSshPublicKeyId_,
        $sel:userName:DeleteSshPublicKey' :: Text
userName = Text
pUserName_
      }

-- | A system-assigned unique identifier for a file transfer protocol-enabled
-- server instance that has the user assigned to it.
deleteSshPublicKey_serverId :: Lens.Lens' DeleteSshPublicKey Prelude.Text
deleteSshPublicKey_serverId :: Lens' DeleteSshPublicKey Text
deleteSshPublicKey_serverId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteSshPublicKey' {Text
serverId :: Text
$sel:serverId:DeleteSshPublicKey' :: DeleteSshPublicKey -> Text
serverId} -> Text
serverId) (\s :: DeleteSshPublicKey
s@DeleteSshPublicKey' {} Text
a -> DeleteSshPublicKey
s {$sel:serverId:DeleteSshPublicKey' :: Text
serverId = Text
a} :: DeleteSshPublicKey)

-- | A unique identifier used to reference your user\'s specific SSH key.
deleteSshPublicKey_sshPublicKeyId :: Lens.Lens' DeleteSshPublicKey Prelude.Text
deleteSshPublicKey_sshPublicKeyId :: Lens' DeleteSshPublicKey Text
deleteSshPublicKey_sshPublicKeyId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteSshPublicKey' {Text
sshPublicKeyId :: Text
$sel:sshPublicKeyId:DeleteSshPublicKey' :: DeleteSshPublicKey -> Text
sshPublicKeyId} -> Text
sshPublicKeyId) (\s :: DeleteSshPublicKey
s@DeleteSshPublicKey' {} Text
a -> DeleteSshPublicKey
s {$sel:sshPublicKeyId:DeleteSshPublicKey' :: Text
sshPublicKeyId = Text
a} :: DeleteSshPublicKey)

-- | A unique string that identifies a user whose public key is being
-- deleted.
deleteSshPublicKey_userName :: Lens.Lens' DeleteSshPublicKey Prelude.Text
deleteSshPublicKey_userName :: Lens' DeleteSshPublicKey Text
deleteSshPublicKey_userName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteSshPublicKey' {Text
userName :: Text
$sel:userName:DeleteSshPublicKey' :: DeleteSshPublicKey -> Text
userName} -> Text
userName) (\s :: DeleteSshPublicKey
s@DeleteSshPublicKey' {} Text
a -> DeleteSshPublicKey
s {$sel:userName:DeleteSshPublicKey' :: Text
userName = Text
a} :: DeleteSshPublicKey)

instance Core.AWSRequest DeleteSshPublicKey where
  type
    AWSResponse DeleteSshPublicKey =
      DeleteSshPublicKeyResponse
  request :: (Service -> Service)
-> DeleteSshPublicKey -> Request DeleteSshPublicKey
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 DeleteSshPublicKey
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DeleteSshPublicKey)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull DeleteSshPublicKeyResponse
DeleteSshPublicKeyResponse'

instance Prelude.Hashable DeleteSshPublicKey where
  hashWithSalt :: Int -> DeleteSshPublicKey -> Int
hashWithSalt Int
_salt DeleteSshPublicKey' {Text
userName :: Text
sshPublicKeyId :: Text
serverId :: Text
$sel:userName:DeleteSshPublicKey' :: DeleteSshPublicKey -> Text
$sel:sshPublicKeyId:DeleteSshPublicKey' :: DeleteSshPublicKey -> Text
$sel:serverId:DeleteSshPublicKey' :: DeleteSshPublicKey -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
serverId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
sshPublicKeyId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
userName

instance Prelude.NFData DeleteSshPublicKey where
  rnf :: DeleteSshPublicKey -> ()
rnf DeleteSshPublicKey' {Text
userName :: Text
sshPublicKeyId :: Text
serverId :: Text
$sel:userName:DeleteSshPublicKey' :: DeleteSshPublicKey -> Text
$sel:sshPublicKeyId:DeleteSshPublicKey' :: DeleteSshPublicKey -> Text
$sel:serverId:DeleteSshPublicKey' :: DeleteSshPublicKey -> Text
..} =
    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
sshPublicKeyId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
userName

instance Data.ToHeaders DeleteSshPublicKey where
  toHeaders :: DeleteSshPublicKey -> [Header]
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 -> [Header]
Data.=# ( ByteString
"TransferService.DeleteSshPublicKey" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> [Header]
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON DeleteSshPublicKey where
  toJSON :: DeleteSshPublicKey -> Value
toJSON DeleteSshPublicKey' {Text
userName :: Text
sshPublicKeyId :: Text
serverId :: Text
$sel:userName:DeleteSshPublicKey' :: DeleteSshPublicKey -> Text
$sel:sshPublicKeyId:DeleteSshPublicKey' :: DeleteSshPublicKey -> Text
$sel:serverId:DeleteSshPublicKey' :: DeleteSshPublicKey -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ 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
"SshPublicKeyId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
sshPublicKeyId),
            forall a. a -> Maybe a
Prelude.Just (Key
"UserName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
userName)
          ]
      )

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

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

-- | /See:/ 'newDeleteSshPublicKeyResponse' smart constructor.
data DeleteSshPublicKeyResponse = DeleteSshPublicKeyResponse'
  {
  }
  deriving (DeleteSshPublicKeyResponse -> DeleteSshPublicKeyResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteSshPublicKeyResponse -> DeleteSshPublicKeyResponse -> Bool
$c/= :: DeleteSshPublicKeyResponse -> DeleteSshPublicKeyResponse -> Bool
== :: DeleteSshPublicKeyResponse -> DeleteSshPublicKeyResponse -> Bool
$c== :: DeleteSshPublicKeyResponse -> DeleteSshPublicKeyResponse -> Bool
Prelude.Eq, ReadPrec [DeleteSshPublicKeyResponse]
ReadPrec DeleteSshPublicKeyResponse
Int -> ReadS DeleteSshPublicKeyResponse
ReadS [DeleteSshPublicKeyResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteSshPublicKeyResponse]
$creadListPrec :: ReadPrec [DeleteSshPublicKeyResponse]
readPrec :: ReadPrec DeleteSshPublicKeyResponse
$creadPrec :: ReadPrec DeleteSshPublicKeyResponse
readList :: ReadS [DeleteSshPublicKeyResponse]
$creadList :: ReadS [DeleteSshPublicKeyResponse]
readsPrec :: Int -> ReadS DeleteSshPublicKeyResponse
$creadsPrec :: Int -> ReadS DeleteSshPublicKeyResponse
Prelude.Read, Int -> DeleteSshPublicKeyResponse -> ShowS
[DeleteSshPublicKeyResponse] -> ShowS
DeleteSshPublicKeyResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteSshPublicKeyResponse] -> ShowS
$cshowList :: [DeleteSshPublicKeyResponse] -> ShowS
show :: DeleteSshPublicKeyResponse -> String
$cshow :: DeleteSshPublicKeyResponse -> String
showsPrec :: Int -> DeleteSshPublicKeyResponse -> ShowS
$cshowsPrec :: Int -> DeleteSshPublicKeyResponse -> ShowS
Prelude.Show, forall x.
Rep DeleteSshPublicKeyResponse x -> DeleteSshPublicKeyResponse
forall x.
DeleteSshPublicKeyResponse -> Rep DeleteSshPublicKeyResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeleteSshPublicKeyResponse x -> DeleteSshPublicKeyResponse
$cfrom :: forall x.
DeleteSshPublicKeyResponse -> Rep DeleteSshPublicKeyResponse x
Prelude.Generic)

-- |
-- Create a value of 'DeleteSshPublicKeyResponse' 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.
newDeleteSshPublicKeyResponse ::
  DeleteSshPublicKeyResponse
newDeleteSshPublicKeyResponse :: DeleteSshPublicKeyResponse
newDeleteSshPublicKeyResponse =
  DeleteSshPublicKeyResponse
DeleteSshPublicKeyResponse'

instance Prelude.NFData DeleteSshPublicKeyResponse where
  rnf :: DeleteSshPublicKeyResponse -> ()
rnf DeleteSshPublicKeyResponse
_ = ()