{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.AppSync.Types.FunctionConfiguration
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.AppSync.Types.FunctionConfiguration where

import Amazonka.AppSync.Types.AppSyncRuntime
import Amazonka.AppSync.Types.SyncConfig
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude

-- | A function is a reusable entity. You can use multiple functions to
-- compose the resolver logic.
--
-- /See:/ 'newFunctionConfiguration' smart constructor.
data FunctionConfiguration = FunctionConfiguration'
  { -- | The @function@ code that contains the request and response functions.
    -- When code is used, the @runtime@ is required. The @runtime@ value must
    -- be @APPSYNC_JS@.
    FunctionConfiguration -> Maybe Text
code :: Prelude.Maybe Prelude.Text,
    -- | The name of the @DataSource@.
    FunctionConfiguration -> Maybe Text
dataSourceName :: Prelude.Maybe Prelude.Text,
    -- | The @Function@ description.
    FunctionConfiguration -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the @Function@ object.
    FunctionConfiguration -> Maybe Text
functionArn :: Prelude.Maybe Prelude.Text,
    -- | A unique ID representing the @Function@ object.
    FunctionConfiguration -> Maybe Text
functionId :: Prelude.Maybe Prelude.Text,
    -- | The version of the request mapping template. Currently, only the
    -- 2018-05-29 version of the template is supported.
    FunctionConfiguration -> Maybe Text
functionVersion :: Prelude.Maybe Prelude.Text,
    -- | The maximum batching size for a resolver.
    FunctionConfiguration -> Maybe Natural
maxBatchSize :: Prelude.Maybe Prelude.Natural,
    -- | The name of the @Function@ object.
    FunctionConfiguration -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | The @Function@ request mapping template. Functions support only the
    -- 2018-05-29 version of the request mapping template.
    FunctionConfiguration -> Maybe Text
requestMappingTemplate :: Prelude.Maybe Prelude.Text,
    -- | The @Function@ response mapping template.
    FunctionConfiguration -> Maybe Text
responseMappingTemplate :: Prelude.Maybe Prelude.Text,
    FunctionConfiguration -> Maybe AppSyncRuntime
runtime :: Prelude.Maybe AppSyncRuntime,
    FunctionConfiguration -> Maybe SyncConfig
syncConfig :: Prelude.Maybe SyncConfig
  }
  deriving (FunctionConfiguration -> FunctionConfiguration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FunctionConfiguration -> FunctionConfiguration -> Bool
$c/= :: FunctionConfiguration -> FunctionConfiguration -> Bool
== :: FunctionConfiguration -> FunctionConfiguration -> Bool
$c== :: FunctionConfiguration -> FunctionConfiguration -> Bool
Prelude.Eq, ReadPrec [FunctionConfiguration]
ReadPrec FunctionConfiguration
Int -> ReadS FunctionConfiguration
ReadS [FunctionConfiguration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [FunctionConfiguration]
$creadListPrec :: ReadPrec [FunctionConfiguration]
readPrec :: ReadPrec FunctionConfiguration
$creadPrec :: ReadPrec FunctionConfiguration
readList :: ReadS [FunctionConfiguration]
$creadList :: ReadS [FunctionConfiguration]
readsPrec :: Int -> ReadS FunctionConfiguration
$creadsPrec :: Int -> ReadS FunctionConfiguration
Prelude.Read, Int -> FunctionConfiguration -> ShowS
[FunctionConfiguration] -> ShowS
FunctionConfiguration -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FunctionConfiguration] -> ShowS
$cshowList :: [FunctionConfiguration] -> ShowS
show :: FunctionConfiguration -> String
$cshow :: FunctionConfiguration -> String
showsPrec :: Int -> FunctionConfiguration -> ShowS
$cshowsPrec :: Int -> FunctionConfiguration -> ShowS
Prelude.Show, forall x. Rep FunctionConfiguration x -> FunctionConfiguration
forall x. FunctionConfiguration -> Rep FunctionConfiguration x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FunctionConfiguration x -> FunctionConfiguration
$cfrom :: forall x. FunctionConfiguration -> Rep FunctionConfiguration x
Prelude.Generic)

-- |
-- Create a value of 'FunctionConfiguration' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'code', 'functionConfiguration_code' - The @function@ code that contains the request and response functions.
-- When code is used, the @runtime@ is required. The @runtime@ value must
-- be @APPSYNC_JS@.
--
-- 'dataSourceName', 'functionConfiguration_dataSourceName' - The name of the @DataSource@.
--
-- 'description', 'functionConfiguration_description' - The @Function@ description.
--
-- 'functionArn', 'functionConfiguration_functionArn' - The Amazon Resource Name (ARN) of the @Function@ object.
--
-- 'functionId', 'functionConfiguration_functionId' - A unique ID representing the @Function@ object.
--
-- 'functionVersion', 'functionConfiguration_functionVersion' - The version of the request mapping template. Currently, only the
-- 2018-05-29 version of the template is supported.
--
-- 'maxBatchSize', 'functionConfiguration_maxBatchSize' - The maximum batching size for a resolver.
--
-- 'name', 'functionConfiguration_name' - The name of the @Function@ object.
--
-- 'requestMappingTemplate', 'functionConfiguration_requestMappingTemplate' - The @Function@ request mapping template. Functions support only the
-- 2018-05-29 version of the request mapping template.
--
-- 'responseMappingTemplate', 'functionConfiguration_responseMappingTemplate' - The @Function@ response mapping template.
--
-- 'runtime', 'functionConfiguration_runtime' - Undocumented member.
--
-- 'syncConfig', 'functionConfiguration_syncConfig' - Undocumented member.
newFunctionConfiguration ::
  FunctionConfiguration
newFunctionConfiguration :: FunctionConfiguration
newFunctionConfiguration =
  FunctionConfiguration'
    { $sel:code:FunctionConfiguration' :: Maybe Text
code = forall a. Maybe a
Prelude.Nothing,
      $sel:dataSourceName:FunctionConfiguration' :: Maybe Text
dataSourceName = forall a. Maybe a
Prelude.Nothing,
      $sel:description:FunctionConfiguration' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:functionArn:FunctionConfiguration' :: Maybe Text
functionArn = forall a. Maybe a
Prelude.Nothing,
      $sel:functionId:FunctionConfiguration' :: Maybe Text
functionId = forall a. Maybe a
Prelude.Nothing,
      $sel:functionVersion:FunctionConfiguration' :: Maybe Text
functionVersion = forall a. Maybe a
Prelude.Nothing,
      $sel:maxBatchSize:FunctionConfiguration' :: Maybe Natural
maxBatchSize = forall a. Maybe a
Prelude.Nothing,
      $sel:name:FunctionConfiguration' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:requestMappingTemplate:FunctionConfiguration' :: Maybe Text
requestMappingTemplate = forall a. Maybe a
Prelude.Nothing,
      $sel:responseMappingTemplate:FunctionConfiguration' :: Maybe Text
responseMappingTemplate = forall a. Maybe a
Prelude.Nothing,
      $sel:runtime:FunctionConfiguration' :: Maybe AppSyncRuntime
runtime = forall a. Maybe a
Prelude.Nothing,
      $sel:syncConfig:FunctionConfiguration' :: Maybe SyncConfig
syncConfig = forall a. Maybe a
Prelude.Nothing
    }

-- | The @function@ code that contains the request and response functions.
-- When code is used, the @runtime@ is required. The @runtime@ value must
-- be @APPSYNC_JS@.
functionConfiguration_code :: Lens.Lens' FunctionConfiguration (Prelude.Maybe Prelude.Text)
functionConfiguration_code :: Lens' FunctionConfiguration (Maybe Text)
functionConfiguration_code = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FunctionConfiguration' {Maybe Text
code :: Maybe Text
$sel:code:FunctionConfiguration' :: FunctionConfiguration -> Maybe Text
code} -> Maybe Text
code) (\s :: FunctionConfiguration
s@FunctionConfiguration' {} Maybe Text
a -> FunctionConfiguration
s {$sel:code:FunctionConfiguration' :: Maybe Text
code = Maybe Text
a} :: FunctionConfiguration)

-- | The name of the @DataSource@.
functionConfiguration_dataSourceName :: Lens.Lens' FunctionConfiguration (Prelude.Maybe Prelude.Text)
functionConfiguration_dataSourceName :: Lens' FunctionConfiguration (Maybe Text)
functionConfiguration_dataSourceName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FunctionConfiguration' {Maybe Text
dataSourceName :: Maybe Text
$sel:dataSourceName:FunctionConfiguration' :: FunctionConfiguration -> Maybe Text
dataSourceName} -> Maybe Text
dataSourceName) (\s :: FunctionConfiguration
s@FunctionConfiguration' {} Maybe Text
a -> FunctionConfiguration
s {$sel:dataSourceName:FunctionConfiguration' :: Maybe Text
dataSourceName = Maybe Text
a} :: FunctionConfiguration)

-- | The @Function@ description.
functionConfiguration_description :: Lens.Lens' FunctionConfiguration (Prelude.Maybe Prelude.Text)
functionConfiguration_description :: Lens' FunctionConfiguration (Maybe Text)
functionConfiguration_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FunctionConfiguration' {Maybe Text
description :: Maybe Text
$sel:description:FunctionConfiguration' :: FunctionConfiguration -> Maybe Text
description} -> Maybe Text
description) (\s :: FunctionConfiguration
s@FunctionConfiguration' {} Maybe Text
a -> FunctionConfiguration
s {$sel:description:FunctionConfiguration' :: Maybe Text
description = Maybe Text
a} :: FunctionConfiguration)

-- | The Amazon Resource Name (ARN) of the @Function@ object.
functionConfiguration_functionArn :: Lens.Lens' FunctionConfiguration (Prelude.Maybe Prelude.Text)
functionConfiguration_functionArn :: Lens' FunctionConfiguration (Maybe Text)
functionConfiguration_functionArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FunctionConfiguration' {Maybe Text
functionArn :: Maybe Text
$sel:functionArn:FunctionConfiguration' :: FunctionConfiguration -> Maybe Text
functionArn} -> Maybe Text
functionArn) (\s :: FunctionConfiguration
s@FunctionConfiguration' {} Maybe Text
a -> FunctionConfiguration
s {$sel:functionArn:FunctionConfiguration' :: Maybe Text
functionArn = Maybe Text
a} :: FunctionConfiguration)

-- | A unique ID representing the @Function@ object.
functionConfiguration_functionId :: Lens.Lens' FunctionConfiguration (Prelude.Maybe Prelude.Text)
functionConfiguration_functionId :: Lens' FunctionConfiguration (Maybe Text)
functionConfiguration_functionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FunctionConfiguration' {Maybe Text
functionId :: Maybe Text
$sel:functionId:FunctionConfiguration' :: FunctionConfiguration -> Maybe Text
functionId} -> Maybe Text
functionId) (\s :: FunctionConfiguration
s@FunctionConfiguration' {} Maybe Text
a -> FunctionConfiguration
s {$sel:functionId:FunctionConfiguration' :: Maybe Text
functionId = Maybe Text
a} :: FunctionConfiguration)

-- | The version of the request mapping template. Currently, only the
-- 2018-05-29 version of the template is supported.
functionConfiguration_functionVersion :: Lens.Lens' FunctionConfiguration (Prelude.Maybe Prelude.Text)
functionConfiguration_functionVersion :: Lens' FunctionConfiguration (Maybe Text)
functionConfiguration_functionVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FunctionConfiguration' {Maybe Text
functionVersion :: Maybe Text
$sel:functionVersion:FunctionConfiguration' :: FunctionConfiguration -> Maybe Text
functionVersion} -> Maybe Text
functionVersion) (\s :: FunctionConfiguration
s@FunctionConfiguration' {} Maybe Text
a -> FunctionConfiguration
s {$sel:functionVersion:FunctionConfiguration' :: Maybe Text
functionVersion = Maybe Text
a} :: FunctionConfiguration)

-- | The maximum batching size for a resolver.
functionConfiguration_maxBatchSize :: Lens.Lens' FunctionConfiguration (Prelude.Maybe Prelude.Natural)
functionConfiguration_maxBatchSize :: Lens' FunctionConfiguration (Maybe Natural)
functionConfiguration_maxBatchSize = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FunctionConfiguration' {Maybe Natural
maxBatchSize :: Maybe Natural
$sel:maxBatchSize:FunctionConfiguration' :: FunctionConfiguration -> Maybe Natural
maxBatchSize} -> Maybe Natural
maxBatchSize) (\s :: FunctionConfiguration
s@FunctionConfiguration' {} Maybe Natural
a -> FunctionConfiguration
s {$sel:maxBatchSize:FunctionConfiguration' :: Maybe Natural
maxBatchSize = Maybe Natural
a} :: FunctionConfiguration)

