{-# 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.ResourceGroups.DeleteGroup
-- 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 the specified resource group. Deleting a resource group does not
-- delete any resources that are members of the group; it only deletes the
-- group structure.
--
-- __Minimum permissions__
--
-- To run this command, you must have the following permissions:
--
-- -   @resource-groups:DeleteGroup@
module Amazonka.ResourceGroups.DeleteGroup
  ( -- * Creating a Request
    DeleteGroup (..),
    newDeleteGroup,

    -- * Request Lenses
    deleteGroup_group,
    deleteGroup_groupName,

    -- * Destructuring the Response
    DeleteGroupResponse (..),
    newDeleteGroupResponse,

    -- * Response Lenses
    deleteGroupResponse_group,
    deleteGroupResponse_httpStatus,
  )
where

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

-- | /See:/ 'newDeleteGroup' smart constructor.
data DeleteGroup = DeleteGroup'
  { -- | The name or the ARN of the resource group to delete.
    DeleteGroup -> Maybe Text
group' :: Prelude.Maybe Prelude.Text,
    -- | Deprecated - don\'t use this parameter. Use @Group@ instead.
    DeleteGroup -> Maybe Text
groupName :: Prelude.Maybe Prelude.Text
  }
  deriving (DeleteGroup -> DeleteGroup -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteGroup -> DeleteGroup -> Bool
$c/= :: DeleteGroup -> DeleteGroup -> Bool
== :: DeleteGroup -> DeleteGroup -> Bool
$c== :: DeleteGroup -> DeleteGroup -> Bool
Prelude.Eq, ReadPrec [DeleteGroup]
ReadPrec DeleteGroup
Int -> ReadS DeleteGroup
ReadS [DeleteGroup]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteGroup]
$creadListPrec :: ReadPrec [DeleteGroup]
readPrec :: ReadPrec DeleteGroup
$creadPrec :: ReadPrec DeleteGroup
readList :: ReadS [DeleteGroup]
$creadList :: ReadS [DeleteGroup]
readsPrec :: Int -> ReadS DeleteGroup
$creadsPrec :: Int -> ReadS DeleteGroup
Prelude.Read, Int -> DeleteGroup -> ShowS
[DeleteGroup] -> ShowS
DeleteGroup -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteGroup] -> ShowS
$cshowList :: [DeleteGroup] -> ShowS
show :: DeleteGroup -> String
$cshow :: DeleteGroup -> String
showsPrec :: Int -> DeleteGroup -> ShowS
$cshowsPrec :: Int -> DeleteGroup -> ShowS
Prelude.Show, forall x. Rep DeleteGroup x -> DeleteGroup
forall x. DeleteGroup -> Rep DeleteGroup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteGroup x -> DeleteGroup
$cfrom :: forall x. DeleteGroup -> Rep DeleteGroup x
Prelude.Generic)

-- |
-- Create a value of 'DeleteGroup' 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:
--
-- 'group'', 'deleteGroup_group' - The name or the ARN of the resource group to delete.
--
-- 'groupName', 'deleteGroup_groupName' - Deprecated - don\'t use this parameter. Use @Group@ instead.
newDeleteGroup ::
  DeleteGroup
newDeleteGroup :: DeleteGroup
newDeleteGroup =
  DeleteGroup'
    { $sel:group':DeleteGroup' :: Maybe Text
group' = forall a. Maybe a
Prelude.Nothing,
      $sel:groupName:DeleteGroup' :: Maybe Text
groupName = forall a. Maybe a
Prelude.Nothing
    }

-- | The name or the ARN of the resource group to delete.
deleteGroup_group :: Lens.Lens' DeleteGroup (Prelude.Maybe Prelude.Text)
deleteGroup_group :: Lens' DeleteGroup (Maybe Text)
deleteGroup_group = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteGroup' {Maybe Text
group' :: Maybe Text
$sel:group':DeleteGroup' :: DeleteGroup -> Maybe Text
group'} -> Maybe Text
group') (\s :: DeleteGroup
s@DeleteGroup' {} Maybe Text
a -> DeleteGroup
s {$sel:group':DeleteGroup' :: Maybe Text
group' = Maybe Text
a} :: DeleteGroup)

-- | Deprecated - don\'t use this parameter. Use @Group@ instead.
deleteGroup_groupName :: Lens.Lens' DeleteGroup (Prelude.Maybe Prelude.Text)
deleteGroup_groupName :: Lens' DeleteGroup (Maybe Text)
deleteGroup_groupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteGroup' {Maybe Text
groupName :: Maybe Text
$sel:groupName:DeleteGroup' :: DeleteGroup -> Maybe Text
groupName} -> Maybe Text
groupName) (\s :: DeleteGroup
s@DeleteGroup' {} Maybe Text
a -> DeleteGroup
s {$sel:groupName:DeleteGroup' :: Maybe Text
groupName = Maybe Text
a} :: DeleteGroup)

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

instance Prelude.NFData DeleteGroup where
  rnf :: DeleteGroup -> ()
rnf DeleteGroup' {Maybe Text
groupName :: Maybe Text
group' :: Maybe Text
$sel:groupName:DeleteGroup' :: DeleteGroup -> Maybe Text
$sel:group':DeleteGroup' :: DeleteGroup -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
group'
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
groupName

instance Data.ToHeaders DeleteGroup where
  toHeaders :: DeleteGroup -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

instance Data.ToJSON DeleteGroup where
  toJSON :: DeleteGroup -> Value
toJSON DeleteGroup' {Maybe Text
groupName :: Maybe Text
group' :: Maybe Text
$sel:groupName:DeleteGroup' :: DeleteGroup -> Maybe Text
$sel:group':DeleteGroup' :: DeleteGroup -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Group" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
group',
            (Key
"GroupName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
groupName
          ]
      )

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

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

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

-- |
-- Create a value of 'DeleteGroupResponse' 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:
--
-- 'group'', 'deleteGroupResponse_group' - A full description of the deleted resource group.
--
-- 'httpStatus', 'deleteGroupResponse_httpStatus' - The response's http status code.
newDeleteGroupResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DeleteGroupResponse
newDeleteGroupResponse :: Int -> DeleteGroupResponse
newDeleteGroupResponse Int
pHttpStatus_ =
  DeleteGroupResponse'
    { $sel:group':DeleteGroupResponse' :: Maybe Group
group' = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DeleteGroupResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A full description of the deleted resource group.
deleteGroupResponse_group :: Lens.Lens' DeleteGroupResponse (Prelude.Maybe Group)
deleteGroupResponse_group :: Lens' DeleteGroupResponse (Maybe Group)
deleteGroupResponse_group = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteGroupResponse' {Maybe Group
group' :: Maybe Group
$sel:group':DeleteGroupResponse' :: DeleteGroupResponse -> Maybe Group
group'} -> Maybe Group
group') (\s :: DeleteGroupResponse
s@DeleteGroupResponse' {} Maybe Group
a -> DeleteGroupResponse
s {$sel:group':DeleteGroupResponse' :: Maybe Group
group' = Maybe Group
a} :: DeleteGroupResponse)

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

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