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

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

-- |
-- Module      : Amazonka.Kendra.DescribeDataSource
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Gets information about an Amazon Kendra data source connector.
module Amazonka.Kendra.DescribeDataSource
  ( -- * Creating a Request
    DescribeDataSource (..),
    newDescribeDataSource,

    -- * Request Lenses
    describeDataSource_id,
    describeDataSource_indexId,

    -- * Destructuring the Response
    DescribeDataSourceResponse (..),
    newDescribeDataSourceResponse,

    -- * Response Lenses
    describeDataSourceResponse_configuration,
    describeDataSourceResponse_createdAt,
    describeDataSourceResponse_customDocumentEnrichmentConfiguration,
    describeDataSourceResponse_description,
    describeDataSourceResponse_errorMessage,
    describeDataSourceResponse_id,
    describeDataSourceResponse_indexId,
    describeDataSourceResponse_languageCode,
    describeDataSourceResponse_name,
    describeDataSourceResponse_roleArn,
    describeDataSourceResponse_schedule,
    describeDataSourceResponse_status,
    describeDataSourceResponse_type,
    describeDataSourceResponse_updatedAt,
    describeDataSourceResponse_vpcConfiguration,
    describeDataSourceResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.Kendra.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newDescribeDataSource' smart constructor.
data DescribeDataSource = DescribeDataSource'
  { -- | The identifier of the data source connector.
    DescribeDataSource -> Text
id :: Prelude.Text,
    -- | The identifier of the index used with the data source connector.
    DescribeDataSource -> Text
indexId :: Prelude.Text
  }
  deriving (DescribeDataSource -> DescribeDataSource -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeDataSource -> DescribeDataSource -> Bool
$c/= :: DescribeDataSource -> DescribeDataSource -> Bool
== :: DescribeDataSource -> DescribeDataSource -> Bool
$c== :: DescribeDataSource -> DescribeDataSource -> Bool
Prelude.Eq, ReadPrec [DescribeDataSource]
ReadPrec DescribeDataSource
Int -> ReadS DescribeDataSource
ReadS [DescribeDataSource]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeDataSource]
$creadListPrec :: ReadPrec [DescribeDataSource]
readPrec :: ReadPrec DescribeDataSource
$creadPrec :: ReadPrec DescribeDataSource
readList :: ReadS [DescribeDataSource]
$creadList :: ReadS [DescribeDataSource]
readsPrec :: Int -> ReadS DescribeDataSource
$creadsPrec :: Int -> ReadS DescribeDataSource
Prelude.Read, Int -> DescribeDataSource -> ShowS
[DescribeDataSource] -> ShowS
DescribeDataSource -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeDataSource] -> ShowS
$cshowList :: [DescribeDataSource] -> ShowS
show :: DescribeDataSource -> String
$cshow :: DescribeDataSource -> String
showsPrec :: Int -> DescribeDataSource -> ShowS
$cshowsPrec :: Int -> DescribeDataSource -> ShowS
Prelude.Show, forall x. Rep DescribeDataSource x -> DescribeDataSource
forall x. DescribeDataSource -> Rep DescribeDataSource x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeDataSource x -> DescribeDataSource
$cfrom :: forall x. DescribeDataSource -> Rep DescribeDataSource x
Prelude.Generic)

-- |
-- Create a value of 'DescribeDataSource' 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:
--
-- 'id', 'describeDataSource_id' - The identifier of the data source connector.
--
-- 'indexId', 'describeDataSource_indexId' - The identifier of the index used with the data source connector.
newDescribeDataSource ::
  -- | 'id'
  Prelude.Text ->
  -- | 'indexId'
  Prelude.Text ->
  DescribeDataSource
newDescribeDataSource :: Text -> Text -> DescribeDataSource
newDescribeDataSource Text
pId_ Text
pIndexId_ =
  DescribeDataSource' {$sel:id:DescribeDataSource' :: Text
id = Text
pId_, $sel:indexId:DescribeDataSource' :: Text
indexId = Text
pIndexId_}

-- | The identifier of the data source connector.
describeDataSource_id :: Lens.Lens' DescribeDataSource Prelude.Text
describeDataSource_id :: Lens' DescribeDataSource Text
describeDataSource_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDataSource' {Text
id :: Text
$sel:id:DescribeDataSource' :: DescribeDataSource -> Text
id} -> Text
id) (\s :: DescribeDataSource
s@DescribeDataSource' {} Text
a -> DescribeDataSource
s {$sel:id:DescribeDataSource' :: Text
id = Text
a} :: DescribeDataSource)

-- | The identifier of the index used with the data source connector.
describeDataSource_indexId :: Lens.Lens' DescribeDataSource Prelude.Text
describeDataSource_indexId :: Lens' DescribeDataSource Text
describeDataSource_indexId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDataSource' {Text
indexId :: Text
$sel:indexId:DescribeDataSource' :: DescribeDataSource -> Text
indexId} -> Text
indexId) (\s :: DescribeDataSource
s@DescribeDataSource' {} Text
a -> DescribeDataSource
s {$sel:indexId:DescribeDataSource' :: Text
indexId = Text
a} :: DescribeDataSource)

instance Core.AWSRequest DescribeDataSource where
  type
    AWSResponse DescribeDataSource =
      DescribeDataSourceResponse
  request :: (Service -> Service)
-> DescribeDataSource -> Request DescribeDataSource
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DescribeDataSource
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeDataSource)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe DataSourceConfiguration
-> Maybe POSIX
-> Maybe CustomDocumentEnrichmentConfiguration
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe DataSourceStatus
-> Maybe DataSourceType
-> Maybe POSIX
-> Maybe DataSourceVpcConfiguration
-> Int
-> DescribeDataSourceResponse
DescribeDataSourceResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"Configuration")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"CreatedAt")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"CustomDocumentEnrichmentConfiguration")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"Description")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"ErrorMessage")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"Id")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"IndexId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"LanguageCode")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"Name")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"RoleArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"Schedule")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"Status")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"Type")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"UpdatedAt")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"VpcConfiguration")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable DescribeDataSource where
  hashWithSalt :: Int -> DescribeDataSource -> Int
hashWithSalt Int
_salt DescribeDataSource' {Text
indexId :: Text
id :: Text
$sel:indexId:DescribeDataSource' :: DescribeDataSource -> Text
$sel:id:DescribeDataSource' :: DescribeDataSource -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
id
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
indexId

instance Prelude.NFData DescribeDataSource where
  rnf :: DescribeDataSource -> ()
rnf DescribeDataSource' {Text
indexId :: Text
id :: Text
$sel:indexId:DescribeDataSource' :: DescribeDataSource -> Text
$sel:id:DescribeDataSource' :: DescribeDataSource -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
id seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
indexId

instance Data.ToHeaders DescribeDataSource where
  toHeaders :: DescribeDataSource -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"AWSKendraFrontendService.DescribeDataSource" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON DescribeDataSource where
  toJSON :: DescribeDataSource -> Value
toJSON DescribeDataSource' {Text
indexId :: Text
id :: Text
$sel:indexId:DescribeDataSource' :: DescribeDataSource -> Text
$sel:id:DescribeDataSource' :: DescribeDataSource -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just (Key
"Id" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
id),
            forall a. a -> Maybe a
Prelude.Just (Key
"IndexId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
indexId)
          ]
      )

instance Data.ToPath DescribeDataSource where
  toPath :: DescribeDataSource -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

-- | /See:/ 'newDescribeDataSourceResponse' smart constructor.
data DescribeDataSourceResponse = DescribeDataSourceResponse'
  { -- | Configuration details for the data source connector. This shows how the
    -- data source is configured. The configuration options for a data source
    -- depend on the data source provider.
    DescribeDataSourceResponse -> Maybe DataSourceConfiguration
configuration :: Prelude.Maybe DataSourceConfiguration,
    -- | The Unix timestamp of when the data source connector was created.
    DescribeDataSourceResponse -> Maybe POSIX
createdAt :: Prelude.Maybe Data.POSIX,
    -- | Configuration information for altering document metadata and content
    -- during the document ingestion process when you describe a data source.
    --
    -- For more information on how to create, modify and delete document
    -- metadata, or make other content alterations when you ingest documents
    -- into Amazon Kendra, see
    -- <https://docs.aws.amazon.com/kendra/latest/dg/custom-document-enrichment.html Customizing document metadata during the ingestion process>.
    DescribeDataSourceResponse
-> Maybe CustomDocumentEnrichmentConfiguration
customDocumentEnrichmentConfiguration :: Prelude.Maybe CustomDocumentEnrichmentConfiguration,
    -- | The description for the data source connector.
    DescribeDataSourceResponse -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | When the @Status@ field value is @FAILED@, the @ErrorMessage@ field
    -- contains a description of the error that caused the data source to fail.
    DescribeDataSourceResponse -> Maybe Text
errorMessage :: Prelude.Maybe Prelude.Text,
    -- | The identifier of the data source connector.
    DescribeDataSourceResponse -> Maybe Text
id :: Prelude.Maybe Prelude.Text,
    -- | The identifier of the index used with the data source connector.
    DescribeDataSourceResponse -> Maybe Text
indexId :: Prelude.Maybe Prelude.Text,
    -- | The code for a language. This shows a supported language for all
    -- documents in the data source. English is supported by default. For more
    -- information on supported languages, including their codes, see
    -- <https://docs.aws.amazon.com/kendra/latest/dg/in-adding-languages.html Adding documents in languages other than English>.
    DescribeDataSourceResponse -> Maybe Text
languageCode :: Prelude.Maybe Prelude.Text,
    -- | The name for the data source connector.
    DescribeDataSourceResponse -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the role with permission to access the
    -- data source and required resources.
    DescribeDataSourceResponse -> Maybe Text
roleArn :: Prelude.Maybe Prelude.Text,
    -- | The schedule for Amazon Kendra to update the index.
    DescribeDataSourceResponse -> Maybe Text
schedule :: Prelude.Maybe Prelude.Text,
    -- | The current status of the data source connector. When the status is
    -- @ACTIVE@ the data source is ready to use. When the status is @FAILED@,
    -- the @ErrorMessage@ field contains the reason that the data source
    -- failed.
    DescribeDataSourceResponse -> Maybe DataSourceStatus
status :: Prelude.Maybe DataSourceStatus,
    -- | The type of the data source. For example, @SHAREPOINT@.
    DescribeDataSourceResponse -> Maybe DataSourceType
type' :: Prelude.Maybe DataSourceType,
    -- | The Unix timestamp of when the data source connector was last updated.
    DescribeDataSourceResponse -> Maybe POSIX
updatedAt :: Prelude.Maybe Data.POSIX,
    -- | Configuration information for an Amazon Virtual Private Cloud to connect
    -- to your data source. For more information, see
    -- <https://docs.aws.amazon.com/kendra/latest/dg/vpc-configuration.html Configuring a VPC>.
    DescribeDataSourceResponse -> Maybe DataSourceVpcConfiguration
vpcConfiguration :: Prelude.Maybe DataSourceVpcConfiguration,
    -- | The response's http status code.
    DescribeDataSourceResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeDataSourceResponse -> DescribeDataSourceResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeDataSourceResponse -> DescribeDataSourceResponse -> Bool
$c/= :: DescribeDataSourceResponse -> DescribeDataSourceResponse -> Bool
== :: DescribeDataSourceResponse -> DescribeDataSourceResponse -> Bool
$c== :: DescribeDataSourceResponse -> DescribeDataSourceResponse -> Bool
Prelude.Eq, ReadPrec [DescribeDataSourceResponse]
ReadPrec DescribeDataSourceResponse
Int -> ReadS DescribeDataSourceResponse
ReadS [DescribeDataSourceResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeDataSourceResponse]
$creadListPrec :: ReadPrec [DescribeDataSourceResponse]
readPrec :: ReadPrec DescribeDataSourceResponse
$creadPrec :: ReadPrec DescribeDataSourceResponse
readList :: ReadS [DescribeDataSourceResponse]
$creadList :: ReadS [DescribeDataSourceResponse]
readsPrec :: Int -> ReadS DescribeDataSourceResponse
$creadsPrec :: Int -> ReadS DescribeDataSourceResponse
Prelude.Read, Int -> DescribeDataSourceResponse -> ShowS
[DescribeDataSourceResponse] -> ShowS
DescribeDataSourceResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeDataSourceResponse] -> ShowS
$cshowList :: [DescribeDataSourceResponse] -> ShowS
show :: DescribeDataSourceResponse -> String
$cshow :: DescribeDataSourceResponse -> String
showsPrec :: Int -> DescribeDataSourceResponse -> ShowS
$cshowsPrec :: Int -> DescribeDataSourceResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeDataSourceResponse x -> DescribeDataSourceResponse
forall x.
DescribeDataSourceResponse -> Rep DescribeDataSourceResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeDataSourceResponse x -> DescribeDataSourceResponse
$cfrom :: forall x.
DescribeDataSourceResponse -> Rep DescribeDataSourceResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeDataSourceResponse' 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:
--
-- 'configuration', 'describeDataSourceResponse_configuration' - Configuration details for the data source connector. This shows how the
-- data source is configured. The configuration options for a data source
-- depend on the data source provider.
--
-- 'createdAt', 'describeDataSourceResponse_createdAt' - The Unix timestamp of when the data source connector was created.
--
-- 'customDocumentEnrichmentConfiguration', 'describeDataSourceResponse_customDocumentEnrichmentConfiguration' - Configuration information for altering document metadata and content
-- during the document ingestion process when you describe a data source.
--
-- For more information on how to create, modify and delete document
-- metadata, or make other content alterations when you ingest documents
-- into Amazon Kendra, see
-- <https://docs.aws.amazon.com/kendra/latest/dg/custom-document-enrichment.html Customizing document metadata during the ingestion process>.
--
-- 'description', 'describeDataSourceResponse_description' - The description for the data source connector.
--
-- 'errorMessage', 'describeDataSourceResponse_errorMessage' - When the @Status@ field value is @FAILED@, the @ErrorMessage@ field
-- contains a description of the error that caused the data source to fail.
--
-- 'id', 'describeDataSourceResponse_id' - The identifier of the data source connector.
--
-- 'indexId', 'describeDataSourceResponse_indexId' - The identifier of the index used with the data source connector.
--
-- 'languageCode', 'describeDataSourceResponse_languageCode' - The code for a language. This shows a supported language for all
-- documents in the data source. English is supported by default. For more
-- information on supported languages, including their codes, see
-- <https://docs.aws.amazon.com/kendra/latest/dg/in-adding-languages.html Adding documents in languages other than English>.
--
-- 'name', 'describeDataSourceResponse_name' - The name for the data source connector.
--
-- 'roleArn', 'describeDataSourceResponse_roleArn' - The Amazon Resource Name (ARN) of the role with permission to access the
-- data source and required resources.
--
-- 'schedule', 'describeDataSourceResponse_schedule' - The schedule for Amazon Kendra to update the index.
--
-- 'status', 'describeDataSourceResponse_status' - The current status of the data source connector. When the status is
-- @ACTIVE@ the data source is ready to use. When the status is @FAILED@,
-- the @ErrorMessage@ field contains the reason that the data source
-- failed.
--
-- 'type'', 'describeDataSourceResponse_type' - The type of the data source. For example, @SHAREPOINT@.
--
-- 'updatedAt', 'describeDataSourceResponse_updatedAt' - The Unix timestamp of when the data source connector was last updated.
--
-- 'vpcConfiguration', 'describeDataSourceResponse_vpcConfiguration' - Configuration information for an Amazon Virtual Private Cloud to connect
-- to your data source. For more information, see
-- <https://docs.aws.amazon.com/kendra/latest/dg/vpc-configuration.html Configuring a VPC>.
--
-- 'httpStatus', 'describeDataSourceResponse_httpStatus' - The response's http status code.
newDescribeDataSourceResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeDataSourceResponse
newDescribeDataSourceResponse :: Int -> DescribeDataSourceResponse
newDescribeDataSourceResponse Int
pHttpStatus_ =
  DescribeDataSourceResponse'
    { $sel:configuration:DescribeDataSourceResponse' :: Maybe DataSourceConfiguration
configuration =
        forall a. Maybe a
Prelude.Nothing,
      $sel:createdAt:DescribeDataSourceResponse' :: Maybe POSIX
createdAt = forall a. Maybe a
Prelude.Nothing,
      $sel:customDocumentEnrichmentConfiguration:DescribeDataSourceResponse' :: Maybe CustomDocumentEnrichmentConfiguration
customDocumentEnrichmentConfiguration =
        forall a. Maybe a
Prelude.Nothing,
      $sel:description:DescribeDataSourceResponse' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:errorMessage:DescribeDataSourceResponse' :: Maybe Text
errorMessage = forall a. Maybe a
Prelude.Nothing,
      $sel:id:DescribeDataSourceResponse' :: Maybe Text
id = forall a. Maybe a
Prelude.Nothing,
      $sel:indexId:DescribeDataSourceResponse' :: Maybe Text
indexId = forall a. Maybe a
Prelude.Nothing,
      $sel:languageCode:DescribeDataSourceResponse' :: Maybe Text
languageCode = forall a. Maybe a
Prelude.Nothing,
      $sel:name:DescribeDataSourceResponse' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:roleArn:DescribeDataSourceResponse' :: Maybe Text
roleArn = forall a. Maybe a
Prelude.Nothing,
      $sel:schedule:DescribeDataSourceResponse' :: Maybe Text
schedule = forall a. Maybe a
Prelude.Nothing,
      $sel:status:DescribeDataSourceResponse' :: Maybe DataSourceStatus
status = forall a. Maybe a
Prelude.Nothing,
      $sel:type':DescribeDataSourceResponse' :: Maybe DataSourceType
type' = forall a. Maybe a
Prelude.Nothing,
      $sel:updatedAt:DescribeDataSourceResponse' :: Maybe POSIX
updatedAt = forall a. Maybe a
Prelude.Nothing,
      $sel:vpcConfiguration:DescribeDataSourceResponse' :: Maybe DataSourceVpcConfiguration
vpcConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeDataSourceResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Configuration details for the data source connector. This shows how the
-- data source is configured. The configuration options for a data source
-- depend on the data source provider.
describeDataSourceResponse_configuration :: Lens.Lens' DescribeDataSourceResponse (Prelude.Maybe DataSourceConfiguration)
describeDataSourceResponse_configuration :: Lens' DescribeDataSourceResponse (Maybe DataSourceConfiguration)
describeDataSourceResponse_configuration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDataSourceResponse' {Maybe DataSourceConfiguration
configuration :: Maybe DataSourceConfiguration
$sel:configuration:DescribeDataSourceResponse' :: DescribeDataSourceResponse -> Maybe DataSourceConfiguration
configuration} -> Maybe DataSourceConfiguration
configuration) (\s :: DescribeDataSourceResponse
s@DescribeDataSourceResponse' {} Maybe DataSourceConfiguration
a -> DescribeDataSourceResponse
s {$sel:configuration:DescribeDataSourceResponse' :: Maybe DataSourceConfiguration
configuration = Maybe DataSourceConfiguration
a} :: DescribeDataSourceResponse)

-- | The Unix timestamp of when the data source connector was created.
describeDataSourceResponse_createdAt :: Lens.Lens' DescribeDataSourceResponse (Prelude.Maybe Prelude.UTCTime)
describeDataSourceResponse_createdAt :: Lens' DescribeDataSourceResponse (Maybe UTCTime)
describeDataSourceResponse_createdAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDataSourceResponse' {Maybe POSIX
createdAt :: Maybe POSIX
$sel:createdAt:DescribeDataSourceResponse' :: DescribeDataSourceResponse -> Maybe POSIX
createdAt} -> Maybe POSIX
createdAt) (\s :: DescribeDataSourceResponse
s@DescribeDataSourceResponse' {} Maybe POSIX
a -> DescribeDataSourceResponse
s {$sel:createdAt:DescribeDataSourceResponse' :: Maybe POSIX
createdAt = Maybe POSIX
a} :: DescribeDataSourceResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | Configuration information for altering document metadata and content
-- during the document ingestion process when you describe a data source.
--
-- For more information on how to create, modify and delete document
-- metadata, or make other content alterations when you ingest documents
-- into Amazon Kendra, see
-- <https://docs.aws.amazon.com/kendra/latest/dg/custom-document-enrichment.html Customizing document metadata during the ingestion process>.
describeDataSourceResponse_customDocumentEnrichmentConfiguration :: Lens.Lens' DescribeDataSourceResponse (Prelude.Maybe CustomDocumentEnrichmentConfiguration)
describeDataSourceResponse_customDocumentEnrichmentConfiguration :: Lens'
  DescribeDataSourceResponse
  (Maybe CustomDocumentEnrichmentConfiguration)
describeDataSourceResponse_customDocumentEnrichmentConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDataSourceResponse' {Maybe CustomDocumentEnrichmentConfiguration
customDocumentEnrichmentConfiguration :: Maybe CustomDocumentEnrichmentConfiguration
$sel:customDocumentEnrichmentConfiguration:DescribeDataSourceResponse' :: DescribeDataSourceResponse
-> Maybe CustomDocumentEnrichmentConfiguration
customDocumentEnrichmentConfiguration} -> Maybe CustomDocumentEnrichmentConfiguration
customDocumentEnrichmentConfiguration) (\s :: DescribeDataSourceResponse
s@DescribeDataSourceResponse' {} Maybe CustomDocumentEnrichmentConfiguration
a -> DescribeDataSourceResponse
s {$sel:customDocumentEnrichmentConfiguration:DescribeDataSourceResponse' :: Maybe CustomDocumentEnrichmentConfiguration
customDocumentEnrichmentConfiguration = Maybe CustomDocumentEnrichmentConfiguration
a} :: DescribeDataSourceResponse)

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

-- | When the @Status@ field value is @FAILED@, the @ErrorMessage@ field
-- contains a description of the error that caused the data source to fail.
describeDataSourceResponse_errorMessage :: Lens.Lens' DescribeDataSourceResponse (Prelude.Maybe Prelude.Text)
describeDataSourceResponse_errorMessage :: Lens' DescribeDataSourceResponse (Maybe Text)
describeDataSourceResponse_errorMessage = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDataSourceResponse' {Maybe Text
errorMessage :: Maybe Text
$sel:errorMessage:DescribeDataSourceResponse' :: DescribeDataSourceResponse -> Maybe Text
errorMessage} -> Maybe Text
errorMessage) (\s :: DescribeDataSourceResponse
s@DescribeDataSourceResponse' {} Maybe Text
a -> DescribeDataSourceResponse
s {$sel:errorMessage:DescribeDataSourceResponse' :: Maybe Text
errorMessage = Maybe Text
a} :: DescribeDataSourceResponse)

-- | The identifier of the data source connector.
describeDataSourceResponse_id :: Lens.Lens' DescribeDataSourceResponse (Prelude.Maybe Prelude.Text)
describeDataSourceResponse_id :: Lens' DescribeDataSourceResponse (Maybe Text)
describeDataSourceResponse_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDataSourceResponse' {Maybe Text
id :: Maybe Text
$sel:id:DescribeDataSourceResponse' :: DescribeDataSourceResponse -> Maybe Text
id} -> Maybe Text
id) (\s :: DescribeDataSourceResponse
s@DescribeDataSourceResponse' {} Maybe Text
a -> DescribeDataSourceResponse
s {$sel:id:DescribeDataSourceResponse' :: Maybe Text
id = Maybe Text
a} :: DescribeDataSourceResponse)

-- | The identifier of the index used with the data source connector.
describeDataSourceResponse_indexId :: Lens.Lens' DescribeDataSourceResponse (Prelude.Maybe Prelude.Text)
describeDataSourceResponse_indexId :: Lens' DescribeDataSourceResponse (Maybe Text)
describeDataSourceResponse_indexId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDataSourceResponse' {Maybe Text
indexId :: Maybe Text
$sel:indexId:DescribeDataSourceResponse' :: DescribeDataSourceResponse -> Maybe Text
indexId} -> Maybe Text
indexId) (\s :: DescribeDataSourceResponse
s@DescribeDataSourceResponse' {} Maybe Text
a -> DescribeDataSourceResponse
s {$sel:indexId:DescribeDataSourceResponse' :: Maybe Text
indexId = Maybe Text
a} :: DescribeDataSourceResponse)

-- | The code for a language. This shows a supported language for all
-- documents in the data source. English is supported by default. For more
-- information on supported languages, including their codes, see
-- <https://docs.aws.amazon.com/kendra/latest/dg/in-adding-languages.html Adding documents in languages other than English>.
describeDataSourceResponse_languageCode :: Lens.Lens' DescribeDataSourceResponse (Prelude.Maybe Prelude.Text)
describeDataSourceResponse_languageCode :: Lens' DescribeDataSourceResponse (Maybe Text)
describeDataSourceResponse_languageCode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDataSourceResponse' {Maybe Text
languageCode :: Maybe Text
$sel:languageCode:DescribeDataSourceResponse' :: DescribeDataSourceResponse -> Maybe Text
languageCode} -> Maybe Text
languageCode) (\s :: DescribeDataSourceResponse
s@DescribeDataSourceResponse' {} Maybe Text
a -> DescribeDataSourceResponse
s {$sel:languageCode:DescribeDataSourceResponse' :: Maybe Text
languageCode = Maybe Text
a} :: DescribeDataSourceResponse)

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

-- | The Amazon Resource Name (ARN) of the role with permission to access the
-- data source and required resources.
describeDataSourceResponse_roleArn :: Lens.Lens' DescribeDataSourceResponse (Prelude.Maybe Prelude.Text)
describeDataSourceResponse_roleArn :: Lens' DescribeDataSourceResponse (Maybe Text)
describeDataSourceResponse_roleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDataSourceResponse' {Maybe Text
roleArn :: Maybe Text
$sel:roleArn:DescribeDataSourceResponse' :: DescribeDataSourceResponse -> Maybe Text
roleArn} -> Maybe Text
roleArn) (\s :: DescribeDataSourceResponse
s@DescribeDataSourceResponse' {} Maybe Text
a -> DescribeDataSourceResponse
s {$sel:roleArn:DescribeDataSourceResponse' :: Maybe Text
roleArn = Maybe Text
a} :: DescribeDataSourceResponse)

-- | The schedule for Amazon Kendra to update the index.
describeDataSourceResponse_schedule :: Lens.Lens' DescribeDataSourceResponse (Prelude.Maybe Prelude.Text)
describeDataSourceResponse_schedule :: Lens' DescribeDataSourceResponse (Maybe Text)
describeDataSourceResponse_schedule = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDataSourceResponse' {Maybe Text
schedule :: Maybe Text
$sel:schedule:DescribeDataSourceResponse' :: DescribeDataSourceResponse -> Maybe Text
schedule} -> Maybe Text
schedule) (\s :: DescribeDataSourceResponse
s@DescribeDataSourceResponse' {} Maybe Text
a -> DescribeDataSourceResponse
s {$sel:schedule:DescribeDataSourceResponse' :: Maybe Text
schedule = Maybe Text
a} :: DescribeDataSourceResponse)

-- | The current status of the data source connector. When the status is
-- @ACTIVE@ the data source is ready to use. When the status is @FAILED@,
-- the @ErrorMessage@ field contains the reason that the data source
-- failed.
describeDataSourceResponse_status :: Lens.Lens' DescribeDataSourceResponse (Prelude.Maybe DataSourceStatus)
describeDataSourceResponse_status :: Lens' DescribeDataSourceResponse (Maybe DataSourceStatus)
describeDataSourceResponse_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDataSourceResponse' {Maybe DataSourceStatus
status :: Maybe DataSourceStatus
$sel:status:DescribeDataSourceResponse' :: DescribeDataSourceResponse -> Maybe DataSourceStatus
status} -> Maybe DataSourceStatus
status) (\s :: DescribeDataSourceResponse
s@DescribeDataSourceResponse' {} Maybe DataSourceStatus
a -> DescribeDataSourceResponse
s {$sel:status:DescribeDataSourceResponse' :: Maybe DataSourceStatus
status = Maybe DataSourceStatus
a} :: DescribeDataSourceResponse)

-- | The type of the data source. For example, @SHAREPOINT@.
describeDataSourceResponse_type :: Lens.Lens' DescribeDataSourceResponse (Prelude.Maybe DataSourceType)
describeDataSourceResponse_type :: Lens' DescribeDataSourceResponse (Maybe DataSourceType)
describeDataSourceResponse_type = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDataSourceResponse' {Maybe DataSourceType
type' :: Maybe DataSourceType
$sel:type':DescribeDataSourceResponse' :: DescribeDataSourceResponse -> Maybe DataSourceType
type'} -> Maybe DataSourceType
type') (\s :: DescribeDataSourceResponse
s@DescribeDataSourceResponse' {} Maybe DataSourceType
a -> DescribeDataSourceResponse
s {$sel:type':DescribeDataSourceResponse' :: Maybe DataSourceType
type' = Maybe DataSourceType
a} :: DescribeDataSourceResponse)

-- | The Unix timestamp of when the data source connector was last updated.
describeDataSourceResponse_updatedAt :: Lens.Lens' DescribeDataSourceResponse (Prelude.Maybe Prelude.UTCTime)
describeDataSourceResponse_updatedAt :: Lens' DescribeDataSourceResponse (Maybe UTCTime)
describeDataSourceResponse_updatedAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDataSourceResponse' {Maybe POSIX
updatedAt :: Maybe POSIX
$sel:updatedAt:DescribeDataSourceResponse' :: DescribeDataSourceResponse -> Maybe POSIX
updatedAt} -> Maybe POSIX
updatedAt) (\s :: DescribeDataSourceResponse
s@DescribeDataSourceResponse' {} Maybe POSIX
a -> DescribeDataSourceResponse
s {$sel:updatedAt:DescribeDataSourceResponse' :: Maybe POSIX
updatedAt = Maybe POSIX
a} :: DescribeDataSourceResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | Configuration information for an Amazon Virtual Private Cloud to connect
-- to your data source. For more information, see
-- <https://docs.aws.amazon.com/kendra/latest/dg/vpc-configuration.html Configuring a VPC>.
describeDataSourceResponse_vpcConfiguration :: Lens.Lens' DescribeDataSourceResponse (Prelude.Maybe DataSourceVpcConfiguration)
describeDataSourceResponse_vpcConfiguration :: Lens' DescribeDataSourceResponse (Maybe DataSourceVpcConfiguration)
describeDataSourceResponse_vpcConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDataSourceResponse' {Maybe DataSourceVpcConfiguration
vpcConfiguration :: Maybe DataSourceVpcConfiguration
$sel:vpcConfiguration:DescribeDataSourceResponse' :: DescribeDataSourceResponse -> Maybe DataSourceVpcConfiguration
vpcConfiguration} -> Maybe DataSourceVpcConfiguration
vpcConfiguration) (\s :: DescribeDataSourceResponse
s@DescribeDataSourceResponse' {} Maybe DataSourceVpcConfiguration
a -> DescribeDataSourceResponse
s {$sel:vpcConfiguration:DescribeDataSourceResponse' :: Maybe DataSourceVpcConfiguration
vpcConfiguration = Maybe DataSourceVpcConfiguration
a} :: DescribeDataSourceResponse)

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

instance Prelude.NFData DescribeDataSourceResponse where
  rnf :: DescribeDataSourceResponse -> ()
rnf DescribeDataSourceResponse' {Int
Maybe Text
Maybe POSIX
Maybe DataSourceStatus
Maybe DataSourceType
Maybe DataSourceVpcConfiguration
Maybe CustomDocumentEnrichmentConfiguration
Maybe DataSourceConfiguration
httpStatus :: Int
vpcConfiguration :: Maybe DataSourceVpcConfiguration
updatedAt :: Maybe POSIX
type' :: Maybe DataSourceType
status :: Maybe DataSourceStatus
schedule :: Maybe Text
roleArn :: Maybe Text
name :: Maybe Text
languageCode :: Maybe Text
indexId :: Maybe Text
id :: Maybe Text
errorMessage :: Maybe Text
description :: Maybe Text
customDocumentEnrichmentConfiguration :: Maybe CustomDocumentEnrichmentConfiguration
createdAt :: Maybe POSIX
configuration :: Maybe DataSourceConfiguration
$sel:httpStatus:DescribeDataSourceResponse' :: DescribeDataSourceResponse -> Int
$sel:vpcConfiguration:DescribeDataSourceResponse' :: DescribeDataSourceResponse -> Maybe DataSourceVpcConfiguration
$sel:updatedAt:DescribeDataSourceResponse' :: DescribeDataSourceResponse -> Maybe POSIX
$sel:type':DescribeDataSourceResponse' :: DescribeDataSourceResponse -> Maybe DataSourceType
$sel:status:DescribeDataSourceResponse' :: DescribeDataSourceResponse -> Maybe DataSourceStatus
$sel:schedule:DescribeDataSourceResponse' :: DescribeDataSourceResponse -> Maybe Text
$sel:roleArn:DescribeDataSourceResponse' :: DescribeDataSourceResponse -> Maybe Text
$sel:name:DescribeDataSourceResponse' :: DescribeDataSourceResponse -> Maybe Text
$sel:languageCode:DescribeDataSourceResponse' :: DescribeDataSourceResponse -> Maybe Text
$sel:indexId:DescribeDataSourceResponse' :: DescribeDataSourceResponse -> Maybe Text
$sel:id:DescribeDataSourceResponse' :: DescribeDataSourceResponse -> Maybe Text
$sel:errorMessage:DescribeDataSourceResponse' :: DescribeDataSourceResponse -> Maybe Text
$sel:description:DescribeDataSourceResponse' :: DescribeDataSourceResponse -> Maybe Text
$sel:customDocumentEnrichmentConfiguration:DescribeDataSourceResponse' :: DescribeDataSourceResponse
-> Maybe CustomDocumentEnrichmentConfiguration
$sel:createdAt:DescribeDataSourceResponse' :: DescribeDataSourceResponse -> Maybe POSIX
$sel:configuration:DescribeDataSourceResponse' :: DescribeDataSourceResponse -> Maybe DataSourceConfiguration
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe DataSourceConfiguration
configuration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
createdAt
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe CustomDocumentEnrichmentConfiguration
customDocumentEnrichmentConfiguration
      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
errorMessage
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
id
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
indexId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
languageCode
      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
roleArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
schedule
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DataSourceStatus
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DataSourceType
type'
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
updatedAt
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DataSourceVpcConfiguration
vpcConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus