module Stratosphere.Lambda.Function (
        module Exports, Function(..), mkFunction
    ) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.Lambda.Function.CodeProperty as Exports
import {-# SOURCE #-} Stratosphere.Lambda.Function.DeadLetterConfigProperty as Exports
import {-# SOURCE #-} Stratosphere.Lambda.Function.EnvironmentProperty as Exports
import {-# SOURCE #-} Stratosphere.Lambda.Function.EphemeralStorageProperty as Exports
import {-# SOURCE #-} Stratosphere.Lambda.Function.FileSystemConfigProperty as Exports
import {-# SOURCE #-} Stratosphere.Lambda.Function.ImageConfigProperty as Exports
import {-# SOURCE #-} Stratosphere.Lambda.Function.LoggingConfigProperty as Exports
import {-# SOURCE #-} Stratosphere.Lambda.Function.RuntimeManagementConfigProperty as Exports
import {-# SOURCE #-} Stratosphere.Lambda.Function.SnapStartProperty as Exports
import {-# SOURCE #-} Stratosphere.Lambda.Function.TracingConfigProperty as Exports
import {-# SOURCE #-} Stratosphere.Lambda.Function.VpcConfigProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Tag
import Stratosphere.Value
data Function
  = -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-lambda-function.html>
    Function {Function -> ()
haddock_workaround_ :: (),
              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-lambda-function.html#cfn-lambda-function-architectures>
              Function -> Maybe (ValueList Text)
architectures :: (Prelude.Maybe (ValueList Prelude.Text)),
              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-lambda-function.html#cfn-lambda-function-code>
              Function -> CodeProperty
code :: CodeProperty,
              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-lambda-function.html#cfn-lambda-function-codesigningconfigarn>
              Function -> Maybe (Value Text)
codeSigningConfigArn :: (Prelude.Maybe (Value Prelude.Text)),
              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-lambda-function.html#cfn-lambda-function-deadletterconfig>
              Function -> Maybe DeadLetterConfigProperty
deadLetterConfig :: (Prelude.Maybe DeadLetterConfigProperty),
              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-lambda-function.html#cfn-lambda-function-description>
              Function -> Maybe (Value Text)
description :: (Prelude.Maybe (Value Prelude.Text)),
              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-lambda-function.html#cfn-lambda-function-environment>
              Function -> Maybe EnvironmentProperty
environment :: (Prelude.Maybe EnvironmentProperty),
              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-lambda-function.html#cfn-lambda-function-ephemeralstorage>
              Function -> Maybe EphemeralStorageProperty
ephemeralStorage :: (Prelude.Maybe EphemeralStorageProperty),
              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-lambda-function.html#cfn-lambda-function-filesystemconfigs>
              Function -> Maybe [FileSystemConfigProperty]
fileSystemConfigs :: (Prelude.Maybe [FileSystemConfigProperty]),
              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-lambda-function.html#cfn-lambda-function-functionname>
              Function -> Maybe (Value Text)
functionName :: (Prelude.Maybe (Value Prelude.Text)),
              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-lambda-function.html#cfn-lambda-function-handler>
              Function -> Maybe (Value Text)
handler :: (Prelude.Maybe (Value Prelude.Text)),
              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-lambda-function.html#cfn-lambda-function-imageconfig>
              Function -> Maybe ImageConfigProperty
imageConfig :: (Prelude.Maybe ImageConfigProperty),
              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-lambda-function.html#cfn-lambda-function-kmskeyarn>
              Function -> Maybe (Value Text)
kmsKeyArn :: (Prelude.Maybe (Value Prelude.Text)),
              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-lambda-function.html#cfn-lambda-function-layers>
              Function -> Maybe (ValueList Text)
layers :: (Prelude.Maybe (ValueList Prelude.Text)),
              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-lambda-function.html#cfn-lambda-function-loggingconfig>
              Function -> Maybe LoggingConfigProperty
loggingConfig :: (Prelude.Maybe LoggingConfigProperty),
              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-lambda-function.html#cfn-lambda-function-memorysize>
              Function -> Maybe (Value Integer)
memorySize :: (Prelude.Maybe (Value Prelude.Integer)),
              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-lambda-function.html#cfn-lambda-function-packagetype>
              Function -> Maybe (Value Text)
packageType :: (Prelude.Maybe (Value Prelude.Text)),
              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-lambda-function.html#cfn-lambda-function-recursiveloop>
              Function -> Maybe (Value Text)
recursiveLoop :: (Prelude.Maybe (Value Prelude.Text)),
              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-lambda-function.html#cfn-lambda-function-reservedconcurrentexecutions>
              Function -> Maybe (Value Integer)
reservedConcurrentExecutions :: (Prelude.Maybe (Value Prelude.Integer)),
              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-lambda-function.html#cfn-lambda-function-role>
              Function -> Value Text
role :: (Value Prelude.Text),
              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-lambda-function.html#cfn-lambda-function-runtime>
              Function -> Maybe (Value Text)
runtime :: (Prelude.Maybe (Value Prelude.Text)),
              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-lambda-function.html#cfn-lambda-function-runtimemanagementconfig>
              Function -> Maybe RuntimeManagementConfigProperty
runtimeManagementConfig :: (Prelude.Maybe RuntimeManagementConfigProperty),
              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-lambda-function.html#cfn-lambda-function-snapstart>
              Function -> Maybe SnapStartProperty
snapStart :: (Prelude.Maybe SnapStartProperty),
              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-lambda-function.html#cfn-lambda-function-tags>
              Function -> Maybe [Tag]
tags :: (Prelude.Maybe [Tag]),
              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-lambda-function.html#cfn-lambda-function-timeout>
              Function -> Maybe (Value Integer)
timeout :: (Prelude.Maybe (Value Prelude.Integer)),
              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-lambda-function.html#cfn-lambda-function-tracingconfig>
              Function -> Maybe TracingConfigProperty
tracingConfig :: (Prelude.Maybe TracingConfigProperty),
              -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-resource-lambda-function.html#cfn-lambda-function-vpcconfig>
              Function -> Maybe VpcConfigProperty
vpcConfig :: (Prelude.Maybe VpcConfigProperty)}
  deriving stock (Function -> Function -> Bool
(Function -> Function -> Bool)
-> (Function -> Function -> Bool) -> Eq Function
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Function -> Function -> Bool
== :: Function -> Function -> Bool
$c/= :: Function -> Function -> Bool
/= :: Function -> Function -> Bool
Prelude.Eq, Int -> Function -> ShowS
[Function] -> ShowS
Function -> String
(Int -> Function -> ShowS)
-> (Function -> String) -> ([Function] -> ShowS) -> Show Function
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Function -> ShowS
showsPrec :: Int -> Function -> ShowS
$cshow :: Function -> String
show :: Function -> String
$cshowList :: [Function] -> ShowS
showList :: [Function] -> ShowS
Prelude.Show)
mkFunction :: CodeProperty -> Value Prelude.Text -> Function
mkFunction :: CodeProperty -> Value Text -> Function
mkFunction CodeProperty
code Value Text
role
  = Function
      {haddock_workaround_ :: ()
haddock_workaround_ = (), code :: CodeProperty
code = CodeProperty
code, role :: Value Text
role = Value Text
role,
       architectures :: Maybe (ValueList Text)
architectures = Maybe (ValueList Text)
forall a. Maybe a
Prelude.Nothing,
       codeSigningConfigArn :: Maybe (Value Text)
codeSigningConfigArn = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
       deadLetterConfig :: Maybe DeadLetterConfigProperty
deadLetterConfig = Maybe DeadLetterConfigProperty
forall a. Maybe a
Prelude.Nothing, description :: Maybe (Value Text)
description = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
       environment :: Maybe EnvironmentProperty
environment = Maybe EnvironmentProperty
forall a. Maybe a
Prelude.Nothing, ephemeralStorage :: Maybe EphemeralStorageProperty
ephemeralStorage = Maybe EphemeralStorageProperty
forall a. Maybe a
Prelude.Nothing,
       fileSystemConfigs :: Maybe [FileSystemConfigProperty]
fileSystemConfigs = Maybe [FileSystemConfigProperty]
forall a. Maybe a
Prelude.Nothing,
       functionName :: Maybe (Value Text)
functionName = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing, handler :: Maybe (Value Text)
handler = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
       imageConfig :: Maybe ImageConfigProperty
imageConfig = Maybe ImageConfigProperty
forall a. Maybe a
Prelude.Nothing, kmsKeyArn :: Maybe (Value Text)
kmsKeyArn = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
       layers :: Maybe (ValueList Text)
layers = Maybe (ValueList Text)
forall a. Maybe a
Prelude.Nothing, loggingConfig :: Maybe LoggingConfigProperty
loggingConfig = Maybe LoggingConfigProperty
forall a. Maybe a
Prelude.Nothing,
       memorySize :: Maybe (Value Integer)
memorySize = Maybe (Value Integer)
forall a. Maybe a
Prelude.Nothing, packageType :: Maybe (Value Text)
packageType = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
       recursiveLoop :: Maybe (Value Text)
recursiveLoop = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
       reservedConcurrentExecutions :: Maybe (Value Integer)
reservedConcurrentExecutions = Maybe (Value Integer)
forall a. Maybe a
Prelude.Nothing,
       runtime :: Maybe (Value Text)
runtime = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
       runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
runtimeManagementConfig = Maybe RuntimeManagementConfigProperty
forall a. Maybe a
Prelude.Nothing,
       snapStart :: Maybe SnapStartProperty
snapStart = Maybe SnapStartProperty
forall a. Maybe a
Prelude.Nothing, tags :: Maybe [Tag]
tags = Maybe [Tag]
forall a. Maybe a
Prelude.Nothing,
       timeout :: Maybe (Value Integer)
timeout = Maybe (Value Integer)
forall a. Maybe a
Prelude.Nothing, tracingConfig :: Maybe TracingConfigProperty
tracingConfig = Maybe TracingConfigProperty
forall a. Maybe a
Prelude.Nothing,
       vpcConfig :: Maybe VpcConfigProperty
vpcConfig = Maybe VpcConfigProperty
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties Function where
  toResourceProperties :: Function -> ResourceProperties
toResourceProperties Function {Maybe [Tag]
Maybe [FileSystemConfigProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeadLetterConfigProperty
Maybe EnvironmentProperty
Maybe EphemeralStorageProperty
Maybe ImageConfigProperty
Maybe LoggingConfigProperty
Maybe RuntimeManagementConfigProperty
Maybe SnapStartProperty
Maybe TracingConfigProperty
Maybe VpcConfigProperty
()
Value Text
CodeProperty
haddock_workaround_ :: Function -> ()
architectures :: Function -> Maybe (ValueList Text)
code :: Function -> CodeProperty
codeSigningConfigArn :: Function -> Maybe (Value Text)
deadLetterConfig :: Function -> Maybe DeadLetterConfigProperty
description :: Function -> Maybe (Value Text)
environment :: Function -> Maybe EnvironmentProperty
ephemeralStorage :: Function -> Maybe EphemeralStorageProperty
fileSystemConfigs :: Function -> Maybe [FileSystemConfigProperty]
functionName :: Function -> Maybe (Value Text)
handler :: Function -> Maybe (Value Text)
imageConfig :: Function -> Maybe ImageConfigProperty
kmsKeyArn :: Function -> Maybe (Value Text)
layers :: Function -> Maybe (ValueList Text)
loggingConfig :: Function -> Maybe LoggingConfigProperty
memorySize :: Function -> Maybe (Value Integer)
packageType :: Function -> Maybe (Value Text)
recursiveLoop :: Function -> Maybe (Value Text)
reservedConcurrentExecutions :: Function -> Maybe (Value Integer)
role :: Function -> Value Text
runtime :: Function -> Maybe (Value Text)
runtimeManagementConfig :: Function -> Maybe RuntimeManagementConfigProperty
snapStart :: Function -> Maybe SnapStartProperty
tags :: Function -> Maybe [Tag]
timeout :: Function -> Maybe (Value Integer)
tracingConfig :: Function -> Maybe TracingConfigProperty
vpcConfig :: Function -> Maybe VpcConfigProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
..}
    = ResourceProperties
        {awsType :: Text
awsType = Text
"AWS::Lambda::Function", supportsTags :: Bool
supportsTags = Bool
Prelude.True,
         properties :: Object
properties = [Item Object] -> Object
forall l. IsList l => [Item l] -> l
Prelude.fromList
                        ([(Key, Value)] -> [(Key, Value)] -> [(Key, Value)]
forall a. Semigroup a => a -> a -> a
(Prelude.<>)
                           [Key
"Code" Key -> CodeProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= CodeProperty
code, Key
"Role" Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Text
role]
                           ([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
                              [Key -> ValueList Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Architectures" (ValueList Text -> (Key, Value))
-> Maybe (ValueList Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (ValueList Text)
architectures,
                               Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"CodeSigningConfigArn" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
codeSigningConfigArn,
                               Key -> DeadLetterConfigProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"DeadLetterConfig" (DeadLetterConfigProperty -> (Key, Value))
-> Maybe DeadLetterConfigProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe DeadLetterConfigProperty
deadLetterConfig,
                               Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Description" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
description,
                               Key -> EnvironmentProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Environment" (EnvironmentProperty -> (Key, Value))
-> Maybe EnvironmentProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe EnvironmentProperty
environment,
                               Key -> EphemeralStorageProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"EphemeralStorage" (EphemeralStorageProperty -> (Key, Value))
-> Maybe EphemeralStorageProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe EphemeralStorageProperty
ephemeralStorage,
                               Key -> [FileSystemConfigProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"FileSystemConfigs" ([FileSystemConfigProperty] -> (Key, Value))
-> Maybe [FileSystemConfigProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [FileSystemConfigProperty]
fileSystemConfigs,
                               Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"FunctionName" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
functionName,
                               Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Handler" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
handler,
                               Key -> ImageConfigProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ImageConfig" (ImageConfigProperty -> (Key, Value))
-> Maybe ImageConfigProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ImageConfigProperty
imageConfig,
                               Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"KmsKeyArn" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
kmsKeyArn,
                               Key -> ValueList Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Layers" (ValueList Text -> (Key, Value))
-> Maybe (ValueList Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (ValueList Text)
layers,
                               Key -> LoggingConfigProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"LoggingConfig" (LoggingConfigProperty -> (Key, Value))
-> Maybe LoggingConfigProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe LoggingConfigProperty
loggingConfig,
                               Key -> Value Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"MemorySize" (Value Integer -> (Key, Value))
-> Maybe (Value Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Integer)
memorySize,
                               Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"PackageType" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
packageType,
                               Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"RecursiveLoop" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
recursiveLoop,
                               Key -> Value Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ReservedConcurrentExecutions"
                                 (Value Integer -> (Key, Value))
-> Maybe (Value Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Integer)
reservedConcurrentExecutions,
                               Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Runtime" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
runtime,
                               Key -> RuntimeManagementConfigProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"RuntimeManagementConfig"
                                 (RuntimeManagementConfigProperty -> (Key, Value))
-> Maybe RuntimeManagementConfigProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe RuntimeManagementConfigProperty
runtimeManagementConfig,
                               Key -> SnapStartProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"SnapStart" (SnapStartProperty -> (Key, Value))
-> Maybe SnapStartProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe SnapStartProperty
snapStart,
                               Key -> [Tag] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Tags" ([Tag] -> (Key, Value)) -> Maybe [Tag] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Tag]
tags,
                               Key -> Value Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Timeout" (Value Integer -> (Key, Value))
-> Maybe (Value Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Integer)
timeout,
                               Key -> TracingConfigProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"TracingConfig" (TracingConfigProperty -> (Key, Value))
-> Maybe TracingConfigProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe TracingConfigProperty
tracingConfig,
                               Key -> VpcConfigProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"VpcConfig" (VpcConfigProperty -> (Key, Value))
-> Maybe VpcConfigProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe VpcConfigProperty
vpcConfig]))}
instance JSON.ToJSON Function where
  toJSON :: Function -> Value
toJSON Function {Maybe [Tag]
Maybe [FileSystemConfigProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeadLetterConfigProperty
Maybe EnvironmentProperty
Maybe EphemeralStorageProperty
Maybe ImageConfigProperty
Maybe LoggingConfigProperty
Maybe RuntimeManagementConfigProperty
Maybe SnapStartProperty
Maybe TracingConfigProperty
Maybe VpcConfigProperty
()
Value Text
CodeProperty
haddock_workaround_ :: Function -> ()
architectures :: Function -> Maybe (ValueList Text)
code :: Function -> CodeProperty
codeSigningConfigArn :: Function -> Maybe (Value Text)
deadLetterConfig :: Function -> Maybe DeadLetterConfigProperty
description :: Function -> Maybe (Value Text)
environment :: Function -> Maybe EnvironmentProperty
ephemeralStorage :: Function -> Maybe EphemeralStorageProperty
fileSystemConfigs :: Function -> Maybe [FileSystemConfigProperty]
functionName :: Function -> Maybe (Value Text)
handler :: Function -> Maybe (Value Text)
imageConfig :: Function -> Maybe ImageConfigProperty
kmsKeyArn :: Function -> Maybe (Value Text)
layers :: Function -> Maybe (ValueList Text)
loggingConfig :: Function -> Maybe LoggingConfigProperty
memorySize :: Function -> Maybe (Value Integer)
packageType :: Function -> Maybe (Value Text)
recursiveLoop :: Function -> Maybe (Value Text)
reservedConcurrentExecutions :: Function -> Maybe (Value Integer)
role :: Function -> Value Text
runtime :: Function -> Maybe (Value Text)
runtimeManagementConfig :: Function -> Maybe RuntimeManagementConfigProperty
snapStart :: Function -> Maybe SnapStartProperty
tags :: Function -> Maybe [Tag]
timeout :: Function -> Maybe (Value Integer)
tracingConfig :: Function -> Maybe TracingConfigProperty
vpcConfig :: Function -> Maybe VpcConfigProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
..}
    = [(Key, Value)] -> Value
JSON.object
        ([Item [(Key, Value)]] -> [(Key, Value)]
forall l. IsList l => [Item l] -> l
Prelude.fromList
           ([(Key, Value)] -> [(Key, Value)] -> [(Key, Value)]
forall a. Semigroup a => a -> a -> a
(Prelude.<>)
              [Key
"Code" Key -> CodeProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= CodeProperty
code, Key
"Role" Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Text
role]
              ([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
                 [Key -> ValueList Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Architectures" (ValueList Text -> (Key, Value))
-> Maybe (ValueList Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (ValueList Text)
architectures,
                  Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"CodeSigningConfigArn" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
codeSigningConfigArn,
                  Key -> DeadLetterConfigProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"DeadLetterConfig" (DeadLetterConfigProperty -> (Key, Value))
-> Maybe DeadLetterConfigProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe DeadLetterConfigProperty
deadLetterConfig,
                  Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Description" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
description,
                  Key -> EnvironmentProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Environment" (EnvironmentProperty -> (Key, Value))
-> Maybe EnvironmentProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe EnvironmentProperty
environment,
                  Key -> EphemeralStorageProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"EphemeralStorage" (EphemeralStorageProperty -> (Key, Value))
-> Maybe EphemeralStorageProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe EphemeralStorageProperty
ephemeralStorage,
                  Key -> [FileSystemConfigProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"FileSystemConfigs" ([FileSystemConfigProperty] -> (Key, Value))
-> Maybe [FileSystemConfigProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [FileSystemConfigProperty]
fileSystemConfigs,
                  Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"FunctionName" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
functionName,
                  Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Handler" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
handler,
                  Key -> ImageConfigProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ImageConfig" (ImageConfigProperty -> (Key, Value))
-> Maybe ImageConfigProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ImageConfigProperty
imageConfig,
                  Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"KmsKeyArn" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
kmsKeyArn,
                  Key -> ValueList Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Layers" (ValueList Text -> (Key, Value))
-> Maybe (ValueList Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (ValueList Text)
layers,
                  Key -> LoggingConfigProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"LoggingConfig" (LoggingConfigProperty -> (Key, Value))
-> Maybe LoggingConfigProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe LoggingConfigProperty
loggingConfig,
                  Key -> Value Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"MemorySize" (Value Integer -> (Key, Value))
-> Maybe (Value Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Integer)
memorySize,
                  Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"PackageType" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
packageType,
                  Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"RecursiveLoop" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
recursiveLoop,
                  Key -> Value Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ReservedConcurrentExecutions"
                    (Value Integer -> (Key, Value))
-> Maybe (Value Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Integer)
reservedConcurrentExecutions,
                  Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Runtime" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
runtime,
                  Key -> RuntimeManagementConfigProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"RuntimeManagementConfig"
                    (RuntimeManagementConfigProperty -> (Key, Value))
-> Maybe RuntimeManagementConfigProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe RuntimeManagementConfigProperty
runtimeManagementConfig,
                  Key -> SnapStartProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"SnapStart" (SnapStartProperty -> (Key, Value))
-> Maybe SnapStartProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe SnapStartProperty
snapStart,
                  Key -> [Tag] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Tags" ([Tag] -> (Key, Value)) -> Maybe [Tag] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Tag]
tags,
                  Key -> Value Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Timeout" (Value Integer -> (Key, Value))
-> Maybe (Value Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Integer)
timeout,
                  Key -> TracingConfigProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"TracingConfig" (TracingConfigProperty -> (Key, Value))
-> Maybe TracingConfigProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe TracingConfigProperty
tracingConfig,
                  Key -> VpcConfigProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"VpcConfig" (VpcConfigProperty -> (Key, Value))
-> Maybe VpcConfigProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe VpcConfigProperty
vpcConfig])))
instance Property "Architectures" Function where
  type PropertyType "Architectures" Function = ValueList Prelude.Text
  set :: PropertyType "Architectures" Function -> Function -> Function
set PropertyType "Architectures" Function
newValue Function {Maybe [Tag]
Maybe [FileSystemConfigProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeadLetterConfigProperty
Maybe EnvironmentProperty
Maybe EphemeralStorageProperty
Maybe ImageConfigProperty
Maybe LoggingConfigProperty
Maybe RuntimeManagementConfigProperty
Maybe SnapStartProperty
Maybe TracingConfigProperty
Maybe VpcConfigProperty
()
Value Text
CodeProperty
haddock_workaround_ :: Function -> ()
architectures :: Function -> Maybe (ValueList Text)
code :: Function -> CodeProperty
codeSigningConfigArn :: Function -> Maybe (Value Text)
deadLetterConfig :: Function -> Maybe DeadLetterConfigProperty
description :: Function -> Maybe (Value Text)
environment :: Function -> Maybe EnvironmentProperty
ephemeralStorage :: Function -> Maybe EphemeralStorageProperty
fileSystemConfigs :: Function -> Maybe [FileSystemConfigProperty]
functionName :: Function -> Maybe (Value Text)
handler :: Function -> Maybe (Value Text)
imageConfig :: Function -> Maybe ImageConfigProperty
kmsKeyArn :: Function -> Maybe (Value Text)
layers :: Function -> Maybe (ValueList Text)
loggingConfig :: Function -> Maybe LoggingConfigProperty
memorySize :: Function -> Maybe (Value Integer)
packageType :: Function -> Maybe (Value Text)
recursiveLoop :: Function -> Maybe (Value Text)
reservedConcurrentExecutions :: Function -> Maybe (Value Integer)
role :: Function -> Value Text
runtime :: Function -> Maybe (Value Text)
runtimeManagementConfig :: Function -> Maybe RuntimeManagementConfigProperty
snapStart :: Function -> Maybe SnapStartProperty
tags :: Function -> Maybe [Tag]
timeout :: Function -> Maybe (Value Integer)
tracingConfig :: Function -> Maybe TracingConfigProperty
vpcConfig :: Function -> Maybe VpcConfigProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
..}
    = Function {architectures :: Maybe (ValueList Text)
architectures = ValueList Text -> Maybe (ValueList Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "Architectures" Function
ValueList Text
newValue, Maybe [Tag]
Maybe [FileSystemConfigProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeadLetterConfigProperty
Maybe EnvironmentProperty
Maybe EphemeralStorageProperty
Maybe ImageConfigProperty
Maybe LoggingConfigProperty
Maybe RuntimeManagementConfigProperty
Maybe SnapStartProperty
Maybe TracingConfigProperty
Maybe VpcConfigProperty
()
Value Text
CodeProperty
haddock_workaround_ :: ()
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
haddock_workaround_ :: ()
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
..}
instance Property "Code" Function where
  type PropertyType "Code" Function = CodeProperty
  set :: PropertyType "Code" Function -> Function -> Function
set PropertyType "Code" Function
newValue Function {Maybe [Tag]
Maybe [FileSystemConfigProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeadLetterConfigProperty
Maybe EnvironmentProperty
Maybe EphemeralStorageProperty
Maybe ImageConfigProperty
Maybe LoggingConfigProperty
Maybe RuntimeManagementConfigProperty
Maybe SnapStartProperty
Maybe TracingConfigProperty
Maybe VpcConfigProperty
()
Value Text
CodeProperty
haddock_workaround_ :: Function -> ()
architectures :: Function -> Maybe (ValueList Text)
code :: Function -> CodeProperty
codeSigningConfigArn :: Function -> Maybe (Value Text)
deadLetterConfig :: Function -> Maybe DeadLetterConfigProperty
description :: Function -> Maybe (Value Text)
environment :: Function -> Maybe EnvironmentProperty
ephemeralStorage :: Function -> Maybe EphemeralStorageProperty
fileSystemConfigs :: Function -> Maybe [FileSystemConfigProperty]
functionName :: Function -> Maybe (Value Text)
handler :: Function -> Maybe (Value Text)
imageConfig :: Function -> Maybe ImageConfigProperty
kmsKeyArn :: Function -> Maybe (Value Text)
layers :: Function -> Maybe (ValueList Text)
loggingConfig :: Function -> Maybe LoggingConfigProperty
memorySize :: Function -> Maybe (Value Integer)
packageType :: Function -> Maybe (Value Text)
recursiveLoop :: Function -> Maybe (Value Text)
reservedConcurrentExecutions :: Function -> Maybe (Value Integer)
role :: Function -> Value Text
runtime :: Function -> Maybe (Value Text)
runtimeManagementConfig :: Function -> Maybe RuntimeManagementConfigProperty
snapStart :: Function -> Maybe SnapStartProperty
tags :: Function -> Maybe [Tag]
timeout :: Function -> Maybe (Value Integer)
tracingConfig :: Function -> Maybe TracingConfigProperty
vpcConfig :: Function -> Maybe VpcConfigProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
..} = Function {code :: CodeProperty
code = PropertyType "Code" Function
CodeProperty
newValue, Maybe [Tag]
Maybe [FileSystemConfigProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeadLetterConfigProperty
Maybe EnvironmentProperty
Maybe EphemeralStorageProperty
Maybe ImageConfigProperty
Maybe LoggingConfigProperty
Maybe RuntimeManagementConfigProperty
Maybe SnapStartProperty
Maybe TracingConfigProperty
Maybe VpcConfigProperty
()
Value Text
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
..}
instance Property "CodeSigningConfigArn" Function where
  type PropertyType "CodeSigningConfigArn" Function = Value Prelude.Text
  set :: PropertyType "CodeSigningConfigArn" Function
-> Function -> Function
set PropertyType "CodeSigningConfigArn" Function
newValue Function {Maybe [Tag]
Maybe [FileSystemConfigProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeadLetterConfigProperty
Maybe EnvironmentProperty
Maybe EphemeralStorageProperty
Maybe ImageConfigProperty
Maybe LoggingConfigProperty
Maybe RuntimeManagementConfigProperty
Maybe SnapStartProperty
Maybe TracingConfigProperty
Maybe VpcConfigProperty
()
Value Text
CodeProperty
haddock_workaround_ :: Function -> ()
architectures :: Function -> Maybe (ValueList Text)
code :: Function -> CodeProperty
codeSigningConfigArn :: Function -> Maybe (Value Text)
deadLetterConfig :: Function -> Maybe DeadLetterConfigProperty
description :: Function -> Maybe (Value Text)
environment :: Function -> Maybe EnvironmentProperty
ephemeralStorage :: Function -> Maybe EphemeralStorageProperty
fileSystemConfigs :: Function -> Maybe [FileSystemConfigProperty]
functionName :: Function -> Maybe (Value Text)
handler :: Function -> Maybe (Value Text)
imageConfig :: Function -> Maybe ImageConfigProperty
kmsKeyArn :: Function -> Maybe (Value Text)
layers :: Function -> Maybe (ValueList Text)
loggingConfig :: Function -> Maybe LoggingConfigProperty
memorySize :: Function -> Maybe (Value Integer)
packageType :: Function -> Maybe (Value Text)
recursiveLoop :: Function -> Maybe (Value Text)
reservedConcurrentExecutions :: Function -> Maybe (Value Integer)
role :: Function -> Value Text
runtime :: Function -> Maybe (Value Text)
runtimeManagementConfig :: Function -> Maybe RuntimeManagementConfigProperty
snapStart :: Function -> Maybe SnapStartProperty
tags :: Function -> Maybe [Tag]
timeout :: Function -> Maybe (Value Integer)
tracingConfig :: Function -> Maybe TracingConfigProperty
vpcConfig :: Function -> Maybe VpcConfigProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
..}
    = Function {codeSigningConfigArn :: Maybe (Value Text)
codeSigningConfigArn = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "CodeSigningConfigArn" Function
Value Text
newValue, Maybe [Tag]
Maybe [FileSystemConfigProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeadLetterConfigProperty
Maybe EnvironmentProperty
Maybe EphemeralStorageProperty
Maybe ImageConfigProperty
Maybe LoggingConfigProperty
Maybe RuntimeManagementConfigProperty
Maybe SnapStartProperty
Maybe TracingConfigProperty
Maybe VpcConfigProperty
()
Value Text
CodeProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
..}
instance Property "DeadLetterConfig" Function where
  type PropertyType "DeadLetterConfig" Function = DeadLetterConfigProperty
  set :: PropertyType "DeadLetterConfig" Function -> Function -> Function
set PropertyType "DeadLetterConfig" Function
newValue Function {Maybe [Tag]
Maybe [FileSystemConfigProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeadLetterConfigProperty
Maybe EnvironmentProperty
Maybe EphemeralStorageProperty
Maybe ImageConfigProperty
Maybe LoggingConfigProperty
Maybe RuntimeManagementConfigProperty
Maybe SnapStartProperty
Maybe TracingConfigProperty
Maybe VpcConfigProperty
()
Value Text
CodeProperty
haddock_workaround_ :: Function -> ()
architectures :: Function -> Maybe (ValueList Text)
code :: Function -> CodeProperty
codeSigningConfigArn :: Function -> Maybe (Value Text)
deadLetterConfig :: Function -> Maybe DeadLetterConfigProperty
description :: Function -> Maybe (Value Text)
environment :: Function -> Maybe EnvironmentProperty
ephemeralStorage :: Function -> Maybe EphemeralStorageProperty
fileSystemConfigs :: Function -> Maybe [FileSystemConfigProperty]
functionName :: Function -> Maybe (Value Text)
handler :: Function -> Maybe (Value Text)
imageConfig :: Function -> Maybe ImageConfigProperty
kmsKeyArn :: Function -> Maybe (Value Text)
layers :: Function -> Maybe (ValueList Text)
loggingConfig :: Function -> Maybe LoggingConfigProperty
memorySize :: Function -> Maybe (Value Integer)
packageType :: Function -> Maybe (Value Text)
recursiveLoop :: Function -> Maybe (Value Text)
reservedConcurrentExecutions :: Function -> Maybe (Value Integer)
role :: Function -> Value Text
runtime :: Function -> Maybe (Value Text)
runtimeManagementConfig :: Function -> Maybe RuntimeManagementConfigProperty
snapStart :: Function -> Maybe SnapStartProperty
tags :: Function -> Maybe [Tag]
timeout :: Function -> Maybe (Value Integer)
tracingConfig :: Function -> Maybe TracingConfigProperty
vpcConfig :: Function -> Maybe VpcConfigProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
..}
    = Function {deadLetterConfig :: Maybe DeadLetterConfigProperty
deadLetterConfig = DeadLetterConfigProperty -> Maybe DeadLetterConfigProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "DeadLetterConfig" Function
DeadLetterConfigProperty
newValue, Maybe [Tag]
Maybe [FileSystemConfigProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe EnvironmentProperty
Maybe EphemeralStorageProperty
Maybe ImageConfigProperty
Maybe LoggingConfigProperty
Maybe RuntimeManagementConfigProperty
Maybe SnapStartProperty
Maybe TracingConfigProperty
Maybe VpcConfigProperty
()
Value Text
CodeProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
..}
instance Property "Description" Function where
  type PropertyType "Description" Function = Value Prelude.Text
  set :: PropertyType "Description" Function -> Function -> Function
set PropertyType "Description" Function
newValue Function {Maybe [Tag]
Maybe [FileSystemConfigProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeadLetterConfigProperty
Maybe EnvironmentProperty
Maybe EphemeralStorageProperty
Maybe ImageConfigProperty
Maybe LoggingConfigProperty
Maybe RuntimeManagementConfigProperty
Maybe SnapStartProperty
Maybe TracingConfigProperty
Maybe VpcConfigProperty
()
Value Text
CodeProperty
haddock_workaround_ :: Function -> ()
architectures :: Function -> Maybe (ValueList Text)
code :: Function -> CodeProperty
codeSigningConfigArn :: Function -> Maybe (Value Text)
deadLetterConfig :: Function -> Maybe DeadLetterConfigProperty
description :: Function -> Maybe (Value Text)
environment :: Function -> Maybe EnvironmentProperty
ephemeralStorage :: Function -> Maybe EphemeralStorageProperty
fileSystemConfigs :: Function -> Maybe [FileSystemConfigProperty]
functionName :: Function -> Maybe (Value Text)
handler :: Function -> Maybe (Value Text)
imageConfig :: Function -> Maybe ImageConfigProperty
kmsKeyArn :: Function -> Maybe (Value Text)
layers :: Function -> Maybe (ValueList Text)
loggingConfig :: Function -> Maybe LoggingConfigProperty
memorySize :: Function -> Maybe (Value Integer)
packageType :: Function -> Maybe (Value Text)
recursiveLoop :: Function -> Maybe (Value Text)
reservedConcurrentExecutions :: Function -> Maybe (Value Integer)
role :: Function -> Value Text
runtime :: Function -> Maybe (Value Text)
runtimeManagementConfig :: Function -> Maybe RuntimeManagementConfigProperty
snapStart :: Function -> Maybe SnapStartProperty
tags :: Function -> Maybe [Tag]
timeout :: Function -> Maybe (Value Integer)
tracingConfig :: Function -> Maybe TracingConfigProperty
vpcConfig :: Function -> Maybe VpcConfigProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
..}
    = Function {description :: Maybe (Value Text)
description = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "Description" Function
Value Text
newValue, Maybe [Tag]
Maybe [FileSystemConfigProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeadLetterConfigProperty
Maybe EnvironmentProperty
Maybe EphemeralStorageProperty
Maybe ImageConfigProperty
Maybe LoggingConfigProperty
Maybe RuntimeManagementConfigProperty
Maybe SnapStartProperty
Maybe TracingConfigProperty
Maybe VpcConfigProperty
()
Value Text
CodeProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
..}
instance Property "Environment" Function where
  type PropertyType "Environment" Function = EnvironmentProperty
  set :: PropertyType "Environment" Function -> Function -> Function
set PropertyType "Environment" Function
newValue Function {Maybe [Tag]
Maybe [FileSystemConfigProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeadLetterConfigProperty
Maybe EnvironmentProperty
Maybe EphemeralStorageProperty
Maybe ImageConfigProperty
Maybe LoggingConfigProperty
Maybe RuntimeManagementConfigProperty
Maybe SnapStartProperty
Maybe TracingConfigProperty
Maybe VpcConfigProperty
()
Value Text
CodeProperty
haddock_workaround_ :: Function -> ()
architectures :: Function -> Maybe (ValueList Text)
code :: Function -> CodeProperty
codeSigningConfigArn :: Function -> Maybe (Value Text)
deadLetterConfig :: Function -> Maybe DeadLetterConfigProperty
description :: Function -> Maybe (Value Text)
environment :: Function -> Maybe EnvironmentProperty
ephemeralStorage :: Function -> Maybe EphemeralStorageProperty
fileSystemConfigs :: Function -> Maybe [FileSystemConfigProperty]
functionName :: Function -> Maybe (Value Text)
handler :: Function -> Maybe (Value Text)
imageConfig :: Function -> Maybe ImageConfigProperty
kmsKeyArn :: Function -> Maybe (Value Text)
layers :: Function -> Maybe (ValueList Text)
loggingConfig :: Function -> Maybe LoggingConfigProperty
memorySize :: Function -> Maybe (Value Integer)
packageType :: Function -> Maybe (Value Text)
recursiveLoop :: Function -> Maybe (Value Text)
reservedConcurrentExecutions :: Function -> Maybe (Value Integer)
role :: Function -> Value Text
runtime :: Function -> Maybe (Value Text)
runtimeManagementConfig :: Function -> Maybe RuntimeManagementConfigProperty
snapStart :: Function -> Maybe SnapStartProperty
tags :: Function -> Maybe [Tag]
timeout :: Function -> Maybe (Value Integer)
tracingConfig :: Function -> Maybe TracingConfigProperty
vpcConfig :: Function -> Maybe VpcConfigProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
..}
    = Function {environment :: Maybe EnvironmentProperty
environment = EnvironmentProperty -> Maybe EnvironmentProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "Environment" Function
EnvironmentProperty
newValue, Maybe [Tag]
Maybe [FileSystemConfigProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeadLetterConfigProperty
Maybe EphemeralStorageProperty
Maybe ImageConfigProperty
Maybe LoggingConfigProperty
Maybe RuntimeManagementConfigProperty
Maybe SnapStartProperty
Maybe TracingConfigProperty
Maybe VpcConfigProperty
()
Value Text
CodeProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
..}
instance Property "EphemeralStorage" Function where
  type PropertyType "EphemeralStorage" Function = EphemeralStorageProperty
  set :: PropertyType "EphemeralStorage" Function -> Function -> Function
set PropertyType "EphemeralStorage" Function
newValue Function {Maybe [Tag]
Maybe [FileSystemConfigProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeadLetterConfigProperty
Maybe EnvironmentProperty
Maybe EphemeralStorageProperty
Maybe ImageConfigProperty
Maybe LoggingConfigProperty
Maybe RuntimeManagementConfigProperty
Maybe SnapStartProperty
Maybe TracingConfigProperty
Maybe VpcConfigProperty
()
Value Text
CodeProperty
haddock_workaround_ :: Function -> ()
architectures :: Function -> Maybe (ValueList Text)
code :: Function -> CodeProperty
codeSigningConfigArn :: Function -> Maybe (Value Text)
deadLetterConfig :: Function -> Maybe DeadLetterConfigProperty
description :: Function -> Maybe (Value Text)
environment :: Function -> Maybe EnvironmentProperty
ephemeralStorage :: Function -> Maybe EphemeralStorageProperty
fileSystemConfigs :: Function -> Maybe [FileSystemConfigProperty]
functionName :: Function -> Maybe (Value Text)
handler :: Function -> Maybe (Value Text)
imageConfig :: Function -> Maybe ImageConfigProperty
kmsKeyArn :: Function -> Maybe (Value Text)
layers :: Function -> Maybe (ValueList Text)
loggingConfig :: Function -> Maybe LoggingConfigProperty
memorySize :: Function -> Maybe (Value Integer)
packageType :: Function -> Maybe (Value Text)
recursiveLoop :: Function -> Maybe (Value Text)
reservedConcurrentExecutions :: Function -> Maybe (Value Integer)
role :: Function -> Value Text
runtime :: Function -> Maybe (Value Text)
runtimeManagementConfig :: Function -> Maybe RuntimeManagementConfigProperty
snapStart :: Function -> Maybe SnapStartProperty
tags :: Function -> Maybe [Tag]
timeout :: Function -> Maybe (Value Integer)
tracingConfig :: Function -> Maybe TracingConfigProperty
vpcConfig :: Function -> Maybe VpcConfigProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
..}
    = Function {ephemeralStorage :: Maybe EphemeralStorageProperty
ephemeralStorage = EphemeralStorageProperty -> Maybe EphemeralStorageProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "EphemeralStorage" Function
EphemeralStorageProperty
newValue, Maybe [Tag]
Maybe [FileSystemConfigProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeadLetterConfigProperty
Maybe EnvironmentProperty
Maybe ImageConfigProperty
Maybe LoggingConfigProperty
Maybe RuntimeManagementConfigProperty
Maybe SnapStartProperty
Maybe TracingConfigProperty
Maybe VpcConfigProperty
()
Value Text
CodeProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
..}
instance Property "FileSystemConfigs" Function where
  type PropertyType "FileSystemConfigs" Function = [FileSystemConfigProperty]
  set :: PropertyType "FileSystemConfigs" Function -> Function -> Function
set PropertyType "FileSystemConfigs" Function
newValue Function {Maybe [Tag]
Maybe [FileSystemConfigProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeadLetterConfigProperty
Maybe EnvironmentProperty
Maybe EphemeralStorageProperty
Maybe ImageConfigProperty
Maybe LoggingConfigProperty
Maybe RuntimeManagementConfigProperty
Maybe SnapStartProperty
Maybe TracingConfigProperty
Maybe VpcConfigProperty
()
Value Text
CodeProperty
haddock_workaround_ :: Function -> ()
architectures :: Function -> Maybe (ValueList Text)
code :: Function -> CodeProperty
codeSigningConfigArn :: Function -> Maybe (Value Text)
deadLetterConfig :: Function -> Maybe DeadLetterConfigProperty
description :: Function -> Maybe (Value Text)
environment :: Function -> Maybe EnvironmentProperty
ephemeralStorage :: Function -> Maybe EphemeralStorageProperty
fileSystemConfigs :: Function -> Maybe [FileSystemConfigProperty]
functionName :: Function -> Maybe (Value Text)
handler :: Function -> Maybe (Value Text)
imageConfig :: Function -> Maybe ImageConfigProperty
kmsKeyArn :: Function -> Maybe (Value Text)
layers :: Function -> Maybe (ValueList Text)
loggingConfig :: Function -> Maybe LoggingConfigProperty
memorySize :: Function -> Maybe (Value Integer)
packageType :: Function -> Maybe (Value Text)
recursiveLoop :: Function -> Maybe (Value Text)
reservedConcurrentExecutions :: Function -> Maybe (Value Integer)
role :: Function -> Value Text
runtime :: Function -> Maybe (Value Text)
runtimeManagementConfig :: Function -> Maybe RuntimeManagementConfigProperty
snapStart :: Function -> Maybe SnapStartProperty
tags :: Function -> Maybe [Tag]
timeout :: Function -> Maybe (Value Integer)
tracingConfig :: Function -> Maybe TracingConfigProperty
vpcConfig :: Function -> Maybe VpcConfigProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
..}
    = Function {fileSystemConfigs :: Maybe [FileSystemConfigProperty]
fileSystemConfigs = [FileSystemConfigProperty] -> Maybe [FileSystemConfigProperty]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [FileSystemConfigProperty]
PropertyType "FileSystemConfigs" Function
newValue, Maybe [Tag]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeadLetterConfigProperty
Maybe EnvironmentProperty
Maybe EphemeralStorageProperty
Maybe ImageConfigProperty
Maybe LoggingConfigProperty
Maybe RuntimeManagementConfigProperty
Maybe SnapStartProperty
Maybe TracingConfigProperty
Maybe VpcConfigProperty
()
Value Text
CodeProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
..}
instance Property "FunctionName" Function where
  type PropertyType "FunctionName" Function = Value Prelude.Text
  set :: PropertyType "FunctionName" Function -> Function -> Function
set PropertyType "FunctionName" Function
newValue Function {Maybe [Tag]
Maybe [FileSystemConfigProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeadLetterConfigProperty
Maybe EnvironmentProperty
Maybe EphemeralStorageProperty
Maybe ImageConfigProperty
Maybe LoggingConfigProperty
Maybe RuntimeManagementConfigProperty
Maybe SnapStartProperty
Maybe TracingConfigProperty
Maybe VpcConfigProperty
()
Value Text
CodeProperty
haddock_workaround_ :: Function -> ()
architectures :: Function -> Maybe (ValueList Text)
code :: Function -> CodeProperty
codeSigningConfigArn :: Function -> Maybe (Value Text)
deadLetterConfig :: Function -> Maybe DeadLetterConfigProperty
description :: Function -> Maybe (Value Text)
environment :: Function -> Maybe EnvironmentProperty
ephemeralStorage :: Function -> Maybe EphemeralStorageProperty
fileSystemConfigs :: Function -> Maybe [FileSystemConfigProperty]
functionName :: Function -> Maybe (Value Text)
handler :: Function -> Maybe (Value Text)
imageConfig :: Function -> Maybe ImageConfigProperty
kmsKeyArn :: Function -> Maybe (Value Text)
layers :: Function -> Maybe (ValueList Text)
loggingConfig :: Function -> Maybe LoggingConfigProperty
memorySize :: Function -> Maybe (Value Integer)
packageType :: Function -> Maybe (Value Text)
recursiveLoop :: Function -> Maybe (Value Text)
reservedConcurrentExecutions :: Function -> Maybe (Value Integer)
role :: Function -> Value Text
runtime :: Function -> Maybe (Value Text)
runtimeManagementConfig :: Function -> Maybe RuntimeManagementConfigProperty
snapStart :: Function -> Maybe SnapStartProperty
tags :: Function -> Maybe [Tag]
timeout :: Function -> Maybe (Value Integer)
tracingConfig :: Function -> Maybe TracingConfigProperty
vpcConfig :: Function -> Maybe VpcConfigProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
..}
    = Function {functionName :: Maybe (Value Text)
functionName = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "FunctionName" Function
Value Text
newValue, Maybe [Tag]
Maybe [FileSystemConfigProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeadLetterConfigProperty
Maybe EnvironmentProperty
Maybe EphemeralStorageProperty
Maybe ImageConfigProperty
Maybe LoggingConfigProperty
Maybe RuntimeManagementConfigProperty
Maybe SnapStartProperty
Maybe TracingConfigProperty
Maybe VpcConfigProperty
()
Value Text
CodeProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
..}
instance Property "Handler" Function where
  type PropertyType "Handler" Function = Value Prelude.Text
  set :: PropertyType "Handler" Function -> Function -> Function
set PropertyType "Handler" Function
newValue Function {Maybe [Tag]
Maybe [FileSystemConfigProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeadLetterConfigProperty
Maybe EnvironmentProperty
Maybe EphemeralStorageProperty
Maybe ImageConfigProperty
Maybe LoggingConfigProperty
Maybe RuntimeManagementConfigProperty
Maybe SnapStartProperty
Maybe TracingConfigProperty
Maybe VpcConfigProperty
()
Value Text
CodeProperty
haddock_workaround_ :: Function -> ()
architectures :: Function -> Maybe (ValueList Text)
code :: Function -> CodeProperty
codeSigningConfigArn :: Function -> Maybe (Value Text)
deadLetterConfig :: Function -> Maybe DeadLetterConfigProperty
description :: Function -> Maybe (Value Text)
environment :: Function -> Maybe EnvironmentProperty
ephemeralStorage :: Function -> Maybe EphemeralStorageProperty
fileSystemConfigs :: Function -> Maybe [FileSystemConfigProperty]
functionName :: Function -> Maybe (Value Text)
handler :: Function -> Maybe (Value Text)
imageConfig :: Function -> Maybe ImageConfigProperty
kmsKeyArn :: Function -> Maybe (Value Text)
layers :: Function -> Maybe (ValueList Text)
loggingConfig :: Function -> Maybe LoggingConfigProperty
memorySize :: Function -> Maybe (Value Integer)
packageType :: Function -> Maybe (Value Text)
recursiveLoop :: Function -> Maybe (Value Text)
reservedConcurrentExecutions :: Function -> Maybe (Value Integer)
role :: Function -> Value Text
runtime :: Function -> Maybe (Value Text)
runtimeManagementConfig :: Function -> Maybe RuntimeManagementConfigProperty
snapStart :: Function -> Maybe SnapStartProperty
tags :: Function -> Maybe [Tag]
timeout :: Function -> Maybe (Value Integer)
tracingConfig :: Function -> Maybe TracingConfigProperty
vpcConfig :: Function -> Maybe VpcConfigProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
..}
    = Function {handler :: Maybe (Value Text)
handler = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "Handler" Function
Value Text
newValue, Maybe [Tag]
Maybe [FileSystemConfigProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeadLetterConfigProperty
Maybe EnvironmentProperty
Maybe EphemeralStorageProperty
Maybe ImageConfigProperty
Maybe LoggingConfigProperty
Maybe RuntimeManagementConfigProperty
Maybe SnapStartProperty
Maybe TracingConfigProperty
Maybe VpcConfigProperty
()
Value Text
CodeProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
..}
instance Property "ImageConfig" Function where
  type PropertyType "ImageConfig" Function = ImageConfigProperty
  set :: PropertyType "ImageConfig" Function -> Function -> Function
set PropertyType "ImageConfig" Function
newValue Function {Maybe [Tag]
Maybe [FileSystemConfigProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeadLetterConfigProperty
Maybe EnvironmentProperty
Maybe EphemeralStorageProperty
Maybe ImageConfigProperty
Maybe LoggingConfigProperty
Maybe RuntimeManagementConfigProperty
Maybe SnapStartProperty
Maybe TracingConfigProperty
Maybe VpcConfigProperty
()
Value Text
CodeProperty
haddock_workaround_ :: Function -> ()
architectures :: Function -> Maybe (ValueList Text)
code :: Function -> CodeProperty
codeSigningConfigArn :: Function -> Maybe (Value Text)
deadLetterConfig :: Function -> Maybe DeadLetterConfigProperty
description :: Function -> Maybe (Value Text)
environment :: Function -> Maybe EnvironmentProperty
ephemeralStorage :: Function -> Maybe EphemeralStorageProperty
fileSystemConfigs :: Function -> Maybe [FileSystemConfigProperty]
functionName :: Function -> Maybe (Value Text)
handler :: Function -> Maybe (Value Text)
imageConfig :: Function -> Maybe ImageConfigProperty
kmsKeyArn :: Function -> Maybe (Value Text)
layers :: Function -> Maybe (ValueList Text)
loggingConfig :: Function -> Maybe LoggingConfigProperty
memorySize :: Function -> Maybe (Value Integer)
packageType :: Function -> Maybe (Value Text)
recursiveLoop :: Function -> Maybe (Value Text)
reservedConcurrentExecutions :: Function -> Maybe (Value Integer)
role :: Function -> Value Text
runtime :: Function -> Maybe (Value Text)
runtimeManagementConfig :: Function -> Maybe RuntimeManagementConfigProperty
snapStart :: Function -> Maybe SnapStartProperty
tags :: Function -> Maybe [Tag]
timeout :: Function -> Maybe (Value Integer)
tracingConfig :: Function -> Maybe TracingConfigProperty
vpcConfig :: Function -> Maybe VpcConfigProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
..}
    = Function {imageConfig :: Maybe ImageConfigProperty
imageConfig = ImageConfigProperty -> Maybe ImageConfigProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "ImageConfig" Function
ImageConfigProperty
newValue, Maybe [Tag]
Maybe [FileSystemConfigProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeadLetterConfigProperty
Maybe EnvironmentProperty
Maybe EphemeralStorageProperty
Maybe LoggingConfigProperty
Maybe RuntimeManagementConfigProperty
Maybe SnapStartProperty
Maybe TracingConfigProperty
Maybe VpcConfigProperty
()
Value Text
CodeProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
..}
instance Property "KmsKeyArn" Function where
  type PropertyType "KmsKeyArn" Function = Value Prelude.Text
  set :: PropertyType "KmsKeyArn" Function -> Function -> Function
set PropertyType "KmsKeyArn" Function
newValue Function {Maybe [Tag]
Maybe [FileSystemConfigProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeadLetterConfigProperty
Maybe EnvironmentProperty
Maybe EphemeralStorageProperty
Maybe ImageConfigProperty
Maybe LoggingConfigProperty
Maybe RuntimeManagementConfigProperty
Maybe SnapStartProperty
Maybe TracingConfigProperty
Maybe VpcConfigProperty
()
Value Text
CodeProperty
haddock_workaround_ :: Function -> ()
architectures :: Function -> Maybe (ValueList Text)
code :: Function -> CodeProperty
codeSigningConfigArn :: Function -> Maybe (Value Text)
deadLetterConfig :: Function -> Maybe DeadLetterConfigProperty
description :: Function -> Maybe (Value Text)
environment :: Function -> Maybe EnvironmentProperty
ephemeralStorage :: Function -> Maybe EphemeralStorageProperty
fileSystemConfigs :: Function -> Maybe [FileSystemConfigProperty]
functionName :: Function -> Maybe (Value Text)
handler :: Function -> Maybe (Value Text)
imageConfig :: Function -> Maybe ImageConfigProperty
kmsKeyArn :: Function -> Maybe (Value Text)
layers :: Function -> Maybe (ValueList Text)
loggingConfig :: Function -> Maybe LoggingConfigProperty
memorySize :: Function -> Maybe (Value Integer)
packageType :: Function -> Maybe (Value Text)
recursiveLoop :: Function -> Maybe (Value Text)
reservedConcurrentExecutions :: Function -> Maybe (Value Integer)
role :: Function -> Value Text
runtime :: Function -> Maybe (Value Text)
runtimeManagementConfig :: Function -> Maybe RuntimeManagementConfigProperty
snapStart :: Function -> Maybe SnapStartProperty
tags :: Function -> Maybe [Tag]
timeout :: Function -> Maybe (Value Integer)
tracingConfig :: Function -> Maybe TracingConfigProperty
vpcConfig :: Function -> Maybe VpcConfigProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
..}
    = Function {kmsKeyArn :: Maybe (Value Text)
kmsKeyArn = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "KmsKeyArn" Function
Value Text
newValue, Maybe [Tag]
Maybe [FileSystemConfigProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeadLetterConfigProperty
Maybe EnvironmentProperty
Maybe EphemeralStorageProperty
Maybe ImageConfigProperty
Maybe LoggingConfigProperty
Maybe RuntimeManagementConfigProperty
Maybe SnapStartProperty
Maybe TracingConfigProperty
Maybe VpcConfigProperty
()
Value Text
CodeProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
..}
instance Property "Layers" Function where
  type PropertyType "Layers" Function = ValueList Prelude.Text
  set :: PropertyType "Layers" Function -> Function -> Function
set PropertyType "Layers" Function
newValue Function {Maybe [Tag]
Maybe [FileSystemConfigProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeadLetterConfigProperty
Maybe EnvironmentProperty
Maybe EphemeralStorageProperty
Maybe ImageConfigProperty
Maybe LoggingConfigProperty
Maybe RuntimeManagementConfigProperty
Maybe SnapStartProperty
Maybe TracingConfigProperty
Maybe VpcConfigProperty
()
Value Text
CodeProperty
haddock_workaround_ :: Function -> ()
architectures :: Function -> Maybe (ValueList Text)
code :: Function -> CodeProperty
codeSigningConfigArn :: Function -> Maybe (Value Text)
deadLetterConfig :: Function -> Maybe DeadLetterConfigProperty
description :: Function -> Maybe (Value Text)
environment :: Function -> Maybe EnvironmentProperty
ephemeralStorage :: Function -> Maybe EphemeralStorageProperty
fileSystemConfigs :: Function -> Maybe [FileSystemConfigProperty]
functionName :: Function -> Maybe (Value Text)
handler :: Function -> Maybe (Value Text)
imageConfig :: Function -> Maybe ImageConfigProperty
kmsKeyArn :: Function -> Maybe (Value Text)
layers :: Function -> Maybe (ValueList Text)
loggingConfig :: Function -> Maybe LoggingConfigProperty
memorySize :: Function -> Maybe (Value Integer)
packageType :: Function -> Maybe (Value Text)
recursiveLoop :: Function -> Maybe (Value Text)
reservedConcurrentExecutions :: Function -> Maybe (Value Integer)
role :: Function -> Value Text
runtime :: Function -> Maybe (Value Text)
runtimeManagementConfig :: Function -> Maybe RuntimeManagementConfigProperty
snapStart :: Function -> Maybe SnapStartProperty
tags :: Function -> Maybe [Tag]
timeout :: Function -> Maybe (Value Integer)
tracingConfig :: Function -> Maybe TracingConfigProperty
vpcConfig :: Function -> Maybe VpcConfigProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
..}
    = Function {layers :: Maybe (ValueList Text)
layers = ValueList Text -> Maybe (ValueList Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "Layers" Function
ValueList Text
newValue, Maybe [Tag]
Maybe [FileSystemConfigProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeadLetterConfigProperty
Maybe EnvironmentProperty
Maybe EphemeralStorageProperty
Maybe ImageConfigProperty
Maybe LoggingConfigProperty
Maybe RuntimeManagementConfigProperty
Maybe SnapStartProperty
Maybe TracingConfigProperty
Maybe VpcConfigProperty
()
Value Text
CodeProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
..}
instance Property "LoggingConfig" Function where
  type PropertyType "LoggingConfig" Function = LoggingConfigProperty
  set :: PropertyType "LoggingConfig" Function -> Function -> Function
set PropertyType "LoggingConfig" Function
newValue Function {Maybe [Tag]
Maybe [FileSystemConfigProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeadLetterConfigProperty
Maybe EnvironmentProperty
Maybe EphemeralStorageProperty
Maybe ImageConfigProperty
Maybe LoggingConfigProperty
Maybe RuntimeManagementConfigProperty
Maybe SnapStartProperty
Maybe TracingConfigProperty
Maybe VpcConfigProperty
()
Value Text
CodeProperty
haddock_workaround_ :: Function -> ()
architectures :: Function -> Maybe (ValueList Text)
code :: Function -> CodeProperty
codeSigningConfigArn :: Function -> Maybe (Value Text)
deadLetterConfig :: Function -> Maybe DeadLetterConfigProperty
description :: Function -> Maybe (Value Text)
environment :: Function -> Maybe EnvironmentProperty
ephemeralStorage :: Function -> Maybe EphemeralStorageProperty
fileSystemConfigs :: Function -> Maybe [FileSystemConfigProperty]
functionName :: Function -> Maybe (Value Text)
handler :: Function -> Maybe (Value Text)
imageConfig :: Function -> Maybe ImageConfigProperty
kmsKeyArn :: Function -> Maybe (Value Text)
layers :: Function -> Maybe (ValueList Text)
loggingConfig :: Function -> Maybe LoggingConfigProperty
memorySize :: Function -> Maybe (Value Integer)
packageType :: Function -> Maybe (Value Text)
recursiveLoop :: Function -> Maybe (Value Text)
reservedConcurrentExecutions :: Function -> Maybe (Value Integer)
role :: Function -> Value Text
runtime :: Function -> Maybe (Value Text)
runtimeManagementConfig :: Function -> Maybe RuntimeManagementConfigProperty
snapStart :: Function -> Maybe SnapStartProperty
tags :: Function -> Maybe [Tag]
timeout :: Function -> Maybe (Value Integer)
tracingConfig :: Function -> Maybe TracingConfigProperty
vpcConfig :: Function -> Maybe VpcConfigProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
..}
    = Function {loggingConfig :: Maybe LoggingConfigProperty
loggingConfig = LoggingConfigProperty -> Maybe LoggingConfigProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "LoggingConfig" Function
LoggingConfigProperty
newValue, Maybe [Tag]
Maybe [FileSystemConfigProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeadLetterConfigProperty
Maybe EnvironmentProperty
Maybe EphemeralStorageProperty
Maybe ImageConfigProperty
Maybe RuntimeManagementConfigProperty
Maybe SnapStartProperty
Maybe TracingConfigProperty
Maybe VpcConfigProperty
()
Value Text
CodeProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
..}
instance Property "MemorySize" Function where
  type PropertyType "MemorySize" Function = Value Prelude.Integer
  set :: PropertyType "MemorySize" Function -> Function -> Function
set PropertyType "MemorySize" Function
newValue Function {Maybe [Tag]
Maybe [FileSystemConfigProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeadLetterConfigProperty
Maybe EnvironmentProperty
Maybe EphemeralStorageProperty
Maybe ImageConfigProperty
Maybe LoggingConfigProperty
Maybe RuntimeManagementConfigProperty
Maybe SnapStartProperty
Maybe TracingConfigProperty
Maybe VpcConfigProperty
()
Value Text
CodeProperty
haddock_workaround_ :: Function -> ()
architectures :: Function -> Maybe (ValueList Text)
code :: Function -> CodeProperty
codeSigningConfigArn :: Function -> Maybe (Value Text)
deadLetterConfig :: Function -> Maybe DeadLetterConfigProperty
description :: Function -> Maybe (Value Text)
environment :: Function -> Maybe EnvironmentProperty
ephemeralStorage :: Function -> Maybe EphemeralStorageProperty
fileSystemConfigs :: Function -> Maybe [FileSystemConfigProperty]
functionName :: Function -> Maybe (Value Text)
handler :: Function -> Maybe (Value Text)
imageConfig :: Function -> Maybe ImageConfigProperty
kmsKeyArn :: Function -> Maybe (Value Text)
layers :: Function -> Maybe (ValueList Text)
loggingConfig :: Function -> Maybe LoggingConfigProperty
memorySize :: Function -> Maybe (Value Integer)
packageType :: Function -> Maybe (Value Text)
recursiveLoop :: Function -> Maybe (Value Text)
reservedConcurrentExecutions :: Function -> Maybe (Value Integer)
role :: Function -> Value Text
runtime :: Function -> Maybe (Value Text)
runtimeManagementConfig :: Function -> Maybe RuntimeManagementConfigProperty
snapStart :: Function -> Maybe SnapStartProperty
tags :: Function -> Maybe [Tag]
timeout :: Function -> Maybe (Value Integer)
tracingConfig :: Function -> Maybe TracingConfigProperty
vpcConfig :: Function -> Maybe VpcConfigProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
..}
    = Function {memorySize :: Maybe (Value Integer)
memorySize = Value Integer -> Maybe (Value Integer)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "MemorySize" Function
Value Integer
newValue, Maybe [Tag]
Maybe [FileSystemConfigProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeadLetterConfigProperty
Maybe EnvironmentProperty
Maybe EphemeralStorageProperty
Maybe ImageConfigProperty
Maybe LoggingConfigProperty
Maybe RuntimeManagementConfigProperty
Maybe SnapStartProperty
Maybe TracingConfigProperty
Maybe VpcConfigProperty
()
Value Text
CodeProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
..}
instance Property "PackageType" Function where
  type PropertyType "PackageType" Function = Value Prelude.Text
  set :: PropertyType "PackageType" Function -> Function -> Function
set PropertyType "PackageType" Function
newValue Function {Maybe [Tag]
Maybe [FileSystemConfigProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeadLetterConfigProperty
Maybe EnvironmentProperty
Maybe EphemeralStorageProperty
Maybe ImageConfigProperty
Maybe LoggingConfigProperty
Maybe RuntimeManagementConfigProperty
Maybe SnapStartProperty
Maybe TracingConfigProperty
Maybe VpcConfigProperty
()
Value Text
CodeProperty
haddock_workaround_ :: Function -> ()
architectures :: Function -> Maybe (ValueList Text)
code :: Function -> CodeProperty
codeSigningConfigArn :: Function -> Maybe (Value Text)
deadLetterConfig :: Function -> Maybe DeadLetterConfigProperty
description :: Function -> Maybe (Value Text)
environment :: Function -> Maybe EnvironmentProperty
ephemeralStorage :: Function -> Maybe EphemeralStorageProperty
fileSystemConfigs :: Function -> Maybe [FileSystemConfigProperty]
functionName :: Function -> Maybe (Value Text)
handler :: Function -> Maybe (Value Text)
imageConfig :: Function -> Maybe ImageConfigProperty
kmsKeyArn :: Function -> Maybe (Value Text)
layers :: Function -> Maybe (ValueList Text)
loggingConfig :: Function -> Maybe LoggingConfigProperty
memorySize :: Function -> Maybe (Value Integer)
packageType :: Function -> Maybe (Value Text)
recursiveLoop :: Function -> Maybe (Value Text)
reservedConcurrentExecutions :: Function -> Maybe (Value Integer)
role :: Function -> Value Text
runtime :: Function -> Maybe (Value Text)
runtimeManagementConfig :: Function -> Maybe RuntimeManagementConfigProperty
snapStart :: Function -> Maybe SnapStartProperty
tags :: Function -> Maybe [Tag]
timeout :: Function -> Maybe (Value Integer)
tracingConfig :: Function -> Maybe TracingConfigProperty
vpcConfig :: Function -> Maybe VpcConfigProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
..}
    = Function {packageType :: Maybe (Value Text)
packageType = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "PackageType" Function
Value Text
newValue, Maybe [Tag]
Maybe [FileSystemConfigProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeadLetterConfigProperty
Maybe EnvironmentProperty
Maybe EphemeralStorageProperty
Maybe ImageConfigProperty
Maybe LoggingConfigProperty
Maybe RuntimeManagementConfigProperty
Maybe SnapStartProperty
Maybe TracingConfigProperty
Maybe VpcConfigProperty
()
Value Text
CodeProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
..}
instance Property "RecursiveLoop" Function where
  type PropertyType "RecursiveLoop" Function = Value Prelude.Text
  set :: PropertyType "RecursiveLoop" Function -> Function -> Function
set PropertyType "RecursiveLoop" Function
newValue Function {Maybe [Tag]
Maybe [FileSystemConfigProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeadLetterConfigProperty
Maybe EnvironmentProperty
Maybe EphemeralStorageProperty
Maybe ImageConfigProperty
Maybe LoggingConfigProperty
Maybe RuntimeManagementConfigProperty
Maybe SnapStartProperty
Maybe TracingConfigProperty
Maybe VpcConfigProperty
()
Value Text
CodeProperty
haddock_workaround_ :: Function -> ()
architectures :: Function -> Maybe (ValueList Text)
code :: Function -> CodeProperty
codeSigningConfigArn :: Function -> Maybe (Value Text)
deadLetterConfig :: Function -> Maybe DeadLetterConfigProperty
description :: Function -> Maybe (Value Text)
environment :: Function -> Maybe EnvironmentProperty
ephemeralStorage :: Function -> Maybe EphemeralStorageProperty
fileSystemConfigs :: Function -> Maybe [FileSystemConfigProperty]
functionName :: Function -> Maybe (Value Text)
handler :: Function -> Maybe (Value Text)
imageConfig :: Function -> Maybe ImageConfigProperty
kmsKeyArn :: Function -> Maybe (Value Text)
layers :: Function -> Maybe (ValueList Text)
loggingConfig :: Function -> Maybe LoggingConfigProperty
memorySize :: Function -> Maybe (Value Integer)
packageType :: Function -> Maybe (Value Text)
recursiveLoop :: Function -> Maybe (Value Text)
reservedConcurrentExecutions :: Function -> Maybe (Value Integer)
role :: Function -> Value Text
runtime :: Function -> Maybe (Value Text)
runtimeManagementConfig :: Function -> Maybe RuntimeManagementConfigProperty
snapStart :: Function -> Maybe SnapStartProperty
tags :: Function -> Maybe [Tag]
timeout :: Function -> Maybe (Value Integer)
tracingConfig :: Function -> Maybe TracingConfigProperty
vpcConfig :: Function -> Maybe VpcConfigProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
..}
    = Function {recursiveLoop :: Maybe (Value Text)
recursiveLoop = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "RecursiveLoop" Function
Value Text
newValue, Maybe [Tag]
Maybe [FileSystemConfigProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeadLetterConfigProperty
Maybe EnvironmentProperty
Maybe EphemeralStorageProperty
Maybe ImageConfigProperty
Maybe LoggingConfigProperty
Maybe RuntimeManagementConfigProperty
Maybe SnapStartProperty
Maybe TracingConfigProperty
Maybe VpcConfigProperty
()
Value Text
CodeProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
..}
instance Property "ReservedConcurrentExecutions" Function where
  type PropertyType "ReservedConcurrentExecutions" Function = Value Prelude.Integer
  set :: PropertyType "ReservedConcurrentExecutions" Function
-> Function -> Function
set PropertyType "ReservedConcurrentExecutions" Function
newValue Function {Maybe [Tag]
Maybe [FileSystemConfigProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeadLetterConfigProperty
Maybe EnvironmentProperty
Maybe EphemeralStorageProperty
Maybe ImageConfigProperty
Maybe LoggingConfigProperty
Maybe RuntimeManagementConfigProperty
Maybe SnapStartProperty
Maybe TracingConfigProperty
Maybe VpcConfigProperty
()
Value Text
CodeProperty
haddock_workaround_ :: Function -> ()
architectures :: Function -> Maybe (ValueList Text)
code :: Function -> CodeProperty
codeSigningConfigArn :: Function -> Maybe (Value Text)
deadLetterConfig :: Function -> Maybe DeadLetterConfigProperty
description :: Function -> Maybe (Value Text)
environment :: Function -> Maybe EnvironmentProperty
ephemeralStorage :: Function -> Maybe EphemeralStorageProperty
fileSystemConfigs :: Function -> Maybe [FileSystemConfigProperty]
functionName :: Function -> Maybe (Value Text)
handler :: Function -> Maybe (Value Text)
imageConfig :: Function -> Maybe ImageConfigProperty
kmsKeyArn :: Function -> Maybe (Value Text)
layers :: Function -> Maybe (ValueList Text)
loggingConfig :: Function -> Maybe LoggingConfigProperty
memorySize :: Function -> Maybe (Value Integer)
packageType :: Function -> Maybe (Value Text)
recursiveLoop :: Function -> Maybe (Value Text)
reservedConcurrentExecutions :: Function -> Maybe (Value Integer)
role :: Function -> Value Text
runtime :: Function -> Maybe (Value Text)
runtimeManagementConfig :: Function -> Maybe RuntimeManagementConfigProperty
snapStart :: Function -> Maybe SnapStartProperty
tags :: Function -> Maybe [Tag]
timeout :: Function -> Maybe (Value Integer)
tracingConfig :: Function -> Maybe TracingConfigProperty
vpcConfig :: Function -> Maybe VpcConfigProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
..}
    = Function
        {reservedConcurrentExecutions :: Maybe (Value Integer)
reservedConcurrentExecutions = Value Integer -> Maybe (Value Integer)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "ReservedConcurrentExecutions" Function
Value Integer
newValue, Maybe [Tag]
Maybe [FileSystemConfigProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeadLetterConfigProperty
Maybe EnvironmentProperty
Maybe EphemeralStorageProperty
Maybe ImageConfigProperty
Maybe LoggingConfigProperty
Maybe RuntimeManagementConfigProperty
Maybe SnapStartProperty
Maybe TracingConfigProperty
Maybe VpcConfigProperty
()
Value Text
CodeProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
..}
instance Property "Role" Function where
  type PropertyType "Role" Function = Value Prelude.Text
  set :: PropertyType "Role" Function -> Function -> Function
set PropertyType "Role" Function
newValue Function {Maybe [Tag]
Maybe [FileSystemConfigProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeadLetterConfigProperty
Maybe EnvironmentProperty
Maybe EphemeralStorageProperty
Maybe ImageConfigProperty
Maybe LoggingConfigProperty
Maybe RuntimeManagementConfigProperty
Maybe SnapStartProperty
Maybe TracingConfigProperty
Maybe VpcConfigProperty
()
Value Text
CodeProperty
haddock_workaround_ :: Function -> ()
architectures :: Function -> Maybe (ValueList Text)
code :: Function -> CodeProperty
codeSigningConfigArn :: Function -> Maybe (Value Text)
deadLetterConfig :: Function -> Maybe DeadLetterConfigProperty
description :: Function -> Maybe (Value Text)
environment :: Function -> Maybe EnvironmentProperty
ephemeralStorage :: Function -> Maybe EphemeralStorageProperty
fileSystemConfigs :: Function -> Maybe [FileSystemConfigProperty]
functionName :: Function -> Maybe (Value Text)
handler :: Function -> Maybe (Value Text)
imageConfig :: Function -> Maybe ImageConfigProperty
kmsKeyArn :: Function -> Maybe (Value Text)
layers :: Function -> Maybe (ValueList Text)
loggingConfig :: Function -> Maybe LoggingConfigProperty
memorySize :: Function -> Maybe (Value Integer)
packageType :: Function -> Maybe (Value Text)
recursiveLoop :: Function -> Maybe (Value Text)
reservedConcurrentExecutions :: Function -> Maybe (Value Integer)
role :: Function -> Value Text
runtime :: Function -> Maybe (Value Text)
runtimeManagementConfig :: Function -> Maybe RuntimeManagementConfigProperty
snapStart :: Function -> Maybe SnapStartProperty
tags :: Function -> Maybe [Tag]
timeout :: Function -> Maybe (Value Integer)
tracingConfig :: Function -> Maybe TracingConfigProperty
vpcConfig :: Function -> Maybe VpcConfigProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
..} = Function {role :: Value Text
role = PropertyType "Role" Function
Value Text
newValue, Maybe [Tag]
Maybe [FileSystemConfigProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeadLetterConfigProperty
Maybe EnvironmentProperty
Maybe EphemeralStorageProperty
Maybe ImageConfigProperty
Maybe LoggingConfigProperty
Maybe RuntimeManagementConfigProperty
Maybe SnapStartProperty
Maybe TracingConfigProperty
Maybe VpcConfigProperty
()
CodeProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
..}
instance Property "Runtime" Function where
  type PropertyType "Runtime" Function = Value Prelude.Text
  set :: PropertyType "Runtime" Function -> Function -> Function
set PropertyType "Runtime" Function
newValue Function {Maybe [Tag]
Maybe [FileSystemConfigProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeadLetterConfigProperty
Maybe EnvironmentProperty
Maybe EphemeralStorageProperty
Maybe ImageConfigProperty
Maybe LoggingConfigProperty
Maybe RuntimeManagementConfigProperty
Maybe SnapStartProperty
Maybe TracingConfigProperty
Maybe VpcConfigProperty
()
Value Text
CodeProperty
haddock_workaround_ :: Function -> ()
architectures :: Function -> Maybe (ValueList Text)
code :: Function -> CodeProperty
codeSigningConfigArn :: Function -> Maybe (Value Text)
deadLetterConfig :: Function -> Maybe DeadLetterConfigProperty
description :: Function -> Maybe (Value Text)
environment :: Function -> Maybe EnvironmentProperty
ephemeralStorage :: Function -> Maybe EphemeralStorageProperty
fileSystemConfigs :: Function -> Maybe [FileSystemConfigProperty]
functionName :: Function -> Maybe (Value Text)
handler :: Function -> Maybe (Value Text)
imageConfig :: Function -> Maybe ImageConfigProperty
kmsKeyArn :: Function -> Maybe (Value Text)
layers :: Function -> Maybe (ValueList Text)
loggingConfig :: Function -> Maybe LoggingConfigProperty
memorySize :: Function -> Maybe (Value Integer)
packageType :: Function -> Maybe (Value Text)
recursiveLoop :: Function -> Maybe (Value Text)
reservedConcurrentExecutions :: Function -> Maybe (Value Integer)
role :: Function -> Value Text
runtime :: Function -> Maybe (Value Text)
runtimeManagementConfig :: Function -> Maybe RuntimeManagementConfigProperty
snapStart :: Function -> Maybe SnapStartProperty
tags :: Function -> Maybe [Tag]
timeout :: Function -> Maybe (Value Integer)
tracingConfig :: Function -> Maybe TracingConfigProperty
vpcConfig :: Function -> Maybe VpcConfigProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
..}
    = Function {runtime :: Maybe (Value Text)
runtime = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "Runtime" Function
Value Text
newValue, Maybe [Tag]
Maybe [FileSystemConfigProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeadLetterConfigProperty
Maybe EnvironmentProperty
Maybe EphemeralStorageProperty
Maybe ImageConfigProperty
Maybe LoggingConfigProperty
Maybe RuntimeManagementConfigProperty
Maybe SnapStartProperty
Maybe TracingConfigProperty
Maybe VpcConfigProperty
()
Value Text
CodeProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
..}
instance Property "RuntimeManagementConfig" Function where
  type PropertyType "RuntimeManagementConfig" Function = RuntimeManagementConfigProperty
  set :: PropertyType "RuntimeManagementConfig" Function
-> Function -> Function
set PropertyType "RuntimeManagementConfig" Function
newValue Function {Maybe [Tag]
Maybe [FileSystemConfigProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeadLetterConfigProperty
Maybe EnvironmentProperty
Maybe EphemeralStorageProperty
Maybe ImageConfigProperty
Maybe LoggingConfigProperty
Maybe RuntimeManagementConfigProperty
Maybe SnapStartProperty
Maybe TracingConfigProperty
Maybe VpcConfigProperty
()
Value Text
CodeProperty
haddock_workaround_ :: Function -> ()
architectures :: Function -> Maybe (ValueList Text)
code :: Function -> CodeProperty
codeSigningConfigArn :: Function -> Maybe (Value Text)
deadLetterConfig :: Function -> Maybe DeadLetterConfigProperty
description :: Function -> Maybe (Value Text)
environment :: Function -> Maybe EnvironmentProperty
ephemeralStorage :: Function -> Maybe EphemeralStorageProperty
fileSystemConfigs :: Function -> Maybe [FileSystemConfigProperty]
functionName :: Function -> Maybe (Value Text)
handler :: Function -> Maybe (Value Text)
imageConfig :: Function -> Maybe ImageConfigProperty
kmsKeyArn :: Function -> Maybe (Value Text)
layers :: Function -> Maybe (ValueList Text)
loggingConfig :: Function -> Maybe LoggingConfigProperty
memorySize :: Function -> Maybe (Value Integer)
packageType :: Function -> Maybe (Value Text)
recursiveLoop :: Function -> Maybe (Value Text)
reservedConcurrentExecutions :: Function -> Maybe (Value Integer)
role :: Function -> Value Text
runtime :: Function -> Maybe (Value Text)
runtimeManagementConfig :: Function -> Maybe RuntimeManagementConfigProperty
snapStart :: Function -> Maybe SnapStartProperty
tags :: Function -> Maybe [Tag]
timeout :: Function -> Maybe (Value Integer)
tracingConfig :: Function -> Maybe TracingConfigProperty
vpcConfig :: Function -> Maybe VpcConfigProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
..}
    = Function {runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
runtimeManagementConfig = RuntimeManagementConfigProperty
-> Maybe RuntimeManagementConfigProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "RuntimeManagementConfig" Function
RuntimeManagementConfigProperty
newValue, Maybe [Tag]
Maybe [FileSystemConfigProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeadLetterConfigProperty
Maybe EnvironmentProperty
Maybe EphemeralStorageProperty
Maybe ImageConfigProperty
Maybe LoggingConfigProperty
Maybe SnapStartProperty
Maybe TracingConfigProperty
Maybe VpcConfigProperty
()
Value Text
CodeProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
..}
instance Property "SnapStart" Function where
  type PropertyType "SnapStart" Function = SnapStartProperty
  set :: PropertyType "SnapStart" Function -> Function -> Function
set PropertyType "SnapStart" Function
newValue Function {Maybe [Tag]
Maybe [FileSystemConfigProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeadLetterConfigProperty
Maybe EnvironmentProperty
Maybe EphemeralStorageProperty
Maybe ImageConfigProperty
Maybe LoggingConfigProperty
Maybe RuntimeManagementConfigProperty
Maybe SnapStartProperty
Maybe TracingConfigProperty
Maybe VpcConfigProperty
()
Value Text
CodeProperty
haddock_workaround_ :: Function -> ()
architectures :: Function -> Maybe (ValueList Text)
code :: Function -> CodeProperty
codeSigningConfigArn :: Function -> Maybe (Value Text)
deadLetterConfig :: Function -> Maybe DeadLetterConfigProperty
description :: Function -> Maybe (Value Text)
environment :: Function -> Maybe EnvironmentProperty
ephemeralStorage :: Function -> Maybe EphemeralStorageProperty
fileSystemConfigs :: Function -> Maybe [FileSystemConfigProperty]
functionName :: Function -> Maybe (Value Text)
handler :: Function -> Maybe (Value Text)
imageConfig :: Function -> Maybe ImageConfigProperty
kmsKeyArn :: Function -> Maybe (Value Text)
layers :: Function -> Maybe (ValueList Text)
loggingConfig :: Function -> Maybe LoggingConfigProperty
memorySize :: Function -> Maybe (Value Integer)
packageType :: Function -> Maybe (Value Text)
recursiveLoop :: Function -> Maybe (Value Text)
reservedConcurrentExecutions :: Function -> Maybe (Value Integer)
role :: Function -> Value Text
runtime :: Function -> Maybe (Value Text)
runtimeManagementConfig :: Function -> Maybe RuntimeManagementConfigProperty
snapStart :: Function -> Maybe SnapStartProperty
tags :: Function -> Maybe [Tag]
timeout :: Function -> Maybe (Value Integer)
tracingConfig :: Function -> Maybe TracingConfigProperty
vpcConfig :: Function -> Maybe VpcConfigProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
..}
    = Function {snapStart :: Maybe SnapStartProperty
snapStart = SnapStartProperty -> Maybe SnapStartProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "SnapStart" Function
SnapStartProperty
newValue, Maybe [Tag]
Maybe [FileSystemConfigProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeadLetterConfigProperty
Maybe EnvironmentProperty
Maybe EphemeralStorageProperty
Maybe ImageConfigProperty
Maybe LoggingConfigProperty
Maybe RuntimeManagementConfigProperty
Maybe TracingConfigProperty
Maybe VpcConfigProperty
()
Value Text
CodeProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
..}
instance Property "Tags" Function where
  type PropertyType "Tags" Function = [Tag]
  set :: PropertyType "Tags" Function -> Function -> Function
set PropertyType "Tags" Function
newValue Function {Maybe [Tag]
Maybe [FileSystemConfigProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeadLetterConfigProperty
Maybe EnvironmentProperty
Maybe EphemeralStorageProperty
Maybe ImageConfigProperty
Maybe LoggingConfigProperty
Maybe RuntimeManagementConfigProperty
Maybe SnapStartProperty
Maybe TracingConfigProperty
Maybe VpcConfigProperty
()
Value Text
CodeProperty
haddock_workaround_ :: Function -> ()
architectures :: Function -> Maybe (ValueList Text)
code :: Function -> CodeProperty
codeSigningConfigArn :: Function -> Maybe (Value Text)
deadLetterConfig :: Function -> Maybe DeadLetterConfigProperty
description :: Function -> Maybe (Value Text)
environment :: Function -> Maybe EnvironmentProperty
ephemeralStorage :: Function -> Maybe EphemeralStorageProperty
fileSystemConfigs :: Function -> Maybe [FileSystemConfigProperty]
functionName :: Function -> Maybe (Value Text)
handler :: Function -> Maybe (Value Text)
imageConfig :: Function -> Maybe ImageConfigProperty
kmsKeyArn :: Function -> Maybe (Value Text)
layers :: Function -> Maybe (ValueList Text)
loggingConfig :: Function -> Maybe LoggingConfigProperty
memorySize :: Function -> Maybe (Value Integer)
packageType :: Function -> Maybe (Value Text)
recursiveLoop :: Function -> Maybe (Value Text)
reservedConcurrentExecutions :: Function -> Maybe (Value Integer)
role :: Function -> Value Text
runtime :: Function -> Maybe (Value Text)
runtimeManagementConfig :: Function -> Maybe RuntimeManagementConfigProperty
snapStart :: Function -> Maybe SnapStartProperty
tags :: Function -> Maybe [Tag]
timeout :: Function -> Maybe (Value Integer)
tracingConfig :: Function -> Maybe TracingConfigProperty
vpcConfig :: Function -> Maybe VpcConfigProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
..}
    = Function {tags :: Maybe [Tag]
tags = [Tag] -> Maybe [Tag]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [Tag]
PropertyType "Tags" Function
newValue, Maybe [FileSystemConfigProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeadLetterConfigProperty
Maybe EnvironmentProperty
Maybe EphemeralStorageProperty
Maybe ImageConfigProperty
Maybe LoggingConfigProperty
Maybe RuntimeManagementConfigProperty
Maybe SnapStartProperty
Maybe TracingConfigProperty
Maybe VpcConfigProperty
()
Value Text
CodeProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
..}
instance Property "Timeout" Function where
  type PropertyType "Timeout" Function = Value Prelude.Integer
  set :: PropertyType "Timeout" Function -> Function -> Function
set PropertyType "Timeout" Function
newValue Function {Maybe [Tag]
Maybe [FileSystemConfigProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeadLetterConfigProperty
Maybe EnvironmentProperty
Maybe EphemeralStorageProperty
Maybe ImageConfigProperty
Maybe LoggingConfigProperty
Maybe RuntimeManagementConfigProperty
Maybe SnapStartProperty
Maybe TracingConfigProperty
Maybe VpcConfigProperty
()
Value Text
CodeProperty
haddock_workaround_ :: Function -> ()
architectures :: Function -> Maybe (ValueList Text)
code :: Function -> CodeProperty
codeSigningConfigArn :: Function -> Maybe (Value Text)
deadLetterConfig :: Function -> Maybe DeadLetterConfigProperty
description :: Function -> Maybe (Value Text)
environment :: Function -> Maybe EnvironmentProperty
ephemeralStorage :: Function -> Maybe EphemeralStorageProperty
fileSystemConfigs :: Function -> Maybe [FileSystemConfigProperty]
functionName :: Function -> Maybe (Value Text)
handler :: Function -> Maybe (Value Text)
imageConfig :: Function -> Maybe ImageConfigProperty
kmsKeyArn :: Function -> Maybe (Value Text)
layers :: Function -> Maybe (ValueList Text)
loggingConfig :: Function -> Maybe LoggingConfigProperty
memorySize :: Function -> Maybe (Value Integer)
packageType :: Function -> Maybe (Value Text)
recursiveLoop :: Function -> Maybe (Value Text)
reservedConcurrentExecutions :: Function -> Maybe (Value Integer)
role :: Function -> Value Text
runtime :: Function -> Maybe (Value Text)
runtimeManagementConfig :: Function -> Maybe RuntimeManagementConfigProperty
snapStart :: Function -> Maybe SnapStartProperty
tags :: Function -> Maybe [Tag]
timeout :: Function -> Maybe (Value Integer)
tracingConfig :: Function -> Maybe TracingConfigProperty
vpcConfig :: Function -> Maybe VpcConfigProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
..}
    = Function {timeout :: Maybe (Value Integer)
timeout = Value Integer -> Maybe (Value Integer)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "Timeout" Function
Value Integer
newValue, Maybe [Tag]
Maybe [FileSystemConfigProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeadLetterConfigProperty
Maybe EnvironmentProperty
Maybe EphemeralStorageProperty
Maybe ImageConfigProperty
Maybe LoggingConfigProperty
Maybe RuntimeManagementConfigProperty
Maybe SnapStartProperty
Maybe TracingConfigProperty
Maybe VpcConfigProperty
()
Value Text
CodeProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
..}
instance Property "TracingConfig" Function where
  type PropertyType "TracingConfig" Function = TracingConfigProperty
  set :: PropertyType "TracingConfig" Function -> Function -> Function
set PropertyType "TracingConfig" Function
newValue Function {Maybe [Tag]
Maybe [FileSystemConfigProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeadLetterConfigProperty
Maybe EnvironmentProperty
Maybe EphemeralStorageProperty
Maybe ImageConfigProperty
Maybe LoggingConfigProperty
Maybe RuntimeManagementConfigProperty
Maybe SnapStartProperty
Maybe TracingConfigProperty
Maybe VpcConfigProperty
()
Value Text
CodeProperty
haddock_workaround_ :: Function -> ()
architectures :: Function -> Maybe (ValueList Text)
code :: Function -> CodeProperty
codeSigningConfigArn :: Function -> Maybe (Value Text)
deadLetterConfig :: Function -> Maybe DeadLetterConfigProperty
description :: Function -> Maybe (Value Text)
environment :: Function -> Maybe EnvironmentProperty
ephemeralStorage :: Function -> Maybe EphemeralStorageProperty
fileSystemConfigs :: Function -> Maybe [FileSystemConfigProperty]
functionName :: Function -> Maybe (Value Text)
handler :: Function -> Maybe (Value Text)
imageConfig :: Function -> Maybe ImageConfigProperty
kmsKeyArn :: Function -> Maybe (Value Text)
layers :: Function -> Maybe (ValueList Text)
loggingConfig :: Function -> Maybe LoggingConfigProperty
memorySize :: Function -> Maybe (Value Integer)
packageType :: Function -> Maybe (Value Text)
recursiveLoop :: Function -> Maybe (Value Text)
reservedConcurrentExecutions :: Function -> Maybe (Value Integer)
role :: Function -> Value Text
runtime :: Function -> Maybe (Value Text)
runtimeManagementConfig :: Function -> Maybe RuntimeManagementConfigProperty
snapStart :: Function -> Maybe SnapStartProperty
tags :: Function -> Maybe [Tag]
timeout :: Function -> Maybe (Value Integer)
tracingConfig :: Function -> Maybe TracingConfigProperty
vpcConfig :: Function -> Maybe VpcConfigProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
..}
    = Function {tracingConfig :: Maybe TracingConfigProperty
tracingConfig = TracingConfigProperty -> Maybe TracingConfigProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "TracingConfig" Function
TracingConfigProperty
newValue, Maybe [Tag]
Maybe [FileSystemConfigProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeadLetterConfigProperty
Maybe EnvironmentProperty
Maybe EphemeralStorageProperty
Maybe ImageConfigProperty
Maybe LoggingConfigProperty
Maybe RuntimeManagementConfigProperty
Maybe SnapStartProperty
Maybe VpcConfigProperty
()
Value Text
CodeProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
vpcConfig :: Maybe VpcConfigProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
vpcConfig :: Maybe VpcConfigProperty
..}
instance Property "VpcConfig" Function where
  type PropertyType "VpcConfig" Function = VpcConfigProperty
  set :: PropertyType "VpcConfig" Function -> Function -> Function
set PropertyType "VpcConfig" Function
newValue Function {Maybe [Tag]
Maybe [FileSystemConfigProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeadLetterConfigProperty
Maybe EnvironmentProperty
Maybe EphemeralStorageProperty
Maybe ImageConfigProperty
Maybe LoggingConfigProperty
Maybe RuntimeManagementConfigProperty
Maybe SnapStartProperty
Maybe TracingConfigProperty
Maybe VpcConfigProperty
()
Value Text
CodeProperty
haddock_workaround_ :: Function -> ()
architectures :: Function -> Maybe (ValueList Text)
code :: Function -> CodeProperty
codeSigningConfigArn :: Function -> Maybe (Value Text)
deadLetterConfig :: Function -> Maybe DeadLetterConfigProperty
description :: Function -> Maybe (Value Text)
environment :: Function -> Maybe EnvironmentProperty
ephemeralStorage :: Function -> Maybe EphemeralStorageProperty
fileSystemConfigs :: Function -> Maybe [FileSystemConfigProperty]
functionName :: Function -> Maybe (Value Text)
handler :: Function -> Maybe (Value Text)
imageConfig :: Function -> Maybe ImageConfigProperty
kmsKeyArn :: Function -> Maybe (Value Text)
layers :: Function -> Maybe (ValueList Text)
loggingConfig :: Function -> Maybe LoggingConfigProperty
memorySize :: Function -> Maybe (Value Integer)
packageType :: Function -> Maybe (Value Text)
recursiveLoop :: Function -> Maybe (Value Text)
reservedConcurrentExecutions :: Function -> Maybe (Value Integer)
role :: Function -> Value Text
runtime :: Function -> Maybe (Value Text)
runtimeManagementConfig :: Function -> Maybe RuntimeManagementConfigProperty
snapStart :: Function -> Maybe SnapStartProperty
tags :: Function -> Maybe [Tag]
timeout :: Function -> Maybe (Value Integer)
tracingConfig :: Function -> Maybe TracingConfigProperty
vpcConfig :: Function -> Maybe VpcConfigProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
vpcConfig :: Maybe VpcConfigProperty
..}
    = Function {vpcConfig :: Maybe VpcConfigProperty
vpcConfig = VpcConfigProperty -> Maybe VpcConfigProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "VpcConfig" Function
VpcConfigProperty
newValue, Maybe [Tag]
Maybe [FileSystemConfigProperty]
Maybe (ValueList Text)
Maybe (Value Integer)
Maybe (Value Text)
Maybe DeadLetterConfigProperty
Maybe EnvironmentProperty
Maybe EphemeralStorageProperty
Maybe ImageConfigProperty
Maybe LoggingConfigProperty
Maybe RuntimeManagementConfigProperty
Maybe SnapStartProperty
Maybe TracingConfigProperty
()
Value Text
CodeProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
haddock_workaround_ :: ()
architectures :: Maybe (ValueList Text)
code :: CodeProperty
codeSigningConfigArn :: Maybe (Value Text)
deadLetterConfig :: Maybe DeadLetterConfigProperty
description :: Maybe (Value Text)
environment :: Maybe EnvironmentProperty
ephemeralStorage :: Maybe EphemeralStorageProperty
fileSystemConfigs :: Maybe [FileSystemConfigProperty]
functionName :: Maybe (Value Text)
handler :: Maybe (Value Text)
imageConfig :: Maybe ImageConfigProperty
kmsKeyArn :: Maybe (Value Text)
layers :: Maybe (ValueList Text)
loggingConfig :: Maybe LoggingConfigProperty
memorySize :: Maybe (Value Integer)
packageType :: Maybe (Value Text)
recursiveLoop :: Maybe (Value Text)
reservedConcurrentExecutions :: Maybe (Value Integer)
role :: Value Text
runtime :: Maybe (Value Text)
runtimeManagementConfig :: Maybe RuntimeManagementConfigProperty
snapStart :: Maybe SnapStartProperty
tags :: Maybe [Tag]
timeout :: Maybe (Value Integer)
tracingConfig :: Maybe TracingConfigProperty
..}