{-# 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.XRay.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 group resource with a name and a filter expression.
module Amazonka.XRay.CreateGroup
  ( -- * Creating a Request
    CreateGroup (..),
    newCreateGroup,

    -- * Request Lenses
    createGroup_filterExpression,
    createGroup_insightsConfiguration,
    createGroup_tags,
    createGroup_groupName,

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

    -- * Response Lenses
    createGroupResponse_group,
    createGroupResponse_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 qualified Amazonka.Response as Response
import Amazonka.XRay.Types

-- | /See:/ 'newCreateGroup' smart constructor.
data CreateGroup = CreateGroup'
  { -- | The filter expression defining criteria by which to group traces.
    CreateGroup -> Maybe Text
filterExpression :: Prelude.Maybe Prelude.Text,
    -- | The structure containing configurations related to insights.
    --
    -- -   The InsightsEnabled boolean can be set to true to enable insights
    --     for the new group or false to disable insights for the new group.
    --
    -- -   The NotificationsEnabled boolean can be set to true to enable
    --     insights notifications for the new group. Notifications may only be
    --     enabled on a group with InsightsEnabled set to true.
    CreateGroup -> Maybe InsightsConfiguration
insightsConfiguration :: Prelude.Maybe InsightsConfiguration,
    -- | A map that contains one or more tag keys and tag values to attach to an
    -- X-Ray group. For more information about ways to use tags, see
    -- <https://docs.aws.amazon.com/general/latest/gr/aws_tagging.html Tagging Amazon Web Services resources>
    -- in the /Amazon Web Services General Reference/.
    --
    -- The following restrictions apply to tags:
    --
    -- -   Maximum number of user-applied tags per resource: 50
    --
    -- -   Maximum tag key length: 128 Unicode characters
    --
    -- -   Maximum tag value length: 256 Unicode characters
    --
    -- -   Valid values for key and value: a-z, A-Z, 0-9, space, and the
    --     following characters: _ . : \/ = + - and \@
    --
    -- -   Tag keys and values are case sensitive.
    --
    -- -   Don\'t use @aws:@ as a prefix for keys; it\'s reserved for Amazon
    --     Web Services use.
    CreateGroup -> Maybe [Tag]
tags :: Prelude.Maybe [Tag],
    -- | The case-sensitive name of the new group. Default is a reserved name and
    -- names must be unique.
    CreateGroup -> Text
groupName :: 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:
--
-- 'filterExpression', 'createGroup_filterExpression' - The filter expression defining criteria by which to group traces.
--
-- 'insightsConfiguration', 'createGroup_insightsConfiguration' - The structure containing configurations related to insights.
--
-- -   The InsightsEnabled boolean can be set to true to enable insights
--     for the new group or false to disable insights for the new group.
--
-- -   The NotificationsEnabled boolean can be set to true to enable
--     insights notifications for the new group. Notifications may only be
--     enabled on a group with InsightsEnabled set to true.
--
-- 'tags', 'createGroup_tags' - A map that contains one or more tag keys and tag values to attach to an
-- X-Ray group. For more information about ways to use tags, see
-- <https://docs.aws.amazon.com/general/latest/gr/aws_tagging.html Tagging Amazon Web Services resources>
-- in the /Amazon Web Services General Reference/.
--
-- The following restrictions apply to tags:
--
-- -   Maximum number of user-applied tags per resource: 50
--
-- -   Maximum tag key length: 128 Unicode characters
--
-- -   Maximum tag value length: 256 Unicode characters
--
-- -   Valid values for key and value: a-z, A-Z, 0-9, space, and the
--     following characters: _ . : \/ = + - and \@
--
-- -   Tag keys and values are case sensitive.
--
-- -   Don\'t use @aws:@ as a prefix for keys; it\'s reserved for Amazon
--     Web Services use.
--
-- 'groupName', 'createGroup_groupName' - The case-sensitive name of the new group. Default is a reserved name and
-- names must be unique.
newCreateGroup ::
  -- | 'groupName'
  Prelude.Text ->
  CreateGroup
newCreateGroup :: Text -> CreateGroup
newCreateGroup Text
pGroupName_ =
  CreateGroup'
    { $sel:filterExpression:CreateGroup' :: Maybe Text
filterExpression = forall a. Maybe a
Prelude.Nothing,
      $sel:insightsConfiguration:CreateGroup' :: Maybe InsightsConfiguration
insightsConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:CreateGroup' :: Maybe [Tag]
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:groupName:CreateGroup' :: Text
groupName = Text
pGroupName_
    }

-- | The filter expression defining criteria by which to group traces.
createGroup_filterExpression :: Lens.Lens' CreateGroup (Prelude.Maybe Prelude.Text)
createGroup_filterExpression :: Lens' CreateGroup (Maybe Text)
createGroup_filterExpression = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateGroup' {Maybe Text
filterExpression :: Maybe Text
$sel:filterExpression:CreateGroup' :: CreateGroup -> Maybe Text
filterExpression} -> Maybe Text
filterExpression) (\s :: CreateGroup
s@CreateGroup' {} Maybe Text
a -> CreateGroup
s {$sel:filterExpression:CreateGroup' :: Maybe Text
filterExpression = Maybe Text
a} :: CreateGroup)

-- | The structure containing configurations related to insights.
--
-- -   The InsightsEnabled boolean can be set to true to enable insights
--     for the new group or false to disable insights for the new group.
--
-- -   The NotificationsEnabled boolean can be set to true to enable
--     insights notifications for the new group. Notifications may only be
--     enabled on a group with InsightsEnabled set to true.
createGroup_insightsConfiguration :: Lens.Lens' CreateGroup (Prelude.Maybe InsightsConfiguration)
createGroup_insightsConfiguration :: Lens' CreateGroup (Maybe InsightsConfiguration)
createGroup_insightsConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateGroup' {Maybe InsightsConfiguration
insightsConfiguration :: Maybe InsightsConfiguration
$sel:insightsConfiguration:CreateGroup' :: CreateGroup -> Maybe InsightsConfiguration
insightsConfiguration} -> Maybe InsightsConfiguration
insightsConfiguration) (\s :: CreateGroup
s@CreateGroup' {} Maybe InsightsConfiguration
a -> CreateGroup
s {$sel:insightsConfiguration:CreateGroup' :: Maybe InsightsConfiguration
insightsConfiguration = Maybe InsightsConfiguration
a} :: CreateGroup)

