{-# 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.DeleteKnownHostKeys
-- 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 known host key or certificate used by the Amazon Lightsail
-- browser-based SSH or RDP clients to authenticate an instance. This
-- operation enables the Lightsail browser-based SSH or RDP clients to
-- connect to the instance after a host key mismatch.
--
-- Perform this operation only if you were expecting the host key or
-- certificate mismatch or if you are familiar with the new host key or
-- certificate on the instance. For more information, see
-- <https://lightsail.aws.amazon.com/ls/docs/en_us/articles/amazon-lightsail-troubleshooting-browser-based-ssh-rdp-client-connection Troubleshooting connection issues when using the Amazon Lightsail browser-based SSH or RDP client>.
module Amazonka.Lightsail.DeleteKnownHostKeys
  ( -- * Creating a Request
    DeleteKnownHostKeys (..),
    newDeleteKnownHostKeys,

    -- * Request Lenses
    deleteKnownHostKeys_instanceName,

    -- * Destructuring the Response
    DeleteKnownHostKeysResponse (..),
    newDeleteKnownHostKeysResponse,

    -- * Response Lenses
    deleteKnownHostKeysResponse_operations,
    deleteKnownHostKeysResponse_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:/ 'newDeleteKnownHostKeys' smart constructor.
data DeleteKnownHostKeys = DeleteKnownHostKeys'
  { -- | The name of the instance for which you want to reset the host key or
    -- certificate.
    DeleteKnownHostKeys -> Text
instanceName :: Prelude.Text
  }
  deriving (DeleteKnownHostKeys -> DeleteKnownHostKeys -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteKnownHostKeys -> DeleteKnownHostKeys -> Bool
$c/= :: DeleteKnownHostKeys -> DeleteKnownHostKeys -> Bool
== :: DeleteKnownHostKeys -> DeleteKnownHostKeys -> Bool
$c== :: DeleteKnownHostKeys -> DeleteKnownHostKeys -> Bool
Prelude.Eq, ReadPrec [DeleteKnownHostKeys]
ReadPrec DeleteKnownHostKeys
Int -> ReadS DeleteKnownHostKeys
ReadS [DeleteKnownHostKeys]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteKnownHostKeys]
$creadListPrec :: ReadPrec [DeleteKnownHostKeys]
readPrec :: ReadPrec DeleteKnownHostKeys
$creadPrec :: ReadPrec DeleteKnownHostKeys
readList :: ReadS [DeleteKnownHostKeys]
$creadList :: ReadS [DeleteKnownHostKeys]
readsPrec :: Int -> ReadS DeleteKnownHostKeys
$creadsPrec :: Int -> ReadS DeleteKnownHostKeys
Prelude.Read, Int -> DeleteKnownHostKeys -> ShowS
[DeleteKnownHostKeys] -> ShowS
DeleteKnownHostKeys -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteKnownHostKeys] -> ShowS
$cshowList :: [DeleteKnownHostKeys] -> ShowS
show :: DeleteKnownHostKeys -> String
$cshow :: DeleteKnownHostKeys -> String
showsPrec :: Int -> DeleteKnownHostKeys -> ShowS
$cshowsPrec :: Int -> DeleteKnownHostKeys -> ShowS
Prelude.Show, forall x. Rep DeleteKnownHostKeys x -> DeleteKnownHostKeys
forall x. DeleteKnownHostKeys -> Rep DeleteKnownHostKeys x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteKnownHostKeys x -> DeleteKnownHostKeys
$cfrom :: forall x. DeleteKnownHostKeys -> Rep DeleteKnownHostKeys x
Prelude.Generic)

-- |
-- Create a value of 'DeleteKnownHostKeys' 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:
--
-- 'instanceName', 'deleteKnownHostKeys_instanceName' - The name of the instance for which you want to reset the host key or
-- certificate.
newDeleteKnownHostKeys ::
  -- | 'instanceName'
  Prelude.Text ->
  DeleteKnownHostKeys
newDeleteKnownHostKeys :: Text -> DeleteKnownHostKeys
newDeleteKnownHostKeys Text
pInstanceName_ =
  DeleteKnownHostKeys' {$sel:instanceName:DeleteKnownHostKeys' :: Text
instanceName = Text
pInstanceName_}

-- | The name of the instance for which you want to reset the host key or
-- certificate.
deleteKnownHostKeys_instanceName :: Lens.Lens' DeleteKnownHostKeys Prelude.Text
deleteKnownHostKeys_instanceName :: Lens' DeleteKnownHostKeys Text
deleteKnownHostKeys_instanceName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteKnownHostKeys' {Text
instanceName :: Text
$sel:instanceName:DeleteKnownHostKeys' :: DeleteKnownHostKeys -> Text
instanceName} -> Text
instanceName) (\s :: DeleteKnownHostKeys
s@DeleteKnownHostKeys' {} Text
a -> DeleteKnownHostKeys
s {$sel:instanceName:DeleteKnownHostKeys' :: Text
instanceName = Text
a} :: DeleteKnownHostKeys)

instance Core.AWSRequest DeleteKnownHostKeys where
  type
    AWSResponse DeleteKnownHostKeys =
      DeleteKnownHostKeysResponse
  request :: (Service -> Service)
-> DeleteKnownHostKeys -> Request DeleteKnownHostKeys
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 DeleteKnownHostKeys
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DeleteKnownHostKeys)))
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 -> DeleteKnownHostKeysResponse
DeleteKnownHostKeysResponse'
            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
"operations" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
            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 DeleteKnownHostKeys where
  hashWithSalt :: Int -> DeleteKnownHostKeys -> Int
hashWithSalt Int
_salt DeleteKnownHostKeys' {Text
instanceName :: Text
$sel:instanceName:DeleteKnownHostKeys' :: DeleteKnownHostKeys -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
instanceName

instance Prelude.NFData DeleteKnownHostKeys where
  rnf :: DeleteKnownHostKeys -> ()
rnf DeleteKnownHostKeys' {Text
instanceName :: Text
$sel:instanceName:DeleteKnownHostKeys' :: DeleteKnownHostKeys -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
instanceName

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

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

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

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

-- |
-- Create a value of 'DeleteKnownHostKeysResponse' 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:
--
-- 'operations', 'deleteKnownHostKeysResponse_operations' - 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', 'deleteKnownHostKeysResponse_httpStatus' - The response's http status code.
newDeleteKnownHostKeysResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DeleteKnownHostKeysResponse
newDeleteKnownHostKeysResponse :: Int -> DeleteKnownHostKeysResponse
newDeleteKnownHostKeysResponse Int
pHttpStatus_ =
  DeleteKnownHostKeysResponse'
    { $sel:operations:DeleteKnownHostKeysResponse' :: Maybe [Operation]
operations =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DeleteKnownHostKeysResponse' :: 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.
deleteKnownHostKeysResponse_operations :: Lens.Lens' DeleteKnownHostKeysResponse (Prelude.Maybe [Operation])
deleteKnownHostKeysResponse_operations :: Lens' DeleteKnownHostKeysResponse (Maybe [Operation])
deleteKnownHostKeysResponse_operations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteKnownHostKeysResponse' {Maybe [Operation]
operations :: Maybe [Operation]
$sel:operations:DeleteKnownHostKeysResponse' :: DeleteKnownHostKeysResponse -> Maybe [Operation]
operations} -> Maybe [Operation]
operations) (\s :: DeleteKnownHostKeysResponse
s@DeleteKnownHostKeysResponse' {} Maybe [Operation]
a -> DeleteKnownHostKeysResponse
s {$sel:operations:DeleteKnownHostKeysResponse' :: Maybe [Operation]
operations = Maybe [Operation]
a} :: DeleteKnownHostKeysResponse) 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 response's http status code.
deleteKnownHostKeysResponse_httpStatus :: Lens.Lens' DeleteKnownHostKeysResponse Prelude.Int
deleteKnownHostKeysResponse_httpStatus :: Lens' DeleteKnownHostKeysResponse Int
deleteKnownHostKeysResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteKnownHostKeysResponse' {Int
httpStatus :: Int
$sel:httpStatus:DeleteKnownHostKeysResponse' :: DeleteKnownHostKeysResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: DeleteKnownHostKeysResponse
s@DeleteKnownHostKeysResponse' {} Int
a -> DeleteKnownHostKeysResponse
s {$sel:httpStatus:DeleteKnownHostKeysResponse' :: Int
httpStatus = Int
a} :: DeleteKnownHostKeysResponse)

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