{-# 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.Wisdom.DeleteKnowledgeBase
-- 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 the knowledge base.
--
-- When you use this API to delete an external knowledge base such as
-- Salesforce or ServiceNow, you must also delete the
-- <https://docs.aws.amazon.com/appintegrations/latest/APIReference/Welcome.html Amazon AppIntegrations>
-- DataIntegration. This is because you can\'t reuse the DataIntegration
-- after it\'s been associated with an external knowledge base. However,
-- you can delete and recreate it. See
-- <https://docs.aws.amazon.com/appintegrations/latest/APIReference/API_DeleteDataIntegration.html DeleteDataIntegration>
-- and
-- <https://docs.aws.amazon.com/appintegrations/latest/APIReference/API_CreateDataIntegration.html CreateDataIntegration>
-- in the /Amazon AppIntegrations API Reference/.
module Amazonka.Wisdom.DeleteKnowledgeBase
  ( -- * Creating a Request
    DeleteKnowledgeBase (..),
    newDeleteKnowledgeBase,

    -- * Request Lenses
    deleteKnowledgeBase_knowledgeBaseId,

    -- * Destructuring the Response
    DeleteKnowledgeBaseResponse (..),
    newDeleteKnowledgeBaseResponse,

    -- * Response Lenses
    deleteKnowledgeBaseResponse_httpStatus,
  )
where

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
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
import Amazonka.Wisdom.Types

-- | /See:/ 'newDeleteKnowledgeBase' smart constructor.
data DeleteKnowledgeBase = DeleteKnowledgeBase'
  { -- | The knowledge base to delete content from. Can be either the ID or the
    -- ARN. URLs cannot contain the ARN.
    DeleteKnowledgeBase -> Text
knowledgeBaseId :: Prelude.Text
  }
  deriving (DeleteKnowledgeBase -> DeleteKnowledgeBase -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteKnowledgeBase -> DeleteKnowledgeBase -> Bool
$c/= :: DeleteKnowledgeBase -> DeleteKnowledgeBase -> Bool
== :: DeleteKnowledgeBase -> DeleteKnowledgeBase -> Bool
$c== :: DeleteKnowledgeBase -> DeleteKnowledgeBase -> Bool
Prelude.Eq, ReadPrec [DeleteKnowledgeBase]
ReadPrec DeleteKnowledgeBase
Int -> ReadS DeleteKnowledgeBase
ReadS [DeleteKnowledgeBase]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteKnowledgeBase]
$creadListPrec :: ReadPrec [DeleteKnowledgeBase]
readPrec :: ReadPrec DeleteKnowledgeBase
$creadPrec :: ReadPrec DeleteKnowledgeBase
readList :: ReadS [DeleteKnowledgeBase]
$creadList :: ReadS [DeleteKnowledgeBase]
readsPrec :: Int -> ReadS DeleteKnowledgeBase
$creadsPrec :: Int -> ReadS DeleteKnowledgeBase
Prelude.Read, Int -> DeleteKnowledgeBase -> ShowS
[DeleteKnowledgeBase] -> ShowS
DeleteKnowledgeBase -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteKnowledgeBase] -> ShowS
$cshowList :: [DeleteKnowledgeBase] -> ShowS
show :: DeleteKnowledgeBase -> String
$cshow :: DeleteKnowledgeBase -> String
showsPrec :: Int -> DeleteKnowledgeBase -> ShowS
$cshowsPrec :: Int -> DeleteKnowledgeBase -> ShowS
Prelude.Show, forall x. Rep DeleteKnowledgeBase x -> DeleteKnowledgeBase
forall x. DeleteKnowledgeBase -> Rep DeleteKnowledgeBase x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteKnowledgeBase x -> DeleteKnowledgeBase
$cfrom :: forall x. DeleteKnowledgeBase -> Rep DeleteKnowledgeBase x
Prelude.Generic)

-- |
-- Create a value of 'DeleteKnowledgeBase' 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:
--
-- 'knowledgeBaseId', 'deleteKnowledgeBase_knowledgeBaseId' - The knowledge base to delete content from. Can be either the ID or the
-- ARN. URLs cannot contain the ARN.
newDeleteKnowledgeBase ::
  -- | 'knowledgeBaseId'
  Prelude.Text ->
  DeleteKnowledgeBase
newDeleteKnowledgeBase :: Text -> DeleteKnowledgeBase
newDeleteKnowledgeBase Text
pKnowledgeBaseId_ =
  DeleteKnowledgeBase'
    { $sel:knowledgeBaseId:DeleteKnowledgeBase' :: Text
knowledgeBaseId =
        Text
pKnowledgeBaseId_
    }

-- | The knowledge base to delete content from. Can be either the ID or the
-- ARN. URLs cannot contain the ARN.
deleteKnowledgeBase_knowledgeBaseId :: Lens.Lens' DeleteKnowledgeBase Prelude.Text
deleteKnowledgeBase_knowledgeBaseId :: Lens' DeleteKnowledgeBase Text
deleteKnowledgeBase_knowledgeBaseId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteKnowledgeBase' {Text
knowledgeBaseId :: Text
$sel:knowledgeBaseId:DeleteKnowledgeBase' :: DeleteKnowledgeBase -> Text
knowledgeBaseId} -> Text
knowledgeBaseId) (\s :: DeleteKnowledgeBase
s@DeleteKnowledgeBase' {} Text
a -> DeleteKnowledgeBase
s {$sel:knowledgeBaseId:DeleteKnowledgeBase' :: Text
knowledgeBaseId = Text
a} :: DeleteKnowledgeBase)

instance Core.AWSRequest DeleteKnowledgeBase where
  type
    AWSResponse DeleteKnowledgeBase =
      DeleteKnowledgeBaseResponse
  request :: (Service -> Service)
-> DeleteKnowledgeBase -> Request DeleteKnowledgeBase
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.delete (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DeleteKnowledgeBase
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DeleteKnowledgeBase)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> () -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveEmpty
      ( \Int
s ResponseHeaders
h ()
x ->
          Int -> DeleteKnowledgeBaseResponse
DeleteKnowledgeBaseResponse'
            forall (f :: * -> *) a b. Functor 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 DeleteKnowledgeBase where
  hashWithSalt :: Int -> DeleteKnowledgeBase -> Int
hashWithSalt Int
_salt DeleteKnowledgeBase' {Text
knowledgeBaseId :: Text
$sel:knowledgeBaseId:DeleteKnowledgeBase' :: DeleteKnowledgeBase -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
knowledgeBaseId

instance Prelude.NFData DeleteKnowledgeBase where
  rnf :: DeleteKnowledgeBase -> ()
rnf DeleteKnowledgeBase' {Text
knowledgeBaseId :: Text
$sel:knowledgeBaseId:DeleteKnowledgeBase' :: DeleteKnowledgeBase -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
knowledgeBaseId

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

instance Data.ToPath DeleteKnowledgeBase where
  toPath :: DeleteKnowledgeBase -> ByteString
toPath DeleteKnowledgeBase' {Text
knowledgeBaseId :: Text
$sel:knowledgeBaseId:DeleteKnowledgeBase' :: DeleteKnowledgeBase -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/knowledgeBases/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
knowledgeBaseId]

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

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

-- |
-- Create a value of 'DeleteKnowledgeBaseResponse' 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:
--
-- 'httpStatus', 'deleteKnowledgeBaseResponse_httpStatus' - The response's http status code.
newDeleteKnowledgeBaseResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DeleteKnowledgeBaseResponse
newDeleteKnowledgeBaseResponse :: Int -> DeleteKnowledgeBaseResponse
newDeleteKnowledgeBaseResponse Int
pHttpStatus_ =
  DeleteKnowledgeBaseResponse'
    { $sel:httpStatus:DeleteKnowledgeBaseResponse' :: Int
httpStatus =
        Int
pHttpStatus_
    }

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

instance Prelude.NFData DeleteKnowledgeBaseResponse where
  rnf :: DeleteKnowledgeBaseResponse -> ()
rnf DeleteKnowledgeBaseResponse' {Int
httpStatus :: Int
$sel:httpStatus:DeleteKnowledgeBaseResponse' :: DeleteKnowledgeBaseResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus