{-# 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.Greengrass.GetGroupCertificateAuthority
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Retreives the CA associated with a group. Returns the public key of the
-- CA.
module Amazonka.Greengrass.GetGroupCertificateAuthority
  ( -- * Creating a Request
    GetGroupCertificateAuthority (..),
    newGetGroupCertificateAuthority,

    -- * Request Lenses
    getGroupCertificateAuthority_certificateAuthorityId,
    getGroupCertificateAuthority_groupId,

    -- * Destructuring the Response
    GetGroupCertificateAuthorityResponse (..),
    newGetGroupCertificateAuthorityResponse,

    -- * Response Lenses
    getGroupCertificateAuthorityResponse_groupCertificateAuthorityArn,
    getGroupCertificateAuthorityResponse_groupCertificateAuthorityId,
    getGroupCertificateAuthorityResponse_pemEncodedCertificate,
    getGroupCertificateAuthorityResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.Greengrass.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newGetGroupCertificateAuthority' smart constructor.
data GetGroupCertificateAuthority = GetGroupCertificateAuthority'
  { -- | The ID of the certificate authority.
    GetGroupCertificateAuthority -> Text
certificateAuthorityId :: Prelude.Text,
    -- | The ID of the Greengrass group.
    GetGroupCertificateAuthority -> Text
groupId :: Prelude.Text
  }
  deriving (GetGroupCertificateAuthority
-> GetGroupCertificateAuthority -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetGroupCertificateAuthority
-> GetGroupCertificateAuthority -> Bool
$c/= :: GetGroupCertificateAuthority
-> GetGroupCertificateAuthority -> Bool
== :: GetGroupCertificateAuthority
-> GetGroupCertificateAuthority -> Bool
$c== :: GetGroupCertificateAuthority
-> GetGroupCertificateAuthority -> Bool
Prelude.Eq, ReadPrec [GetGroupCertificateAuthority]
ReadPrec GetGroupCertificateAuthority
Int -> ReadS GetGroupCertificateAuthority
ReadS [GetGroupCertificateAuthority]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetGroupCertificateAuthority]
$creadListPrec :: ReadPrec [GetGroupCertificateAuthority]
readPrec :: ReadPrec GetGroupCertificateAuthority
$creadPrec :: ReadPrec GetGroupCertificateAuthority
readList :: ReadS [GetGroupCertificateAuthority]
$creadList :: ReadS [GetGroupCertificateAuthority]
readsPrec :: Int -> ReadS GetGroupCertificateAuthority
$creadsPrec :: Int -> ReadS GetGroupCertificateAuthority
Prelude.Read, Int -> GetGroupCertificateAuthority -> ShowS
[GetGroupCertificateAuthority] -> ShowS
GetGroupCertificateAuthority -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetGroupCertificateAuthority] -> ShowS
$cshowList :: [GetGroupCertificateAuthority] -> ShowS
show :: GetGroupCertificateAuthority -> String
$cshow :: GetGroupCertificateAuthority -> String
showsPrec :: Int -> GetGroupCertificateAuthority -> ShowS
$cshowsPrec :: Int -> GetGroupCertificateAuthority -> ShowS
Prelude.Show, forall x.
Rep GetGroupCertificateAuthority x -> GetGroupCertificateAuthority
forall x.
GetGroupCertificateAuthority -> Rep GetGroupCertificateAuthority x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetGroupCertificateAuthority x -> GetGroupCertificateAuthority
$cfrom :: forall x.
GetGroupCertificateAuthority -> Rep GetGroupCertificateAuthority x
Prelude.Generic)

-- |
-- Create a value of 'GetGroupCertificateAuthority' 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:
--
-- 'certificateAuthorityId', 'getGroupCertificateAuthority_certificateAuthorityId' - The ID of the certificate authority.
--
-- 'groupId', 'getGroupCertificateAuthority_groupId' - The ID of the Greengrass group.
newGetGroupCertificateAuthority ::
  -- | 'certificateAuthorityId'
  Prelude.Text ->
  -- | 'groupId'
  Prelude.Text ->
  GetGroupCertificateAuthority
newGetGroupCertificateAuthority :: Text -> Text -> GetGroupCertificateAuthority
newGetGroupCertificateAuthority
  Text
pCertificateAuthorityId_
  Text
pGroupId_ =
    GetGroupCertificateAuthority'
      { $sel:certificateAuthorityId:GetGroupCertificateAuthority' :: Text
certificateAuthorityId =
          Text
pCertificateAuthorityId_,
        $sel:groupId:GetGroupCertificateAuthority' :: Text
groupId = Text
pGroupId_
      }

