{-# 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.RemoveKnowledgeBaseTemplateUri
-- 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 a URI template from a knowledge base.
module Amazonka.Wisdom.RemoveKnowledgeBaseTemplateUri
  ( -- * Creating a Request
    RemoveKnowledgeBaseTemplateUri (..),
    newRemoveKnowledgeBaseTemplateUri,

    -- * Request Lenses
    removeKnowledgeBaseTemplateUri_knowledgeBaseId,

    -- * Destructuring the Response
    RemoveKnowledgeBaseTemplateUriResponse (..),
    newRemoveKnowledgeBaseTemplateUriResponse,

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

-- |
-- Create a value of 'RemoveKnowledgeBaseTemplateUri' 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', 'removeKnowledgeBaseTemplateUri_knowledgeBaseId' - The identifier of the knowledge base. Can be either the ID or the ARN.
-- URLs cannot contain the ARN.
newRemoveKnowledgeBaseTemplateUri ::
  -- | 'knowledgeBaseId'
  Prelude.Text ->
  RemoveKnowledgeBaseTemplateUri
newRemoveKnowledgeBaseTemplateUri :: Text -> RemoveKnowledgeBaseTemplateUri
newRemoveKnowledgeBaseTemplateUri Text
pKnowledgeBaseId_ =
  RemoveKnowledgeBaseTemplateUri'
    { $sel:knowledgeBaseId:RemoveKnowledgeBaseTemplateUri' :: Text
knowledgeBaseId =
        Text
pKnowledgeBaseId_
    }

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

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

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

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

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

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

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

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

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