{-# 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.DeleteCustomEntityType
-- 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 custom pattern by specifying its name.
module Amazonka.Glue.DeleteCustomEntityType
  ( -- * Creating a Request
    DeleteCustomEntityType (..),
    newDeleteCustomEntityType,

    -- * Request Lenses
    deleteCustomEntityType_name,

    -- * Destructuring the Response
    DeleteCustomEntityTypeResponse (..),
    newDeleteCustomEntityTypeResponse,

    -- * Response Lenses
    deleteCustomEntityTypeResponse_name,
    deleteCustomEntityTypeResponse_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:/ 'newDeleteCustomEntityType' smart constructor.
data DeleteCustomEntityType = DeleteCustomEntityType'
  { -- | The name of the custom pattern that you want to delete.
    DeleteCustomEntityType -> Text
name :: Prelude.Text
  }
  deriving (DeleteCustomEntityType -> DeleteCustomEntityType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteCustomEntityType -> DeleteCustomEntityType -> Bool
$c/= :: DeleteCustomEntityType -> DeleteCustomEntityType -> Bool
== :: DeleteCustomEntityType -> DeleteCustomEntityType -> Bool
$c== :: DeleteCustomEntityType -> DeleteCustomEntityType -> Bool
Prelude.Eq, ReadPrec [DeleteCustomEntityType]
ReadPrec DeleteCustomEntityType
Int -> ReadS DeleteCustomEntityType
ReadS [DeleteCustomEntityType]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteCustomEntityType]
$creadListPrec :: ReadPrec [DeleteCustomEntityType]
readPrec :: ReadPrec DeleteCustomEntityType
$creadPrec :: ReadPrec DeleteCustomEntityType
readList :: ReadS [DeleteCustomEntityType]
$creadList :: ReadS [DeleteCustomEntityType]
readsPrec :: Int -> ReadS DeleteCustomEntityType
$creadsPrec :: Int -> ReadS DeleteCustomEntityType
Prelude.Read, Int -> DeleteCustomEntityType -> ShowS
[DeleteCustomEntityType] -> ShowS
DeleteCustomEntityType -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteCustomEntityType] -> ShowS
$cshowList :: [DeleteCustomEntityType] -> ShowS
show :: DeleteCustomEntityType -> String
$cshow :: DeleteCustomEntityType -> String
showsPrec :: Int -> DeleteCustomEntityType -> ShowS
$cshowsPrec :: Int -> DeleteCustomEntityType -> ShowS
Prelude.Show, forall x. Rep DeleteCustomEntityType x -> DeleteCustomEntityType
forall x. DeleteCustomEntityType -> Rep DeleteCustomEntityType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteCustomEntityType x -> DeleteCustomEntityType
$cfrom :: forall x. DeleteCustomEntityType -> Rep DeleteCustomEntityType x
Prelude.Generic)

-- |
-- Create a value of 'DeleteCustomEntityType' 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', 'deleteCustomEntityType_name' - The name of the custom pattern that you want to delete.
newDeleteCustomEntityType ::
  -- | 'name'
  Prelude.Text ->
  DeleteCustomEntityType
newDeleteCustomEntityType :: Text -> DeleteCustomEntityType
newDeleteCustomEntityType Text
pName_ =
  DeleteCustomEntityType' {$sel:name:DeleteCustomEntityType' :: Text
name = Text
pName_}

-- | The name of the custom pattern that you want to delete.
deleteCustomEntityType_name :: Lens.Lens' DeleteCustomEntityType Prelude.Text
deleteCustomEntityType_name :: Lens' DeleteCustomEntityType Text
deleteCustomEntityType_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteCustomEntityType' {Text
name :: Text
$sel:name:DeleteCustomEntityType' :: DeleteCustomEntityType -> Text
name} -> Text
name) (\s :: DeleteCustomEntityType
s@DeleteCustomEntityType' {} Text
a -> DeleteCustomEntityType
s {$sel:name:DeleteCustomEntityType' :: Text
name = Text
a} :: DeleteCustomEntityType)

instance Core.AWSRequest DeleteCustomEntityType where
  type
    AWSResponse DeleteCustomEntityType =
      DeleteCustomEntityTypeResponse
  request :: (Service -> Service)
-> DeleteCustomEntityType -> Request DeleteCustomEntityType
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 DeleteCustomEntityType
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DeleteCustomEntityType)))
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 ->
          Maybe Text -> Int -> DeleteCustomEntityTypeResponse
DeleteCustomEntityTypeResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"Name")
            forall (f :: * -> *) a b. Applicative f => 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 DeleteCustomEntityType where
  hashWithSalt :: Int -> DeleteCustomEntityType -> Int
hashWithSalt Int
_salt DeleteCustomEntityType' {Text
name :: Text
$sel:name:DeleteCustomEntityType' :: DeleteCustomEntityType -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name

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

instance Data.ToHeaders DeleteCustomEntityType where
  toHeaders :: DeleteCustomEntityType -> 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.DeleteCustomEntityType" ::
                          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 DeleteCustomEntityType where
  toJSON :: DeleteCustomEntityType -> Value
toJSON DeleteCustomEntityType' {Text
name :: Text
$sel:name:DeleteCustomEntityType' :: DeleteCustomEntityType -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [forall a. a -> Maybe a
Prelude.Just (Key
"Name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
name)]
      )

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

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

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

-- |
-- Create a value of 'DeleteCustomEntityTypeResponse' 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', 'deleteCustomEntityTypeResponse_name' - The name of the custom pattern you deleted.
--
-- 'httpStatus', 'deleteCustomEntityTypeResponse_httpStatus' - The response's http status code.
newDeleteCustomEntityTypeResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DeleteCustomEntityTypeResponse
newDeleteCustomEntityTypeResponse :: Int -> DeleteCustomEntityTypeResponse
newDeleteCustomEntityTypeResponse Int
pHttpStatus_ =
  DeleteCustomEntityTypeResponse'
    { $sel:name:DeleteCustomEntityTypeResponse' :: Maybe Text
name =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DeleteCustomEntityTypeResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The name of the custom pattern you deleted.
deleteCustomEntityTypeResponse_name :: Lens.Lens' DeleteCustomEntityTypeResponse (Prelude.Maybe Prelude.Text)
deleteCustomEntityTypeResponse_name :: Lens' DeleteCustomEntityTypeResponse (Maybe Text)
deleteCustomEntityTypeResponse_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteCustomEntityTypeResponse' {Maybe Text
name :: Maybe Text
$sel:name:DeleteCustomEntityTypeResponse' :: DeleteCustomEntityTypeResponse -> Maybe Text
name} -> Maybe Text
name) (\s :: DeleteCustomEntityTypeResponse
s@DeleteCustomEntityTypeResponse' {} Maybe Text
a -> DeleteCustomEntityTypeResponse
s {$sel:name:DeleteCustomEntityTypeResponse' :: Maybe Text
name = Maybe Text
a} :: DeleteCustomEntityTypeResponse)

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

instance
  Prelude.NFData
    DeleteCustomEntityTypeResponse
  where
  rnf :: DeleteCustomEntityTypeResponse -> ()
rnf DeleteCustomEntityTypeResponse' {Int
Maybe Text
httpStatus :: Int
name :: Maybe Text
$sel:httpStatus:DeleteCustomEntityTypeResponse' :: DeleteCustomEntityTypeResponse -> Int
$sel:name:DeleteCustomEntityTypeResponse' :: DeleteCustomEntityTypeResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus