{-# 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.UpdateFunctionConfiguration
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Modify the version-specific settings of a Lambda function.
--
-- When you update a function, Lambda provisions an instance of the
-- function and its supporting resources. If your function connects to a
-- VPC, this process can take a minute. During this time, you can\'t modify
-- the function, but you can still invoke it. The @LastUpdateStatus@,
-- @LastUpdateStatusReason@, and @LastUpdateStatusReasonCode@ fields in the
-- response from GetFunctionConfiguration indicate when the update is
-- complete and the function is processing events with the new
-- configuration. For more information, see
-- <https://docs.aws.amazon.com/lambda/latest/dg/functions-states.html Lambda function states>.
--
-- These settings can vary between versions of a function and are locked
-- when you publish a version. You can\'t modify the configuration of a
-- published version, only the unpublished version.
--
-- To configure function concurrency, use PutFunctionConcurrency. To grant
-- invoke permissions to an Amazon Web Services account or Amazon Web
-- Service, use AddPermission.
module Amazonka.Lambda.UpdateFunctionConfiguration
  ( -- * Creating a Request
    UpdateFunctionConfiguration (..),
    newUpdateFunctionConfiguration,

    -- * Request Lenses
    updateFunctionConfiguration_deadLetterConfig,
    updateFunctionConfiguration_description,
    updateFunctionConfiguration_environment,
    updateFunctionConfiguration_ephemeralStorage,
    updateFunctionConfiguration_fileSystemConfigs,
    updateFunctionConfiguration_handler,
    updateFunctionConfiguration_imageConfig,
    updateFunctionConfiguration_kmsKeyArn,
    updateFunctionConfiguration_layers,
    updateFunctionConfiguration_memorySize,
    updateFunctionConfiguration_revisionId,
    updateFunctionConfiguration_role,
    updateFunctionConfiguration_runtime,
    updateFunctionConfiguration_snapStart,
    updateFunctionConfiguration_timeout,
    updateFunctionConfiguration_tracingConfig,
    updateFunctionConfiguration_vpcConfig,
    updateFunctionConfiguration_functionName,

    -- * Destructuring the Response
    FunctionConfiguration (..),
    newFunctionConfiguration,

    -- * Response Lenses
    functionConfiguration_architectures,
    functionConfiguration_codeSha256,
    functionConfiguration_codeSize,
    functionConfiguration_deadLetterConfig,
    functionConfiguration_description,
    functionConfiguration_environment,
    functionConfiguration_ephemeralStorage,
    functionConfiguration_fileSystemConfigs,
    functionConfiguration_functionArn,
    functionConfiguration_functionName,
    functionConfiguration_handler,
    functionConfiguration_imageConfigResponse,
    functionConfiguration_kmsKeyArn,
    functionConfiguration_lastModified,
    functionConfiguration_lastUpdateStatus,
    functionConfiguration_lastUpdateStatusReason,
    functionConfiguration_lastUpdateStatusReasonCode,
    functionConfiguration_layers,
    functionConfiguration_masterArn,
    functionConfiguration_memorySize,
    functionConfiguration_packageType,
    functionConfiguration_revisionId,
    functionConfiguration_role,
    functionConfiguration_runtime,
    functionConfiguration_signingJobArn,
    functionConfiguration_signingProfileVersionArn,
    functionConfiguration_snapStart,
    functionConfiguration_state,
    functionConfiguration_stateReason,
    functionConfiguration_stateReasonCode,
    functionConfiguration_timeout,
    functionConfiguration_tracingConfig,
    functionConfiguration_version,
    functionConfiguration_vpcConfig,
  )
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:/ 'newUpdateFunctionConfiguration' smart constructor.
data UpdateFunctionConfiguration = UpdateFunctionConfiguration'
  { -- | A dead-letter queue configuration that specifies the queue or topic
    -- where Lambda sends asynchronous events when they fail processing. For
    -- more information, see
    -- <https://docs.aws.amazon.com/lambda/latest/dg/invocation-async.html#invocation-dlq Dead-letter queues>.
    UpdateFunctionConfiguration -> Maybe DeadLetterConfig
deadLetterConfig :: Prelude.Maybe DeadLetterConfig,
    -- | A description of the function.
    UpdateFunctionConfiguration -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | Environment variables that are accessible from function code during
    -- execution.
    UpdateFunctionConfiguration -> Maybe Environment
environment :: Prelude.Maybe Environment,
    -- | The size of the function\'s @\/tmp@ directory in MB. The default value
    -- is 512, but can be any whole number between 512 and 10,240 MB.
    UpdateFunctionConfiguration -> Maybe EphemeralStorage
ephemeralStorage :: Prelude.Maybe EphemeralStorage,
    -- | Connection settings for an Amazon EFS file system.
    UpdateFunctionConfiguration -> Maybe [FileSystemConfig]
fileSystemConfigs :: Prelude.Maybe [FileSystemConfig],
    -- | The name of the method within your code that Lambda calls to run your
    -- function. Handler is required if the deployment package is a .zip file
    -- archive. The format includes the file name. It can also include
    -- namespaces and other qualifiers, depending on the runtime. For more
    -- information, see
    -- <https://docs.aws.amazon.com/lambda/latest/dg/foundation-progmodel.html Lambda programming model>.
    UpdateFunctionConfiguration -> Maybe Text
handler :: Prelude.Maybe Prelude.Text,
    -- | <https://docs.aws.amazon.com/lambda/latest/dg/images-parms.html Container image configuration values>
    -- that override the values in the container image Docker file.
    UpdateFunctionConfiguration -> Maybe ImageConfig
imageConfig :: Prelude.Maybe ImageConfig,
    -- | The ARN of the Key Management Service (KMS) key that\'s used to encrypt
    -- your function\'s environment variables. If it\'s not provided, Lambda
    -- uses a default service key.
    UpdateFunctionConfiguration -> Maybe Text
kmsKeyArn :: Prelude.Maybe Prelude.Text,
    -- | A list of
    -- <https://docs.aws.amazon.com/lambda/latest/dg/configuration-layers.html function layers>
    -- to add to the function\'s execution environment. Specify each layer by
    -- its ARN, including the version.
    UpdateFunctionConfiguration -> Maybe [Text]
layers :: Prelude.Maybe [Prelude.Text],
    -- | The amount of
    -- <https://docs.aws.amazon.com/lambda/latest/dg/configuration-function-common.html#configuration-memory-console memory available to the function>
    -- at runtime. Increasing the function memory also increases its CPU
    -- allocation. The default value is 128 MB. The value can be any multiple
    -- of 1 MB.
    UpdateFunctionConfiguration -> Maybe Natural
memorySize :: Prelude.Maybe Prelude.Natural,
    -- | Update the function only if the revision ID matches the ID that\'s
    -- specified. Use this option to avoid modifying a function that has
    -- changed since you last read it.
    UpdateFunctionConfiguration -> Maybe Text
revisionId :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the function\'s execution role.
    UpdateFunctionConfiguration -> Maybe Text
role' :: Prelude.Maybe Prelude.Text,
    -- | The identifier of the function\'s
    -- <https://docs.aws.amazon.com/lambda/latest/dg/lambda-runtimes.html runtime>.
    -- Runtime is required if the deployment package is a .zip file archive.
    UpdateFunctionConfiguration -> Maybe Runtime
runtime :: Prelude.Maybe Runtime,
    -- | The function\'s
    -- <https://docs.aws.amazon.com/lambda/latest/dg/snapstart.html SnapStart>
    -- setting.
    UpdateFunctionConfiguration -> Maybe SnapStart
snapStart :: Prelude.Maybe SnapStart,
    -- | The amount of time (in seconds) that Lambda allows a function to run
    -- before stopping it. The default is 3 seconds. The maximum allowed value
    -- is 900 seconds. For more information, see
    -- <https://docs.aws.amazon.com/lambda/latest/dg/runtimes-context.html Lambda execution environment>.
    UpdateFunctionConfiguration -> Maybe Natural
timeout :: Prelude.Maybe Prelude.Natural,
    -- | Set @Mode@ to @Active@ to sample and trace a subset of incoming requests
    -- with
    -- <https://docs.aws.amazon.com/lambda/latest/dg/services-xray.html X-Ray>.
    UpdateFunctionConfiguration -> Maybe TracingConfig
tracingConfig :: Prelude.Maybe TracingConfig,
    -- | For network connectivity to Amazon Web Services resources in a VPC,
    -- specify a list of security groups and subnets in the VPC. When you
    -- connect a function to a VPC, it can access resources and the internet
    -- only through that VPC. For more information, see
    -- <https://docs.aws.amazon.com/lambda/latest/dg/configuration-vpc.html Configuring a Lambda function to access resources in a VPC>.
    UpdateFunctionConfiguration -> Maybe VpcConfig
vpcConfig :: Prelude.Maybe VpcConfig,
    -- | The name of the Lambda function.
    --
    -- __Name formats__
    --
    -- -   __Function name__ – @my-function@.
    --
    -- -   __Function ARN__ –
    --     @arn:aws:lambda:us-west-2:123456789012:function:my-function@.
    --
    -- -   __Partial ARN__ – @123456789012:function:my-function@.
    --
    -- The length constraint applies only to the full ARN. If you specify only
    -- the function name, it is limited to 64 characters in length.
    UpdateFunctionConfiguration -> Text
functionName :: Prelude.Text
  }
  deriving (UpdateFunctionConfiguration -> UpdateFunctionConfiguration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateFunctionConfiguration -> UpdateFunctionConfiguration -> Bool
$c/= :: UpdateFunctionConfiguration -> UpdateFunctionConfiguration -> Bool
== :: UpdateFunctionConfiguration -> UpdateFunctionConfiguration -> Bool
$c== :: UpdateFunctionConfiguration -> UpdateFunctionConfiguration -> Bool
Prelude.Eq, Int -> UpdateFunctionConfiguration -> ShowS
[UpdateFunctionConfiguration] -> ShowS
UpdateFunctionConfiguration -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateFunctionConfiguration] -> ShowS
$cshowList :: [UpdateFunctionConfiguration] -> ShowS
show :: UpdateFunctionConfiguration -> String
$cshow :: UpdateFunctionConfiguration -> String
showsPrec :: Int -> UpdateFunctionConfiguration -> ShowS
$cshowsPrec :: Int -> UpdateFunctionConfiguration -> ShowS
Prelude.Show, forall x.
Rep UpdateFunctionConfiguration x -> UpdateFunctionConfiguration
forall x.
UpdateFunctionConfiguration -> Rep UpdateFunctionConfiguration x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateFunctionConfiguration x -> UpdateFunctionConfiguration
$cfrom :: forall x.
UpdateFunctionConfiguration -> Rep UpdateFunctionConfiguration x
Prelude.Generic)

-- |
-- Create a value of 'UpdateFunctionConfiguration' 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:
--
-- 'deadLetterConfig', 'updateFunctionConfiguration_deadLetterConfig' - A dead-letter queue configuration that specifies the queue or topic
-- where Lambda sends asynchronous events when they fail processing. For
-- more information, see
-- <https://docs.aws.amazon.com/lambda/latest/dg/invocation-async.html#invocation-dlq Dead-letter queues>.
--
-- 'description', 'updateFunctionConfiguration_description' - A description of the function.
--
-- 'environment', 'updateFunctionConfiguration_environment' - Environment variables that are accessible from function code during
-- execution.
--
-- 'ephemeralStorage', 'updateFunctionConfiguration_ephemeralStorage' - The size of the function\'s @\/tmp@ directory in MB. The default value
-- is 512, but can be any whole number between 512 and 10,240 MB.
--
-- 'fileSystemConfigs', 'updateFunctionConfiguration_fileSystemConfigs' - Connection settings for an Amazon EFS file system.
--
-- 'handler', 'updateFunctionConfiguration_handler' - The name of the method within your code that Lambda calls to run your
-- function. Handler is required if the deployment package is a .zip file
-- archive. The format includes the file name. It can also include
-- namespaces and other qualifiers, depending on the runtime. For more
-- information, see
-- <https://docs.aws.amazon.com/lambda/latest/dg/foundation-progmodel.html Lambda programming model>.
--
-- 'imageConfig', 'updateFunctionConfiguration_imageConfig' - <https://docs.aws.amazon.com/lambda/latest/dg/images-parms.html Container image configuration values>
-- that override the values in the container image Docker file.
--
-- 'kmsKeyArn', 'updateFunctionConfiguration_kmsKeyArn' - The ARN of the Key Management Service (KMS) key that\'s used to encrypt
-- your function\'s environment variables. If it\'s not provided, Lambda
-- uses a default service key.
--
-- 'layers', 'updateFunctionConfiguration_layers' - A list of
-- <https://docs.aws.amazon.com/lambda/latest/dg/configuration-layers.html function layers>
-- to add to the function\'s execution environment. Specify each layer by
-- its ARN, including the version.
--
-- 'memorySize', 'updateFunctionConfiguration_memorySize' - The amount of
-- <https://docs.aws.amazon.com/lambda/latest/dg/configuration-function-common.html#configuration-memory-console memory available to the function>
-- at runtime. Increasing the function memory also increases its CPU
-- allocation. The default value is 128 MB. The value can be any multiple
-- of 1 MB.
--
-- 'revisionId', 'updateFunctionConfiguration_revisionId' - Update the function only if the revision ID matches the ID that\'s
-- specified. Use this option to avoid modifying a function that has
-- changed since you last read it.
--
-- 'role'', 'updateFunctionConfiguration_role' - The Amazon Resource Name (ARN) of the function\'s execution role.
--
-- 'runtime', 'updateFunctionConfiguration_runtime' - The identifier of the function\'s
-- <https://docs.aws.amazon.com/lambda/latest/dg/lambda-runtimes.html runtime>.
-- Runtime is required if the deployment package is a .zip file archive.
--
-- 'snapStart', 'updateFunctionConfiguration_snapStart' - The function\'s
-- <https://docs.aws.amazon.com/lambda/latest/dg/snapstart.html SnapStart>
-- setting.
--
-- 'timeout', 'updateFunctionConfiguration_timeout' - The amount of time (in seconds) that Lambda allows a function to run
-- before stopping it. The default is 3 seconds. The maximum allowed value
-- is 900 seconds. For more information, see
-- <https://docs.aws.amazon.com/lambda/latest/dg/runtimes-context.html Lambda execution environment>.
--
-- 'tracingConfig', 'updateFunctionConfiguration_tracingConfig' - Set @Mode@ to @Active@ to sample and trace a subset of incoming requests
-- with
-- <https://docs.aws.amazon.com/lambda/latest/dg/services-xray.html X-Ray>.
--
-- 'vpcConfig', 'updateFunctionConfiguration_vpcConfig' - For network connectivity to Amazon Web Services resources in a VPC,
-- specify a list of security groups and subnets in the VPC. When you
-- connect a function to a VPC, it can access resources and the internet
-- only through that VPC. For more information, see
-- <https://docs.aws.amazon.com/lambda/latest/dg/configuration-vpc.html Configuring a Lambda function to access resources in a VPC>.
--
-- 'functionName', 'updateFunctionConfiguration_functionName' - The name of the Lambda function.
--
-- __Name formats__
--
-- -   __Function name__ – @my-function@.
--
-- -   __Function ARN__ –
--     @arn:aws:lambda:us-west-2:123456789012:function:my-function@.
--
-- -   __Partial ARN__ – @123456789012:function:my-function@.
--
-- The length constraint applies only to the full ARN. If you specify only
-- the function name, it is limited to 64 characters in length.
newUpdateFunctionConfiguration ::
  -- | 'functionName'
  Prelude.Text ->
  UpdateFunctionConfiguration
newUpdateFunctionConfiguration :: Text -> UpdateFunctionConfiguration
newUpdateFunctionConfiguration Text
pFunctionName_ =
  UpdateFunctionConfiguration'
    { $sel:deadLetterConfig:UpdateFunctionConfiguration' :: Maybe DeadLetterConfig
deadLetterConfig =
        forall a. Maybe a
Prelude.Nothing,
      $sel:description:UpdateFunctionConfiguration' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:environment:UpdateFunctionConfiguration' :: Maybe Environment
environment = forall a. Maybe a
Prelude.Nothing,
      $sel:ephemeralStorage:UpdateFunctionConfiguration' :: Maybe EphemeralStorage
ephemeralStorage = forall a. Maybe a
Prelude.Nothing,
      $sel:fileSystemConfigs:UpdateFunctionConfiguration' :: Maybe [FileSystemConfig]
fileSystemConfigs = forall a. Maybe a
Prelude.Nothing,
      $sel:handler:UpdateFunctionConfiguration' :: Maybe Text
handler = forall a. Maybe a
Prelude.Nothing,
      $sel:imageConfig:UpdateFunctionConfiguration' :: Maybe ImageConfig
imageConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:kmsKeyArn:UpdateFunctionConfiguration' :: Maybe Text
kmsKeyArn = forall a. Maybe a
Prelude.Nothing,
      $sel:layers:UpdateFunctionConfiguration' :: Maybe [Text]
layers = forall a. Maybe a
Prelude.Nothing,
      $sel:memorySize:UpdateFunctionConfiguration' :: Maybe Natural
memorySize = forall a. Maybe a
Prelude.Nothing,
      $sel:revisionId:UpdateFunctionConfiguration' :: Maybe Text
revisionId = forall a. Maybe a
Prelude.Nothing,
      $sel:role':UpdateFunctionConfiguration' :: Maybe Text
role' = forall a. Maybe a
Prelude.Nothing,
      $sel:runtime:UpdateFunctionConfiguration' :: Maybe Runtime
runtime = forall a. Maybe a
Prelude.Nothing,
      $sel:snapStart:UpdateFunctionConfiguration' :: Maybe SnapStart
snapStart = forall a. Maybe a
Prelude.Nothing,
      $sel:timeout:UpdateFunctionConfiguration' :: Maybe Natural
timeout = forall a. Maybe a
Prelude.Nothing,
      $sel:tracingConfig:UpdateFunctionConfiguration' :: Maybe TracingConfig
tracingConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:vpcConfig:UpdateFunctionConfiguration' :: Maybe VpcConfig
vpcConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:functionName:UpdateFunctionConfiguration' :: Text
functionName = Text
pFunctionName_
    }

