{-# 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.IoT.ListCACertificates
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Lists the CA certificates registered for your Amazon Web Services
-- account.
--
-- The results are paginated with a default page size of 25. You can use
-- the returned marker to retrieve additional results.
--
-- Requires permission to access the
-- <https://docs.aws.amazon.com/service-authorization/latest/reference/list_awsiot.html#awsiot-actions-as-permissions ListCACertificates>
-- action.
--
-- This operation returns paginated results.
module Amazonka.IoT.ListCACertificates
  ( -- * Creating a Request
    ListCACertificates (..),
    newListCACertificates,

    -- * Request Lenses
    listCACertificates_ascendingOrder,
    listCACertificates_marker,
    listCACertificates_pageSize,
    listCACertificates_templateName,

    -- * Destructuring the Response
    ListCACertificatesResponse (..),
    newListCACertificatesResponse,

    -- * Response Lenses
    listCACertificatesResponse_certificates,
    listCACertificatesResponse_nextMarker,
    listCACertificatesResponse_httpStatus,
  )
where

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

-- | Input for the ListCACertificates operation.
--
-- /See:/ 'newListCACertificates' smart constructor.
data ListCACertificates = ListCACertificates'
  { -- | Determines the order of the results.
    ListCACertificates -> Maybe Bool
ascendingOrder :: Prelude.Maybe Prelude.Bool,
    -- | The marker for the next set of results.
    ListCACertificates -> Maybe Text
marker :: Prelude.Maybe Prelude.Text,
    -- | The result page size.
    ListCACertificates -> Maybe Natural
pageSize :: Prelude.Maybe Prelude.Natural,
    -- | The name of the provisioning template.
    ListCACertificates -> Maybe Text
templateName :: Prelude.Maybe Prelude.Text
  }
  deriving (ListCACertificates -> ListCACertificates -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListCACertificates -> ListCACertificates -> Bool
$c/= :: ListCACertificates -> ListCACertificates -> Bool
== :: ListCACertificates -> ListCACertificates -> Bool
$c== :: ListCACertificates -> ListCACertificates -> Bool
Prelude.Eq, ReadPrec [ListCACertificates]
ReadPrec ListCACertificates
Int -> ReadS ListCACertificates
ReadS [ListCACertificates]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListCACertificates]
$creadListPrec :: ReadPrec [ListCACertificates]
readPrec :: ReadPrec ListCACertificates
$creadPrec :: ReadPrec ListCACertificates
readList :: ReadS [ListCACertificates]
$creadList :: ReadS [ListCACertificates]
readsPrec :: Int -> ReadS ListCACertificates
$creadsPrec :: Int -> ReadS ListCACertificates
Prelude.Read, Int -> ListCACertificates -> ShowS
[ListCACertificates] -> ShowS
ListCACertificates -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListCACertificates] -> ShowS
$cshowList :: [ListCACertificates] -> ShowS
show :: ListCACertificates -> String
$cshow :: ListCACertificates -> String
showsPrec :: Int -> ListCACertificates -> ShowS
$cshowsPrec :: Int -> ListCACertificates -> ShowS
Prelude.Show, forall x. Rep ListCACertificates x -> ListCACertificates
forall x. ListCACertificates -> Rep ListCACertificates x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListCACertificates x -> ListCACertificates
$cfrom :: forall x. ListCACertificates -> Rep ListCACertificates x
Prelude.Generic)

-- |
-- Create a value of 'ListCACertificates' 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:
--
-- 'ascendingOrder', 'listCACertificates_ascendingOrder' - Determines the order of the results.
--
-- 'marker', 'listCACertificates_marker' - The marker for the next set of results.
--
-- 'pageSize', 'listCACertificates_pageSize' - The result page size.
--
-- 'templateName', 'listCACertificates_templateName' - The name of the provisioning template.
newListCACertificates ::
  ListCACertificates
newListCACertificates :: ListCACertificates
newListCACertificates =
  ListCACertificates'
    { $sel:ascendingOrder:ListCACertificates' :: Maybe Bool
ascendingOrder =
        forall a. Maybe a
Prelude.Nothing,
      $sel:marker:ListCACertificates' :: Maybe Text
marker = forall a. Maybe a
Prelude.Nothing,
      $sel:pageSize:ListCACertificates' :: Maybe Natural
pageSize = forall a. Maybe a
Prelude.Nothing,
      $sel:templateName:ListCACertificates' :: Maybe Text
templateName = forall a. Maybe a
Prelude.Nothing
    }

-- | Determines the order of the results.
listCACertificates_ascendingOrder :: Lens.Lens' ListCACertificates (Prelude.Maybe Prelude.Bool)
listCACertificates_ascendingOrder :: Lens' ListCACertificates (Maybe Bool)
listCACertificates_ascendingOrder = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListCACertificates' {Maybe Bool
ascendingOrder :: Maybe Bool
$sel:ascendingOrder:ListCACertificates' :: ListCACertificates -> Maybe Bool
ascendingOrder} -> Maybe Bool
ascendingOrder) (\s :: ListCACertificates
s@ListCACertificates' {} Maybe Bool
a -> ListCACertificates
s {$sel:ascendingOrder:ListCACertificates' :: Maybe Bool
ascendingOrder = Maybe Bool
a} :: ListCACertificates)

-- | The marker for the next set of results.
listCACertificates_marker :: Lens.Lens' ListCACertificates (Prelude.Maybe Prelude.Text)
listCACertificates_marker :: Lens' ListCACertificates (Maybe Text)
listCACertificates_marker = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListCACertificates' {Maybe Text
marker :: Maybe Text
$sel:marker:ListCACertificates' :: ListCACertificates -> Maybe Text
marker} -> Maybe Text
marker) (\s :: ListCACertificates
s@ListCACertificates' {} Maybe Text
a -> ListCACertificates
s {$sel:marker:ListCACertificates' :: Maybe Text
marker = Maybe Text
a} :: ListCACertificates)

-- | The result page size.
listCACertificates_pageSize :: Lens.Lens' ListCACertificates (Prelude.Maybe Prelude.Natural)
listCACertificates_pageSize :: Lens' ListCACertificates (Maybe Natural)
listCACertificates_pageSize = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListCACertificates' {Maybe Natural
pageSize :: Maybe Natural
$sel:pageSize:ListCACertificates' :: ListCACertificates -> Maybe Natural
pageSize} -> Maybe Natural
pageSize) (\s :: ListCACertificates
s@ListCACertificates' {} Maybe Natural
a -> ListCACertificates
s {$sel:pageSize:ListCACertificates' :: Maybe Natural
pageSize = Maybe Natural
a} :: ListCACertificates)

-- | The name of the provisioning template.
listCACertificates_templateName :: Lens.Lens' ListCACertificates (Prelude.Maybe Prelude.Text)
listCACertificates_templateName :: Lens' ListCACertificates (Maybe Text)
listCACertificates_templateName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListCACertificates' {Maybe Text
templateName :: Maybe Text
$sel:templateName:ListCACertificates' :: ListCACertificates -> Maybe Text
templateName} -> Maybe Text
templateName) (\s :: ListCACertificates
s@ListCACertificates' {} Maybe Text
a -> ListCACertificates
s {$sel:templateName:ListCACertificates' :: Maybe Text
templateName = Maybe Text
a} :: ListCACertificates)

instance Core.AWSPager ListCACertificates where
  page :: ListCACertificates
-> AWSResponse ListCACertificates -> Maybe ListCACertificates
page ListCACertificates
rq AWSResponse ListCACertificates
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListCACertificates
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListCACertificatesResponse (Maybe Text)
listCACertificatesResponse_nextMarker
            forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
        ) =
        forall a. Maybe a
Prelude.Nothing
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListCACertificates
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListCACertificatesResponse (Maybe [CACertificate])
listCACertificatesResponse_certificates
            forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
        ) =
        forall a. Maybe a
Prelude.Nothing
    | Bool
Prelude.otherwise =
        forall a. a -> Maybe a
Prelude.Just
          forall a b. (a -> b) -> a -> b
Prelude.$ ListCACertificates
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListCACertificates (Maybe Text)
listCACertificates_marker
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListCACertificates
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListCACertificatesResponse (Maybe Text)
listCACertificatesResponse_nextMarker
          forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just

instance Core.AWSRequest ListCACertificates where
  type
    AWSResponse ListCACertificates =
      ListCACertificatesResponse
  request :: (Service -> Service)