-- | The ID of the certificate authority.
getGroupCertificateAuthority_certificateAuthorityId :: Lens.Lens' GetGroupCertificateAuthority Prelude.Text
getGroupCertificateAuthority_certificateAuthorityId :: Lens' GetGroupCertificateAuthority Text
getGroupCertificateAuthority_certificateAuthorityId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetGroupCertificateAuthority' {Text
certificateAuthorityId :: Text
$sel:certificateAuthorityId:GetGroupCertificateAuthority' :: GetGroupCertificateAuthority -> Text
certificateAuthorityId} -> Text
certificateAuthorityId) (\s :: GetGroupCertificateAuthority
s@GetGroupCertificateAuthority' {} Text
a -> GetGroupCertificateAuthority
s {$sel:certificateAuthorityId:GetGroupCertificateAuthority' :: Text
certificateAuthorityId = Text
a} :: GetGroupCertificateAuthority)

-- | The ID of the Greengrass group.
getGroupCertificateAuthority_groupId :: Lens.Lens' GetGroupCertificateAuthority Prelude.Text
getGroupCertificateAuthority_groupId :: Lens' GetGroupCertificateAuthority Text
getGroupCertificateAuthority_groupId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetGroupCertificateAuthority' {Text
groupId :: Text
$sel:groupId:GetGroupCertificateAuthority' :: GetGroupCertificateAuthority -> Text
groupId} -> Text
groupId) (\s :: GetGroupCertificateAuthority
s@GetGroupCertificateAuthority' {} Text
a -> GetGroupCertificateAuthority
s {$sel:groupId:GetGroupCertificateAuthority' :: Text
groupId = Text
a} :: GetGroupCertificateAuthority)

instance Core.AWSRequest GetGroupCertificateAuthority where
  type
    AWSResponse GetGroupCertificateAuthority =
      GetGroupCertificateAuthorityResponse
  request :: (Service -> Service)
-> GetGroupCertificateAuthority
-> Request GetGroupCertificateAuthority
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 GetGroupCertificateAuthority
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetGroupCertificateAuthority)))
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 Text
-> Maybe Text
-> Maybe Text
-> Int
-> GetGroupCertificateAuthorityResponse
GetGroupCertificateAuthorityResponse'
            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
"GroupCertificateAuthorityArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"GroupCertificateAuthorityId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"PemEncodedCertificate")
            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
    GetGroupCertificateAuthority
  where
  hashWithSalt :: Int -> GetGroupCertificateAuthority -> Int
hashWithSalt Int
_salt GetGroupCertificateAuthority' {Text
groupId :: Text
certificateAuthorityId :: Text
$sel:groupId:GetGroupCertificateAuthority' :: GetGroupCertificateAuthority -> Text
$sel:certificateAuthorityId:GetGroupCertificateAuthority' :: GetGroupCertificateAuthority -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
certificateAuthorityId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
groupId

instance Prelude.NFData GetGroupCertificateAuthority where
  rnf :: GetGroupCertificateAuthority -> ()
rnf GetGroupCertificateAuthority' {Text
groupId :: Text
certificateAuthorityId :: Text
$sel:groupId:GetGroupCertificateAuthority' :: GetGroupCertificateAuthority -> Text
$sel:certificateAuthorityId:GetGroupCertificateAuthority' :: GetGroupCertificateAuthority -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
certificateAuthorityId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
groupId

instance Data.ToHeaders GetGroupCertificateAuthority where
  toHeaders :: GetGroupCertificateAuthority -> 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 GetGroupCertificateAuthority where
  toPath :: GetGroupCertificateAuthority -> ByteString
toPath GetGroupCertificateAuthority' {Text
groupId :: Text
certificateAuthorityId :: Text
$sel:groupId:GetGroupCertificateAuthority' :: GetGroupCertificateAuthority -> Text
$sel:certificateAuthorityId:GetGroupCertificateAuthority' :: GetGroupCertificateAuthority -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/greengrass/groups/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
groupId,
        ByteString
"/certificateauthorities/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
certificateAuthorityId
      ]

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

-- | /See:/ 'newGetGroupCertificateAuthorityResponse' smart constructor.
data GetGroupCertificateAuthorityResponse = GetGroupCertificateAuthorityResponse'
  { -- | The ARN of the certificate authority for the group.
    GetGroupCertificateAuthorityResponse -> Maybe Text
groupCertificateAuthorityArn :: Prelude.Maybe Prelude.Text,
    -- | The ID of the certificate authority for the group.
    GetGroupCertificateAuthorityResponse -> Maybe Text
groupCertificateAuthorityId :: Prelude.Maybe Prelude.Text,
    -- | The PEM encoded certificate for the group.
    GetGroupCertificateAuthorityResponse -> Maybe Text
pemEncodedCertificate :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    GetGroupCertificateAuthorityResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetGroupCertificateAuthorityResponse
-> GetGroupCertificateAuthorityResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetGroupCertificateAuthorityResponse
-> GetGroupCertificateAuthorityResponse -> Bool
$c/= :: GetGroupCertificateAuthorityResponse
-> GetGroupCertificateAuthorityResponse -> Bool
== :: GetGroupCertificateAuthorityResponse
-> GetGroupCertificateAuthorityResponse -> Bool
$c== :: GetGroupCertificateAuthorityResponse
-> GetGroupCertificateAuthorityResponse -> Bool
Prelude.Eq, ReadPrec [GetGroupCertificateAuthorityResponse]
ReadPrec GetGroupCertificateAuthorityResponse
Int -> ReadS GetGroupCertificateAuthorityResponse
ReadS [GetGroupCertificateAuthorityResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetGroupCertificateAuthorityResponse]
$creadListPrec :: ReadPrec [GetGroupCertificateAuthorityResponse]
readPrec :: ReadPrec GetGroupCertificateAuthorityResponse
$creadPrec :: ReadPrec GetGroupCertificateAuthorityResponse
readList :: ReadS [GetGroupCertificateAuthorityResponse]
$creadList :: ReadS [GetGroupCertificateAuthorityResponse]
readsPrec :: Int -> ReadS GetGroupCertificateAuthorityResponse
$creadsPrec :: Int -> ReadS GetGroupCertificateAuthorityResponse
Prelude.Read, Int -> GetGroupCertificateAuthorityResponse -> ShowS
[GetGroupCertificateAuthorityResponse] -> ShowS
GetGroupCertificateAuthorityResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetGroupCertificateAuthorityResponse] -> ShowS
$cshowList :: [GetGroupCertificateAuthorityResponse] -> ShowS
show :: GetGroupCertificateAuthorityResponse -> String
$cshow :: GetGroupCertificateAuthorityResponse -> String
showsPrec :: Int -> GetGroupCertificateAuthorityResponse -> ShowS
$cshowsPrec :: Int -> GetGroupCertificateAuthorityResponse -> ShowS
Prelude.Show, forall x.
Rep GetGroupCertificateAuthorityResponse x
-> GetGroupCertificateAuthorityResponse
forall x.
GetGroupCertificateAuthorityResponse
-> Rep GetGroupCertificateAuthorityResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetGroupCertificateAuthorityResponse x
-> GetGroupCertificateAuthorityResponse
$cfrom :: forall x.
GetGroupCertificateAuthorityResponse
-> Rep GetGroupCertificateAuthorityResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetGroupCertificateAuthorityResponse' 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:
--
-- 'groupCertificateAuthorityArn', 'getGroupCertificateAuthorityResponse_groupCertificateAuthorityArn' - The ARN of the certificate authority for the group.
--
-- 'groupCertificateAuthorityId', 'getGroupCertificateAuthorityResponse_groupCertificateAuthorityId' - The ID of the certificate authority for the group.
--
-- 'pemEncodedCertificate', 'getGroupCertificateAuthorityResponse_pemEncodedCertificate' - The PEM encoded certificate for the group.
--
-- 'httpStatus', 'getGroupCertificateAuthorityResponse_httpStatus' - The response's http status code.
newGetGroupCertificateAuthorityResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetGroupCertificateAuthorityResponse
newGetGroupCertificateAuthorityResponse :: Int -> GetGroupCertificateAuthorityResponse
newGetGroupCertificateAuthorityResponse Int
pHttpStatus_ =
  GetGroupCertificateAuthorityResponse'
    { $sel:groupCertificateAuthorityArn:GetGroupCertificateAuthorityResponse' :: Maybe Text
groupCertificateAuthorityArn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:groupCertificateAuthorityId:GetGroupCertificateAuthorityResponse' :: Maybe Text
groupCertificateAuthorityId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:pemEncodedCertificate:GetGroupCertificateAuthorityResponse' :: Maybe Text
pemEncodedCertificate =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetGroupCertificateAuthorityResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The ARN of the certificate authority for the group.
getGroupCertificateAuthorityResponse_groupCertificateAuthorityArn :: Lens.Lens' GetGroupCertificateAuthorityResponse (Prelude.Maybe Prelude.Text)
getGroupCertificateAuthorityResponse_groupCertificateAuthorityArn :: Lens' GetGroupCertificateAuthorityResponse (Maybe Text)
getGroupCertificateAuthorityResponse_groupCertificateAuthorityArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetGroupCertificateAuthorityResponse' {Maybe Text
groupCertificateAuthorityArn :: Maybe Text
$sel:groupCertificateAuthorityArn:GetGroupCertificateAuthorityResponse' :: GetGroupCertificateAuthorityResponse -> Maybe Text
groupCertificateAuthorityArn} -> Maybe Text
groupCertificateAuthorityArn) (\s :: GetGroupCertificateAuthorityResponse
s@GetGroupCertificateAuthorityResponse' {} Maybe Text
a -> GetGroupCertificateAuthorityResponse
s {$sel:groupCertificateAuthorityArn:GetGroupCertificateAuthorityResponse' :: Maybe Text
groupCertificateAuthorityArn = Maybe Text
a} :: GetGroupCertificateAuthorityResponse)

-- | The ID of the certificate authority for the group.
getGroupCertificateAuthorityResponse_groupCertificateAuthorityId :: Lens.Lens' GetGroupCertificateAuthorityResponse (Prelude.Maybe Prelude.Text)
getGroupCertificateAuthorityResponse_groupCertificateAuthorityId :: Lens' GetGroupCertificateAuthorityResponse (Maybe Text)
getGroupCertificateAuthorityResponse_groupCertificateAuthorityId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetGroupCertificateAuthorityResponse' {Maybe Text
groupCertificateAuthorityId :: Maybe Text
$sel:groupCertificateAuthorityId:GetGroupCertificateAuthorityResponse' :: GetGroupCertificateAuthorityResponse -> Maybe Text
groupCertificateAuthorityId} -> Maybe Text
groupCertificateAuthorityId) (\s :: GetGroupCertificateAuthorityResponse
s@GetGroupCertificateAuthorityResponse' {} Maybe Text
a -> GetGroupCertificateAuthorityResponse
s {$sel:groupCertificateAuthorityId:GetGroupCertificateAuthorityResponse' :: Maybe Text
groupCertificateAuthorityId = Maybe Text
a} :: GetGroupCertificateAuthorityResponse)

-- | The PEM encoded certificate for the group.
getGroupCertificateAuthorityResponse_pemEncodedCertificate :: Lens.Lens' GetGroupCertificateAuthorityResponse (Prelude.Maybe Prelude.Text)
getGroupCertificateAuthorityResponse_pemEncodedCertificate :: Lens' GetGroupCertificateAuthorityResponse (Maybe Text)
getGroupCertificateAuthorityResponse_pemEncodedCertificate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetGroupCertificateAuthorityResponse' {Maybe Text
pemEncodedCertificate :: Maybe Text
$sel:pemEncodedCertificate:GetGroupCertificateAuthorityResponse' :: GetGroupCertificateAuthorityResponse -> Maybe Text
pemEncodedCertificate} -> Maybe Text
pemEncodedCertificate) (\s :: GetGroupCertificateAuthorityResponse
s@GetGroupCertificateAuthorityResponse' {} Maybe Text
a -> GetGroupCertificateAuthorityResponse
s {$sel:pemEncodedCertificate:GetGroupCertificateAuthorityResponse' :: Maybe Text
pemEncodedCertificate = Maybe Text
a} :: GetGroupCertificateAuthorityResponse)

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

instance
  Prelude.NFData
    GetGroupCertificateAuthorityResponse
  where
  rnf :: GetGroupCertificateAuthorityResponse -> ()
rnf GetGroupCertificateAuthorityResponse' {Int
Maybe Text
httpStatus :: Int
pemEncodedCertificate :: Maybe Text
groupCertificateAuthorityId :: Maybe Text
groupCertificateAuthorityArn :: Maybe Text
$sel:httpStatus:GetGroupCertificateAuthorityResponse' :: GetGroupCertificateAuthorityResponse -> Int
$sel:pemEncodedCertificate:GetGroupCertificateAuthorityResponse' :: GetGroupCertificateAuthorityResponse -> Maybe Text
$sel:groupCertificateAuthorityId:GetGroupCertificateAuthorityResponse' :: GetGroupCertificateAuthorityResponse -> Maybe Text
$sel:groupCertificateAuthorityArn:GetGroupCertificateAuthorityResponse' :: GetGroupCertificateAuthorityResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
groupCertificateAuthorityArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
groupCertificateAuthorityId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
pemEncodedCertificate
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus