{-# 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.Glue.DeleteDevEndpoint
-- 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 specified development endpoint.
module Amazonka.Glue.DeleteDevEndpoint
  ( -- * Creating a Request
    DeleteDevEndpoint (..),
    newDeleteDevEndpoint,

    -- * Request Lenses
    deleteDevEndpoint_endpointName,

    -- * Destructuring the Response
    DeleteDevEndpointResponse (..),
    newDeleteDevEndpointResponse,

    -- * Response Lenses
    deleteDevEndpointResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.Glue.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

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

-- |
-- Create a value of 'DeleteDevEndpoint' 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:
--
-- 'endpointName', 'deleteDevEndpoint_endpointName' - The name of the @DevEndpoint@.
newDeleteDevEndpoint ::
  -- | 'endpointName'
  Prelude.Text ->
  DeleteDevEndpoint
newDeleteDevEndpoint :: Text -> DeleteDevEndpoint
newDeleteDevEndpoint Text
pEndpointName_ =
  DeleteDevEndpoint' {$sel:endpointName:DeleteDevEndpoint' :: Text
endpointName = Text
pEndpointName_}

-- | The name of the @DevEndpoint@.
deleteDevEndpoint_endpointName :: Lens.Lens' DeleteDevEndpoint Prelude.Text
deleteDevEndpoint_endpointName :: Lens' DeleteDevEndpoint Text
deleteDevEndpoint_endpointName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteDevEndpoint' {Text
endpointName :: Text
$sel:endpointName:DeleteDevEndpoint' :: DeleteDevEndpoint -> Text
endpointName} -> Text
endpointName) (\s :: DeleteDevEndpoint
s@DeleteDevEndpoint' {} Text
a -> DeleteDevEndpoint
s {$sel:endpointName:DeleteDevEndpoint' :: Text
endpointName = Text
a} :: DeleteDevEndpoint)

instance Core.AWSRequest DeleteDevEndpoint where
  type
    AWSResponse DeleteDevEndpoint =
      DeleteDevEndpointResponse
  request :: (Service -> Service)
-> DeleteDevEndpoint -> Request DeleteDevEndpoint
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DeleteDevEndpoint
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DeleteDevEndpoint)))
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 -> DeleteDevEndpointResponse
DeleteDevEndpointResponse'
            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 DeleteDevEndpoint where
  hashWithSalt :: Int -> DeleteDevEndpoint -> Int
hashWithSalt Int
_salt DeleteDevEndpoint' {Text
endpointName :: Text
$sel:endpointName:DeleteDevEndpoint' :: DeleteDevEndpoint -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
endpointName

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

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

instance Data.ToJSON DeleteDevEndpoint where
  toJSON :: DeleteDevEndpoint -> Value
toJSON DeleteDevEndpoint' {Text
endpointName :: Text
$sel:endpointName:DeleteDevEndpoint' :: DeleteDevEndpoint -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [forall a. a -> Maybe a
Prelude.Just (Key
"EndpointName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
endpointName)]
      )

instance Data.ToPath DeleteDevEndpoint where
  toPath :: DeleteDevEndpoint -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

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

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

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

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