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

    -- * Request Lenses
    getKeyPair_keyPairName,

    -- * Destructuring the Response
    GetKeyPairResponse (..),
    newGetKeyPairResponse,

    -- * Response Lenses
    getKeyPairResponse_keyPair,
    getKeyPairResponse_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:/ 'newGetKeyPair' smart constructor.
data GetKeyPair = GetKeyPair'
  { -- | The name of the key pair for which you are requesting information.
    GetKeyPair -> Text
keyPairName :: Prelude.Text
  }
  deriving (GetKeyPair -> GetKeyPair -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetKeyPair -> GetKeyPair -> Bool
$c/= :: GetKeyPair -> GetKeyPair -> Bool
== :: GetKeyPair -> GetKeyPair -> Bool
$c== :: GetKeyPair -> GetKeyPair -> Bool
Prelude.Eq, ReadPrec [GetKeyPair]
ReadPrec GetKeyPair
Int -> ReadS GetKeyPair
ReadS [GetKeyPair]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetKeyPair]
$creadListPrec :: ReadPrec [GetKeyPair]
readPrec :: ReadPrec GetKeyPair
$creadPrec :: ReadPrec GetKeyPair
readList :: ReadS [GetKeyPair]
$creadList :: ReadS [GetKeyPair]
readsPrec :: Int -> ReadS GetKeyPair
$creadsPrec :: Int -> ReadS GetKeyPair
Prelude.Read, Int -> GetKeyPair -> ShowS
[GetKeyPair] -> ShowS
GetKeyPair -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetKeyPair] -> ShowS
$cshowList :: [GetKeyPair] -> ShowS
show :: GetKeyPair -> String
$cshow :: GetKeyPair -> String
showsPrec :: Int -> GetKeyPair -> ShowS
$cshowsPrec :: Int -> GetKeyPair -> ShowS
Prelude.Show, forall x. Rep GetKeyPair x -> GetKeyPair
forall x. GetKeyPair -> Rep GetKeyPair x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetKeyPair x -> GetKeyPair
$cfrom :: forall x. GetKeyPair -> Rep GetKeyPair x
Prelude.Generic)

-- |
-- Create a value of 'GetKeyPair' 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', 'getKeyPair_keyPairName' - The name of the key pair for which you are requesting information.
newGetKeyPair ::
  -- | 'keyPairName'
  Prelude.Text ->
  GetKeyPair
newGetKeyPair :: Text -> GetKeyPair
newGetKeyPair Text
pKeyPairName_ =
  GetKeyPair' {$sel:keyPairName:GetKeyPair' :: Text
keyPairName = Text
pKeyPairName_}

-- | The name of the key pair for which you are requesting information.
getKeyPair_keyPairName :: Lens.Lens' GetKeyPair Prelude.Text
getKeyPair_keyPairName :: Lens' GetKeyPair Text
getKeyPair_keyPairName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetKeyPair' {Text
keyPairName :: Text
$sel:keyPairName:GetKeyPair' :: GetKeyPair -> Text
keyPairName} -> Text
keyPairName) (\s :: GetKeyPair
s@GetKeyPair' {} Text
a -> GetKeyPair
s {$sel:keyPairName:GetKeyPair' :: Text
keyPairName = Text
a} :: GetKeyPair)

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

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

instance Data.ToHeaders GetKeyPair where
  toHeaders :: GetKeyPair -> 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.GetKeyPair" ::
                          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 GetKeyPair where
  toJSON :: GetKeyPair -> Value
toJSON GetKeyPair' {Text
keyPairName :: Text
$sel:keyPairName:GetKeyPair' :: GetKeyPair -> 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)]
      )

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

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

-- | /See:/ 'newGetKeyPairResponse' smart constructor.
data GetKeyPairResponse = GetKeyPairResponse'
  { -- | An array of key-value pairs containing information about the key pair.
    GetKeyPairResponse -> Maybe KeyPair
keyPair :: Prelude.Maybe KeyPair,
    -- | The response's http status code.
    GetKeyPairResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetKeyPairResponse -> GetKeyPairResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetKeyPairResponse -> GetKeyPairResponse -> Bool
$c/= :: GetKeyPairResponse -> GetKeyPairResponse -> Bool
== :: GetKeyPairResponse -> GetKeyPairResponse -> Bool
$c== :: GetKeyPairResponse -> GetKeyPairResponse -> Bool
Prelude.Eq, ReadPrec [GetKeyPairResponse]
ReadPrec GetKeyPairResponse
Int -> ReadS GetKeyPairResponse
ReadS [GetKeyPairResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetKeyPairResponse]
$creadListPrec :: ReadPrec [GetKeyPairResponse]
readPrec :: ReadPrec GetKeyPairResponse
$creadPrec :: ReadPrec GetKeyPairResponse
readList :: ReadS [GetKeyPairResponse]
$creadList :: ReadS [GetKeyPairResponse]
readsPrec :: Int -> ReadS GetKeyPairResponse
$creadsPrec :: Int -> ReadS GetKeyPairResponse
Prelude.Read, Int -> GetKeyPairResponse -> ShowS
[GetKeyPairResponse] -> ShowS
GetKeyPairResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetKeyPairResponse] -> ShowS
$cshowList :: [GetKeyPairResponse] -> ShowS
show :: GetKeyPairResponse -> String
$cshow :: GetKeyPairResponse -> String
showsPrec :: Int -> GetKeyPairResponse -> ShowS
$cshowsPrec :: Int -> GetKeyPairResponse -> ShowS
Prelude.Show, forall x. Rep GetKeyPairResponse x -> GetKeyPairResponse
forall x. GetKeyPairResponse -> Rep GetKeyPairResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetKeyPairResponse x -> GetKeyPairResponse
$cfrom :: forall x. GetKeyPairResponse -> Rep GetKeyPairResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetKeyPairResponse' 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:
--
-- 'keyPair', 'getKeyPairResponse_keyPair' - An array of key-value pairs containing information about the key pair.
--
-- 'httpStatus', 'getKeyPairResponse_httpStatus' - The response's http status code.
newGetKeyPairResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetKeyPairResponse
newGetKeyPairResponse :: Int -> GetKeyPairResponse
newGetKeyPairResponse Int
pHttpStatus_ =
  GetKeyPairResponse'
    { $sel:keyPair:GetKeyPairResponse' :: Maybe KeyPair
keyPair = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetKeyPairResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | An array of key-value pairs containing information about the key pair.
getKeyPairResponse_keyPair :: Lens.Lens' GetKeyPairResponse (Prelude.Maybe KeyPair)
getKeyPairResponse_keyPair :: Lens' GetKeyPairResponse (Maybe KeyPair)
getKeyPairResponse_keyPair = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetKeyPairResponse' {Maybe KeyPair
keyPair :: Maybe KeyPair
$sel:keyPair:GetKeyPairResponse' :: GetKeyPairResponse -> Maybe KeyPair
keyPair} -> Maybe KeyPair
keyPair) (\s :: GetKeyPairResponse
s@GetKeyPairResponse' {} Maybe KeyPair
a -> GetKeyPairResponse
s {$sel:keyPair:GetKeyPairResponse' :: Maybe KeyPair
keyPair = Maybe KeyPair
a} :: GetKeyPairResponse)

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

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