{-# 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.DeleteBlueprint
-- 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 an existing blueprint.
module Amazonka.Glue.DeleteBlueprint
  ( -- * Creating a Request
    DeleteBlueprint (..),
    newDeleteBlueprint,

    -- * Request Lenses
    deleteBlueprint_name,

    -- * Destructuring the Response
    DeleteBlueprintResponse (..),
    newDeleteBlueprintResponse,

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

-- |
-- Create a value of 'DeleteBlueprint' 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', 'deleteBlueprint_name' - The name of the blueprint to delete.
newDeleteBlueprint ::
  -- | 'name'
  Prelude.Text ->
  DeleteBlueprint
newDeleteBlueprint :: Text -> DeleteBlueprint
newDeleteBlueprint Text
pName_ =
  DeleteBlueprint' {$sel:name:DeleteBlueprint' :: Text
name = Text
pName_}

-- | The name of the blueprint to delete.
deleteBlueprint_name :: Lens.Lens' DeleteBlueprint Prelude.Text
deleteBlueprint_name :: Lens' DeleteBlueprint Text
deleteBlueprint_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteBlueprint' {Text
name :: Text
$sel:name:DeleteBlueprint' :: DeleteBlueprint -> Text
name} -> Text
name) (\s :: DeleteBlueprint
s@DeleteBlueprint' {} Text
a -> DeleteBlueprint
s {$sel:name:DeleteBlueprint' :: Text
name = Text
a} :: DeleteBlueprint)

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

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

instance Data.ToHeaders DeleteBlueprint where
  toHeaders :: DeleteBlueprint -> 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.DeleteBlueprint" :: 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 DeleteBlueprint where
  toJSON :: DeleteBlueprint -> Value
toJSON DeleteBlueprint' {Text
name :: Text
$sel:name:DeleteBlueprint' :: DeleteBlueprint -> 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 DeleteBlueprint where
  toPath :: DeleteBlueprint -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

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

-- |
-- Create a value of 'DeleteBlueprintResponse' 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', 'deleteBlueprintResponse_name' - Returns the name of the blueprint that was deleted.
--
-- 'httpStatus', 'deleteBlueprintResponse_httpStatus' - The response's http status code.
newDeleteBlueprintResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DeleteBlueprintResponse
newDeleteBlueprintResponse :: Int -> DeleteBlueprintResponse
newDeleteBlueprintResponse Int
pHttpStatus_ =
  DeleteBlueprintResponse'
    { $sel:name:DeleteBlueprintResponse' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DeleteBlueprintResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Returns the name of the blueprint that was deleted.
deleteBlueprintResponse_name :: Lens.Lens' DeleteBlueprintResponse (Prelude.Maybe Prelude.Text)
deleteBlueprintResponse_name :: Lens' DeleteBlueprintResponse (Maybe Text)
deleteBlueprintResponse_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteBlueprintResponse' {Maybe Text
name :: Maybe Text
$sel:name:DeleteBlueprintResponse' :: DeleteBlueprintResponse -> Maybe Text
name} -> Maybe Text
name) (\s :: DeleteBlueprintResponse
s@DeleteBlueprintResponse' {} Maybe Text
a -> DeleteBlueprintResponse
s {$sel:name:DeleteBlueprintResponse' :: Maybe Text
name = Maybe Text
a} :: DeleteBlueprintResponse)

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

instance Prelude.NFData DeleteBlueprintResponse where
  rnf :: DeleteBlueprintResponse -> ()
rnf DeleteBlueprintResponse' {Int
Maybe Text
httpStatus :: Int
name :: Maybe Text
$sel:httpStatus:DeleteBlueprintResponse' :: DeleteBlueprintResponse -> Int
$sel:name:DeleteBlueprintResponse' :: DeleteBlueprintResponse -> 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