{-# 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.RolesAnywhere.GetCrl
-- 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 a certificate revocation list (CRL).
--
-- __Required permissions:__ @rolesanywhere:GetCrl@.
module Amazonka.RolesAnywhere.GetCrl
  ( -- * Creating a Request
    GetCrl (..),
    newGetCrl,

    -- * Request Lenses
    getCrl_crlId,

    -- * Destructuring the Response
    CrlDetailResponse (..),
    newCrlDetailResponse,

    -- * Response Lenses
    crlDetailResponse_crl,
  )
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.RolesAnywhere.Types

-- | /See:/ 'newGetCrl' smart constructor.
data GetCrl = GetCrl'
  { -- | The unique identifier of the certificate revocation list (CRL).
    GetCrl -> Text
crlId :: Prelude.Text
  }
  deriving (GetCrl -> GetCrl -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetCrl -> GetCrl -> Bool
$c/= :: GetCrl -> GetCrl -> Bool
== :: GetCrl -> GetCrl -> Bool
$c== :: GetCrl -> GetCrl -> Bool
Prelude.Eq, ReadPrec [GetCrl]
ReadPrec GetCrl
Int -> ReadS GetCrl
ReadS [GetCrl]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetCrl]
$creadListPrec :: ReadPrec [GetCrl]
readPrec :: ReadPrec GetCrl
$creadPrec :: ReadPrec GetCrl
readList :: ReadS [GetCrl]
$creadList :: ReadS [GetCrl]
readsPrec :: Int -> ReadS GetCrl
$creadsPrec :: Int -> ReadS GetCrl
Prelude.Read, Int -> GetCrl -> ShowS
[GetCrl] -> ShowS
GetCrl -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetCrl] -> ShowS
$cshowList :: [GetCrl] -> ShowS
show :: GetCrl -> String
$cshow :: GetCrl -> String
showsPrec :: Int -> GetCrl -> ShowS
$cshowsPrec :: Int -> GetCrl -> ShowS
Prelude.Show, forall x. Rep GetCrl x -> GetCrl
forall x. GetCrl -> Rep GetCrl x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetCrl x -> GetCrl
$cfrom :: forall x. GetCrl -> Rep GetCrl x
Prelude.Generic)

-- |
-- Create a value of 'GetCrl' 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:
--
-- 'crlId', 'getCrl_crlId' - The unique identifier of the certificate revocation list (CRL).
newGetCrl ::
  -- | 'crlId'
  Prelude.Text ->
  GetCrl
newGetCrl :: Text -> GetCrl
newGetCrl Text
pCrlId_ = GetCrl' {$sel:crlId:GetCrl' :: Text
crlId = Text
pCrlId_}

-- | The unique identifier of the certificate revocation list (CRL).
getCrl_crlId :: Lens.Lens' GetCrl Prelude.Text
getCrl_crlId :: Lens' GetCrl Text
getCrl_crlId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCrl' {Text
crlId :: Text
$sel:crlId:GetCrl' :: GetCrl -> Text
crlId} -> Text
crlId) (\s :: GetCrl
s@GetCrl' {} Text
a -> GetCrl
s {$sel:crlId:GetCrl' :: Text
crlId = Text
a} :: GetCrl)

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

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

instance Data.ToHeaders GetCrl where
  toHeaders :: GetCrl -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

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

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