{-# 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.DataSource
-- 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.DataSource where

import Amazonka.AppSync.Types.DataSourceType
import Amazonka.AppSync.Types.DynamodbDataSourceConfig
import Amazonka.AppSync.Types.ElasticsearchDataSourceConfig
import Amazonka.AppSync.Types.HttpDataSourceConfig
import Amazonka.AppSync.Types.LambdaDataSourceConfig
import Amazonka.AppSync.Types.OpenSearchServiceDataSourceConfig
import Amazonka.AppSync.Types.RelationalDatabaseDataSourceConfig
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

-- | Describes a data source.
--
-- /See:/ 'newDataSource' smart constructor.
data DataSource = DataSource'
  { -- | The data source Amazon Resource Name (ARN).
    DataSource -> Maybe Text
dataSourceArn :: Prelude.Maybe Prelude.Text,
    -- | The description of the data source.
    DataSource -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | DynamoDB settings.
    DataSource -> Maybe DynamodbDataSourceConfig
dynamodbConfig :: Prelude.Maybe DynamodbDataSourceConfig,
    -- | Amazon OpenSearch Service settings.
    DataSource -> Maybe ElasticsearchDataSourceConfig
elasticsearchConfig :: Prelude.Maybe ElasticsearchDataSourceConfig,
    -- | HTTP endpoint settings.
    DataSource -> Maybe HttpDataSourceConfig
httpConfig :: Prelude.Maybe HttpDataSourceConfig,
    -- | Lambda settings.
    DataSource -> Maybe LambdaDataSourceConfig
lambdaConfig :: Prelude.Maybe LambdaDataSourceConfig,
    -- | The name of the data source.
    DataSource -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | Amazon OpenSearch Service settings.
    DataSource -> Maybe OpenSearchServiceDataSourceConfig
openSearchServiceConfig :: Prelude.Maybe OpenSearchServiceDataSourceConfig,
    -- | Relational database settings.
    DataSource -> Maybe RelationalDatabaseDataSourceConfig
relationalDatabaseConfig :: Prelude.Maybe RelationalDatabaseDataSourceConfig,
    -- | The Identity and Access Management (IAM) service role Amazon Resource
    -- Name (ARN) for the data source. The system assumes this role when
    -- accessing the data source.
    DataSource -> Maybe Text
serviceRoleArn :: Prelude.Maybe Prelude.Text,
    -- | The type of the data source.
    --
    -- -   __AWS_LAMBDA__: The data source is an Lambda function.
    --
    -- -   __AMAZON_DYNAMODB__: The data source is an Amazon DynamoDB table.
    --
    -- -   __AMAZON_ELASTICSEARCH__: The data source is an Amazon OpenSearch
    --     Service domain.
    --
    -- -   __AMAZON_OPENSEARCH_SERVICE__: The data source is an Amazon
    --     OpenSearch Service domain.
    --
    -- -   __NONE__: There is no data source. Use this type when you want to
    --     invoke a GraphQL operation without connecting to a data source, such
    --     as when you\'re performing data transformation with resolvers or
    --     invoking a subscription from a mutation.
    --
    -- -   __HTTP__: The data source is an HTTP endpoint.
    --
    -- -   __RELATIONAL_DATABASE__: The data source is a relational database.
    DataSource -> Maybe DataSourceType
type' :: Prelude.Maybe DataSourceType
  }
  deriving (DataSource -> DataSource -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DataSource -> DataSource -> Bool
$c/= :: DataSource -> DataSource -> Bool
== :: DataSource -> DataSource -> Bool
$c== :: DataSource -> DataSource -> Bool
Prelude.Eq, ReadPrec [DataSource]
ReadPrec DataSource
Int -> ReadS DataSource
ReadS [DataSource]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DataSource]
$creadListPrec :: ReadPrec [DataSource]
readPrec :: ReadPrec DataSource
$creadPrec :: ReadPrec DataSource
readList :: ReadS [DataSource]
$creadList :: ReadS [DataSource]
readsPrec :: Int -> ReadS DataSource
$creadsPrec :: Int -> ReadS DataSource
Prelude.Read, Int -> DataSource -> ShowS
[DataSource] -> ShowS
DataSource -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DataSource] -> ShowS
$cshowList :: [DataSource] -> ShowS
show :: DataSource -> String
$cshow :: DataSource -> String
showsPrec :: Int -> DataSource -> ShowS
$cshowsPrec :: Int -> DataSource -> ShowS
Prelude.Show, forall x. Rep DataSource x -> DataSource
forall x. DataSource -> Rep DataSource x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DataSource x -> DataSource
$cfrom :: forall x. DataSource -> Rep DataSource x
Prelude.Generic)

-- |
-- Create a value of 'DataSource' 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:
--
-- 'dataSourceArn', 'dataSource_dataSourceArn' - The data source Amazon Resource Name (ARN).
--
-- 'description', 'dataSource_description' - The description of the data source.
--
-- 'dynamodbConfig', 'dataSource_dynamodbConfig' - DynamoDB settings.
--
-- 'elasticsearchConfig', 'dataSource_elasticsearchConfig' - Amazon OpenSearch Service settings.
--
-- 'httpConfig', 'dataSource_httpConfig' - HTTP endpoint settings.
--
-- 'lambdaConfig', 'dataSource_lambdaConfig' - Lambda settings.
--
-- 'name', 'dataSource_name' - The name of the data source.
--
-- 'openSearchServiceConfig', 'dataSource_openSearchServiceConfig' - Amazon OpenSearch Service settings.
--
-- 'relationalDatabaseConfig', 'dataSource_relationalDatabaseConfig' - Relational database settings.
--
-- 'serviceRoleArn', 'dataSource_serviceRoleArn' - The Identity and Access Management (IAM) service role Amazon Resource
-- Name (ARN) for the data source. The system assumes this role when
-- accessing the data source.
--
-- 'type'', 'dataSource_type' - The type of the data source.
--
-- -   __AWS_LAMBDA__: The data source is an Lambda function.
--
-- -   __AMAZON_DYNAMODB__: The data source is an Amazon DynamoDB table.
--
-- -   __AMAZON_ELASTICSEARCH__: The data source is an Amazon OpenSearch
--     Service domain.
--
-- -   __AMAZON_OPENSEARCH_SERVICE__: The data source is an Amazon
--     OpenSearch Service domain.
--
-- -   __NONE__: There is no data source. Use this type when you want to
--     invoke a GraphQL operation without connecting to a data source, such
--     as when you\'re performing data transformation with resolvers or
--     invoking a subscription from a mutation.
--
-- -   __HTTP__: The data source is an HTTP endpoint.
--
-- -   __RELATIONAL_DATABASE__: The data source is a relational database.
newDataSource ::
  DataSource
newDataSource :: DataSource
newDataSource =
  DataSource'
    { $sel:dataSourceArn:DataSource' :: Maybe Text
dataSourceArn = forall a. Maybe a
Prelude.Nothing,
      $sel:description:DataSource' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:dynamodbConfig:DataSource' :: Maybe DynamodbDataSourceConfig
dynamodbConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:elasticsearchConfig:DataSource' :: Maybe ElasticsearchDataSourceConfig
elasticsearchConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:httpConfig:DataSource' :: Maybe HttpDataSourceConfig
httpConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:lambdaConfig:DataSource' :: Maybe LambdaDataSourceConfig
lambdaConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:name:DataSource' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:openSearchServiceConfig:DataSource' :: Maybe OpenSearchServiceDataSourceConfig
openSearchServiceConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:relationalDatabaseConfig:DataSource' :: Maybe RelationalDatabaseDataSourceConfig
relationalDatabaseConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:serviceRoleArn:DataSource' :: Maybe Text
serviceRoleArn = forall a. Maybe a
Prelude.Nothing,
      $sel:type':DataSource' :: Maybe DataSourceType
type' = forall a. Maybe a
Prelude.Nothing
    }

-- | The data source Amazon Resource Name (ARN).
dataSource_dataSourceArn :: Lens.Lens' DataSource (Prelude.Maybe Prelude.Text)
dataSource_dataSourceArn :: Lens' DataSource (Maybe Text)
dataSource_dataSourceArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DataSource' {Maybe Text
dataSourceArn :: Maybe Text
$sel:dataSourceArn:DataSource' :: DataSource -> Maybe Text
dataSourceArn} -> Maybe Text
dataSourceArn) (\s :: DataSource
s@DataSource' {} Maybe Text
a -> DataSource
s {$sel:dataSourceArn:DataSource' :: Maybe Text
dataSourceArn = Maybe Text
a} :: DataSource)

-- | The description of the data source.
dataSource_description :: Lens.Lens' DataSource (Prelude.Maybe Prelude.Text)
dataSource_description :: Lens' DataSource (Maybe Text)
dataSource_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DataSource' {Maybe Text
description :: Maybe Text
$sel:description:DataSource' :: DataSource -> Maybe Text
description} -> Maybe Text
description) (\s :: DataSource
s@DataSource' {} Maybe Text
a -> DataSource
s {$sel:description:DataSource' :: Maybe Text
description = Maybe Text
a} :: DataSource)

-- | DynamoDB settings.
dataSource_dynamodbConfig :: Lens.Lens' DataSource (Prelude.Maybe DynamodbDataSourceConfig)
dataSource_dynamodbConfig :: Lens' DataSource (Maybe DynamodbDataSourceConfig)
dataSource_dynamodbConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DataSource' {Maybe DynamodbDataSourceConfig
dynamodbConfig :: Maybe DynamodbDataSourceConfig
$sel:dynamodbConfig:DataSource' :: DataSource -> Maybe DynamodbDataSourceConfig
dynamodbConfig} -> Maybe DynamodbDataSourceConfig
dynamodbConfig) (\s :: DataSource
s@DataSource' {} Maybe DynamodbDataSourceConfig
a -> DataSource
s {$sel:dynamodbConfig:DataSource' :: Maybe DynamodbDataSourceConfig
dynamodbConfig = Maybe DynamodbDataSourceConfig
a} :: DataSource)

-- | Amazon OpenSearch Service settings.
dataSource_elasticsearchConfig :: Lens.Lens' DataSource (Prelude.Maybe ElasticsearchDataSourceConfig)
dataSource_elasticsearchConfig :: Lens' DataSource (Maybe ElasticsearchDataSourceConfig)
dataSource_elasticsearchConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DataSource' {Maybe ElasticsearchDataSourceConfig
elasticsearchConfig :: Maybe ElasticsearchDataSourceConfig
$sel:elasticsearchConfig:DataSource' :: DataSource -> Maybe ElasticsearchDataSourceConfig
elasticsearchConfig} -> Maybe ElasticsearchDataSourceConfig
elasticsearchConfig) (\s :: DataSource
s@DataSource' {} Maybe ElasticsearchDataSourceConfig
a -> DataSource
s {$sel:elasticsearchConfig:DataSource' :: Maybe ElasticsearchDataSourceConfig
elasticsearchConfig = Maybe ElasticsearchDataSourceConfig
a} :: DataSource)

-- | HTTP endpoint settings.
dataSource_httpConfig :: Lens.Lens' DataSource (Prelude.Maybe HttpDataSourceConfig)
dataSource_httpConfig :: Lens' DataSource (Maybe HttpDataSourceConfig)
dataSource_httpConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DataSource' {Maybe HttpDataSourceConfig
httpConfig :: Maybe HttpDataSourceConfig
$sel:httpConfig:DataSource' :: DataSource -> Maybe HttpDataSourceConfig
httpConfig} -> Maybe HttpDataSourceConfig
httpConfig) (\s :: DataSource
s@DataSource' {} Maybe HttpDataSourceConfig
a -> DataSource
s {$sel:httpConfig:DataSource' :: Maybe HttpDataSourceConfig
httpConfig = Maybe HttpDataSourceConfig
a} :: DataSource)

-- | Lambda settings.
dataSource_lambdaConfig :: Lens.Lens' DataSource (Prelude.Maybe LambdaDataSourceConfig)
dataSource_lambdaConfig :: Lens' DataSource (Maybe LambdaDataSourceConfig)
dataSource_lambdaConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DataSource' {Maybe LambdaDataSourceConfig
lambdaConfig :: Maybe LambdaDataSourceConfig
$sel:lambdaConfig:DataSource' :: DataSource -> Maybe LambdaDataSourceConfig
lambdaConfig} -> Maybe LambdaDataSourceConfig
lambdaConfig) (\s :: DataSource
s@DataSource' {} Maybe LambdaDataSourceConfig
a -> DataSource
s {$sel:lambdaConfig:DataSource' :: Maybe LambdaDataSourceConfig
lambdaConfig = Maybe LambdaDataSourceConfig
a} :: DataSource)

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

-- | Amazon OpenSearch Service settings.
dataSource_openSearchServiceConfig :: Lens.Lens' DataSource (Prelude.Maybe OpenSearchServiceDataSourceConfig)
dataSource_openSearchServiceConfig :: Lens' DataSource (Maybe OpenSearchServiceDataSourceConfig)
dataSource_openSearchServiceConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DataSource' {Maybe OpenSearchServiceDataSourceConfig
openSearchServiceConfig :: Maybe OpenSearchServiceDataSourceConfig
$sel:openSearchServiceConfig:DataSource' :: DataSource -> Maybe OpenSearchServiceDataSourceConfig
openSearchServiceConfig} -> Maybe OpenSearchServiceDataSourceConfig
openSearchServiceConfig) (\s :: DataSource
s@DataSource' {} Maybe OpenSearchServiceDataSourceConfig
a -> DataSource
s {$sel:openSearchServiceConfig:DataSource' :: Maybe OpenSearchServiceDataSourceConfig
openSearchServiceConfig = Maybe OpenSearchServiceDataSourceConfig
a} :: DataSource)

-- | Relational database settings.
dataSource_relationalDatabaseConfig :: Lens.Lens' DataSource (Prelude.Maybe RelationalDatabaseDataSourceConfig)
dataSource_relationalDatabaseConfig :: Lens' DataSource (Maybe RelationalDatabaseDataSourceConfig)
dataSource_relationalDatabaseConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DataSource' {Maybe RelationalDatabaseDataSourceConfig
relationalDatabaseConfig :: Maybe RelationalDatabaseDataSourceConfig
$sel:relationalDatabaseConfig:DataSource' :: DataSource -> Maybe RelationalDatabaseDataSourceConfig
relationalDatabaseConfig} -> Maybe RelationalDatabaseDataSourceConfig
relationalDatabaseConfig) (\s :: DataSource
s@DataSource' {} Maybe RelationalDatabaseDataSourceConfig
a -> DataSource
s {$sel:relationalDatabaseConfig:DataSource' :: Maybe RelationalDatabaseDataSourceConfig
relationalDatabaseConfig = Maybe RelationalDatabaseDataSourceConfig
a} :: DataSource)

-- | The Identity and Access Management (IAM) service role Amazon Resource
-- Name (ARN) for the data source. The system assumes this role when
-- accessing the data source.
dataSource_serviceRoleArn :: Lens.Lens' DataSource (Prelude.Maybe Prelude.Text)
dataSource_serviceRoleArn :: Lens' DataSource (Maybe Text)
dataSource_serviceRoleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DataSource' {Maybe Text
serviceRoleArn :: Maybe Text
$sel:serviceRoleArn:DataSource' :: DataSource -> Maybe Text
serviceRoleArn} -> Maybe Text
serviceRoleArn) (\s :: DataSource
s@DataSource' {} Maybe Text
a -> DataSource
s {$sel:serviceRoleArn:DataSource' :: Maybe Text
serviceRoleArn = Maybe Text
a} :: DataSource)

