{-# 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.AppIntegrationS.DeleteEventIntegration
-- 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 specified existing event integration. If the event
-- integration is associated with clients, the request is rejected.
module Amazonka.AppIntegrationS.DeleteEventIntegration
  ( -- * Creating a Request
    DeleteEventIntegration (..),
    newDeleteEventIntegration,

    -- * Request Lenses
    deleteEventIntegration_name,

    -- * Destructuring the Response
    DeleteEventIntegrationResponse (..),
    newDeleteEventIntegrationResponse,

    -- * Response Lenses
    deleteEventIntegrationResponse_httpStatus,
  )
where

import Amazonka.AppIntegrationS.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

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

-- |
-- Create a value of 'DeleteEventIntegration' 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:
--
-- 'name', 'deleteEventIntegration_name' - The name of the event integration.
newDeleteEventIntegration ::
  -- | 'name'
  Prelude.Text ->
  DeleteEventIntegration
newDeleteEventIntegration :: Text -> DeleteEventIntegration
newDeleteEventIntegration Text
pName_ =
  DeleteEventIntegration' {$sel:name:DeleteEventIntegration' :: Text
name = Text
pName_}

-- | The name of the event integration.
deleteEventIntegration_name :: Lens.Lens' DeleteEventIntegration Prelude.Text
deleteEventIntegration_name :: Lens' DeleteEventIntegration Text
deleteEventIntegration_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteEventIntegration' {Text
name :: Text
$sel:name:DeleteEventIntegration' :: DeleteEventIntegration -> Text
name} -> Text
name) (\s :: DeleteEventIntegration
s@DeleteEventIntegration' {} Text
a -> DeleteEventIntegration
s {$sel:name:DeleteEventIntegration' :: Text
name = Text
a} :: DeleteEventIntegration)

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

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

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

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

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

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

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

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