-- | A dead-letter queue configuration that specifies the queue or topic
-- where Lambda sends asynchronous events when they fail processing. For
-- more information, see
-- <https://docs.aws.amazon.com/lambda/latest/dg/invocation-async.html#invocation-dlq Dead-letter queues>.
updateFunctionConfiguration_deadLetterConfig :: Lens.Lens' UpdateFunctionConfiguration (Prelude.Maybe DeadLetterConfig)
updateFunctionConfiguration_deadLetterConfig :: Lens' UpdateFunctionConfiguration (Maybe DeadLetterConfig)
updateFunctionConfiguration_deadLetterConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateFunctionConfiguration' {Maybe DeadLetterConfig
deadLetterConfig :: Maybe DeadLetterConfig
$sel:deadLetterConfig:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe DeadLetterConfig
deadLetterConfig} -> Maybe DeadLetterConfig
deadLetterConfig) (\s :: UpdateFunctionConfiguration
s@UpdateFunctionConfiguration' {} Maybe DeadLetterConfig
a -> UpdateFunctionConfiguration
s {$sel:deadLetterConfig:UpdateFunctionConfiguration' :: Maybe DeadLetterConfig
deadLetterConfig = Maybe DeadLetterConfig
a} :: UpdateFunctionConfiguration)

-- | A description of the function.
updateFunctionConfiguration_description :: Lens.Lens' UpdateFunctionConfiguration (Prelude.Maybe Prelude.Text)
updateFunctionConfiguration_description :: Lens' UpdateFunctionConfiguration (Maybe Text)
updateFunctionConfiguration_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateFunctionConfiguration' {Maybe Text
description :: Maybe Text
$sel:description:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe Text
description} -> Maybe Text
description) (\s :: UpdateFunctionConfiguration
s@UpdateFunctionConfiguration' {} Maybe Text
a -> UpdateFunctionConfiguration
s {$sel:description:UpdateFunctionConfiguration' :: Maybe Text
description = Maybe Text
a} :: UpdateFunctionConfiguration)

-- | Environment variables that are accessible from function code during
-- execution.
updateFunctionConfiguration_environment :: Lens.Lens' UpdateFunctionConfiguration (Prelude.Maybe Environment)
updateFunctionConfiguration_environment :: Lens' UpdateFunctionConfiguration (Maybe Environment)
updateFunctionConfiguration_environment = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateFunctionConfiguration' {Maybe Environment
environment :: Maybe Environment
$sel:environment:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe Environment
environment} -> Maybe Environment
environment) (\s :: UpdateFunctionConfiguration
s@UpdateFunctionConfiguration' {} Maybe Environment
a -> UpdateFunctionConfiguration
s {$sel:environment:UpdateFunctionConfiguration' :: Maybe Environment
environment = Maybe Environment
a} :: UpdateFunctionConfiguration)

-- | The size of the function\'s @\/tmp@ directory in MB. The default value
-- is 512, but can be any whole number between 512 and 10,240 MB.
updateFunctionConfiguration_ephemeralStorage :: Lens.Lens' UpdateFunctionConfiguration (Prelude.Maybe EphemeralStorage)
updateFunctionConfiguration_ephemeralStorage :: Lens' UpdateFunctionConfiguration (Maybe EphemeralStorage)
updateFunctionConfiguration_ephemeralStorage = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateFunctionConfiguration' {Maybe EphemeralStorage
ephemeralStorage :: Maybe EphemeralStorage
$sel:ephemeralStorage:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe EphemeralStorage
ephemeralStorage} -> Maybe EphemeralStorage
ephemeralStorage) (\s :: UpdateFunctionConfiguration
s@UpdateFunctionConfiguration' {} Maybe EphemeralStorage
a -> UpdateFunctionConfiguration
s {$sel:ephemeralStorage:UpdateFunctionConfiguration' :: Maybe EphemeralStorage
ephemeralStorage = Maybe EphemeralStorage
a} :: UpdateFunctionConfiguration)

-- | Connection settings for an Amazon EFS file system.
updateFunctionConfiguration_fileSystemConfigs :: Lens.Lens' UpdateFunctionConfiguration (Prelude.Maybe [FileSystemConfig])
updateFunctionConfiguration_fileSystemConfigs :: Lens' UpdateFunctionConfiguration (Maybe [FileSystemConfig])
updateFunctionConfiguration_fileSystemConfigs = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateFunctionConfiguration' {Maybe [FileSystemConfig]
fileSystemConfigs :: Maybe [FileSystemConfig]
$sel:fileSystemConfigs:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe [FileSystemConfig]
fileSystemConfigs} -> Maybe [FileSystemConfig]
fileSystemConfigs) (\s :: UpdateFunctionConfiguration
s@UpdateFunctionConfiguration' {} Maybe [FileSystemConfig]
a -> UpdateFunctionConfiguration
s {$sel:fileSystemConfigs:UpdateFunctionConfiguration' :: Maybe [FileSystemConfig]
fileSystemConfigs = Maybe [FileSystemConfig]
a} :: UpdateFunctionConfiguration) 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 name of the method within your code that Lambda calls to run your
-- function. Handler is required if the deployment package is a .zip file
-- archive. The format includes the file name. It can also include
-- namespaces and other qualifiers, depending on the runtime. For more
-- information, see
-- <https://docs.aws.amazon.com/lambda/latest/dg/foundation-progmodel.html Lambda programming model>.
updateFunctionConfiguration_handler :: Lens.Lens' UpdateFunctionConfiguration (Prelude.Maybe Prelude.Text)
updateFunctionConfiguration_handler :: Lens' UpdateFunctionConfiguration (Maybe Text)
updateFunctionConfiguration_handler = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateFunctionConfiguration' {Maybe Text
handler :: Maybe Text
$sel:handler:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe Text
handler} -> Maybe Text
handler) (\s :: UpdateFunctionConfiguration
s@UpdateFunctionConfiguration' {} Maybe Text
a -> UpdateFunctionConfiguration
s {$sel:handler:UpdateFunctionConfiguration' :: Maybe Text
handler = Maybe Text
a} :: UpdateFunctionConfiguration)

-- | <https://docs.aws.amazon.com/lambda/latest/dg/images-parms.html Container image configuration values>
-- that override the values in the container image Docker file.
updateFunctionConfiguration_imageConfig :: Lens.Lens' UpdateFunctionConfiguration (Prelude.Maybe ImageConfig)
updateFunctionConfiguration_imageConfig :: Lens' UpdateFunctionConfiguration (Maybe ImageConfig)
updateFunctionConfiguration_imageConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateFunctionConfiguration' {Maybe ImageConfig
imageConfig :: Maybe ImageConfig
$sel:imageConfig:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe ImageConfig
imageConfig} -> Maybe ImageConfig
imageConfig) (\s :: UpdateFunctionConfiguration
s@UpdateFunctionConfiguration' {} Maybe ImageConfig
a -> UpdateFunctionConfiguration
s {$sel:imageConfig:UpdateFunctionConfiguration' :: Maybe ImageConfig
imageConfig = Maybe ImageConfig
a} :: UpdateFunctionConfiguration)

-- | The ARN of the Key Management Service (KMS) key that\'s used to encrypt
-- your function\'s environment variables. If it\'s not provided, Lambda
-- uses a default service key.
updateFunctionConfiguration_kmsKeyArn :: Lens.Lens' UpdateFunctionConfiguration (Prelude.Maybe Prelude.Text)
updateFunctionConfiguration_kmsKeyArn :: Lens' UpdateFunctionConfiguration (Maybe Text)
updateFunctionConfiguration_kmsKeyArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateFunctionConfiguration' {Maybe Text
kmsKeyArn :: Maybe Text
$sel:kmsKeyArn:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe Text
kmsKeyArn} -> Maybe Text
kmsKeyArn) (\s :: UpdateFunctionConfiguration
s@UpdateFunctionConfiguration' {} Maybe Text
a -> UpdateFunctionConfiguration
s {$sel:kmsKeyArn:UpdateFunctionConfiguration' :: Maybe Text
kmsKeyArn = Maybe Text
a} :: UpdateFunctionConfiguration)

-- | A list of
-- <https://docs.aws.amazon.com/lambda/latest/dg/configuration-layers.html function layers>
-- to add to the function\'s execution environment. Specify each layer by
-- its ARN, including the version.
updateFunctionConfiguration_layers :: Lens.Lens' UpdateFunctionConfiguration (Prelude.Maybe [Prelude.Text])
updateFunctionConfiguration_layers :: Lens' UpdateFunctionConfiguration (Maybe [Text])
updateFunctionConfiguration_layers = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateFunctionConfiguration' {Maybe [Text]
layers :: Maybe [Text]
$sel:layers:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe [Text]
layers} -> Maybe [Text]
layers) (\s :: UpdateFunctionConfiguration
s@UpdateFunctionConfiguration' {} Maybe [Text]
a -> UpdateFunctionConfiguration
s {$sel:layers:UpdateFunctionConfiguration' :: Maybe [Text]
layers = Maybe [Text]
a} :: UpdateFunctionConfiguration) 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 amount of
-- <https://docs.aws.amazon.com/lambda/latest/dg/configuration-function-common.html#configuration-memory-console memory available to the function>
-- at runtime. Increasing the function memory also increases its CPU
-- allocation. The default value is 128 MB. The value can be any multiple
-- of 1 MB.
updateFunctionConfiguration_memorySize :: Lens.Lens' UpdateFunctionConfiguration (Prelude.Maybe Prelude.Natural)
updateFunctionConfiguration_memorySize :: Lens' UpdateFunctionConfiguration (Maybe Natural)
updateFunctionConfiguration_memorySize = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateFunctionConfiguration' {Maybe Natural
memorySize :: Maybe Natural
$sel:memorySize:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe Natural
memorySize} -> Maybe Natural
memorySize) (\s :: UpdateFunctionConfiguration
s@UpdateFunctionConfiguration' {} Maybe Natural
a -> UpdateFunctionConfiguration
s {$sel:memorySize:UpdateFunctionConfiguration' :: Maybe Natural
memorySize = Maybe Natural
a} :: UpdateFunctionConfiguration)

-- | Update the function only if the revision ID matches the ID that\'s
-- specified. Use this option to avoid modifying a function that has
-- changed since you last read it.
updateFunctionConfiguration_revisionId :: Lens.Lens' UpdateFunctionConfiguration (Prelude.Maybe Prelude.Text)
updateFunctionConfiguration_revisionId :: Lens' UpdateFunctionConfiguration (Maybe Text)
updateFunctionConfiguration_revisionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateFunctionConfiguration' {Maybe Text
revisionId :: Maybe Text
$sel:revisionId:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe Text
revisionId} -> Maybe Text
revisionId) (\s :: UpdateFunctionConfiguration
s@UpdateFunctionConfiguration' {} Maybe Text
a -> UpdateFunctionConfiguration
s {$sel:revisionId:UpdateFunctionConfiguration' :: Maybe Text
revisionId = Maybe Text
a} :: UpdateFunctionConfiguration)

-- | The Amazon Resource Name (ARN) of the function\'s execution role.
updateFunctionConfiguration_role :: Lens.Lens' UpdateFunctionConfiguration (Prelude.Maybe Prelude.Text)
updateFunctionConfiguration_role :: Lens' UpdateFunctionConfiguration (Maybe Text)
updateFunctionConfiguration_role = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateFunctionConfiguration' {Maybe Text
role' :: Maybe Text
$sel:role':UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe Text
role'} -> Maybe Text
role') (\s :: UpdateFunctionConfiguration
s@UpdateFunctionConfiguration' {} Maybe Text
a -> UpdateFunctionConfiguration
s {$sel:role':UpdateFunctionConfiguration' :: Maybe Text
role' = Maybe Text
a} :: UpdateFunctionConfiguration)

-- | The identifier of the function\'s
-- <https://docs.aws.amazon.com/lambda/latest/dg/lambda-runtimes.html runtime>.
-- Runtime is required if the deployment package is a .zip file archive.
updateFunctionConfiguration_runtime :: Lens.Lens' UpdateFunctionConfiguration (Prelude.Maybe Runtime)
updateFunctionConfiguration_runtime :: Lens' UpdateFunctionConfiguration (Maybe Runtime)
updateFunctionConfiguration_runtime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateFunctionConfiguration' {Maybe Runtime
runtime :: Maybe Runtime
$sel:runtime:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe Runtime
runtime} -> Maybe Runtime
runtime) (\s :: UpdateFunctionConfiguration
s@UpdateFunctionConfiguration' {} Maybe Runtime
a -> UpdateFunctionConfiguration
s {$sel:runtime:UpdateFunctionConfiguration' :: Maybe Runtime
runtime = Maybe Runtime
a} :: UpdateFunctionConfiguration)

-- | The function\'s
-- <https://docs.aws.amazon.com/lambda/latest/dg/snapstart.html SnapStart>
-- setting.
updateFunctionConfiguration_snapStart :: Lens.Lens' UpdateFunctionConfiguration (Prelude.Maybe SnapStart)
updateFunctionConfiguration_snapStart :: Lens' UpdateFunctionConfiguration (Maybe SnapStart)
updateFunctionConfiguration_snapStart = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateFunctionConfiguration' {Maybe SnapStart
snapStart :: Maybe SnapStart
$sel:snapStart:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe SnapStart
snapStart} -> Maybe SnapStart
snapStart) (\s :: UpdateFunctionConfiguration
s@UpdateFunctionConfiguration' {} Maybe SnapStart
a -> UpdateFunctionConfiguration
s {$sel:snapStart:UpdateFunctionConfiguration' :: Maybe SnapStart
snapStart = Maybe SnapStart
a} :: UpdateFunctionConfiguration)

-- | The amount of time (in seconds) that Lambda allows a function to run
-- before stopping it. The default is 3 seconds. The maximum allowed value
-- is 900 seconds. For more information, see
-- <https://docs.aws.amazon.com/lambda/latest/dg/runtimes-context.html Lambda execution environment>.
updateFunctionConfiguration_timeout :: Lens.Lens' UpdateFunctionConfiguration (Prelude.Maybe Prelude.Natural)
updateFunctionConfiguration_timeout :: Lens' UpdateFunctionConfiguration (Maybe Natural)
updateFunctionConfiguration_timeout = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateFunctionConfiguration' {Maybe Natural
timeout :: Maybe Natural
$sel:timeout:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe Natural
timeout} -> Maybe Natural
timeout) (\s :: UpdateFunctionConfiguration
s@UpdateFunctionConfiguration' {} Maybe Natural
a -> UpdateFunctionConfiguration
s {$sel:timeout:UpdateFunctionConfiguration' :: Maybe Natural
timeout = Maybe Natural
a} :: UpdateFunctionConfiguration)

-- | Set @Mode@ to @Active@ to sample and trace a subset of incoming requests
-- with
-- <https://docs.aws.amazon.com/lambda/latest/dg/services-xray.html X-Ray>.
updateFunctionConfiguration_tracingConfig :: Lens.Lens' UpdateFunctionConfiguration (Prelude.Maybe TracingConfig)
updateFunctionConfiguration_tracingConfig :: Lens' UpdateFunctionConfiguration (Maybe TracingConfig)
updateFunctionConfiguration_tracingConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateFunctionConfiguration' {Maybe TracingConfig
tracingConfig :: Maybe TracingConfig
$sel:tracingConfig:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe TracingConfig
tracingConfig} -> Maybe TracingConfig
tracingConfig) (\s :: UpdateFunctionConfiguration
s@UpdateFunctionConfiguration' {} Maybe TracingConfig
a -> UpdateFunctionConfiguration
s {$sel:tracingConfig:UpdateFunctionConfiguration' :: Maybe TracingConfig
tracingConfig = Maybe TracingConfig
a} :: UpdateFunctionConfiguration)

-- | For network connectivity to Amazon Web Services resources in a VPC,
-- specify a list of security groups and subnets in the VPC. When you
-- connect a function to a VPC, it can access resources and the internet
-- only through that VPC. For more information, see
-- <https://docs.aws.amazon.com/lambda/latest/dg/configuration-vpc.html Configuring a Lambda function to access resources in a VPC>.
updateFunctionConfiguration_vpcConfig :: Lens.Lens' UpdateFunctionConfiguration (Prelude.Maybe VpcConfig)
updateFunctionConfiguration_vpcConfig :: Lens' UpdateFunctionConfiguration (Maybe VpcConfig)
updateFunctionConfiguration_vpcConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateFunctionConfiguration' {Maybe VpcConfig
vpcConfig :: Maybe VpcConfig
$sel:vpcConfig:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe VpcConfig
vpcConfig} -> Maybe VpcConfig
vpcConfig) (\s :: UpdateFunctionConfiguration
s@UpdateFunctionConfiguration' {} Maybe VpcConfig
a -> UpdateFunctionConfiguration
s {$sel:vpcConfig:UpdateFunctionConfiguration' :: Maybe VpcConfig
vpcConfig = Maybe VpcConfig
a} :: UpdateFunctionConfiguration)

-- | The name of the Lambda function.
--
-- __Name formats__
--
-- -   __Function name__ – @my-function@.
--
-- -   __Function ARN__ –
--     @arn:aws:lambda:us-west-2:123456789012:function:my-function@.
--
-- -   __Partial ARN__ – @123456789012:function:my-function@.
--
-- The length constraint applies only to the full ARN. If you specify only
-- the function name, it is limited to 64 characters in length.
updateFunctionConfiguration_functionName :: Lens.Lens' UpdateFunctionConfiguration Prelude.Text
updateFunctionConfiguration_functionName :: Lens' UpdateFunctionConfiguration Text
updateFunctionConfiguration_functionName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateFunctionConfiguration' {Text
functionName :: Text
$sel:functionName:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Text
functionName} -> Text
functionName) (\s :: UpdateFunctionConfiguration
s@UpdateFunctionConfiguration' {} Text
a -> UpdateFunctionConfiguration
s {$sel:functionName:UpdateFunctionConfiguration' :: Text
functionName = Text
a} :: UpdateFunctionConfiguration)

instance Core.AWSRequest UpdateFunctionConfiguration where
  type
    AWSResponse UpdateFunctionConfiguration =
      FunctionConfiguration
  request :: (Service -> Service)
-> UpdateFunctionConfiguration
-> Request UpdateFunctionConfiguration
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.putJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy UpdateFunctionConfiguration
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse UpdateFunctionConfiguration)))
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 UpdateFunctionConfiguration where
  hashWithSalt :: Int -> UpdateFunctionConfiguration -> Int
hashWithSalt Int
_salt UpdateFunctionConfiguration' {Maybe Natural
Maybe [Text]
Maybe [FileSystemConfig]
Maybe Text
Maybe DeadLetterConfig
Maybe Environment
Maybe EphemeralStorage
Maybe ImageConfig
Maybe Runtime
Maybe SnapStart
Maybe TracingConfig
Maybe VpcConfig
Text
functionName :: Text
vpcConfig :: Maybe VpcConfig
tracingConfig :: Maybe TracingConfig
timeout :: Maybe Natural
snapStart :: Maybe SnapStart
runtime :: Maybe Runtime
role' :: Maybe Text
revisionId :: Maybe Text
memorySize :: Maybe Natural
layers :: Maybe [Text]
kmsKeyArn :: Maybe Text
imageConfig :: Maybe ImageConfig
handler :: Maybe Text
fileSystemConfigs :: Maybe [FileSystemConfig]
ephemeralStorage :: Maybe EphemeralStorage
environment :: Maybe Environment
description :: Maybe Text
deadLetterConfig :: Maybe DeadLetterConfig
$sel:functionName:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Text
$sel:vpcConfig:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe VpcConfig
$sel:tracingConfig:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe TracingConfig
$sel:timeout:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe Natural
$sel:snapStart:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe SnapStart
$sel:runtime:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe Runtime
$sel:role':UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe Text
$sel:revisionId:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe Text
$sel:memorySize:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe Natural
$sel:layers:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe [Text]
$sel:kmsKeyArn:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe Text
$sel:imageConfig:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe ImageConfig
$sel:handler:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe Text
$sel:fileSystemConfigs:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe [FileSystemConfig]
$sel:ephemeralStorage:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe EphemeralStorage
$sel:environment:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe Environment
$sel:description:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe Text
$sel:deadLetterConfig:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe DeadLetterConfig
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DeadLetterConfig
deadLetterConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Environment
environment
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe EphemeralStorage
ephemeralStorage
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [FileSystemConfig]
fileSystemConfigs
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
handler
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ImageConfig
imageConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
kmsKeyArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
layers
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
memorySize
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
revisionId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
role'
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Runtime
runtime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe SnapStart
snapStart
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
timeout
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe TracingConfig
tracingConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe VpcConfig
vpcConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
functionName

instance Prelude.NFData UpdateFunctionConfiguration where
  rnf :: UpdateFunctionConfiguration -> ()
rnf UpdateFunctionConfiguration' {Maybe Natural
Maybe [Text]
Maybe [FileSystemConfig]
Maybe Text
Maybe DeadLetterConfig
Maybe Environment
Maybe EphemeralStorage
Maybe ImageConfig
Maybe Runtime
Maybe SnapStart
Maybe TracingConfig
Maybe VpcConfig
Text
functionName :: Text
vpcConfig :: Maybe VpcConfig
tracingConfig :: Maybe TracingConfig
timeout :: Maybe Natural
snapStart :: Maybe SnapStart
runtime :: Maybe Runtime
role' :: Maybe Text
revisionId :: Maybe Text
memorySize :: Maybe Natural
layers :: Maybe [Text]
kmsKeyArn :: Maybe Text
imageConfig :: Maybe ImageConfig
handler :: Maybe Text
fileSystemConfigs :: Maybe [FileSystemConfig]
ephemeralStorage :: Maybe EphemeralStorage
environment :: Maybe Environment
description :: Maybe Text
deadLetterConfig :: Maybe DeadLetterConfig
$sel:functionName:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Text
$sel:vpcConfig:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe VpcConfig
$sel:tracingConfig:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe TracingConfig
$sel:timeout:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe Natural
$sel:snapStart:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe SnapStart
$sel:runtime:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe Runtime
$sel:role':UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe Text
$sel:revisionId:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe Text
$sel:memorySize:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe Natural
$sel:layers:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe [Text]
$sel:kmsKeyArn:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe Text
$sel:imageConfig:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe ImageConfig
$sel:handler:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe Text
$sel:fileSystemConfigs:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe [FileSystemConfig]
$sel:ephemeralStorage:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe EphemeralStorage
$sel:environment:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe Environment
$sel:description:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe Text
$sel:deadLetterConfig:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe DeadLetterConfig
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe DeadLetterConfig
deadLetterConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Environment
environment
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe EphemeralStorage
ephemeralStorage
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [FileSystemConfig]
fileSystemConfigs
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
handler
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ImageConfig
imageConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
kmsKeyArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
layers
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
memorySize
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
revisionId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
role'
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Runtime
runtime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe SnapStart
snapStart
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
timeout
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe TracingConfig
tracingConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe VpcConfig
vpcConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
functionName

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

