{-# 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.ListFunctions
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Returns a list of Lambda functions, with the version-specific
-- configuration of each. Lambda returns up to 50 functions per call.
--
-- Set @FunctionVersion@ to @ALL@ to include all published versions of each
-- function in addition to the unpublished version.
--
-- The @ListFunctions@ operation returns a subset of the
-- FunctionConfiguration fields. To get the additional fields (State,
-- StateReasonCode, StateReason, LastUpdateStatus, LastUpdateStatusReason,
-- LastUpdateStatusReasonCode) for a function or version, use GetFunction.
--
-- This operation returns paginated results.
module Amazonka.Lambda.ListFunctions
  ( -- * Creating a Request
    ListFunctions (..),
    newListFunctions,

    -- * Request Lenses
    listFunctions_functionVersion,
    listFunctions_marker,
    listFunctions_masterRegion,
    listFunctions_maxItems,

    -- * Destructuring the Response
    ListFunctionsResponse (..),
    newListFunctionsResponse,

    -- * Response Lenses
    listFunctionsResponse_functions,
    listFunctionsResponse_nextMarker,
    listFunctionsResponse_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:/ 'newListFunctions' smart constructor.
data ListFunctions = ListFunctions'
  { -- | Set to @ALL@ to include entries for all published versions of each
    -- function.
    ListFunctions -> Maybe FunctionVersion
functionVersion :: Prelude.Maybe FunctionVersion,
    -- | Specify the pagination token that\'s returned by a previous request to
    -- retrieve the next page of results.
    ListFunctions -> Maybe Text
marker :: Prelude.Maybe Prelude.Text,
    -- | For Lambda\@Edge functions, the Amazon Web Services Region of the master
    -- function. For example, @us-east-1@ filters the list of functions to
    -- include only Lambda\@Edge functions replicated from a master function in
    -- US East (N. Virginia). If specified, you must set @FunctionVersion@ to
    -- @ALL@.
    ListFunctions -> Maybe Text
masterRegion :: Prelude.Maybe Prelude.Text,
    -- | The maximum number of functions to return in the response. Note that
    -- @ListFunctions@ returns a maximum of 50 items in each response, even if
    -- you set the number higher.
    ListFunctions -> Maybe Natural
maxItems :: Prelude.Maybe Prelude.Natural
  }
  deriving (ListFunctions -> ListFunctions -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListFunctions -> ListFunctions -> Bool
$c/= :: ListFunctions -> ListFunctions -> Bool
== :: ListFunctions -> ListFunctions -> Bool
$c== :: ListFunctions -> ListFunctions -> Bool
Prelude.Eq, ReadPrec [ListFunctions]
ReadPrec ListFunctions
Int -> ReadS ListFunctions
ReadS [ListFunctions]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListFunctions]
$creadListPrec :: ReadPrec [ListFunctions]
readPrec :: ReadPrec ListFunctions
$creadPrec :: ReadPrec ListFunctions
readList :: ReadS [ListFunctions]
$creadList :: ReadS [ListFunctions]
readsPrec :: Int -> ReadS ListFunctions
$creadsPrec :: Int -> ReadS ListFunctions
Prelude.Read, Int -> ListFunctions -> ShowS
[ListFunctions] -> ShowS
ListFunctions -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListFunctions] -> ShowS
$cshowList :: [ListFunctions] -> ShowS
show :: ListFunctions -> String
$cshow :: ListFunctions -> String
showsPrec :: Int -> ListFunctions -> ShowS
$cshowsPrec :: Int -> ListFunctions -> ShowS
Prelude.Show, forall x. Rep ListFunctions x -> ListFunctions
forall x. ListFunctions -> Rep ListFunctions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListFunctions x -> ListFunctions
$cfrom :: forall x. ListFunctions -> Rep ListFunctions x
Prelude.Generic)

