{-# 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.EMRContainers.DeleteVirtualCluster
-- 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 virtual cluster. Virtual cluster is a managed entity on Amazon
-- EMR on EKS. You can create, describe, list and delete virtual clusters.
-- They do not consume any additional resource in your system. A single
-- virtual cluster maps to a single Kubernetes namespace. Given this
-- relationship, you can model virtual clusters the same way you model
-- Kubernetes namespaces to meet your requirements.
module Amazonka.EMRContainers.DeleteVirtualCluster
  ( -- * Creating a Request
    DeleteVirtualCluster (..),
    newDeleteVirtualCluster,

    -- * Request Lenses
    deleteVirtualCluster_id,

    -- * Destructuring the Response
    DeleteVirtualClusterResponse (..),
    newDeleteVirtualClusterResponse,

    -- * Response Lenses
    deleteVirtualClusterResponse_id,
    deleteVirtualClusterResponse_httpStatus,
  )
where

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

-- | /See:/ 'newDeleteVirtualCluster' smart constructor.
data DeleteVirtualCluster = DeleteVirtualCluster'
  { -- | The ID of the virtual cluster that will be deleted.
    DeleteVirtualCluster -> Text
id :: Prelude.Text
  }
  deriving (DeleteVirtualCluster -> DeleteVirtualCluster -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteVirtualCluster -> DeleteVirtualCluster -> Bool
$c/= :: DeleteVirtualCluster -> DeleteVirtualCluster -> Bool
== :: DeleteVirtualCluster -> DeleteVirtualCluster -> Bool
$c== :: DeleteVirtualCluster -> DeleteVirtualCluster -> Bool
Prelude.Eq, ReadPrec [DeleteVirtualCluster]
ReadPrec DeleteVirtualCluster
Int -> ReadS DeleteVirtualCluster
ReadS [DeleteVirtualCluster]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteVirtualCluster]
$creadListPrec :: ReadPrec [DeleteVirtualCluster]
readPrec :: ReadPrec DeleteVirtualCluster
$creadPrec :: ReadPrec DeleteVirtualCluster
readList :: ReadS [DeleteVirtualCluster]
$creadList :: ReadS [DeleteVirtualCluster]
readsPrec :: Int -> ReadS DeleteVirtualCluster
$creadsPrec :: Int -> ReadS DeleteVirtualCluster
Prelude.Read, Int -> DeleteVirtualCluster -> ShowS
[DeleteVirtualCluster] -> ShowS
DeleteVirtualCluster -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteVirtualCluster] -> ShowS
$cshowList :: [DeleteVirtualCluster] -> ShowS
show :: DeleteVirtualCluster -> String
$cshow :: DeleteVirtualCluster -> String
showsPrec :: Int -> DeleteVirtualCluster -> ShowS
$cshowsPrec :: Int -> DeleteVirtualCluster -> ShowS
Prelude.Show, forall x. Rep DeleteVirtualCluster x -> DeleteVirtualCluster
forall x. DeleteVirtualCluster -> Rep DeleteVirtualCluster x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteVirtualCluster x -> DeleteVirtualCluster
$cfrom :: forall x. DeleteVirtualCluster -> Rep DeleteVirtualCluster x
Prelude.Generic)

-- |
-- Create a value of 'DeleteVirtualCluster' 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:
--
-- 'id', 'deleteVirtualCluster_id' - The ID of the virtual cluster that will be deleted.
newDeleteVirtualCluster ::
  -- | 'id'
  Prelude.Text ->
  DeleteVirtualCluster
newDeleteVirtualCluster :: Text -> DeleteVirtualCluster
newDeleteVirtualCluster Text
pId_ =
  DeleteVirtualCluster' {$sel:id:DeleteVirtualCluster' :: Text
id = Text
pId_}

-- | The ID of the virtual cluster that will be deleted.
deleteVirtualCluster_id :: Lens.Lens' DeleteVirtualCluster Prelude.Text
deleteVirtualCluster_id :: Lens' DeleteVirtualCluster Text
deleteVirtualCluster_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteVirtualCluster' {Text
id :: Text
$sel:id:DeleteVirtualCluster' :: DeleteVirtualCluster -> Text
id} -> Text
id) (\s :: DeleteVirtualCluster
s@DeleteVirtualCluster' {} Text
a -> DeleteVirtualCluster
s {$sel:id:DeleteVirtualCluster' :: Text
id = Text
a} :: DeleteVirtualCluster)

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

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

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

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

-- | /See:/ 'newDeleteVirtualClusterResponse' smart constructor.
data DeleteVirtualClusterResponse = DeleteVirtualClusterResponse'
  { -- | This output contains the ID of the virtual cluster that will be deleted.
    DeleteVirtualClusterResponse -> Maybe Text
id :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    DeleteVirtualClusterResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DeleteVirtualClusterResponse
-> DeleteVirtualClusterResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteVirtualClusterResponse
-> DeleteVirtualClusterResponse -> Bool
$c/= :: DeleteVirtualClusterResponse
-> DeleteVirtualClusterResponse -> Bool
== :: DeleteVirtualClusterResponse
-> DeleteVirtualClusterResponse -> Bool
$c== :: DeleteVirtualClusterResponse
-> DeleteVirtualClusterResponse -> Bool
Prelude.Eq, ReadPrec [DeleteVirtualClusterResponse]
ReadPrec DeleteVirtualClusterResponse
Int -> ReadS DeleteVirtualClusterResponse
ReadS [DeleteVirtualClusterResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteVirtualClusterResponse]
$creadListPrec :: ReadPrec [DeleteVirtualClusterResponse]
readPrec :: ReadPrec DeleteVirtualClusterResponse
$creadPrec :: ReadPrec DeleteVirtualClusterResponse
readList :: ReadS [DeleteVirtualClusterResponse]
$creadList :: ReadS [DeleteVirtualClusterResponse]
readsPrec :: Int -> ReadS DeleteVirtualClusterResponse
$creadsPrec :: Int -> ReadS DeleteVirtualClusterResponse
Prelude.Read, Int -> DeleteVirtualClusterResponse -> ShowS
[DeleteVirtualClusterResponse] -> ShowS
DeleteVirtualClusterResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteVirtualClusterResponse] -> ShowS
$cshowList :: [DeleteVirtualClusterResponse] -> ShowS
show :: DeleteVirtualClusterResponse -> String
$cshow :: DeleteVirtualClusterResponse -> String
showsPrec :: Int -> DeleteVirtualClusterResponse -> ShowS
$cshowsPrec :: Int -> DeleteVirtualClusterResponse -> ShowS
Prelude.Show, forall x.
Rep DeleteVirtualClusterResponse x -> DeleteVirtualClusterResponse
forall x.
DeleteVirtualClusterResponse -> Rep DeleteVirtualClusterResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeleteVirtualClusterResponse x -> DeleteVirtualClusterResponse
$cfrom :: forall x.
DeleteVirtualClusterResponse -> Rep DeleteVirtualClusterResponse x
Prelude.Generic)

-- |
-- Create a value of 'DeleteVirtualClusterResponse' 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:
--
-- 'id', 'deleteVirtualClusterResponse_id' - This output contains the ID of the virtual cluster that will be deleted.
--
-- 'httpStatus', 'deleteVirtualClusterResponse_httpStatus' - The response's http status code.
newDeleteVirtualClusterResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DeleteVirtualClusterResponse
newDeleteVirtualClusterResponse :: Int -> DeleteVirtualClusterResponse
newDeleteVirtualClusterResponse Int
pHttpStatus_ =
  DeleteVirtualClusterResponse'
    { $sel:id:DeleteVirtualClusterResponse' :: Maybe Text
id = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DeleteVirtualClusterResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | This output contains the ID of the virtual cluster that will be deleted.
deleteVirtualClusterResponse_id :: Lens.Lens' DeleteVirtualClusterResponse (Prelude.Maybe Prelude.Text)
deleteVirtualClusterResponse_id :: Lens' DeleteVirtualClusterResponse (Maybe Text)
deleteVirtualClusterResponse_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteVirtualClusterResponse' {Maybe Text
id :: Maybe Text
$sel:id:DeleteVirtualClusterResponse' :: DeleteVirtualClusterResponse -> Maybe Text
id} -> Maybe Text
id) (\s :: DeleteVirtualClusterResponse
s@DeleteVirtualClusterResponse' {} Maybe Text
a -> DeleteVirtualClusterResponse
s {$sel:id:DeleteVirtualClusterResponse' :: Maybe Text
id = Maybe Text
a} :: DeleteVirtualClusterResponse)

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

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