{-# 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.DeleteDataSource
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Deletes an Amazon Kendra data source connector. An exception is not
-- thrown if the data source is already being deleted. While the data
-- source is being deleted, the @Status@ field returned by a call to the
-- @DescribeDataSource@ API is set to @DELETING@. For more information, see
-- <https://docs.aws.amazon.com/kendra/latest/dg/delete-data-source.html Deleting Data Sources>.
module Amazonka.Kendra.DeleteDataSource
  ( -- * Creating a Request
    DeleteDataSource (..),
    newDeleteDataSource,

    -- * Request Lenses
    deleteDataSource_id,
    deleteDataSource_indexId,

    -- * Destructuring the Response
    DeleteDataSourceResponse (..),
    newDeleteDataSourceResponse,
  )
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:/ 'newDeleteDataSource' smart constructor.
data DeleteDataSource = DeleteDataSource'
  { -- | The identifier of the data source connector you want to delete.
    DeleteDataSource -> Text
id :: Prelude.Text,
    -- | The identifier of the index used with the data source connector.
    DeleteDataSource -> Text
indexId :: Prelude.Text
  }
  deriving (DeleteDataSource -> DeleteDataSource -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteDataSource -> DeleteDataSource -> Bool
$c/= :: DeleteDataSource -> DeleteDataSource -> Bool
== :: DeleteDataSource -> DeleteDataSource -> Bool
$c== :: DeleteDataSource -> DeleteDataSource -> Bool
Prelude.Eq, ReadPrec [DeleteDataSource]
ReadPrec DeleteDataSource
Int -> ReadS DeleteDataSource
ReadS [DeleteDataSource]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteDataSource]
$creadListPrec :: ReadPrec [DeleteDataSource]
readPrec :: ReadPrec DeleteDataSource
$creadPrec :: ReadPrec DeleteDataSource
readList :: ReadS [DeleteDataSource]
$creadList :: ReadS [DeleteDataSource]
readsPrec :: Int -> ReadS DeleteDataSource
$creadsPrec :: Int -> ReadS DeleteDataSource
Prelude.Read, Int -> DeleteDataSource -> ShowS
[DeleteDataSource] -> ShowS
DeleteDataSource -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteDataSource] -> ShowS
$cshowList :: [DeleteDataSource] -> ShowS
show :: DeleteDataSource -> String
$cshow :: DeleteDataSource -> String
showsPrec :: Int -> DeleteDataSource -> ShowS
$cshowsPrec :: Int -> DeleteDataSource -> ShowS
Prelude.Show, forall x. Rep DeleteDataSource x -> DeleteDataSource
forall x. DeleteDataSource -> Rep DeleteDataSource x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteDataSource x -> DeleteDataSource
$cfrom :: forall x. DeleteDataSource -> Rep DeleteDataSource x
Prelude.Generic)

-- |
-- Create a value of 'DeleteDataSource' 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', 'deleteDataSource_id' - The identifier of the data source connector you want to delete.
--
-- 'indexId', 'deleteDataSource_indexId' - The identifier of the index used with the data source connector.
newDeleteDataSource ::
  -- | 'id'
  Prelude.Text ->
  -- | 'indexId'
  Prelude.Text ->
  DeleteDataSource
newDeleteDataSource :: Text -> Text -> DeleteDataSource
newDeleteDataSource Text
pId_ Text
pIndexId_ =
  DeleteDataSource' {$sel:id:DeleteDataSource' :: Text
id = Text
pId_, $sel:indexId:DeleteDataSource' :: Text
indexId = Text
pIndexId_}

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

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

instance Core.AWSRequest DeleteDataSource where
  type
    AWSResponse DeleteDataSource =
      DeleteDataSourceResponse
  request :: (Service -> Service)
-> DeleteDataSource -> Request DeleteDataSource
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 DeleteDataSource
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DeleteDataSource)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull DeleteDataSourceResponse
DeleteDataSourceResponse'

instance Prelude.Hashable DeleteDataSource where
  hashWithSalt :: Int -> DeleteDataSource -> Int
hashWithSalt Int
_salt DeleteDataSource' {Text
indexId :: Text
id :: Text
$sel:indexId:DeleteDataSource' :: DeleteDataSource -> Text
$sel:id:DeleteDataSource' :: DeleteDataSource -> 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 DeleteDataSource where
  rnf :: DeleteDataSource -> ()
rnf DeleteDataSource' {Text
indexId :: Text
id :: Text
$sel:indexId:DeleteDataSource' :: DeleteDataSource -> Text
$sel:id:DeleteDataSource' :: DeleteDataSource -> 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 DeleteDataSource where
  toHeaders :: DeleteDataSource -> [Header]
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 -> [Header]
Data.=# ( ByteString
"AWSKendraFrontendService.DeleteDataSource" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> [Header]
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON DeleteDataSource where
  toJSON :: DeleteDataSource -> Value
toJSON DeleteDataSource' {Text
indexId :: Text
id :: Text
$sel:indexId:DeleteDataSource' :: DeleteDataSource -> Text
$sel:id:DeleteDataSource' :: DeleteDataSource -> 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 DeleteDataSource where
  toPath :: DeleteDataSource -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

-- | /See:/ 'newDeleteDataSourceResponse' smart constructor.
data DeleteDataSourceResponse = DeleteDataSourceResponse'
  {
  }
  deriving (DeleteDataSourceResponse -> DeleteDataSourceResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteDataSourceResponse -> DeleteDataSourceResponse -> Bool
$c/= :: DeleteDataSourceResponse -> DeleteDataSourceResponse -> Bool
== :: DeleteDataSourceResponse -> DeleteDataSourceResponse -> Bool
$c== :: DeleteDataSourceResponse -> DeleteDataSourceResponse -> Bool
Prelude.Eq, ReadPrec [DeleteDataSourceResponse]
ReadPrec DeleteDataSourceResponse
Int -> ReadS DeleteDataSourceResponse
ReadS [DeleteDataSourceResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteDataSourceResponse]
$creadListPrec :: ReadPrec [DeleteDataSourceResponse]
readPrec :: ReadPrec DeleteDataSourceResponse
$creadPrec :: ReadPrec DeleteDataSourceResponse
readList :: ReadS [DeleteDataSourceResponse]
$creadList :: ReadS [DeleteDataSourceResponse]
readsPrec :: Int -> ReadS DeleteDataSourceResponse
$creadsPrec :: Int -> ReadS DeleteDataSourceResponse
Prelude.Read, Int -> DeleteDataSourceResponse -> ShowS
[DeleteDataSourceResponse] -> ShowS
DeleteDataSourceResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteDataSourceResponse] -> ShowS
$cshowList :: [DeleteDataSourceResponse] -> ShowS
show :: DeleteDataSourceResponse -> String
$cshow :: DeleteDataSourceResponse -> String
showsPrec :: Int -> DeleteDataSourceResponse -> ShowS
$cshowsPrec :: Int -> DeleteDataSourceResponse -> ShowS
Prelude.Show, forall x.
Rep DeleteDataSourceResponse x -> DeleteDataSourceResponse
forall x.
DeleteDataSourceResponse -> Rep DeleteDataSourceResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeleteDataSourceResponse x -> DeleteDataSourceResponse
$cfrom :: forall x.
DeleteDataSourceResponse -> Rep DeleteDataSourceResponse x
Prelude.Generic)

-- |
-- Create a value of 'DeleteDataSourceResponse' 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.
newDeleteDataSourceResponse ::
  DeleteDataSourceResponse
newDeleteDataSourceResponse :: DeleteDataSourceResponse
newDeleteDataSourceResponse =
  DeleteDataSourceResponse
DeleteDataSourceResponse'

instance Prelude.NFData DeleteDataSourceResponse where
  rnf :: DeleteDataSourceResponse -> ()
rnf DeleteDataSourceResponse
_ = ()