{-# 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.UpdateGroup
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Updates the description for an existing group. You cannot update the
-- name of a resource group.
--
-- __Minimum permissions__
--
-- To run this command, you must have the following permissions:
--
-- -   @resource-groups:UpdateGroup@
module Amazonka.ResourceGroups.UpdateGroup
  ( -- * Creating a Request
    UpdateGroup (..),
    newUpdateGroup,

    -- * Request Lenses
    updateGroup_description,
    updateGroup_group,
    updateGroup_groupName,

    -- * Destructuring the Response
    UpdateGroupResponse (..),
    newUpdateGroupResponse,

    -- * Response Lenses
    updateGroupResponse_group,
    updateGroupResponse_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:/ 'newUpdateGroup' smart constructor.
data UpdateGroup = UpdateGroup'
  { -- | The new description that you want to update the resource group with.
    -- Descriptions can contain letters, numbers, hyphens, underscores,
    -- periods, and spaces.
    UpdateGroup -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | The name or the ARN of the resource group to modify.
    UpdateGroup -> Maybe Text
group' :: Prelude.Maybe Prelude.Text,
    -- | Don\'t use this parameter. Use @Group@ instead.
    UpdateGroup -> Maybe Text
groupName :: Prelude.Maybe Prelude.Text
  }
  deriving (UpdateGroup -> UpdateGroup -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateGroup -> UpdateGroup -> Bool
$c/= :: UpdateGroup -> UpdateGroup -> Bool
== :: UpdateGroup -> UpdateGroup -> Bool
$c== :: UpdateGroup -> UpdateGroup -> Bool
Prelude.Eq, ReadPrec [UpdateGroup]
ReadPrec UpdateGroup
Int -> ReadS UpdateGroup
ReadS [UpdateGroup]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateGroup]
$creadListPrec :: ReadPrec [UpdateGroup]
readPrec :: ReadPrec UpdateGroup
$creadPrec :: ReadPrec UpdateGroup
readList :: ReadS [UpdateGroup]
$creadList :: ReadS [UpdateGroup]
readsPrec :: Int -> ReadS UpdateGroup
$creadsPrec :: Int -> ReadS UpdateGroup
Prelude.Read, Int -> UpdateGroup -> ShowS
[UpdateGroup] -> ShowS
UpdateGroup -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateGroup] -> ShowS
$cshowList :: [UpdateGroup] -> ShowS
show :: UpdateGroup -> String
$cshow :: UpdateGroup -> String
showsPrec :: Int -> UpdateGroup -> ShowS
$cshowsPrec :: Int -> UpdateGroup -> ShowS
Prelude.Show, forall x. Rep UpdateGroup x -> UpdateGroup
forall x. UpdateGroup -> Rep UpdateGroup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateGroup x -> UpdateGroup
$cfrom :: forall x. UpdateGroup -> Rep UpdateGroup x
Prelude.Generic)

-- |
-- Create a value of 'UpdateGroup' 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:
--
-- 'description', 'updateGroup_description' - The new description that you want to update the resource group with.
-- Descriptions can contain letters, numbers, hyphens, underscores,
-- periods, and spaces.
--
-- 'group'', 'updateGroup_group' - The name or the ARN of the resource group to modify.
--
-- 'groupName', 'updateGroup_groupName' - Don\'t use this parameter. Use @Group@ instead.
newUpdateGroup ::
  UpdateGroup
newUpdateGroup :: UpdateGroup
newUpdateGroup =
  UpdateGroup'
    { $sel:description:UpdateGroup' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:group':UpdateGroup' :: Maybe Text
group' = forall a. Maybe a
Prelude.Nothing,
      $sel:groupName:UpdateGroup' :: Maybe Text
groupName = forall a. Maybe a
Prelude.Nothing
    }

-- | The new description that you want to update the resource group with.
-- Descriptions can contain letters, numbers, hyphens, underscores,
-- periods, and spaces.
updateGroup_description :: Lens.Lens' UpdateGroup (Prelude.Maybe Prelude.Text)
updateGroup_description :: Lens' UpdateGroup (Maybe Text)
updateGroup_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateGroup' {Maybe Text
description :: Maybe Text
$sel:description:UpdateGroup' :: UpdateGroup -> Maybe Text
description} -> Maybe Text
description) (\s :: UpdateGroup
s@UpdateGroup' {} Maybe Text
a -> UpdateGroup
s {$sel:description:UpdateGroup' :: Maybe Text
description = Maybe Text
a} :: UpdateGroup)

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

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

instance Core.AWSRequest UpdateGroup where
  type AWSResponse UpdateGroup = UpdateGroupResponse
  request :: (Service -> Service) -> UpdateGroup -> Request UpdateGroup
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 UpdateGroup
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse UpdateGroup)))
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 -> UpdateGroupResponse
UpdateGroupResponse'
            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 UpdateGroup where
  hashWithSalt :: Int -> UpdateGroup -> Int
hashWithSalt Int
_salt UpdateGroup' {Maybe Text
groupName :: Maybe Text
group' :: Maybe Text
description :: Maybe Text
$sel:groupName:UpdateGroup' :: UpdateGroup -> Maybe Text
$sel:group':UpdateGroup' :: UpdateGroup -> Maybe Text
$sel:description:UpdateGroup' :: UpdateGroup -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      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 UpdateGroup where
  rnf :: UpdateGroup -> ()
rnf UpdateGroup' {Maybe Text
groupName :: Maybe Text
group' :: Maybe Text
description :: Maybe Text
$sel:groupName:UpdateGroup' :: UpdateGroup -> Maybe Text
$sel:group':UpdateGroup' :: UpdateGroup -> Maybe Text
$sel:description:UpdateGroup' :: UpdateGroup -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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 UpdateGroup where
  toHeaders :: UpdateGroup -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

instance Data.ToJSON UpdateGroup where
  toJSON :: UpdateGroup -> Value
toJSON UpdateGroup' {Maybe Text
groupName :: Maybe Text
group' :: Maybe Text
description :: Maybe Text
$sel:groupName:UpdateGroup' :: UpdateGroup -> Maybe Text
$sel:group':UpdateGroup' :: UpdateGroup -> Maybe Text
$sel:description:UpdateGroup' :: UpdateGroup -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Description" 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
description,
            (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 UpdateGroup where
  toPath :: UpdateGroup -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/update-group"

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

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

-- |
-- Create a value of 'UpdateGroupResponse' 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'', 'updateGroupResponse_group' - The update description of the resource group.
--
-- 'httpStatus', 'updateGroupResponse_httpStatus' - The response's http status code.
newUpdateGroupResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateGroupResponse
newUpdateGroupResponse :: Int -> UpdateGroupResponse
newUpdateGroupResponse Int
pHttpStatus_ =
  UpdateGroupResponse'
    { $sel:group':UpdateGroupResponse' :: Maybe Group
group' = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UpdateGroupResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The update description of the resource group.
updateGroupResponse_group :: Lens.Lens' UpdateGroupResponse (Prelude.Maybe Group)
updateGroupResponse_group :: Lens' UpdateGroupResponse (Maybe Group)
updateGroupResponse_group = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateGroupResponse' {Maybe Group
group' :: Maybe Group
$sel:group':UpdateGroupResponse' :: UpdateGroupResponse -> Maybe Group
group'} -> Maybe Group
group') (\s :: UpdateGroupResponse
s@UpdateGroupResponse' {} Maybe Group
a -> UpdateGroupResponse
s {$sel:group':UpdateGroupResponse' :: Maybe Group
group' = Maybe Group
a} :: UpdateGroupResponse)

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

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