-- | A map that contains one or more tag keys and tag values to attach to an
-- X-Ray group. For more information about ways to use tags, see
-- <https://docs.aws.amazon.com/general/latest/gr/aws_tagging.html Tagging Amazon Web Services resources>
-- in the /Amazon Web Services General Reference/.
--
-- The following restrictions apply to tags:
--
-- -   Maximum number of user-applied tags per resource: 50
--
-- -   Maximum tag key length: 128 Unicode characters
--
-- -   Maximum tag value length: 256 Unicode characters
--
-- -   Valid values for key and value: a-z, A-Z, 0-9, space, and the
--     following characters: _ . : \/ = + - and \@
--
-- -   Tag keys and values are case sensitive.
--
-- -   Don\'t use @aws:@ as a prefix for keys; it\'s reserved for Amazon
--     Web Services use.
createGroup_tags :: Lens.Lens' CreateGroup (Prelude.Maybe [Tag])
createGroup_tags :: Lens' CreateGroup (Maybe [Tag])
createGroup_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateGroup' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:CreateGroup' :: CreateGroup -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: CreateGroup
s@CreateGroup' {} Maybe [Tag]
a -> CreateGroup
s {$sel:tags:CreateGroup' :: Maybe [Tag]
tags = Maybe [Tag]
a} :: CreateGroup) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The case-sensitive name of the new group. Default is a reserved name and
-- names 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)

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 Group -> 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 [Tag]
Maybe Text
Maybe InsightsConfiguration
Text
groupName :: Text
tags :: Maybe [Tag]
insightsConfiguration :: Maybe InsightsConfiguration
filterExpression :: Maybe Text
$sel:groupName:CreateGroup' :: CreateGroup -> Text
$sel:tags:CreateGroup' :: CreateGroup -> Maybe [Tag]
$sel:insightsConfiguration:CreateGroup' :: CreateGroup -> Maybe InsightsConfiguration
$sel:filterExpression:CreateGroup' :: CreateGroup -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
filterExpression
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe InsightsConfiguration
insightsConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Tag]
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
groupName

instance Prelude.NFData CreateGroup where
  rnf :: CreateGroup -> ()
rnf CreateGroup' {Maybe [Tag]
Maybe Text
Maybe InsightsConfiguration
Text
groupName :: Text
tags :: Maybe [Tag]
insightsConfiguration :: Maybe InsightsConfiguration
filterExpression :: Maybe Text
$sel:groupName:CreateGroup' :: CreateGroup -> Text
$sel:tags:CreateGroup' :: CreateGroup -> Maybe [Tag]
$sel:insightsConfiguration:CreateGroup' :: CreateGroup -> Maybe InsightsConfiguration
$sel:filterExpression:CreateGroup' :: CreateGroup -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
filterExpression
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe InsightsConfiguration
insightsConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Tag]
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
groupName

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

instance Data.ToJSON CreateGroup where
  toJSON :: CreateGroup -> Value
toJSON CreateGroup' {Maybe [Tag]
Maybe Text
Maybe InsightsConfiguration
Text
groupName :: Text
tags :: Maybe [Tag]
insightsConfiguration :: Maybe InsightsConfiguration
filterExpression :: Maybe Text
$sel:groupName:CreateGroup' :: CreateGroup -> Text
$sel:tags:CreateGroup' :: CreateGroup -> Maybe [Tag]
$sel:insightsConfiguration:CreateGroup' :: CreateGroup -> Maybe InsightsConfiguration
$sel:filterExpression:CreateGroup' :: CreateGroup -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"FilterExpression" 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
filterExpression,
            (Key
"InsightsConfiguration" 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 InsightsConfiguration
insightsConfiguration,
            (Key
"Tags" 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 [Tag]
tags,
            forall a. a -> Maybe a
Prelude.Just (Key
"GroupName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
groupName)
          ]
      )

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

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 that was created. Contains the name of the group that was
    -- created, the Amazon Resource Name (ARN) of the group that was generated
    -- based on the group name, the filter expression, and the insight
    -- configuration that was assigned to the group.
    CreateGroupResponse -> Maybe Group
group' :: Prelude.Maybe Group,
    -- | 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 that was created. Contains the name of the group that was
-- created, the Amazon Resource Name (ARN) of the group that was generated
-- based on the group name, the filter expression, and the insight
-- configuration that was assigned to 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 Group
group' = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateGroupResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The group that was created. Contains the name of the group that was
-- created, the Amazon Resource Name (ARN) of the group that was generated
-- based on the group name, the filter expression, and the insight
-- configuration that was assigned to the group.
createGroupResponse_group :: Lens.Lens' CreateGroupResponse (Prelude.Maybe Group)
createGroupResponse_group :: Lens' CreateGroupResponse (Maybe Group)
createGroupResponse_group = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateGroupResponse' {Maybe Group
group' :: Maybe Group
$sel:group':CreateGroupResponse' :: CreateGroupResponse -> Maybe Group
group'} -> Maybe Group
group') (\s :: CreateGroupResponse
s@CreateGroupResponse' {} Maybe Group
a -> CreateGroupResponse
s {$sel:group':CreateGroupResponse' :: Maybe Group
group' = Maybe Group
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 Group
httpStatus :: Int
group' :: Maybe Group
$sel:httpStatus:CreateGroupResponse' :: CreateGroupResponse -> Int
$sel:group':CreateGroupResponse' :: CreateGroupResponse -> 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