-> ListCACertificates -> Request ListCACertificates
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 ListCACertificates
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListCACertificates)))
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 [CACertificate]
-> Maybe Text -> Int -> ListCACertificatesResponse
ListCACertificatesResponse'
            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
"certificates" 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.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"nextMarker")
            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 ListCACertificates where
  hashWithSalt :: Int -> ListCACertificates -> Int
hashWithSalt Int
_salt ListCACertificates' {Maybe Bool
Maybe Natural
Maybe Text
templateName :: Maybe Text
pageSize :: Maybe Natural
marker :: Maybe Text
ascendingOrder :: Maybe Bool
$sel:templateName:ListCACertificates' :: ListCACertificates -> Maybe Text
$sel:pageSize:ListCACertificates' :: ListCACertificates -> Maybe Natural
$sel:marker:ListCACertificates' :: ListCACertificates -> Maybe Text
$sel:ascendingOrder:ListCACertificates' :: ListCACertificates -> Maybe Bool
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
ascendingOrder
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
marker
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
pageSize
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
templateName

instance Prelude.NFData ListCACertificates where
  rnf :: ListCACertificates -> ()
rnf ListCACertificates' {Maybe Bool
Maybe Natural
Maybe Text
templateName :: Maybe Text
pageSize :: Maybe Natural
marker :: Maybe Text
ascendingOrder :: Maybe Bool
$sel:templateName:ListCACertificates' :: ListCACertificates -> Maybe Text
$sel:pageSize:ListCACertificates' :: ListCACertificates -> Maybe Natural
$sel:marker:ListCACertificates' :: ListCACertificates -> Maybe Text
$sel:ascendingOrder:ListCACertificates' :: ListCACertificates -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
ascendingOrder
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
marker
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
pageSize
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
templateName

instance Data.ToHeaders ListCACertificates where
  toHeaders :: ListCACertificates -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance Data.ToQuery ListCACertificates where
  toQuery :: ListCACertificates -> QueryString
toQuery ListCACertificates' {Maybe Bool
Maybe Natural
Maybe Text
templateName :: Maybe Text
pageSize :: Maybe Natural
marker :: Maybe Text
ascendingOrder :: Maybe Bool
$sel:templateName:ListCACertificates' :: ListCACertificates -> Maybe Text
$sel:pageSize:ListCACertificates' :: ListCACertificates -> Maybe Natural
$sel:marker:ListCACertificates' :: ListCACertificates -> Maybe Text
$sel:ascendingOrder:ListCACertificates' :: ListCACertificates -> Maybe Bool
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"isAscendingOrder" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
ascendingOrder,
        ByteString
"marker" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
marker,
        ByteString
"pageSize" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Natural
pageSize,
        ByteString
"templateName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
templateName
      ]

-- | The output from the ListCACertificates operation.
--
-- /See:/ 'newListCACertificatesResponse' smart constructor.
data ListCACertificatesResponse = ListCACertificatesResponse'
  { -- | The CA certificates registered in your Amazon Web Services account.
    ListCACertificatesResponse -> Maybe [CACertificate]
certificates :: Prelude.Maybe [CACertificate],
    -- | The current position within the list of CA certificates.
    ListCACertificatesResponse -> Maybe Text
nextMarker :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListCACertificatesResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListCACertificatesResponse -> ListCACertificatesResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListCACertificatesResponse -> ListCACertificatesResponse -> Bool
$c/= :: ListCACertificatesResponse -> ListCACertificatesResponse -> Bool
== :: ListCACertificatesResponse -> ListCACertificatesResponse -> Bool
$c== :: ListCACertificatesResponse -> ListCACertificatesResponse -> Bool
Prelude.Eq, ReadPrec [ListCACertificatesResponse]
ReadPrec ListCACertificatesResponse
Int -> ReadS ListCACertificatesResponse
ReadS [ListCACertificatesResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListCACertificatesResponse]
$creadListPrec :: ReadPrec [ListCACertificatesResponse]
readPrec :: ReadPrec ListCACertificatesResponse
$creadPrec :: ReadPrec ListCACertificatesResponse
readList :: ReadS [ListCACertificatesResponse]
$creadList :: ReadS [ListCACertificatesResponse]
readsPrec :: Int -> ReadS ListCACertificatesResponse
$creadsPrec :: Int -> ReadS ListCACertificatesResponse
Prelude.Read, Int -> ListCACertificatesResponse -> ShowS
[ListCACertificatesResponse] -> ShowS
ListCACertificatesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListCACertificatesResponse] -> ShowS
$cshowList :: [ListCACertificatesResponse] -> ShowS
show :: ListCACertificatesResponse -> String
$cshow :: ListCACertificatesResponse -> String
showsPrec :: Int -> ListCACertificatesResponse -> ShowS
$cshowsPrec :: Int -> ListCACertificatesResponse -> ShowS
Prelude.Show, forall x.
Rep ListCACertificatesResponse x -> ListCACertificatesResponse
forall x.
ListCACertificatesResponse -> Rep ListCACertificatesResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListCACertificatesResponse x -> ListCACertificatesResponse
$cfrom :: forall x.
ListCACertificatesResponse -> Rep ListCACertificatesResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListCACertificatesResponse' 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:
--
-- 'certificates', 'listCACertificatesResponse_certificates' - The CA certificates registered in your Amazon Web Services account.
--
-- 'nextMarker', 'listCACertificatesResponse_nextMarker' - The current position within the list of CA certificates.
--
-- 'httpStatus', 'listCACertificatesResponse_httpStatus' - The response's http status code.
newListCACertificatesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListCACertificatesResponse
newListCACertificatesResponse :: Int -> ListCACertificatesResponse
newListCACertificatesResponse Int
pHttpStatus_ =
  ListCACertificatesResponse'
    { $sel:certificates:ListCACertificatesResponse' :: Maybe [CACertificate]
certificates =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextMarker:ListCACertificatesResponse' :: Maybe Text
nextMarker = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListCACertificatesResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The CA certificates registered in your Amazon Web Services account.
listCACertificatesResponse_certificates :: Lens.Lens' ListCACertificatesResponse (Prelude.Maybe [CACertificate])
listCACertificatesResponse_certificates :: Lens' ListCACertificatesResponse (Maybe [CACertificate])
listCACertificatesResponse_certificates = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListCACertificatesResponse' {Maybe [CACertificate]
certificates :: Maybe [CACertificate]
$sel:certificates:ListCACertificatesResponse' :: ListCACertificatesResponse -> Maybe [CACertificate]
certificates} -> Maybe [CACertificate]
certificates) (\s :: ListCACertificatesResponse
s@ListCACertificatesResponse' {} Maybe [CACertificate]
a -> ListCACertificatesResponse
s {$sel:certificates:ListCACertificatesResponse' :: Maybe [CACertificate]
certificates = Maybe [CACertificate]
a} :: ListCACertificatesResponse) 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 current position within the list of CA certificates.
listCACertificatesResponse_nextMarker :: Lens.Lens' ListCACertificatesResponse (Prelude.Maybe Prelude.Text)
listCACertificatesResponse_nextMarker :: Lens' ListCACertificatesResponse (Maybe Text)
listCACertificatesResponse_nextMarker = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListCACertificatesResponse' {Maybe Text
nextMarker :: Maybe Text
$sel:nextMarker:ListCACertificatesResponse' :: ListCACertificatesResponse -> Maybe Text
nextMarker} -> Maybe Text
nextMarker) (\s :: ListCACertificatesResponse
s@ListCACertificatesResponse' {} Maybe Text
a -> ListCACertificatesResponse
s {$sel:nextMarker:ListCACertificatesResponse' :: Maybe Text
nextMarker = Maybe Text
a} :: ListCACertificatesResponse)

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

instance Prelude.NFData ListCACertificatesResponse where
  rnf :: ListCACertificatesResponse -> ()
rnf ListCACertificatesResponse' {Int
Maybe [CACertificate]
Maybe Text
httpStatus :: Int
nextMarker :: Maybe Text
certificates :: Maybe [CACertificate]
$sel:httpStatus:ListCACertificatesResponse' :: ListCACertificatesResponse -> Int
$sel:nextMarker:ListCACertificatesResponse' :: ListCACertificatesResponse -> Maybe Text
$sel:certificates:ListCACertificatesResponse' :: ListCACertificatesResponse -> Maybe [CACertificate]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [CACertificate]
certificates
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextMarker
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus