{-# 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.Lambda.ListLayers
-- 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
-- <https://docs.aws.amazon.com/lambda/latest/dg/invocation-layers.html Lambda layers>
-- and shows information about the latest version of each. Specify a
-- <https://docs.aws.amazon.com/lambda/latest/dg/lambda-runtimes.html runtime identifier>
-- to list only layers that indicate that they\'re compatible with that
-- runtime. Specify a compatible architecture to include only layers that
-- are compatible with that
-- <https://docs.aws.amazon.com/lambda/latest/dg/foundation-arch.html instruction set architecture>.
--
-- This operation returns paginated results.
module Amazonka.Lambda.ListLayers
  ( -- * Creating a Request
    ListLayers (..),
    newListLayers,

    -- * Request Lenses
    listLayers_compatibleArchitecture,
    listLayers_compatibleRuntime,
    listLayers_marker,
    listLayers_maxItems,

    -- * Destructuring the Response
    ListLayersResponse (..),
    newListLayersResponse,

    -- * Response Lenses
    listLayersResponse_layers,
    listLayersResponse_nextMarker,
    listLayersResponse_httpStatus,
  )
where

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

-- | /See:/ 'newListLayers' smart constructor.
data ListLayers = ListLayers'
  { -- | The compatible
    -- <https://docs.aws.amazon.com/lambda/latest/dg/foundation-arch.html instruction set architecture>.
    ListLayers -> Maybe Architecture
compatibleArchitecture :: Prelude.Maybe Architecture,
    -- | A runtime identifier. For example, @go1.x@.
    ListLayers -> Maybe Runtime
compatibleRuntime :: Prelude.Maybe Runtime,
    -- | A pagination token returned by a previous call.
    ListLayers -> Maybe Text
marker :: Prelude.Maybe Prelude.Text,
    -- | The maximum number of layers to return.
    ListLayers -> Maybe Natural
maxItems :: Prelude.Maybe Prelude.Natural
  }
  deriving (ListLayers -> ListLayers -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListLayers -> ListLayers -> Bool
$c/= :: ListLayers -> ListLayers -> Bool
== :: ListLayers -> ListLayers -> Bool
$c== :: ListLayers -> ListLayers -> Bool
Prelude.Eq, ReadPrec [ListLayers]
ReadPrec ListLayers
Int -> ReadS ListLayers
ReadS [ListLayers]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListLayers]
$creadListPrec :: ReadPrec [ListLayers]
readPrec :: ReadPrec ListLayers
$creadPrec :: ReadPrec ListLayers
readList :: ReadS [ListLayers]
$creadList :: ReadS [ListLayers]
readsPrec :: Int -> ReadS ListLayers
$creadsPrec :: Int -> ReadS ListLayers
Prelude.Read, Int -> ListLayers -> ShowS
[ListLayers] -> ShowS
ListLayers -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListLayers] -> ShowS
$cshowList :: [ListLayers] -> ShowS
show :: ListLayers -> String
$cshow :: ListLayers -> String
showsPrec :: Int -> ListLayers -> ShowS
$cshowsPrec :: Int -> ListLayers -> ShowS
Prelude.Show, forall x. Rep ListLayers x -> ListLayers
forall x. ListLayers -> Rep ListLayers x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListLayers x -> ListLayers
$cfrom :: forall x. ListLayers -> Rep ListLayers x
Prelude.Generic)

-- |
-- Create a value of 'ListLayers' 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:
--
-- 'compatibleArchitecture', 'listLayers_compatibleArchitecture' - The compatible
-- <https://docs.aws.amazon.com/lambda/latest/dg/foundation-arch.html instruction set architecture>.
--
-- 'compatibleRuntime', 'listLayers_compatibleRuntime' - A runtime identifier. For example, @go1.x@.
--
-- 'marker', 'listLayers_marker' - A pagination token returned by a previous call.
--
-- 'maxItems', 'listLayers_maxItems' - The maximum number of layers to return.
newListLayers ::
  ListLayers
newListLayers :: ListLayers
newListLayers =
  ListLayers'
    { $sel:compatibleArchitecture:ListLayers' :: Maybe Architecture
compatibleArchitecture =
        forall a. Maybe a
Prelude.Nothing,
      $sel:compatibleRuntime:ListLayers' :: Maybe Runtime
compatibleRuntime = forall a. Maybe a
Prelude.Nothing,
      $sel:marker:ListLayers' :: Maybe Text
marker = forall a. Maybe a
Prelude.Nothing,
      $sel:maxItems:ListLayers' :: Maybe Natural
maxItems = forall a. Maybe a
Prelude.Nothing
    }

-- | The compatible
-- <https://docs.aws.amazon.com/lambda/latest/dg/foundation-arch.html instruction set architecture>.
listLayers_compatibleArchitecture :: Lens.Lens' ListLayers (Prelude.Maybe Architecture)
listLayers_compatibleArchitecture :: Lens' ListLayers (Maybe Architecture)
listLayers_compatibleArchitecture = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListLayers' {Maybe Architecture
compatibleArchitecture :: Maybe Architecture
$sel:compatibleArchitecture:ListLayers' :: ListLayers -> Maybe Architecture
compatibleArchitecture} -> Maybe Architecture
compatibleArchitecture) (\s :: ListLayers
s@ListLayers' {} Maybe Architecture
a -> ListLayers
s {$sel:compatibleArchitecture:ListLayers' :: Maybe Architecture
compatibleArchitecture = Maybe Architecture
a} :: ListLayers)

-- | A runtime identifier. For example, @go1.x@.
listLayers_compatibleRuntime :: Lens.Lens' ListLayers (Prelude.Maybe Runtime)
listLayers_compatibleRuntime :: Lens' ListLayers (Maybe Runtime)
listLayers_compatibleRuntime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListLayers' {Maybe Runtime
compatibleRuntime :: Maybe Runtime
$sel:compatibleRuntime:ListLayers' :: ListLayers -> Maybe Runtime
compatibleRuntime} -> Maybe Runtime
compatibleRuntime) (\s :: ListLayers
s@ListLayers' {} Maybe Runtime
a -> ListLayers
s {$sel:compatibleRuntime:ListLayers' :: Maybe Runtime
compatibleRuntime = Maybe Runtime
a} :: ListLayers)

-- | A pagination token returned by a previous call.
listLayers_marker :: Lens.Lens' ListLayers (Prelude.Maybe Prelude.Text)
listLayers_marker :: Lens' ListLayers (Maybe Text)
listLayers_marker = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListLayers' {Maybe Text
marker :: Maybe Text
$sel:marker:ListLayers' :: ListLayers -> Maybe Text
marker} -> Maybe Text
marker) (\s :: ListLayers
s@ListLayers' {} Maybe Text
a -> ListLayers
s {$sel:marker:ListLayers' :: Maybe Text
marker = Maybe Text
a} :: ListLayers)

-- | The maximum number of layers to return.
listLayers_maxItems :: Lens.Lens' ListLayers (Prelude.Maybe Prelude.Natural)
listLayers_maxItems :: Lens' ListLayers (Maybe Natural)
listLayers_maxItems = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListLayers' {Maybe Natural
maxItems :: Maybe Natural
$sel:maxItems:ListLayers' :: ListLayers -> Maybe Natural
maxItems} -> Maybe Natural
maxItems) (\s :: ListLayers
s@ListLayers' {} Maybe Natural
a -> ListLayers
s {$sel:maxItems:ListLayers' :: Maybe Natural
maxItems = Maybe Natural
a} :: ListLayers)

instance Core.AWSPager ListLayers where
  page :: ListLayers -> AWSResponse ListLayers -> Maybe ListLayers
page ListLayers
rq AWSResponse ListLayers
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListLayers
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListLayersResponse (Maybe Text)
listLayersResponse_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 ListLayers
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListLayersResponse (Maybe [LayersListItem])
listLayersResponse_layers
            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.$ ListLayers
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListLayers (Maybe Text)
listLayers_marker
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListLayers
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListLayersResponse (Maybe Text)
listLayersResponse_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 ListLayers where
  type AWSResponse ListLayers = ListLayersResponse
  request :: (Service -> Service) -> ListLayers -> Request ListLayers
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 ListLayers
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListLayers)))
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 [LayersListItem] -> Maybe Text -> Int -> ListLayersResponse
ListLayersResponse'
            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
"Layers" 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 ListLayers where
  hashWithSalt :: Int -> ListLayers -> Int
hashWithSalt Int
_salt ListLayers' {Maybe Natural
Maybe Text
Maybe Architecture
Maybe Runtime
maxItems :: Maybe Natural
marker :: Maybe Text
compatibleRuntime :: Maybe Runtime
compatibleArchitecture :: Maybe Architecture
$sel:maxItems:ListLayers' :: ListLayers -> Maybe Natural
$sel:marker:ListLayers' :: ListLayers -> Maybe Text
$sel:compatibleRuntime:ListLayers' :: ListLayers -> Maybe Runtime
$sel:compatibleArchitecture:ListLayers' :: ListLayers -> Maybe Architecture
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Architecture
compatibleArchitecture
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Runtime
compatibleRuntime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
marker
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maxItems

instance Prelude.NFData ListLayers where
  rnf :: ListLayers -> ()
rnf ListLayers' {Maybe Natural
Maybe Text
Maybe Architecture
Maybe Runtime
maxItems :: Maybe Natural
marker :: Maybe Text
compatibleRuntime :: Maybe Runtime
compatibleArchitecture :: Maybe Architecture
$sel:maxItems:ListLayers' :: ListLayers -> Maybe Natural
$sel:marker:ListLayers' :: ListLayers -> Maybe Text
$sel:compatibleRuntime:ListLayers' :: ListLayers -> Maybe Runtime
$sel:compatibleArchitecture:ListLayers' :: ListLayers -> Maybe Architecture
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Architecture
compatibleArchitecture
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Runtime
compatibleRuntime
      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
maxItems

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

instance Data.ToPath ListLayers where
  toPath :: ListLayers -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/2018-10-31/layers"

instance Data.ToQuery ListLayers where
  toQuery :: ListLayers -> QueryString
toQuery ListLayers' {Maybe Natural
Maybe Text
Maybe Architecture
Maybe Runtime
maxItems :: Maybe Natural
marker :: Maybe Text
compatibleRuntime :: Maybe Runtime
compatibleArchitecture :: Maybe Architecture
$sel:maxItems:ListLayers' :: ListLayers -> Maybe Natural
$sel:marker:ListLayers' :: ListLayers -> Maybe Text
$sel:compatibleRuntime:ListLayers' :: ListLayers -> Maybe Runtime
$sel:compatibleArchitecture:ListLayers' :: ListLayers -> Maybe Architecture
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"CompatibleArchitecture"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Architecture
compatibleArchitecture,
        ByteString
"CompatibleRuntime" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Runtime
compatibleRuntime,
        ByteString
"Marker" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
marker,
        ByteString
"MaxItems" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Natural
maxItems
      ]

-- | /See:/ 'newListLayersResponse' smart constructor.
data ListLayersResponse = ListLayersResponse'
  { -- | A list of function layers.
    ListLayersResponse -> Maybe [LayersListItem]
layers :: Prelude.Maybe [LayersListItem],
    -- | A pagination token returned when the response doesn\'t contain all
    -- layers.
    ListLayersResponse -> Maybe Text
nextMarker :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListLayersResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListLayersResponse -> ListLayersResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListLayersResponse -> ListLayersResponse -> Bool
$c/= :: ListLayersResponse -> ListLayersResponse -> Bool
== :: ListLayersResponse -> ListLayersResponse -> Bool
$c== :: ListLayersResponse -> ListLayersResponse -> Bool
Prelude.Eq, ReadPrec [ListLayersResponse]
ReadPrec ListLayersResponse
Int -> ReadS ListLayersResponse
ReadS [ListLayersResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListLayersResponse]
$creadListPrec :: ReadPrec [ListLayersResponse]
readPrec :: ReadPrec ListLayersResponse
$creadPrec :: ReadPrec ListLayersResponse
readList :: ReadS [ListLayersResponse]
$creadList :: ReadS [ListLayersResponse]
readsPrec :: Int -> ReadS ListLayersResponse
$creadsPrec :: Int -> ReadS ListLayersResponse
Prelude.Read, Int -> ListLayersResponse -> ShowS
[ListLayersResponse] -> ShowS
ListLayersResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListLayersResponse] -> ShowS
$cshowList :: [ListLayersResponse] -> ShowS
show :: ListLayersResponse -> String
$cshow :: ListLayersResponse -> String
showsPrec :: Int -> ListLayersResponse -> ShowS
$cshowsPrec :: Int -> ListLayersResponse -> ShowS
Prelude.Show, forall x. Rep ListLayersResponse x -> ListLayersResponse
forall x. ListLayersResponse -> Rep ListLayersResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListLayersResponse x -> ListLayersResponse
$cfrom :: forall x. ListLayersResponse -> Rep ListLayersResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListLayersResponse' 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:
--
-- 'layers', 'listLayersResponse_layers' - A list of function layers.
--
-- 'nextMarker', 'listLayersResponse_nextMarker' - A pagination token returned when the response doesn\'t contain all
-- layers.
--
-- 'httpStatus', 'listLayersResponse_httpStatus' - The response's http status code.
newListLayersResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListLayersResponse
newListLayersResponse :: Int -> ListLayersResponse
newListLayersResponse Int
pHttpStatus_ =
  ListLayersResponse'
    { $sel:layers:ListLayersResponse' :: Maybe [LayersListItem]
layers = forall a. Maybe a
Prelude.Nothing,
      $sel:nextMarker:ListLayersResponse' :: Maybe Text
nextMarker = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListLayersResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A list of function layers.
listLayersResponse_layers :: Lens.Lens' ListLayersResponse (Prelude.Maybe [LayersListItem])
listLayersResponse_layers :: Lens' ListLayersResponse (Maybe [LayersListItem])
listLayersResponse_layers = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListLayersResponse' {Maybe [LayersListItem]
layers :: Maybe [LayersListItem]
$sel:layers:ListLayersResponse' :: ListLayersResponse -> Maybe [LayersListItem]
layers} -> Maybe [LayersListItem]
layers) (\s :: ListLayersResponse
s@ListLayersResponse' {} Maybe [LayersListItem]
a -> ListLayersResponse
s {$sel:layers:ListLayersResponse' :: Maybe [LayersListItem]
layers = Maybe [LayersListItem]
a} :: ListLayersResponse) 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

-- | A pagination token returned when the response doesn\'t contain all
-- layers.
listLayersResponse_nextMarker :: Lens.Lens' ListLayersResponse (Prelude.Maybe Prelude.Text)
listLayersResponse_nextMarker :: Lens' ListLayersResponse (Maybe Text)
listLayersResponse_nextMarker = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListLayersResponse' {Maybe Text
nextMarker :: Maybe Text
$sel:nextMarker:ListLayersResponse' :: ListLayersResponse -> Maybe Text
nextMarker} -> Maybe Text
nextMarker) (\s :: ListLayersResponse
s@ListLayersResponse' {} Maybe Text
a -> ListLayersResponse
s {$sel:nextMarker:ListLayersResponse' :: Maybe Text
nextMarker = Maybe Text
a} :: ListLayersResponse)

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

instance Prelude.NFData ListLayersResponse where
  rnf :: ListLayersResponse -> ()
rnf ListLayersResponse' {Int
Maybe [LayersListItem]
Maybe Text
httpStatus :: Int
nextMarker :: Maybe Text
layers :: Maybe [LayersListItem]
$sel:httpStatus:ListLayersResponse' :: ListLayersResponse -> Int
$sel:nextMarker:ListLayersResponse' :: ListLayersResponse -> Maybe Text
$sel:layers:ListLayersResponse' :: ListLayersResponse -> Maybe [LayersListItem]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [LayersListItem]
layers
      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