{-# 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.APIGateway.GetClientCertificate
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Gets information about the current ClientCertificate resource.
module Amazonka.APIGateway.GetClientCertificate
  ( -- * Creating a Request
    GetClientCertificate (..),
    newGetClientCertificate,

    -- * Request Lenses
    getClientCertificate_clientCertificateId,

    -- * Destructuring the Response
    ClientCertificate (..),
    newClientCertificate,

    -- * Response Lenses
    clientCertificate_clientCertificateId,
    clientCertificate_createdDate,
    clientCertificate_description,
    clientCertificate_expirationDate,
    clientCertificate_pemEncodedCertificate,
    clientCertificate_tags,
  )
where

import Amazonka.APIGateway.Types
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

-- | A request to get information about the current ClientCertificate
-- resource.
--
-- /See:/ 'newGetClientCertificate' smart constructor.
data GetClientCertificate = GetClientCertificate'
  { -- | The identifier of the ClientCertificate resource to be described.
    GetClientCertificate -> Text
clientCertificateId :: Prelude.Text
  }
  deriving (GetClientCertificate -> GetClientCertificate -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetClientCertificate -> GetClientCertificate -> Bool
$c/= :: GetClientCertificate -> GetClientCertificate -> Bool
== :: GetClientCertificate -> GetClientCertificate -> Bool
$c== :: GetClientCertificate -> GetClientCertificate -> Bool
Prelude.Eq, ReadPrec [GetClientCertificate]
ReadPrec GetClientCertificate
Int -> ReadS GetClientCertificate
ReadS [GetClientCertificate]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetClientCertificate]
$creadListPrec :: ReadPrec [GetClientCertificate]
readPrec :: ReadPrec GetClientCertificate
$creadPrec :: ReadPrec GetClientCertificate
readList :: ReadS [GetClientCertificate]
$creadList :: ReadS [GetClientCertificate]
readsPrec :: Int -> ReadS GetClientCertificate
$creadsPrec :: Int -> ReadS GetClientCertificate
Prelude.Read, Int -> GetClientCertificate -> ShowS
[GetClientCertificate] -> ShowS
GetClientCertificate -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetClientCertificate] -> ShowS
$cshowList :: [GetClientCertificate] -> ShowS
show :: GetClientCertificate -> String
$cshow :: GetClientCertificate -> String
showsPrec :: Int -> GetClientCertificate -> ShowS
$cshowsPrec :: Int -> GetClientCertificate -> ShowS
Prelude.Show, forall x. Rep GetClientCertificate x -> GetClientCertificate
forall x. GetClientCertificate -> Rep GetClientCertificate x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetClientCertificate x -> GetClientCertificate
$cfrom :: forall x. GetClientCertificate -> Rep GetClientCertificate x
Prelude.Generic)

-- |
-- Create a value of 'GetClientCertificate' 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:
--
-- 'clientCertificateId', 'getClientCertificate_clientCertificateId' - The identifier of the ClientCertificate resource to be described.
newGetClientCertificate ::
  -- | 'clientCertificateId'
  Prelude.Text ->
  GetClientCertificate
newGetClientCertificate :: Text -> GetClientCertificate
newGetClientCertificate Text
pClientCertificateId_ =
  GetClientCertificate'
    { $sel:clientCertificateId:GetClientCertificate' :: Text
clientCertificateId =
        Text
pClientCertificateId_
    }

-- | The identifier of the ClientCertificate resource to be described.
getClientCertificate_clientCertificateId :: Lens.Lens' GetClientCertificate Prelude.Text
getClientCertificate_clientCertificateId :: Lens' GetClientCertificate Text
getClientCertificate_clientCertificateId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetClientCertificate' {Text
clientCertificateId :: Text
$sel:clientCertificateId:GetClientCertificate' :: GetClientCertificate -> Text
clientCertificateId} -> Text
clientCertificateId) (\s :: GetClientCertificate
s@GetClientCertificate' {} Text
a -> GetClientCertificate
s {$sel:clientCertificateId:GetClientCertificate' :: Text
clientCertificateId = Text
a} :: GetClientCertificate)

instance Core.AWSRequest GetClientCertificate where
  type
    AWSResponse GetClientCertificate =
      ClientCertificate
  request :: (Service -> Service)
-> GetClientCertificate -> Request GetClientCertificate
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.get (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy GetClientCertificate
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetClientCertificate)))
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 -> forall a. FromJSON a => Object -> Either String a
Data.eitherParseJSON Object
x)

instance Prelude.Hashable GetClientCertificate where
  hashWithSalt :: Int -> GetClientCertificate -> Int
hashWithSalt Int
_salt GetClientCertificate' {Text
clientCertificateId :: Text
$sel:clientCertificateId:GetClientCertificate' :: GetClientCertificate -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
clientCertificateId

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

instance Data.ToHeaders GetClientCertificate where
  toHeaders :: GetClientCertificate -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Accept"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# (ByteString
"application/json" :: Prelude.ByteString)
          ]
      )

instance Data.ToPath GetClientCertificate where
  toPath :: GetClientCertificate -> ByteString
toPath GetClientCertificate' {Text
clientCertificateId :: Text
$sel:clientCertificateId:GetClientCertificate' :: GetClientCertificate -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/clientcertificates/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
clientCertificateId
      ]

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