{-# 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.EKS.DeleteNodegroup
-- 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 Amazon EKS node group for a cluster.
module Amazonka.EKS.DeleteNodegroup
  ( -- * Creating a Request
    DeleteNodegroup (..),
    newDeleteNodegroup,

    -- * Request Lenses
    deleteNodegroup_clusterName,
    deleteNodegroup_nodegroupName,

    -- * Destructuring the Response
    DeleteNodegroupResponse (..),
    newDeleteNodegroupResponse,

    -- * Response Lenses
    deleteNodegroupResponse_nodegroup,
    deleteNodegroupResponse_httpStatus,
  )
where

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

-- | /See:/ 'newDeleteNodegroup' smart constructor.
data DeleteNodegroup = DeleteNodegroup'
  { -- | The name of the Amazon EKS cluster that is associated with your node
    -- group.
    DeleteNodegroup -> Text
clusterName :: Prelude.Text,
    -- | The name of the node group to delete.
    DeleteNodegroup -> Text
nodegroupName :: Prelude.Text
  }
  deriving (DeleteNodegroup -> DeleteNodegroup -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteNodegroup -> DeleteNodegroup -> Bool
$c/= :: DeleteNodegroup -> DeleteNodegroup -> Bool
== :: DeleteNodegroup -> DeleteNodegroup -> Bool
$c== :: DeleteNodegroup -> DeleteNodegroup -> Bool
Prelude.Eq, ReadPrec [DeleteNodegroup]
ReadPrec DeleteNodegroup
Int -> ReadS DeleteNodegroup
ReadS [DeleteNodegroup]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteNodegroup]
$creadListPrec :: ReadPrec [DeleteNodegroup]
readPrec :: ReadPrec DeleteNodegroup
$creadPrec :: ReadPrec DeleteNodegroup
readList :: ReadS [DeleteNodegroup]
$creadList :: ReadS [DeleteNodegroup]
readsPrec :: Int -> ReadS DeleteNodegroup
$creadsPrec :: Int -> ReadS DeleteNodegroup
Prelude.Read, Int -> DeleteNodegroup -> ShowS
[DeleteNodegroup] -> ShowS
DeleteNodegroup -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteNodegroup] -> ShowS
$cshowList :: [DeleteNodegroup] -> ShowS
show :: DeleteNodegroup -> String
$cshow :: DeleteNodegroup -> String
showsPrec :: Int -> DeleteNodegroup -> ShowS
$cshowsPrec :: Int -> DeleteNodegroup -> ShowS
Prelude.Show, forall x. Rep DeleteNodegroup x -> DeleteNodegroup
forall x. DeleteNodegroup -> Rep DeleteNodegroup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteNodegroup x -> DeleteNodegroup
$cfrom :: forall x. DeleteNodegroup -> Rep DeleteNodegroup x
Prelude.Generic)

-- |
-- Create a value of 'DeleteNodegroup' 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:
--
-- 'clusterName', 'deleteNodegroup_clusterName' - The name of the Amazon EKS cluster that is associated with your node
-- group.
--
-- 'nodegroupName', 'deleteNodegroup_nodegroupName' - The name of the node group to delete.
newDeleteNodegroup ::
  -- | 'clusterName'
  Prelude.Text ->
  -- | 'nodegroupName'
  Prelude.Text ->
  DeleteNodegroup
newDeleteNodegroup :: Text -> Text -> DeleteNodegroup
newDeleteNodegroup Text
pClusterName_ Text
pNodegroupName_ =
  DeleteNodegroup'
    { $sel:clusterName:DeleteNodegroup' :: Text
clusterName = Text
pClusterName_,
      $sel:nodegroupName:DeleteNodegroup' :: Text
nodegroupName = Text
pNodegroupName_
    }

-- | The name of the Amazon EKS cluster that is associated with your node
-- group.
deleteNodegroup_clusterName :: Lens.Lens' DeleteNodegroup Prelude.Text
deleteNodegroup_clusterName :: Lens' DeleteNodegroup Text
deleteNodegroup_clusterName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteNodegroup' {Text
clusterName :: Text
$sel:clusterName:DeleteNodegroup' :: DeleteNodegroup -> Text
clusterName} -> Text
clusterName) (\s :: DeleteNodegroup
s@DeleteNodegroup' {} Text
a -> DeleteNodegroup
s {$sel:clusterName:DeleteNodegroup' :: Text
clusterName = Text
a} :: DeleteNodegroup)

-- | The name of the node group to delete.
deleteNodegroup_nodegroupName :: Lens.Lens' DeleteNodegroup Prelude.Text
deleteNodegroup_nodegroupName :: Lens' DeleteNodegroup Text
deleteNodegroup_nodegroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteNodegroup' {Text
nodegroupName :: Text
$sel:nodegroupName:DeleteNodegroup' :: DeleteNodegroup -> Text
nodegroupName} -> Text
nodegroupName) (\s :: DeleteNodegroup
s@DeleteNodegroup' {} Text
a -> DeleteNodegroup
s {$sel:nodegroupName:DeleteNodegroup' :: Text
nodegroupName = Text
a} :: DeleteNodegroup)

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

instance Prelude.NFData DeleteNodegroup where
  rnf :: DeleteNodegroup -> ()
rnf DeleteNodegroup' {Text
nodegroupName :: Text
clusterName :: Text
$sel:nodegroupName:DeleteNodegroup' :: DeleteNodegroup -> Text
$sel:clusterName:DeleteNodegroup' :: DeleteNodegroup -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
clusterName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
nodegroupName

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

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

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

-- |
-- Create a value of 'DeleteNodegroupResponse' 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:
--
-- 'nodegroup', 'deleteNodegroupResponse_nodegroup' - The full description of your deleted node group.
--
-- 'httpStatus', 'deleteNodegroupResponse_httpStatus' - The response's http status code.
newDeleteNodegroupResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DeleteNodegroupResponse
newDeleteNodegroupResponse :: Int -> DeleteNodegroupResponse
newDeleteNodegroupResponse Int
pHttpStatus_ =
  DeleteNodegroupResponse'
    { $sel:nodegroup:DeleteNodegroupResponse' :: Maybe Nodegroup
nodegroup =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DeleteNodegroupResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The full description of your deleted node group.
deleteNodegroupResponse_nodegroup :: Lens.Lens' DeleteNodegroupResponse (Prelude.Maybe Nodegroup)
deleteNodegroupResponse_nodegroup :: Lens' DeleteNodegroupResponse (Maybe Nodegroup)
deleteNodegroupResponse_nodegroup = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteNodegroupResponse' {Maybe Nodegroup
nodegroup :: Maybe Nodegroup
$sel:nodegroup:DeleteNodegroupResponse' :: DeleteNodegroupResponse -> Maybe Nodegroup
nodegroup} -> Maybe Nodegroup
nodegroup) (\s :: DeleteNodegroupResponse
s@DeleteNodegroupResponse' {} Maybe Nodegroup
a -> DeleteNodegroupResponse
s {$sel:nodegroup:DeleteNodegroupResponse' :: Maybe Nodegroup
nodegroup = Maybe Nodegroup
a} :: DeleteNodegroupResponse)

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

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