-- | The name of the @Function@ object.
functionConfiguration_name :: Lens.Lens' FunctionConfiguration (Prelude.Maybe Prelude.Text)
functionConfiguration_name :: Lens' FunctionConfiguration (Maybe Text)
functionConfiguration_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FunctionConfiguration' {Maybe Text
name :: Maybe Text
$sel:name:FunctionConfiguration' :: FunctionConfiguration -> Maybe Text
name} -> Maybe Text
name) (\s :: FunctionConfiguration
s@FunctionConfiguration' {} Maybe Text
a -> FunctionConfiguration
s {$sel:name:FunctionConfiguration' :: Maybe Text
name = Maybe Text
a} :: FunctionConfiguration)

-- | The @Function@ request mapping template. Functions support only the
-- 2018-05-29 version of the request mapping template.
functionConfiguration_requestMappingTemplate :: Lens.Lens' FunctionConfiguration (Prelude.Maybe Prelude.Text)
functionConfiguration_requestMappingTemplate :: Lens' FunctionConfiguration (Maybe Text)
functionConfiguration_requestMappingTemplate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FunctionConfiguration' {Maybe Text
requestMappingTemplate :: Maybe Text
$sel:requestMappingTemplate:FunctionConfiguration' :: FunctionConfiguration -> Maybe Text
requestMappingTemplate} -> Maybe Text
requestMappingTemplate) (\s :: FunctionConfiguration
s@FunctionConfiguration' {} Maybe Text
a -> FunctionConfiguration
s {$sel:requestMappingTemplate:FunctionConfiguration' :: Maybe Text
requestMappingTemplate = Maybe Text
a} :: FunctionConfiguration)

-- | The @Function@ response mapping template.
functionConfiguration_responseMappingTemplate :: Lens.Lens' FunctionConfiguration (Prelude.Maybe Prelude.Text)
functionConfiguration_responseMappingTemplate :: Lens' FunctionConfiguration (Maybe Text)
functionConfiguration_responseMappingTemplate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FunctionConfiguration' {Maybe Text
responseMappingTemplate :: Maybe Text
$sel:responseMappingTemplate:FunctionConfiguration' :: FunctionConfiguration -> Maybe Text
responseMappingTemplate} -> Maybe Text
responseMappingTemplate) (\s :: FunctionConfiguration
s@FunctionConfiguration' {} Maybe Text
a -> FunctionConfiguration
s {$sel:responseMappingTemplate:FunctionConfiguration' :: Maybe Text
responseMappingTemplate = Maybe Text
a} :: FunctionConfiguration)

-- | Undocumented member.
functionConfiguration_runtime :: Lens.Lens' FunctionConfiguration (Prelude.Maybe AppSyncRuntime)
functionConfiguration_runtime :: Lens' FunctionConfiguration (Maybe AppSyncRuntime)
functionConfiguration_runtime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FunctionConfiguration' {Maybe AppSyncRuntime
runtime :: Maybe AppSyncRuntime
$sel:runtime:FunctionConfiguration' :: FunctionConfiguration -> Maybe AppSyncRuntime
runtime} -> Maybe AppSyncRuntime
runtime) (\s :: FunctionConfiguration
s@FunctionConfiguration' {} Maybe AppSyncRuntime
a -> FunctionConfiguration
s {$sel:runtime:FunctionConfiguration' :: Maybe AppSyncRuntime
runtime = Maybe AppSyncRuntime
a} :: FunctionConfiguration)

-- | Undocumented member.
functionConfiguration_syncConfig :: Lens.Lens' FunctionConfiguration (Prelude.Maybe SyncConfig)
functionConfiguration_syncConfig :: Lens' FunctionConfiguration (Maybe SyncConfig)
functionConfiguration_syncConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FunctionConfiguration' {Maybe SyncConfig
syncConfig :: Maybe SyncConfig
$sel:syncConfig:FunctionConfiguration' :: FunctionConfiguration -> Maybe SyncConfig
syncConfig} -> Maybe SyncConfig
syncConfig) (\s :: FunctionConfiguration
s@FunctionConfiguration' {} Maybe SyncConfig
a -> FunctionConfiguration
s {$sel:syncConfig:FunctionConfiguration' :: Maybe SyncConfig
syncConfig = Maybe SyncConfig
a} :: FunctionConfiguration)

instance Data.FromJSON FunctionConfiguration where
  parseJSON :: Value -> Parser FunctionConfiguration
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"FunctionConfiguration"
      ( \Object
x ->
          Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Natural
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe AppSyncRuntime
-> Maybe SyncConfig
-> FunctionConfiguration
FunctionConfiguration'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"code")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"dataSourceName")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"description")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"functionArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"functionId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"functionVersion")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"maxBatchSize")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"name")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"requestMappingTemplate")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"responseMappingTemplate")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"runtime")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"syncConfig")
      )

instance Prelude.Hashable FunctionConfiguration where
  hashWithSalt :: Int -> FunctionConfiguration -> Int
hashWithSalt Int
_salt FunctionConfiguration' {Maybe Natural
Maybe Text
Maybe AppSyncRuntime
Maybe SyncConfig
syncConfig :: Maybe SyncConfig
runtime :: Maybe AppSyncRuntime
responseMappingTemplate :: Maybe Text
requestMappingTemplate :: Maybe Text
name :: Maybe Text
maxBatchSize :: Maybe Natural
functionVersion :: Maybe Text
functionId :: Maybe Text
functionArn :: Maybe Text
description :: Maybe Text
dataSourceName :: Maybe Text
code :: Maybe Text
$sel:syncConfig:FunctionConfiguration' :: FunctionConfiguration -> Maybe SyncConfig
$sel:runtime:FunctionConfiguration' :: FunctionConfiguration -> Maybe AppSyncRuntime
$sel:responseMappingTemplate:FunctionConfiguration' :: FunctionConfiguration -> Maybe Text
$sel:requestMappingTemplate:FunctionConfiguration' :: FunctionConfiguration -> Maybe Text
$sel:name:FunctionConfiguration' :: FunctionConfiguration -> Maybe Text
$sel:maxBatchSize:FunctionConfiguration' :: FunctionConfiguration -> Maybe Natural
$sel:functionVersion:FunctionConfiguration' :: FunctionConfiguration -> Maybe Text
$sel:functionId:FunctionConfiguration' :: FunctionConfiguration -> Maybe Text
$sel:functionArn:FunctionConfiguration' :: FunctionConfiguration -> Maybe Text
$sel:description:FunctionConfiguration' :: FunctionConfiguration -> Maybe Text
$sel:dataSourceName:FunctionConfiguration' :: FunctionConfiguration -> Maybe Text
$sel:code:FunctionConfiguration' :: FunctionConfiguration -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
code
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
dataSourceName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
functionArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
functionId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
functionVersion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maxBatchSize
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
requestMappingTemplate
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
responseMappingTemplate
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AppSyncRuntime
runtime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe SyncConfig
syncConfig

instance Prelude.NFData FunctionConfiguration where
  rnf :: FunctionConfiguration -> ()
rnf FunctionConfiguration' {Maybe Natural
Maybe Text
Maybe AppSyncRuntime
Maybe SyncConfig
syncConfig :: Maybe SyncConfig
runtime :: Maybe AppSyncRuntime
responseMappingTemplate :: Maybe Text
requestMappingTemplate :: Maybe Text
name :: Maybe Text
maxBatchSize :: Maybe Natural
functionVersion :: Maybe Text
functionId :: Maybe Text
functionArn :: Maybe Text
description :: Maybe Text
dataSourceName :: Maybe Text
code :: Maybe Text
$sel:syncConfig:FunctionConfiguration' :: FunctionConfiguration -> Maybe SyncConfig
$sel:runtime:FunctionConfiguration' :: FunctionConfiguration -> Maybe AppSyncRuntime
$sel:responseMappingTemplate:FunctionConfiguration' :: FunctionConfiguration -> Maybe Text
$sel:requestMappingTemplate:FunctionConfiguration' :: FunctionConfiguration -> Maybe Text
$sel:name:FunctionConfiguration' :: FunctionConfiguration -> Maybe Text
$sel:maxBatchSize:FunctionConfiguration' :: FunctionConfiguration -> Maybe Natural
$sel:functionVersion:FunctionConfiguration' :: FunctionConfiguration -> Maybe Text
$sel:functionId:FunctionConfiguration' :: FunctionConfiguration -> Maybe Text
$sel:functionArn:FunctionConfiguration' :: FunctionConfiguration -> Maybe Text
$sel:description:FunctionConfiguration' :: FunctionConfiguration -> Maybe Text
$sel:dataSourceName:FunctionConfiguration' :: FunctionConfiguration -> Maybe Text
$sel:code:FunctionConfiguration' :: FunctionConfiguration -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
code
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
dataSourceName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
functionArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
functionId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
functionVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
maxBatchSize
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
requestMappingTemplate
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
responseMappingTemplate
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe AppSyncRuntime
runtime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe SyncConfig
syncConfig