{-# 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.DeleteContent
-- 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 content.
module Amazonka.Wisdom.DeleteContent
  ( -- * Creating a Request
    DeleteContent (..),
    newDeleteContent,

    -- * Request Lenses
    deleteContent_contentId,
    deleteContent_knowledgeBaseId,

    -- * Destructuring the Response
    DeleteContentResponse (..),
    newDeleteContentResponse,

    -- * Response Lenses
    deleteContentResponse_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:/ 'newDeleteContent' smart constructor.
data DeleteContent = DeleteContent'
  { -- | The identifier of the content. Can be either the ID or the ARN. URLs
    -- cannot contain the ARN.
    DeleteContent -> Text
contentId :: Prelude.Text,
    -- | The identifier of the knowledge base. Can be either the ID or the ARN.
    -- URLs cannot contain the ARN.
    DeleteContent -> Text
knowledgeBaseId :: Prelude.Text
  }
  deriving (DeleteContent -> DeleteContent -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteContent -> DeleteContent -> Bool
$c/= :: DeleteContent -> DeleteContent -> Bool
== :: DeleteContent -> DeleteContent -> Bool
$c== :: DeleteContent -> DeleteContent -> Bool
Prelude.Eq, ReadPrec [DeleteContent]
ReadPrec DeleteContent
Int -> ReadS DeleteContent
ReadS [DeleteContent]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteContent]
$creadListPrec :: ReadPrec [DeleteContent]
readPrec :: ReadPrec DeleteContent
$creadPrec :: ReadPrec DeleteContent
readList :: ReadS [DeleteContent]
$creadList :: ReadS [DeleteContent]
readsPrec :: Int -> ReadS DeleteContent
$creadsPrec :: Int -> ReadS DeleteContent
Prelude.Read, Int -> DeleteContent -> ShowS
[DeleteContent] -> ShowS
DeleteContent -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteContent] -> ShowS
$cshowList :: [DeleteContent] -> ShowS
show :: DeleteContent -> String
$cshow :: DeleteContent -> String
showsPrec :: Int -> DeleteContent -> ShowS
$cshowsPrec :: Int -> DeleteContent -> ShowS
Prelude.Show, forall x. Rep DeleteContent x -> DeleteContent
forall x. DeleteContent -> Rep DeleteContent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteContent x -> DeleteContent
$cfrom :: forall x. DeleteContent -> Rep DeleteContent x
Prelude.Generic)

-- |
-- Create a value of 'DeleteContent' 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:
--
-- 'contentId', 'deleteContent_contentId' - The identifier of the content. Can be either the ID or the ARN. URLs
-- cannot contain the ARN.
--
-- 'knowledgeBaseId', 'deleteContent_knowledgeBaseId' - The identifier of the knowledge base. Can be either the ID or the ARN.
-- URLs cannot contain the ARN.
newDeleteContent ::
  -- | 'contentId'
  Prelude.Text ->
  -- | 'knowledgeBaseId'
  Prelude.Text ->
  DeleteContent
newDeleteContent :: Text -> Text -> DeleteContent
newDeleteContent Text
pContentId_ Text
pKnowledgeBaseId_ =
  DeleteContent'
    { $sel:contentId:DeleteContent' :: Text
contentId = Text
pContentId_,
      $sel:knowledgeBaseId:DeleteContent' :: Text
knowledgeBaseId = Text
pKnowledgeBaseId_
    }

-- | The identifier of the content. Can be either the ID or the ARN. URLs
-- cannot contain the ARN.
deleteContent_contentId :: Lens.Lens' DeleteContent Prelude.Text
deleteContent_contentId :: Lens' DeleteContent Text
deleteContent_contentId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteContent' {Text
contentId :: Text
$sel:contentId:DeleteContent' :: DeleteContent -> Text
contentId} -> Text
contentId) (\s :: DeleteContent
s@DeleteContent' {} Text
a -> DeleteContent
s {$sel:contentId:DeleteContent' :: Text
contentId = Text
a} :: DeleteContent)

-- | The identifier of the knowledge base. Can be either the ID or the ARN.
-- URLs cannot contain the ARN.
deleteContent_knowledgeBaseId :: Lens.Lens' DeleteContent Prelude.Text
deleteContent_knowledgeBaseId :: Lens' DeleteContent Text
deleteContent_knowledgeBaseId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteContent' {Text
knowledgeBaseId :: Text
$sel:knowledgeBaseId:DeleteContent' :: DeleteContent -> Text
knowledgeBaseId} -> Text
knowledgeBaseId) (\s :: DeleteContent
s@DeleteContent' {} Text
a -> DeleteContent
s {$sel:knowledgeBaseId:DeleteContent' :: Text
knowledgeBaseId = Text
a} :: DeleteContent)

instance Core.AWSRequest DeleteContent where
  type
    AWSResponse DeleteContent =
      DeleteContentResponse
  request :: (Service -> Service) -> DeleteContent -> Request DeleteContent
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 DeleteContent
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DeleteContent)))
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 -> DeleteContentResponse
DeleteContentResponse'
            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 DeleteContent where
  hashWithSalt :: Int -> DeleteContent -> Int
hashWithSalt Int
_salt DeleteContent' {Text
knowledgeBaseId :: Text
contentId :: Text
$sel:knowledgeBaseId:DeleteContent' :: DeleteContent -> Text
$sel:contentId:DeleteContent' :: DeleteContent -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
contentId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
knowledgeBaseId

instance Prelude.NFData DeleteContent where
  rnf :: DeleteContent -> ()
rnf DeleteContent' {Text
knowledgeBaseId :: Text
contentId :: Text
$sel:knowledgeBaseId:DeleteContent' :: DeleteContent -> Text
$sel:contentId:DeleteContent' :: DeleteContent -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
contentId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
knowledgeBaseId

instance Data.ToHeaders DeleteContent where
  toHeaders :: DeleteContent -> 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 DeleteContent where
  toPath :: DeleteContent -> ByteString
toPath DeleteContent' {Text
knowledgeBaseId :: Text
contentId :: Text
$sel:knowledgeBaseId:DeleteContent' :: DeleteContent -> Text
$sel:contentId:DeleteContent' :: DeleteContent -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/knowledgeBases/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
knowledgeBaseId,
        ByteString
"/contents/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
contentId
      ]

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

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

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

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

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