{-# 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.DeleteFaq
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Removes an FAQ from an index.
module Amazonka.Kendra.DeleteFaq
  ( -- * Creating a Request
    DeleteFaq (..),
    newDeleteFaq,

    -- * Request Lenses
    deleteFaq_id,
    deleteFaq_indexId,

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

-- |
-- Create a value of 'DeleteFaq' 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', 'deleteFaq_id' - The identifier of the FAQ you want to remove.
--
-- 'indexId', 'deleteFaq_indexId' - The identifier of the index for the FAQ.
newDeleteFaq ::
  -- | 'id'
  Prelude.Text ->
  -- | 'indexId'
  Prelude.Text ->
  DeleteFaq
newDeleteFaq :: Text -> Text -> DeleteFaq
newDeleteFaq Text
pId_ Text
pIndexId_ =
  DeleteFaq' {$sel:id:DeleteFaq' :: Text
id = Text
pId_, $sel:indexId:DeleteFaq' :: Text
indexId = Text
pIndexId_}

-- | The identifier of the FAQ you want to remove.
deleteFaq_id :: Lens.Lens' DeleteFaq Prelude.Text
deleteFaq_id :: Lens' DeleteFaq Text
deleteFaq_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteFaq' {Text
id :: Text
$sel:id:DeleteFaq' :: DeleteFaq -> Text
id} -> Text
id) (\s :: DeleteFaq
s@DeleteFaq' {} Text
a -> DeleteFaq
s {$sel:id:DeleteFaq' :: Text
id = Text
a} :: DeleteFaq)

-- | The identifier of the index for the FAQ.
deleteFaq_indexId :: Lens.Lens' DeleteFaq Prelude.Text
deleteFaq_indexId :: Lens' DeleteFaq Text
deleteFaq_indexId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteFaq' {Text
indexId :: Text
$sel:indexId:DeleteFaq' :: DeleteFaq -> Text
indexId} -> Text
indexId) (\s :: DeleteFaq
s@DeleteFaq' {} Text
a -> DeleteFaq
s {$sel:indexId:DeleteFaq' :: Text
indexId = Text
a} :: DeleteFaq)

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

instance Prelude.Hashable DeleteFaq where
  hashWithSalt :: Int -> DeleteFaq -> Int
hashWithSalt Int
_salt DeleteFaq' {Text
indexId :: Text
id :: Text
$sel:indexId:DeleteFaq' :: DeleteFaq -> Text
$sel:id:DeleteFaq' :: DeleteFaq -> 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 DeleteFaq where
  rnf :: DeleteFaq -> ()
rnf DeleteFaq' {Text
indexId :: Text
id :: Text
$sel:indexId:DeleteFaq' :: DeleteFaq -> Text
$sel:id:DeleteFaq' :: DeleteFaq -> 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 DeleteFaq where
  toHeaders :: DeleteFaq -> [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.DeleteFaq" ::
                          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 DeleteFaq where
  toJSON :: DeleteFaq -> Value
toJSON DeleteFaq' {Text
indexId :: Text
id :: Text
$sel:indexId:DeleteFaq' :: DeleteFaq -> Text
$sel:id:DeleteFaq' :: DeleteFaq -> 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 DeleteFaq where
  toPath :: DeleteFaq -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

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

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

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