{-# 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.CreateGroup
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Creates a new group in the specified user pool.
--
-- Calling this action requires developer credentials.
module Amazonka.CognitoIdentityProvider.CreateGroup
  ( -- * Creating a Request
    CreateGroup (..),
    newCreateGroup,

    -- * Request Lenses
    createGroup_description,
    createGroup_precedence,
    createGroup_roleArn,
    createGroup_groupName,
    createGroup_userPoolId,

    -- * Destructuring the Response
    CreateGroupResponse (..),
    newCreateGroupResponse,

    -- * Response Lenses
    createGroupResponse_group,
    createGroupResponse_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:/ 'newCreateGroup' smart constructor.
data CreateGroup = CreateGroup'
  { -- | A string containing the description of the group.
    CreateGroup -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | A non-negative integer value that specifies the precedence of this group
    -- relative to the other groups that a user can belong to in the user pool.
    -- Zero is the highest precedence value. Groups with lower @Precedence@
    -- values take precedence over groups with higher or null @Precedence@
    -- values. If a user belongs to two or more groups, it is the group with
    -- the lowest precedence value whose role ARN is given in the user\'s
    -- tokens for the @cognito:roles@ and @cognito:preferred_role@ claims.
    --
    -- Two groups can have the same @Precedence@ value. If this happens,
    -- neither group takes precedence over the other. If two groups with the
    -- same @Precedence@ have the same role ARN, that role is used in the
    -- @cognito:preferred_role@ claim in tokens for users in each group. If the
    -- two groups have different role ARNs, the @cognito:preferred_role@ claim
    -- isn\'t set in users\' tokens.
    --
    -- The default @Precedence@ value is null. The maximum @Precedence@ value
    -- is @2^31-1@.
    CreateGroup -> Maybe Natural
precedence :: Prelude.Maybe Prelude.Natural,
    -- | The role Amazon Resource Name (ARN) for the group.
    CreateGroup -> Maybe Text
roleArn :: Prelude.Maybe Prelude.Text,
    -- | The name of the group. Must be unique.
    CreateGroup -> Text
groupName :: Prelude.Text,
    -- | The user pool ID for the user pool.
    CreateGroup -> Text
userPoolId :: Prelude.Text
  }
  deriving (CreateGroup -> CreateGroup -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateGroup -> CreateGroup -> Bool
$c/= :: CreateGroup -> CreateGroup -> Bool
== :: CreateGroup -> CreateGroup -> Bool
$c== :: CreateGroup -> CreateGroup -> Bool
Prelude.Eq, ReadPrec [CreateGroup]
ReadPrec CreateGroup
Int -> ReadS CreateGroup
ReadS [CreateGroup]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateGroup]
$creadListPrec :: ReadPrec [CreateGroup]
readPrec :: ReadPrec CreateGroup
$creadPrec :: ReadPrec CreateGroup
readList :: ReadS [CreateGroup]
$creadList :: ReadS [CreateGroup]
readsPrec :: Int -> ReadS CreateGroup
$creadsPrec :: Int -> ReadS CreateGroup
Prelude.Read, Int -> CreateGroup -> ShowS
[CreateGroup] -> ShowS
CreateGroup -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateGroup] -> ShowS
$cshowList :: [CreateGroup] -> ShowS
show :: CreateGroup -> String
$cshow :: CreateGroup -> String
showsPrec :: Int -> CreateGroup -> ShowS
$cshowsPrec :: Int -> CreateGroup -> ShowS
Prelude.Show, forall x. Rep CreateGroup x -> CreateGroup
forall x. CreateGroup -> Rep CreateGroup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateGroup x -> CreateGroup
$cfrom :: forall x. CreateGroup -> Rep CreateGroup x
Prelude.Generic)

-- |
-- Create a value of 'CreateGroup' 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', 'createGroup_description' - A string containing the description of the group.
--
-- 'precedence', 'createGroup_precedence' - A non-negative integer value that specifies the precedence of this group
-- relative to the other groups that a user can belong to in the user pool.
-- Zero is the highest precedence value. Groups with lower @Precedence@
-- values take precedence over groups with higher or null @Precedence@
-- values. If a user belongs to two or more groups, it is the group with
-- the lowest precedence value whose role ARN is given in the user\'s
-- tokens for the @cognito:roles@ and @cognito:preferred_role@ claims.
--
-- Two groups can have the same @Precedence@ value. If this happens,
-- neither group takes precedence over the other. If two groups with the
-- same @Precedence@ have the same role ARN, that role is used in the
-- @cognito:preferred_role@ claim in tokens for users in each group. If the
-- two groups have different role ARNs, the @cognito:preferred_role@ claim
-- isn\'t set in users\' tokens.
--
-- The default @Precedence@ value is null. The maximum @Precedence@ value
-- is @2^31-1@.
--
-- 'roleArn', 'createGroup_roleArn' - The role Amazon Resource Name (ARN) for the group.
--
-- 'groupName', 'createGroup_groupName' - The name of the group. Must be unique.
--
-- 'userPoolId', 'createGroup_userPoolId' - The user pool ID for the user pool.
newCreateGroup ::
  -- | 'groupName'
  Prelude.Text ->
  -- | 'userPoolId'
  Prelude.Text ->
  CreateGroup
newCreateGroup :: Text -> Text -> CreateGroup
newCreateGroup Text
pGroupName_ Text
pUserPoolId_ =
  CreateGroup'
    { $sel:description:CreateGroup' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:precedence:CreateGroup' :: Maybe Natural
precedence = forall a. Maybe a
Prelude.Nothing,
      $sel:roleArn:CreateGroup' :: Maybe Text
roleArn = forall a. Maybe a
Prelude.Nothing,
      $sel:groupName:CreateGroup' :: Text
groupName = Text
pGroupName_,
      $sel:userPoolId:CreateGroup' :: Text
userPoolId = Text
pUserPoolId_
    }

-- | A string containing the description of the group.
createGroup_description :: Lens.Lens' CreateGroup (Prelude.Maybe Prelude.Text)
createGroup_description :: Lens' CreateGroup (Maybe Text)
createGroup_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateGroup' {Maybe Text
description :: Maybe Text
$sel:description:CreateGroup' :: CreateGroup -> Maybe Text
description} -> Maybe Text
description) (\s :: CreateGroup
s@CreateGroup' {} Maybe Text
a -> CreateGroup
s {$sel:description:CreateGroup' :: Maybe Text
description = Maybe Text
a} :: CreateGroup)

-- | A non-negative integer value that specifies the precedence of this group
-- relative to the other groups that a user can belong to in the user pool.
-- Zero is the highest precedence value. Groups with lower @Precedence@
-- values take precedence over groups with higher or null @Precedence@
-- values. If a user belongs to two or more groups, it is the group with
-- the lowest precedence value whose role ARN is given in the user\'s
-- tokens for the @cognito:roles@ and @cognito:preferred_role@ claims.
--
-- Two groups can have the same @Precedence@ value. If this happens,
-- neither group takes precedence over the other. If two groups with the
-- same @Precedence@ have the same role ARN, that role is used in the
-- @cognito:preferred_role@ claim in tokens for users in each group. If the
-- two groups have different role ARNs, the @cognito:preferred_role@ claim
-- isn\'t set in users\' tokens.
--
-- The default @Precedence@ value is null. The maximum @Precedence@ value
-- is @2^31-1@.
createGroup_precedence :: Lens.Lens' CreateGroup (Prelude.Maybe Prelude.Natural)
createGroup_precedence :: Lens' CreateGroup (Maybe Natural)
createGroup_precedence = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateGroup' {Maybe Natural
precedence :: Maybe Natural
$sel:precedence:CreateGroup' :: CreateGroup -> Maybe Natural
precedence} -> Maybe Natural
precedence) (\s :: CreateGroup
s@CreateGroup' {} Maybe Natural
a -> CreateGroup
s {$sel:precedence:CreateGroup' :: Maybe Natural
precedence = Maybe Natural
a} :: CreateGroup)

-- | The role Amazon Resource Name (ARN) for the group.
createGroup_roleArn :: Lens.Lens' CreateGroup (Prelude.Maybe Prelude.Text)
createGroup_roleArn :: Lens' CreateGroup (Maybe Text)
createGroup_roleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateGroup' {Maybe Text
roleArn :: Maybe Text
$sel:roleArn:CreateGroup' :: CreateGroup -> Maybe Text
roleArn} -> Maybe Text
roleArn) (\s :: CreateGroup
s@CreateGroup' {} Maybe Text
a -> CreateGroup
s {$sel:roleArn:CreateGroup' :: Maybe Text
roleArn = Maybe Text
a} :: CreateGroup)

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

-- | The user pool ID for the user pool.
createGroup_userPoolId :: Lens.Lens' CreateGroup Prelude.Text
createGroup_userPoolId :: Lens' CreateGroup Text
createGroup_userPoolId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateGroup' {Text
userPoolId :: Text
$sel:userPoolId:CreateGroup' :: CreateGroup -> Text
userPoolId} -> Text
userPoolId) (\s :: CreateGroup
s@CreateGroup' {} Text
a -> CreateGroup
s {$sel:userPoolId:CreateGroup' :: Text
userPoolId = Text
a} :: CreateGroup)

instance Core.AWSRequest CreateGroup where
  type AWSResponse CreateGroup = CreateGroupResponse
  request :: (Service -> Service) -> CreateGroup -> Request CreateGroup
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 CreateGroup
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse CreateGroup)))
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 -> CreateGroupResponse
CreateGroupResponse'
            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 CreateGroup where
  hashWithSalt :: Int -> CreateGroup -> Int
hashWithSalt Int
_salt CreateGroup' {Maybe Natural
Maybe Text
Text
userPoolId :: Text
groupName :: Text
roleArn :: Maybe Text
precedence :: Maybe Natural
description :: Maybe Text
$sel:userPoolId:CreateGroup' :: CreateGroup -> Text
$sel:groupName:CreateGroup' :: CreateGroup -> Text
$sel:roleArn:CreateGroup' :: CreateGroup -> Maybe Text
$sel:precedence:CreateGroup' :: CreateGroup -> Maybe Natural
$sel:description:CreateGroup' :: CreateGroup -> 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 CreateGroup where
  rnf :: CreateGroup -> ()
rnf CreateGroup' {Maybe Natural
Maybe Text
Text
userPoolId :: Text
groupName :: Text
roleArn :: Maybe Text
precedence :: Maybe Natural
description :: Maybe Text
$sel:userPoolId:CreateGroup' :: CreateGroup -> Text
$sel:groupName:CreateGroup' :: CreateGroup -> Text
$sel:roleArn:CreateGroup' :: CreateGroup -> Maybe Text
$sel:precedence:CreateGroup' :: CreateGroup -> Maybe Natural
$sel:description:CreateGroup' :: CreateGroup -> 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 CreateGroup where
  toHeaders :: CreateGroup -> 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.CreateGroup" ::
                          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 CreateGroup where
  toJSON :: CreateGroup -> Value
toJSON CreateGroup' {Maybe Natural
Maybe Text
Text
userPoolId :: Text
groupName :: Text
roleArn :: Maybe Text
precedence :: Maybe Natural
description :: Maybe Text
$sel:userPoolId:CreateGroup' :: CreateGroup -> Text
$sel:groupName:CreateGroup' :: CreateGroup -> Text
$sel:roleArn:CreateGroup' :: CreateGroup -> Maybe Text
$sel:precedence:CreateGroup' :: CreateGroup -> Maybe Natural
$sel:description:CreateGroup' :: CreateGroup -> 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 CreateGroup where
  toPath :: CreateGroup -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

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

-- |
-- Create a value of 'CreateGroupResponse' 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'', 'createGroupResponse_group' - The group object for the group.
--
-- 'httpStatus', 'createGroupResponse_httpStatus' - The response's http status code.
newCreateGroupResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateGroupResponse
newCreateGroupResponse :: Int -> CreateGroupResponse
newCreateGroupResponse Int
pHttpStatus_ =
  CreateGroupResponse'
    { $sel:group':CreateGroupResponse' :: Maybe GroupType
group' = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateGroupResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The group object for the group.
createGroupResponse_group :: Lens.Lens' CreateGroupResponse (Prelude.Maybe GroupType)
createGroupResponse_group :: Lens' CreateGroupResponse (Maybe GroupType)
createGroupResponse_group = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateGroupResponse' {Maybe GroupType
group' :: Maybe GroupType
$sel:group':CreateGroupResponse' :: CreateGroupResponse -> Maybe GroupType
group'} -> Maybe GroupType
group') (\s :: CreateGroupResponse
s@CreateGroupResponse' {} Maybe GroupType
a -> CreateGroupResponse
s {$sel:group':CreateGroupResponse' :: Maybe GroupType
group' = Maybe GroupType
a} :: CreateGroupResponse)

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

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