instance Data.ToJSON UpdateFunctionConfiguration where
  toJSON :: UpdateFunctionConfiguration -> Value
toJSON UpdateFunctionConfiguration' {Maybe Natural
Maybe [Text]
Maybe [FileSystemConfig]
Maybe Text
Maybe DeadLetterConfig
Maybe Environment
Maybe EphemeralStorage
Maybe ImageConfig
Maybe Runtime
Maybe SnapStart
Maybe TracingConfig
Maybe VpcConfig
Text
functionName :: Text
vpcConfig :: Maybe VpcConfig
tracingConfig :: Maybe TracingConfig
timeout :: Maybe Natural
snapStart :: Maybe SnapStart
runtime :: Maybe Runtime
role' :: Maybe Text
revisionId :: Maybe Text
memorySize :: Maybe Natural
layers :: Maybe [Text]
kmsKeyArn :: Maybe Text
imageConfig :: Maybe ImageConfig
handler :: Maybe Text
fileSystemConfigs :: Maybe [FileSystemConfig]
ephemeralStorage :: Maybe EphemeralStorage
environment :: Maybe Environment
description :: Maybe Text
deadLetterConfig :: Maybe DeadLetterConfig
$sel:functionName:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Text
$sel:vpcConfig:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe VpcConfig
$sel:tracingConfig:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe TracingConfig
$sel:timeout:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe Natural
$sel:snapStart:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe SnapStart
$sel:runtime:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe Runtime
$sel:role':UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe Text
$sel:revisionId:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe Text
$sel:memorySize:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe Natural
$sel:layers:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe [Text]
$sel:kmsKeyArn:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe Text
$sel:imageConfig:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe ImageConfig
$sel:handler:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe Text
$sel:fileSystemConfigs:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe [FileSystemConfig]
$sel:ephemeralStorage:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe EphemeralStorage
$sel:environment:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe Environment
$sel:description:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe Text
$sel:deadLetterConfig:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe DeadLetterConfig
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"DeadLetterConfig" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe DeadLetterConfig
deadLetterConfig,
            (Key
"Description" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
description,
            (Key
"Environment" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Environment
environment,
            (Key
"EphemeralStorage" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe EphemeralStorage
ephemeralStorage,
            (Key
"FileSystemConfigs" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [FileSystemConfig]
fileSystemConfigs,
            (Key
"Handler" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
handler,
            (Key
"ImageConfig" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ImageConfig
imageConfig,
            (Key
"KMSKeyArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
kmsKeyArn,
            (Key
"Layers" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Text]
layers,
            (Key
"MemorySize" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Natural
memorySize,
            (Key
"RevisionId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
revisionId,
            (Key
"Role" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
role',
            (Key
"Runtime" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Runtime
runtime,
            (Key
"SnapStart" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe SnapStart
snapStart,
            (Key
"Timeout" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Natural
timeout,
            (Key
"TracingConfig" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe TracingConfig
tracingConfig,
            (Key
"VpcConfig" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe VpcConfig
vpcConfig
          ]
      )

instance Data.ToPath UpdateFunctionConfiguration where
  toPath :: UpdateFunctionConfiguration -> ByteString
toPath UpdateFunctionConfiguration' {Maybe Natural
Maybe [Text]
Maybe [FileSystemConfig]
Maybe Text
Maybe DeadLetterConfig
Maybe Environment
Maybe EphemeralStorage
Maybe ImageConfig
Maybe Runtime
Maybe SnapStart
Maybe TracingConfig
Maybe VpcConfig
Text
functionName :: Text
vpcConfig :: Maybe VpcConfig
tracingConfig :: Maybe TracingConfig
timeout :: Maybe Natural
snapStart :: Maybe SnapStart
runtime :: Maybe Runtime
role' :: Maybe Text
revisionId :: Maybe Text
memorySize :: Maybe Natural
layers :: Maybe [Text]
kmsKeyArn :: Maybe Text
imageConfig :: Maybe ImageConfig
handler :: Maybe Text
fileSystemConfigs :: Maybe [FileSystemConfig]
ephemeralStorage :: Maybe EphemeralStorage
environment :: Maybe Environment
description :: Maybe Text
deadLetterConfig :: Maybe DeadLetterConfig
$sel:functionName:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Text
$sel:vpcConfig:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe VpcConfig
$sel:tracingConfig:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe TracingConfig
$sel:timeout:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe Natural
$sel:snapStart:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe SnapStart
$sel:runtime:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe Runtime
$sel:role':UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe Text
$sel:revisionId:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe Text
$sel:memorySize:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe Natural
$sel:layers:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe [Text]
$sel:kmsKeyArn:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe Text
$sel:imageConfig:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe ImageConfig
$sel:handler:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe Text
$sel:fileSystemConfigs:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe [FileSystemConfig]
$sel:ephemeralStorage:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe EphemeralStorage
$sel:environment:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe Environment
$sel:description:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe Text
$sel:deadLetterConfig:UpdateFunctionConfiguration' :: UpdateFunctionConfiguration -> Maybe DeadLetterConfig
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/2015-03-31/functions/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
functionName,
        ByteString
"/configuration"
      ]

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