{-# 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.CognitoIdentityProvider.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 specified group with the specified attributes.
--
-- Calling this action requires developer credentials.
module Amazonka.CognitoIdentityProvider.UpdateGroup
  ( -- * Creating a Request
    UpdateGroup (..),
    newUpdateGroup,

    -- * Request Lenses
    updateGroup_description,
    updateGroup_precedence,
    updateGroup_roleArn,
    updateGroup_groupName,
    updateGroup_userPoolId,

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

    -- * Response Lenses
    updateGroupResponse_group,
    updateGroupResponse_httpStatus,
  )
where

import Amazonka.CognitoIdentityProvider.Types
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 qualified Amazonka.Response as Response

-- | /See:/ 'newUpdateGroup' smart constructor.
data UpdateGroup = UpdateGroup'
  { -- | A string containing the new description of the group.
    UpdateGroup -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | The new precedence value for the group. For more information about this
    -- parameter, see
    -- <https://docs.aws.amazon.com/cognito-user-identity-pools/latest/APIReference/API_CreateGroup.html CreateGroup>.
    UpdateGroup -> Maybe Natural
precedence :: Prelude.Maybe Prelude.Natural,
    -- | The new role Amazon Resource Name (ARN) for the group. This is used for
    -- setting the @cognito:roles@ and @cognito:preferred_role@ claims in the
    -- token.
    UpdateGroup -> Maybe Text
roleArn :: Prelude.Maybe Prelude.Text,
    -- | The name of the group.
    UpdateGroup -> Text
groupName :: Prelude.Text,
    -- | The user pool ID for the user pool.
    UpdateGroup -> Text
userPoolId :: 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' - A string containing the new description of the group.
--
-- 'precedence', 'updateGroup_precedence' - The new precedence value for the group. For more information about this
-- parameter, see
-- <https://docs.aws.amazon.com/cognito-user-identity-pools/latest/APIReference/API_CreateGroup.html CreateGroup>.
--
-- 'roleArn', 'updateGroup_roleArn' - The new role Amazon Resource Name (ARN) for the group. This is used for
-- setting the @cognito:roles@ and @cognito:preferred_role@ claims in the
-- token.
--
-- 'groupName', 'updateGroup_groupName' - The name of the group.
--
-- 'userPoolId', 'updateGroup_userPoolId' - The user pool ID for the user pool.
newUpdateGroup ::
  -- | 'groupName'
  Prelude.Text ->
  -- | 'userPoolId'
  Prelude.Text ->
  UpdateGroup
newUpdateGroup :: Text -> Text -> UpdateGroup
newUpdateGroup Text
pGroupName_ Text
pUserPoolId_ =
  UpdateGroup'
    { $sel:description:UpdateGroup' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:precedence:UpdateGroup' :: Maybe Natural
precedence = forall a. Maybe a
Prelude.Nothing,
      $sel:roleArn:UpdateGroup' :: Maybe Text
roleArn = forall a. Maybe a
Prelude.Nothing,
      $sel:groupName:UpdateGroup' :: Text
groupName = Text
pGroupName_,
      $sel:userPoolId:UpdateGroup' :: Text
userPoolId = Text
pUserPoolId_
    }

-- | A string containing the new description of the group.
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 new precedence value for the group. For more information about this
-- parameter, see
-- <https://docs.aws.amazon.com/cognito-user-identity-pools/latest/APIReference/API_CreateGroup.html CreateGroup>.
updateGroup_precedence :: Lens.Lens' UpdateGroup (Prelude.Maybe Prelude.Natural)
updateGroup_precedence :: Lens' UpdateGroup (Maybe Natural)
updateGroup_precedence = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateGroup' {Maybe Natural
precedence :: Maybe Natural
$sel:precedence:UpdateGroup' :: UpdateGroup -> Maybe Natural
precedence} -> Maybe Natural
precedence) (\s :: UpdateGroup
s@UpdateGroup' {} Maybe Natural
a -> UpdateGroup
s {$sel:precedence:UpdateGroup' :: Maybe Natural
precedence = Maybe Natural
a} :: UpdateGroup)

-- | The new role Amazon Resource Name (ARN) for the group. This is used for
-- setting the @cognito:roles@ and @cognito:preferred_role@ claims in the
-- token.
updateGroup_roleArn :: Lens.Lens' UpdateGroup (Prelude.Maybe Prelude.Text)
updateGroup_roleArn :: Lens' UpdateGroup (Maybe Text)
updateGroup_roleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateGroup' {Maybe Text
roleArn :: Maybe Text
$sel:roleArn:UpdateGroup' :: UpdateGroup -> Maybe Text
roleArn} -> Maybe Text
roleArn) (\s :: UpdateGroup
s@UpdateGroup' {} Maybe Text
a -> UpdateGroup
s {$sel:roleArn:UpdateGroup' :: Maybe Text
roleArn = Maybe Text
a} :: UpdateGroup)

-- | The name of the group.
updateGroup_groupName :: Lens.Lens' UpdateGroup Prelude.Text
updateGroup_groupName :: Lens' UpdateGroup Text
updateGroup_groupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateGroup' {Text
groupName :: Text
$sel:groupName:UpdateGroup' :: UpdateGroup -> Text
groupName} -> Text
groupName) (\s :: UpdateGroup
s@UpdateGroup' {} Text
a -> UpdateGroup
s {$sel:groupName:UpdateGroup' :: Text
groupName = Text
a} :: UpdateGroup)

-- | The user pool ID for the user pool.
updateGroup_userPoolId :: Lens.Lens' UpdateGroup Prelude.Text
updateGroup_userPoolId :: Lens' UpdateGroup Text
updateGroup_userPoolId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateGroup' {Text
userPoolId :: Text
$sel:userPoolId:UpdateGroup' :: UpdateGroup -> Text
userPoolId} -> Text
userPoolId) (\s :: UpdateGroup
s@UpdateGroup' {} Text
a -> UpdateGroup
s {$sel:userPoolId:UpdateGroup' :: Text
userPoolId = 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 GroupType -> 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 Natural
Maybe Text
Text
userPoolId :: Text
groupName :: Text
roleArn :: Maybe Text
precedence :: Maybe Natural
description :: Maybe Text
$sel:userPoolId:UpdateGroup' :: UpdateGroup -> Text
$sel:groupName:UpdateGroup' :: UpdateGroup -> Text
$sel:roleArn:UpdateGroup' :: UpdateGroup -> Maybe Text
$sel:precedence:UpdateGroup' :: UpdateGroup -> Maybe Natural
$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 Natural
precedence
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
roleArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
groupName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
userPoolId

instance Prelude.NFData UpdateGroup where
  rnf :: UpdateGroup -> ()
rnf UpdateGroup' {Maybe Natural
Maybe Text
Text
userPoolId :: Text
groupName :: Text
roleArn :: Maybe Text
precedence :: Maybe Natural
description :: Maybe Text
$sel:userPoolId:UpdateGroup' :: UpdateGroup -> Text
$sel:groupName:UpdateGroup' :: UpdateGroup -> Text
$sel:roleArn:UpdateGroup' :: UpdateGroup -> Maybe Text
$sel:precedence:UpdateGroup' :: UpdateGroup -> Maybe Natural
$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 Natural
precedence
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
roleArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
groupName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
userPoolId

instance Data.ToHeaders UpdateGroup where
  toHeaders :: UpdateGroup -> 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
"AWSCognitoIdentityProviderService.UpdateGroup" ::
                          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 UpdateGroup where
  toJSON :: UpdateGroup -> Value
toJSON UpdateGroup' {Maybe Natural
Maybe Text
Text
userPoolId :: Text
groupName :: Text
roleArn :: Maybe Text
precedence :: Maybe Natural
description :: Maybe Text
$sel:userPoolId:UpdateGroup' :: UpdateGroup -> Text
$sel:groupName:UpdateGroup' :: UpdateGroup -> Text
$sel:roleArn:UpdateGroup' :: UpdateGroup -> Maybe Text
$sel:precedence:UpdateGroup' :: UpdateGroup -> Maybe Natural
$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
"Precedence" 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 Natural
precedence,
            (Key
"RoleArn" 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
roleArn,
            forall a. a -> Maybe a
Prelude.Just (Key
"GroupName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
groupName),
            forall a. a -> Maybe a
Prelude.Just (Key
"UserPoolId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
userPoolId)
          ]
      )

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

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 group object for the group.
    UpdateGroupResponse -> Maybe GroupType
group' :: Prelude.Maybe GroupType,
    -- | 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 group object for the 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 GroupType
group' = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UpdateGroupResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The group object for the group.
updateGroupResponse_group :: Lens.Lens' UpdateGroupResponse (Prelude.Maybe GroupType)
updateGroupResponse_group :: Lens' UpdateGroupResponse (Maybe GroupType)
updateGroupResponse_group = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateGroupResponse' {Maybe GroupType
group' :: Maybe GroupType
$sel:group':UpdateGroupResponse' :: UpdateGroupResponse -> Maybe GroupType
group'} -> Maybe GroupType
group') (\s :: UpdateGroupResponse
s@UpdateGroupResponse' {} Maybe GroupType
a -> UpdateGroupResponse
s {$sel:group':UpdateGroupResponse' :: Maybe GroupType
group' = Maybe GroupType
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 GroupType
httpStatus :: Int
group' :: Maybe GroupType
$sel:httpStatus:UpdateGroupResponse' :: UpdateGroupResponse -> Int
$sel:group':UpdateGroupResponse' :: UpdateGroupResponse -> Maybe GroupType
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe GroupType
group'
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus