{-# 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.Amplify.DeleteWebhook
-- 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 a webhook.
module Amazonka.Amplify.DeleteWebhook
  ( -- * Creating a Request
    DeleteWebhook (..),
    newDeleteWebhook,

    -- * Request Lenses
    deleteWebhook_webhookId,

    -- * Destructuring the Response
    DeleteWebhookResponse (..),
    newDeleteWebhookResponse,

    -- * Response Lenses
    deleteWebhookResponse_httpStatus,
    deleteWebhookResponse_webhook,
  )
where

import Amazonka.Amplify.Types
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

-- | The request structure for the delete webhook request.
--
-- /See:/ 'newDeleteWebhook' smart constructor.
data DeleteWebhook = DeleteWebhook'
  { -- | The unique ID for a webhook.
    DeleteWebhook -> Text
webhookId :: Prelude.Text
  }
  deriving (DeleteWebhook -> DeleteWebhook -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteWebhook -> DeleteWebhook -> Bool
$c/= :: DeleteWebhook -> DeleteWebhook -> Bool
== :: DeleteWebhook -> DeleteWebhook -> Bool
$c== :: DeleteWebhook -> DeleteWebhook -> Bool
Prelude.Eq, ReadPrec [DeleteWebhook]
ReadPrec DeleteWebhook
Int -> ReadS DeleteWebhook
ReadS [DeleteWebhook]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteWebhook]
$creadListPrec :: ReadPrec [DeleteWebhook]
readPrec :: ReadPrec DeleteWebhook
$creadPrec :: ReadPrec DeleteWebhook
readList :: ReadS [DeleteWebhook]
$creadList :: ReadS [DeleteWebhook]
readsPrec :: Int -> ReadS DeleteWebhook
$creadsPrec :: Int -> ReadS DeleteWebhook
Prelude.Read, Int -> DeleteWebhook -> ShowS
[DeleteWebhook] -> ShowS
DeleteWebhook -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteWebhook] -> ShowS
$cshowList :: [DeleteWebhook] -> ShowS
show :: DeleteWebhook -> String
$cshow :: DeleteWebhook -> String
showsPrec :: Int -> DeleteWebhook -> ShowS
$cshowsPrec :: Int -> DeleteWebhook -> ShowS
Prelude.Show, forall x. Rep DeleteWebhook x -> DeleteWebhook
forall x. DeleteWebhook -> Rep DeleteWebhook x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteWebhook x -> DeleteWebhook
$cfrom :: forall x. DeleteWebhook -> Rep DeleteWebhook x
Prelude.Generic)

-- |
-- Create a value of 'DeleteWebhook' 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:
--
-- 'webhookId', 'deleteWebhook_webhookId' - The unique ID for a webhook.
newDeleteWebhook ::
  -- | 'webhookId'
  Prelude.Text ->
  DeleteWebhook
newDeleteWebhook :: Text -> DeleteWebhook
newDeleteWebhook Text
pWebhookId_ =
  DeleteWebhook' {$sel:webhookId:DeleteWebhook' :: Text
webhookId = Text
pWebhookId_}

-- | The unique ID for a webhook.
deleteWebhook_webhookId :: Lens.Lens' DeleteWebhook Prelude.Text
deleteWebhook_webhookId :: Lens' DeleteWebhook Text
deleteWebhook_webhookId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteWebhook' {Text
webhookId :: Text
$sel:webhookId:DeleteWebhook' :: DeleteWebhook -> Text
webhookId} -> Text
webhookId) (\s :: DeleteWebhook
s@DeleteWebhook' {} Text
a -> DeleteWebhook
s {$sel:webhookId:DeleteWebhook' :: Text
webhookId = Text
a} :: DeleteWebhook)

instance Core.AWSRequest DeleteWebhook where
  type
    AWSResponse DeleteWebhook =
      DeleteWebhookResponse
  request :: (Service -> Service) -> DeleteWebhook -> Request DeleteWebhook
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 DeleteWebhook
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DeleteWebhook)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Int -> Webhook -> DeleteWebhookResponse
DeleteWebhookResponse'
            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))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"webhook")
      )

instance Prelude.Hashable DeleteWebhook where
  hashWithSalt :: Int -> DeleteWebhook -> Int
hashWithSalt Int
_salt DeleteWebhook' {Text
webhookId :: Text
$sel:webhookId:DeleteWebhook' :: DeleteWebhook -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
webhookId

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

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

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

-- | The result structure for the delete webhook request.
--
-- /See:/ 'newDeleteWebhookResponse' smart constructor.
data DeleteWebhookResponse = DeleteWebhookResponse'
  { -- | The response's http status code.
    DeleteWebhookResponse -> Int
httpStatus :: Prelude.Int,
    -- | Describes a webhook that connects repository events to an Amplify app.
    DeleteWebhookResponse -> Webhook
webhook :: Webhook
  }
  deriving (DeleteWebhookResponse -> DeleteWebhookResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteWebhookResponse -> DeleteWebhookResponse -> Bool
$c/= :: DeleteWebhookResponse -> DeleteWebhookResponse -> Bool
== :: DeleteWebhookResponse -> DeleteWebhookResponse -> Bool
$c== :: DeleteWebhookResponse -> DeleteWebhookResponse -> Bool
Prelude.Eq, ReadPrec [DeleteWebhookResponse]
ReadPrec DeleteWebhookResponse
Int -> ReadS DeleteWebhookResponse
ReadS [DeleteWebhookResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteWebhookResponse]
$creadListPrec :: ReadPrec [DeleteWebhookResponse]
readPrec :: ReadPrec DeleteWebhookResponse
$creadPrec :: ReadPrec DeleteWebhookResponse
readList :: ReadS [DeleteWebhookResponse]
$creadList :: ReadS [DeleteWebhookResponse]
readsPrec :: Int -> ReadS DeleteWebhookResponse
$creadsPrec :: Int -> ReadS DeleteWebhookResponse
Prelude.Read, Int -> DeleteWebhookResponse -> ShowS
[DeleteWebhookResponse] -> ShowS
DeleteWebhookResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteWebhookResponse] -> ShowS
$cshowList :: [DeleteWebhookResponse] -> ShowS
show :: DeleteWebhookResponse -> String
$cshow :: DeleteWebhookResponse -> String
showsPrec :: Int -> DeleteWebhookResponse -> ShowS
$cshowsPrec :: Int -> DeleteWebhookResponse -> ShowS
Prelude.Show, forall x. Rep DeleteWebhookResponse x -> DeleteWebhookResponse
forall x. DeleteWebhookResponse -> Rep DeleteWebhookResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteWebhookResponse x -> DeleteWebhookResponse
$cfrom :: forall x. DeleteWebhookResponse -> Rep DeleteWebhookResponse x
Prelude.Generic)

-- |
-- Create a value of 'DeleteWebhookResponse' 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', 'deleteWebhookResponse_httpStatus' - The response's http status code.
--
-- 'webhook', 'deleteWebhookResponse_webhook' - Describes a webhook that connects repository events to an Amplify app.
newDeleteWebhookResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'webhook'
  Webhook ->
  DeleteWebhookResponse
newDeleteWebhookResponse :: Int -> Webhook -> DeleteWebhookResponse
newDeleteWebhookResponse Int
pHttpStatus_ Webhook
pWebhook_ =
  DeleteWebhookResponse'
    { $sel:httpStatus:DeleteWebhookResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:webhook:DeleteWebhookResponse' :: Webhook
webhook = Webhook
pWebhook_
    }

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

-- | Describes a webhook that connects repository events to an Amplify app.
deleteWebhookResponse_webhook :: Lens.Lens' DeleteWebhookResponse Webhook
deleteWebhookResponse_webhook :: Lens' DeleteWebhookResponse Webhook
deleteWebhookResponse_webhook = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteWebhookResponse' {Webhook
webhook :: Webhook
$sel:webhook:DeleteWebhookResponse' :: DeleteWebhookResponse -> Webhook
webhook} -> Webhook
webhook) (\s :: DeleteWebhookResponse
s@DeleteWebhookResponse' {} Webhook
a -> DeleteWebhookResponse
s {$sel:webhook:DeleteWebhookResponse' :: Webhook
webhook = Webhook
a} :: DeleteWebhookResponse)

instance Prelude.NFData DeleteWebhookResponse where
  rnf :: DeleteWebhookResponse -> ()
rnf DeleteWebhookResponse' {Int
Webhook
webhook :: Webhook
httpStatus :: Int
$sel:webhook:DeleteWebhookResponse' :: DeleteWebhookResponse -> Webhook
$sel:httpStatus:DeleteWebhookResponse' :: DeleteWebhookResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Webhook
webhook