-- |
-- Create a value of 'ListFunctions' 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:
--
-- 'functionVersion', 'listFunctions_functionVersion' - Set to @ALL@ to include entries for all published versions of each
-- function.
--
-- 'marker', 'listFunctions_marker' - Specify the pagination token that\'s returned by a previous request to
-- retrieve the next page of results.
--
-- 'masterRegion', 'listFunctions_masterRegion' - For Lambda\@Edge functions, the Amazon Web Services Region of the master
-- function. For example, @us-east-1@ filters the list of functions to
-- include only Lambda\@Edge functions replicated from a master function in
-- US East (N. Virginia). If specified, you must set @FunctionVersion@ to
-- @ALL@.
--
-- 'maxItems', 'listFunctions_maxItems' - The maximum number of functions to return in the response. Note that
-- @ListFunctions@ returns a maximum of 50 items in each response, even if
-- you set the number higher.
newListFunctions ::
  ListFunctions
newListFunctions :: ListFunctions
newListFunctions =
  ListFunctions'
    { $sel:functionVersion:ListFunctions' :: Maybe FunctionVersion
functionVersion = forall a. Maybe a
Prelude.Nothing,
      $sel:marker:ListFunctions' :: Maybe Text
marker = forall a. Maybe a
Prelude.Nothing,
      $sel:masterRegion:ListFunctions' :: Maybe Text
masterRegion = forall a. Maybe a
Prelude.Nothing,
      $sel:maxItems:ListFunctions' :: Maybe Natural
maxItems = forall a. Maybe a
Prelude.Nothing
    }

-- | Set to @ALL@ to include entries for all published versions of each
-- function.
listFunctions_functionVersion :: Lens.Lens' ListFunctions (Prelude.Maybe FunctionVersion)
listFunctions_functionVersion :: Lens' ListFunctions (Maybe FunctionVersion)
listFunctions_functionVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListFunctions' {Maybe FunctionVersion
functionVersion :: Maybe FunctionVersion
$sel:functionVersion:ListFunctions' :: ListFunctions -> Maybe FunctionVersion
functionVersion} -> Maybe FunctionVersion
functionVersion) (\s :: ListFunctions
s@ListFunctions' {} Maybe FunctionVersion
a -> ListFunctions
s {$sel:functionVersion:ListFunctions' :: Maybe FunctionVersion
functionVersion = Maybe FunctionVersion
a} :: ListFunctions)

-- | Specify the pagination token that\'s returned by a previous request to
-- retrieve the next page of results.
listFunctions_marker :: Lens.Lens' ListFunctions (Prelude.Maybe Prelude.Text)
listFunctions_marker :: Lens' ListFunctions (Maybe Text)
listFunctions_marker = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListFunctions' {Maybe Text
marker :: Maybe Text
$sel:marker:ListFunctions' :: ListFunctions -> Maybe Text
marker} -> Maybe Text
marker) (\s :: ListFunctions
s@ListFunctions' {} Maybe Text
a -> ListFunctions
s {$sel:marker:ListFunctions' :: Maybe Text
marker = Maybe Text
a} :: ListFunctions)

-- | For Lambda\@Edge functions, the Amazon Web Services Region of the master
-- function. For example, @us-east-1@ filters the list of functions to
-- include only Lambda\@Edge functions replicated from a master function in
-- US East (N. Virginia). If specified, you must set @FunctionVersion@ to
-- @ALL@.
listFunctions_masterRegion :: Lens.Lens' ListFunctions (Prelude.Maybe Prelude.Text)
listFunctions_masterRegion :: Lens' ListFunctions (Maybe Text)
listFunctions_masterRegion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListFunctions' {Maybe Text
masterRegion :: Maybe Text
$sel:masterRegion:ListFunctions' :: ListFunctions -> Maybe Text
masterRegion} -> Maybe Text
masterRegion) (\s :: ListFunctions
s@ListFunctions' {} Maybe Text
a -> ListFunctions
s {$sel:masterRegion:ListFunctions' :: Maybe Text
masterRegion = Maybe Text
a} :: ListFunctions)

-- | The maximum number of functions to return in the response. Note that
-- @ListFunctions@ returns a maximum of 50 items in each response, even if
-- you set the number higher.
listFunctions_maxItems :: Lens.Lens' ListFunctions (Prelude.Maybe Prelude.Natural)
listFunctions_maxItems :: Lens' ListFunctions (Maybe Natural)
listFunctions_maxItems = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListFunctions' {Maybe Natural
maxItems :: Maybe Natural
$sel:maxItems:ListFunctions' :: ListFunctions -> Maybe Natural
maxItems} -> Maybe Natural
maxItems) (\s :: ListFunctions
s@ListFunctions' {} Maybe Natural
a -> ListFunctions
s {$sel:maxItems:ListFunctions' :: Maybe Natural
maxItems = Maybe Natural
a} :: ListFunctions)

instance Core.AWSPager ListFunctions where
  page :: ListFunctions -> AWSResponse ListFunctions -> Maybe ListFunctions
page ListFunctions
rq AWSResponse ListFunctions
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListFunctions
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListFunctionsResponse (Maybe Text)
listFunctionsResponse_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 ListFunctions
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListFunctionsResponse (Maybe [FunctionConfiguration])
listFunctionsResponse_functions
            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.$ ListFunctions
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListFunctions (Maybe Text)
listFunctions_marker
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListFunctions
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListFunctionsResponse (Maybe Text)
listFunctionsResponse_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 ListFunctions where
  type
    AWSResponse ListFunctions =
      ListFunctionsResponse
  request :: (Service -> Service) -> ListFunctions -> Request ListFunctions
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 ListFunctions
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListFunctions)))
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 [FunctionConfiguration]
-> Maybe Text -> Int -> ListFunctionsResponse
ListFunctionsResponse'
            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
"Functions" 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 ListFunctions where
  hashWithSalt :: Int -> ListFunctions -> Int
hashWithSalt Int
_salt ListFunctions' {Maybe Natural
Maybe Text
Maybe FunctionVersion
maxItems :: Maybe Natural
masterRegion :: Maybe Text
marker :: Maybe Text
functionVersion :: Maybe FunctionVersion
$sel:maxItems:ListFunctions' :: ListFunctions -> Maybe Natural
$sel:masterRegion:ListFunctions' :: ListFunctions -> Maybe Text
$sel:marker:ListFunctions' :: ListFunctions -> Maybe Text
$sel:functionVersion:ListFunctions' :: ListFunctions -> Maybe FunctionVersion
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe FunctionVersion
functionVersion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
marker
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
masterRegion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maxItems

instance Prelude.NFData ListFunctions where
  rnf :: ListFunctions -> ()
rnf ListFunctions' {Maybe Natural
Maybe Text
Maybe FunctionVersion
maxItems :: Maybe Natural
masterRegion :: Maybe Text
marker :: Maybe Text
functionVersion :: Maybe FunctionVersion
$sel:maxItems:ListFunctions' :: ListFunctions -> Maybe Natural
$sel:masterRegion:ListFunctions' :: ListFunctions -> Maybe Text
$sel:marker:ListFunctions' :: ListFunctions -> Maybe Text
$sel:functionVersion:ListFunctions' :: ListFunctions -> Maybe FunctionVersion
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe FunctionVersion
functionVersion
      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 Text
masterRegion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
maxItems

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

instance Data.ToPath ListFunctions where
  toPath :: ListFunctions -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/2015-03-31/functions/"

instance Data.ToQuery ListFunctions where
  toQuery :: ListFunctions -> QueryString
toQuery ListFunctions' {Maybe Natural
Maybe Text
Maybe FunctionVersion
maxItems :: Maybe Natural
masterRegion :: Maybe Text
marker :: Maybe Text
functionVersion :: Maybe FunctionVersion
$sel:maxItems:ListFunctions' :: ListFunctions -> Maybe Natural
$sel:masterRegion:ListFunctions' :: ListFunctions -> Maybe Text
$sel:marker:ListFunctions' :: ListFunctions -> Maybe Text
$sel:functionVersion:ListFunctions' :: ListFunctions -> Maybe FunctionVersion
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"FunctionVersion" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe FunctionVersion
functionVersion,
        ByteString
"Marker" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
marker,
        ByteString
"MasterRegion" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
masterRegion,
        ByteString
"MaxItems" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Natural
maxItems
      ]

-- | A list of Lambda functions.
--
-- /See:/ 'newListFunctionsResponse' smart constructor.
data ListFunctionsResponse = ListFunctionsResponse'
  { -- | A list of Lambda functions.
    ListFunctionsResponse -> Maybe [FunctionConfiguration]
functions :: Prelude.Maybe [FunctionConfiguration],
    -- | The pagination token that\'s included if more results are available.
    ListFunctionsResponse -> Maybe Text
nextMarker :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListFunctionsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListFunctionsResponse -> ListFunctionsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListFunctionsResponse -> ListFunctionsResponse -> Bool
$c/= :: ListFunctionsResponse -> ListFunctionsResponse -> Bool
== :: ListFunctionsResponse -> ListFunctionsResponse -> Bool
$c== :: ListFunctionsResponse -> ListFunctionsResponse -> Bool
Prelude.Eq, Int -> ListFunctionsResponse -> ShowS
[ListFunctionsResponse] -> ShowS
ListFunctionsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListFunctionsResponse] -> ShowS
$cshowList :: [ListFunctionsResponse] -> ShowS
show :: ListFunctionsResponse -> String
$cshow :: ListFunctionsResponse -> String
showsPrec :: Int -> ListFunctionsResponse -> ShowS
$cshowsPrec :: Int -> ListFunctionsResponse -> ShowS
Prelude.Show, forall x. Rep ListFunctionsResponse x -> ListFunctionsResponse
forall x. ListFunctionsResponse -> Rep ListFunctionsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListFunctionsResponse x -> ListFunctionsResponse
$cfrom :: forall x. ListFunctionsResponse -> Rep ListFunctionsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListFunctionsResponse' 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:
--
-- 'functions', 'listFunctionsResponse_functions' - A list of Lambda functions.
--
-- 'nextMarker', 'listFunctionsResponse_nextMarker' - The pagination token that\'s included if more results are available.
--
-- 'httpStatus', 'listFunctionsResponse_httpStatus' - The response's http status code.
newListFunctionsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListFunctionsResponse
newListFunctionsResponse :: Int -> ListFunctionsResponse
newListFunctionsResponse Int
pHttpStatus_ =
  ListFunctionsResponse'
    { $sel:functions:ListFunctionsResponse' :: Maybe [FunctionConfiguration]
functions = forall a. Maybe a
Prelude.Nothing,
      $sel:nextMarker:ListFunctionsResponse' :: Maybe Text
nextMarker = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListFunctionsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A list of Lambda functions.
listFunctionsResponse_functions :: Lens.Lens' ListFunctionsResponse (Prelude.Maybe [FunctionConfiguration])
listFunctionsResponse_functions :: Lens' ListFunctionsResponse (Maybe [FunctionConfiguration])
listFunctionsResponse_functions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListFunctionsResponse' {Maybe [FunctionConfiguration]
functions :: Maybe [FunctionConfiguration]
$sel:functions:ListFunctionsResponse' :: ListFunctionsResponse -> Maybe [FunctionConfiguration]
functions} -> Maybe [FunctionConfiguration]
functions) (\s :: ListFunctionsResponse
s@ListFunctionsResponse' {} Maybe [FunctionConfiguration]
a -> ListFunctionsResponse
s {$sel:functions:ListFunctionsResponse' :: Maybe [FunctionConfiguration]
functions = Maybe [FunctionConfiguration]
a} :: ListFunctionsResponse) 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 pagination token that\'s included if more results are available.
listFunctionsResponse_nextMarker :: Lens.Lens' ListFunctionsResponse (Prelude.Maybe Prelude.Text)
listFunctionsResponse_nextMarker :: Lens' ListFunctionsResponse (Maybe Text)
listFunctionsResponse_nextMarker = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListFunctionsResponse' {Maybe Text
nextMarker :: Maybe Text
$sel:nextMarker:ListFunctionsResponse' :: ListFunctionsResponse -> Maybe Text
nextMarker} -> Maybe Text
nextMarker) (\s :: ListFunctionsResponse
s@ListFunctionsResponse' {} Maybe Text
a -> ListFunctionsResponse
s {$sel:nextMarker:ListFunctionsResponse' :: Maybe Text
nextMarker = Maybe Text
a} :: ListFunctionsResponse)

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

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