-- | The type of the data source.
--
-- -   __AWS_LAMBDA__: The data source is an Lambda function.
--
-- -   __AMAZON_DYNAMODB__: The data source is an Amazon DynamoDB table.
--
-- -   __AMAZON_ELASTICSEARCH__: The data source is an Amazon OpenSearch
--     Service domain.
--
-- -   __AMAZON_OPENSEARCH_SERVICE__: The data source is an Amazon
--     OpenSearch Service domain.
--
-- -   __NONE__: There is no data source. Use this type when you want to
--     invoke a GraphQL operation without connecting to a data source, such
--     as when you\'re performing data transformation with resolvers or
--     invoking a subscription from a mutation.
--
-- -   __HTTP__: The data source is an HTTP endpoint.
--
-- -   __RELATIONAL_DATABASE__: The data source is a relational database.
dataSource_type :: Lens.Lens' DataSource (Prelude.Maybe DataSourceType)
dataSource_type :: Lens' DataSource (Maybe DataSourceType)
dataSource_type = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DataSource' {Maybe DataSourceType
type' :: Maybe DataSourceType
$sel:type':DataSource' :: DataSource -> Maybe DataSourceType
type'} -> Maybe DataSourceType
type') (\s :: DataSource
s@DataSource' {} Maybe DataSourceType
a -> DataSource
s {$sel:type':DataSource' :: Maybe DataSourceType
type' = Maybe DataSourceType
a} :: DataSource)

instance Data.FromJSON DataSource where
  parseJSON :: Value -> Parser DataSource
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"DataSource"
      ( \Object
x ->
          Maybe Text
-> Maybe Text
-> Maybe DynamodbDataSourceConfig
-> Maybe ElasticsearchDataSourceConfig
-> Maybe HttpDataSourceConfig
-> Maybe LambdaDataSourceConfig
-> Maybe Text
-> Maybe OpenSearchServiceDataSourceConfig
-> Maybe RelationalDatabaseDataSourceConfig
-> Maybe Text
-> Maybe DataSourceType
-> DataSource
DataSource'
            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
"dataSourceArn")
            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
"dynamodbConfig")
            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
"elasticsearchConfig")
            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
"httpConfig")
            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
"lambdaConfig")
            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
"openSearchServiceConfig")
            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
"relationalDatabaseConfig")
            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
"serviceRoleArn")
            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
"type")
      )

instance Prelude.Hashable DataSource where
  hashWithSalt :: Int -> DataSource -> Int
hashWithSalt Int
_salt DataSource' {Maybe Text
Maybe DataSourceType
Maybe DynamodbDataSourceConfig
Maybe ElasticsearchDataSourceConfig
Maybe HttpDataSourceConfig
Maybe LambdaDataSourceConfig
Maybe OpenSearchServiceDataSourceConfig
Maybe RelationalDatabaseDataSourceConfig
type' :: Maybe DataSourceType
serviceRoleArn :: Maybe Text
relationalDatabaseConfig :: Maybe RelationalDatabaseDataSourceConfig
openSearchServiceConfig :: Maybe OpenSearchServiceDataSourceConfig
name :: Maybe Text
lambdaConfig :: Maybe LambdaDataSourceConfig
httpConfig :: Maybe HttpDataSourceConfig
elasticsearchConfig :: Maybe ElasticsearchDataSourceConfig
dynamodbConfig :: Maybe DynamodbDataSourceConfig
description :: Maybe Text
dataSourceArn :: Maybe Text
$sel:type':DataSource' :: DataSource -> Maybe DataSourceType
$sel:serviceRoleArn:DataSource' :: DataSource -> Maybe Text
$sel:relationalDatabaseConfig:DataSource' :: DataSource -> Maybe RelationalDatabaseDataSourceConfig
$sel:openSearchServiceConfig:DataSource' :: DataSource -> Maybe OpenSearchServiceDataSourceConfig
$sel:name:DataSource' :: DataSource -> Maybe Text
$sel:lambdaConfig:DataSource' :: DataSource -> Maybe LambdaDataSourceConfig
$sel:httpConfig:DataSource' :: DataSource -> Maybe HttpDataSourceConfig
$sel:elasticsearchConfig:DataSource' :: DataSource -> Maybe ElasticsearchDataSourceConfig
$sel:dynamodbConfig:DataSource' :: DataSource -> Maybe DynamodbDataSourceConfig
$sel:description:DataSource' :: DataSource -> Maybe Text
$sel:dataSourceArn:DataSource' :: DataSource -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
dataSourceArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DynamodbDataSourceConfig
dynamodbConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ElasticsearchDataSourceConfig
elasticsearchConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe HttpDataSourceConfig
httpConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe LambdaDataSourceConfig
lambdaConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe OpenSearchServiceDataSourceConfig
openSearchServiceConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe RelationalDatabaseDataSourceConfig
relationalDatabaseConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
serviceRoleArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DataSourceType
type'

instance Prelude.NFData DataSource where
  rnf :: DataSource -> ()
rnf DataSource' {Maybe Text
Maybe DataSourceType
Maybe DynamodbDataSourceConfig
Maybe ElasticsearchDataSourceConfig
Maybe HttpDataSourceConfig
Maybe LambdaDataSourceConfig
Maybe OpenSearchServiceDataSourceConfig
Maybe RelationalDatabaseDataSourceConfig
type' :: Maybe DataSourceType
serviceRoleArn :: Maybe Text
relationalDatabaseConfig :: Maybe RelationalDatabaseDataSourceConfig
openSearchServiceConfig :: Maybe OpenSearchServiceDataSourceConfig
name :: Maybe Text
lambdaConfig :: Maybe LambdaDataSourceConfig
httpConfig :: Maybe HttpDataSourceConfig
elasticsearchConfig :: Maybe ElasticsearchDataSourceConfig
dynamodbConfig :: Maybe DynamodbDataSourceConfig
description :: Maybe Text
dataSourceArn :: Maybe Text
$sel:type':DataSource' :: DataSource -> Maybe DataSourceType
$sel:serviceRoleArn:DataSource' :: DataSource -> Maybe Text
$sel:relationalDatabaseConfig:DataSource' :: DataSource -> Maybe RelationalDatabaseDataSourceConfig
$sel:openSearchServiceConfig:DataSource' :: DataSource -> Maybe OpenSearchServiceDataSourceConfig
$sel:name:DataSource' :: DataSource -> Maybe Text
$sel:lambdaConfig:DataSource' :: DataSource -> Maybe LambdaDataSourceConfig
$sel:httpConfig:DataSource' :: DataSource -> Maybe HttpDataSourceConfig
$sel:elasticsearchConfig:DataSource' :: DataSource -> Maybe ElasticsearchDataSourceConfig
$sel:dynamodbConfig:DataSource' :: DataSource -> Maybe DynamodbDataSourceConfig
$sel:description:DataSource' :: DataSource -> Maybe Text
$sel:dataSourceArn:DataSource' :: DataSource -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
dataSourceArn
      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 DynamodbDataSourceConfig
dynamodbConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ElasticsearchDataSourceConfig
elasticsearchConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe HttpDataSourceConfig
httpConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe LambdaDataSourceConfig
lambdaConfig
      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 OpenSearchServiceDataSourceConfig
openSearchServiceConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe RelationalDatabaseDataSourceConfig
relationalDatabaseConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
serviceRoleArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DataSourceType
type'