{-# 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.CodeGuruProfiler.CreateProfilingGroup
-- 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 profiling group.
module Amazonka.CodeGuruProfiler.CreateProfilingGroup
  ( -- * Creating a Request
    CreateProfilingGroup (..),
    newCreateProfilingGroup,

    -- * Request Lenses
    createProfilingGroup_agentOrchestrationConfig,
    createProfilingGroup_computePlatform,
    createProfilingGroup_tags,
    createProfilingGroup_clientToken,
    createProfilingGroup_profilingGroupName,

    -- * Destructuring the Response
    CreateProfilingGroupResponse (..),
    newCreateProfilingGroupResponse,

    -- * Response Lenses
    createProfilingGroupResponse_httpStatus,
    createProfilingGroupResponse_profilingGroup,
  )
where

import Amazonka.CodeGuruProfiler.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

-- | The structure representing the createProfiliingGroupRequest.
--
-- /See:/ 'newCreateProfilingGroup' smart constructor.
data CreateProfilingGroup = CreateProfilingGroup'
  { -- | Specifies whether profiling is enabled or disabled for the created
    -- profiling group.
    CreateProfilingGroup -> Maybe AgentOrchestrationConfig
agentOrchestrationConfig :: Prelude.Maybe AgentOrchestrationConfig,
    -- | The compute platform of the profiling group. Use @AWSLambda@ if your
    -- application runs on AWS Lambda. Use @Default@ if your application runs
    -- on a compute platform that is not AWS Lambda, such an Amazon EC2
    -- instance, an on-premises server, or a different platform. If not
    -- specified, @Default@ is used.
    CreateProfilingGroup -> Maybe ComputePlatform
computePlatform :: Prelude.Maybe ComputePlatform,
    -- | A list of tags to add to the created profiling group.
    CreateProfilingGroup -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | Amazon CodeGuru Profiler uses this universally unique identifier (UUID)
    -- to prevent the accidental creation of duplicate profiling groups if
    -- there are failures and retries.
    CreateProfilingGroup -> Text
clientToken :: Prelude.Text,
    -- | The name of the profiling group to create.
    CreateProfilingGroup -> Text
profilingGroupName :: Prelude.Text
  }
  deriving (CreateProfilingGroup -> CreateProfilingGroup -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateProfilingGroup -> CreateProfilingGroup -> Bool
$c/= :: CreateProfilingGroup -> CreateProfilingGroup -> Bool
== :: CreateProfilingGroup -> CreateProfilingGroup -> Bool
$c== :: CreateProfilingGroup -> CreateProfilingGroup -> Bool
Prelude.Eq, ReadPrec [CreateProfilingGroup]
ReadPrec CreateProfilingGroup
Int -> ReadS CreateProfilingGroup
ReadS [CreateProfilingGroup]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateProfilingGroup]
$creadListPrec :: ReadPrec [CreateProfilingGroup]
readPrec :: ReadPrec CreateProfilingGroup
$creadPrec :: ReadPrec CreateProfilingGroup
readList :: ReadS [CreateProfilingGroup]
$creadList :: ReadS [CreateProfilingGroup]
readsPrec :: Int -> ReadS CreateProfilingGroup
$creadsPrec :: Int -> ReadS CreateProfilingGroup
Prelude.Read, Int -> CreateProfilingGroup -> ShowS
[CreateProfilingGroup] -> ShowS
CreateProfilingGroup -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateProfilingGroup] -> ShowS
$cshowList :: [CreateProfilingGroup] -> ShowS
show :: CreateProfilingGroup -> String
$cshow :: CreateProfilingGroup -> String
showsPrec :: Int -> CreateProfilingGroup -> ShowS
$cshowsPrec :: Int -> CreateProfilingGroup -> ShowS
Prelude.Show, forall x. Rep CreateProfilingGroup x -> CreateProfilingGroup
forall x. CreateProfilingGroup -> Rep CreateProfilingGroup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateProfilingGroup x -> CreateProfilingGroup
$cfrom :: forall x. CreateProfilingGroup -> Rep CreateProfilingGroup x
Prelude.Generic)

-- |
-- Create a value of 'CreateProfilingGroup' 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:
--
-- 'agentOrchestrationConfig', 'createProfilingGroup_agentOrchestrationConfig' - Specifies whether profiling is enabled or disabled for the created
-- profiling group.
--
-- 'computePlatform', 'createProfilingGroup_computePlatform' - The compute platform of the profiling group. Use @AWSLambda@ if your
-- application runs on AWS Lambda. Use @Default@ if your application runs
-- on a compute platform that is not AWS Lambda, such an Amazon EC2
-- instance, an on-premises server, or a different platform. If not
-- specified, @Default@ is used.
--
-- 'tags', 'createProfilingGroup_tags' - A list of tags to add to the created profiling group.
--
-- 'clientToken', 'createProfilingGroup_clientToken' - Amazon CodeGuru Profiler uses this universally unique identifier (UUID)
-- to prevent the accidental creation of duplicate profiling groups if
-- there are failures and retries.
--
-- 'profilingGroupName', 'createProfilingGroup_profilingGroupName' - The name of the profiling group to create.
newCreateProfilingGroup ::
  -- | 'clientToken'
  Prelude.Text ->
  -- | 'profilingGroupName'
  Prelude.Text ->
  CreateProfilingGroup
newCreateProfilingGroup :: Text -> Text -> CreateProfilingGroup
newCreateProfilingGroup
  Text
pClientToken_
  Text
pProfilingGroupName_ =
    CreateProfilingGroup'
      { $sel:agentOrchestrationConfig:CreateProfilingGroup' :: Maybe AgentOrchestrationConfig
agentOrchestrationConfig =
          forall a. Maybe a
Prelude.Nothing,
        $sel:computePlatform:CreateProfilingGroup' :: Maybe ComputePlatform
computePlatform = forall a. Maybe a
Prelude.Nothing,
        $sel:tags:CreateProfilingGroup' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
        $sel:clientToken:CreateProfilingGroup' :: Text
clientToken = Text
pClientToken_,
        $sel:profilingGroupName:CreateProfilingGroup' :: Text
profilingGroupName = Text
pProfilingGroupName_
      }

-- | Specifies whether profiling is enabled or disabled for the created
-- profiling group.
createProfilingGroup_agentOrchestrationConfig :: Lens.Lens' CreateProfilingGroup (Prelude.Maybe AgentOrchestrationConfig)
createProfilingGroup_agentOrchestrationConfig :: Lens' CreateProfilingGroup (Maybe AgentOrchestrationConfig)
createProfilingGroup_agentOrchestrationConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateProfilingGroup' {Maybe AgentOrchestrationConfig
agentOrchestrationConfig :: Maybe AgentOrchestrationConfig
$sel:agentOrchestrationConfig:CreateProfilingGroup' :: CreateProfilingGroup -> Maybe AgentOrchestrationConfig
agentOrchestrationConfig} -> Maybe AgentOrchestrationConfig
agentOrchestrationConfig) (\s :: CreateProfilingGroup
s@CreateProfilingGroup' {} Maybe AgentOrchestrationConfig
a -> CreateProfilingGroup
s {$sel:agentOrchestrationConfig:CreateProfilingGroup' :: Maybe AgentOrchestrationConfig
agentOrchestrationConfig = Maybe AgentOrchestrationConfig
a} :: CreateProfilingGroup)

-- | The compute platform of the profiling group. Use @AWSLambda@ if your
-- application runs on AWS Lambda. Use @Default@ if your application runs
-- on a compute platform that is not AWS Lambda, such an Amazon EC2
-- instance, an on-premises server, or a different platform. If not
-- specified, @Default@ is used.
createProfilingGroup_computePlatform :: Lens.Lens' CreateProfilingGroup (Prelude.Maybe ComputePlatform)
createProfilingGroup_computePlatform :: Lens' CreateProfilingGroup (Maybe ComputePlatform)
createProfilingGroup_computePlatform = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateProfilingGroup' {Maybe ComputePlatform
computePlatform :: Maybe ComputePlatform
$sel:computePlatform:CreateProfilingGroup' :: CreateProfilingGroup -> Maybe ComputePlatform
computePlatform} -> Maybe ComputePlatform
computePlatform) (\s :: CreateProfilingGroup
s@CreateProfilingGroup' {} Maybe ComputePlatform
a -> CreateProfilingGroup
s {$sel:computePlatform:CreateProfilingGroup' :: Maybe ComputePlatform
computePlatform = Maybe ComputePlatform
a} :: CreateProfilingGroup)

-- | A list of tags to add to the created profiling group.
createProfilingGroup_tags :: Lens.Lens' CreateProfilingGroup (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
createProfilingGroup_tags :: Lens' CreateProfilingGroup (Maybe (HashMap Text Text))
createProfilingGroup_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateProfilingGroup' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:CreateProfilingGroup' :: CreateProfilingGroup -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: CreateProfilingGroup
s@CreateProfilingGroup' {} Maybe (HashMap Text Text)
a -> CreateProfilingGroup
s {$sel:tags:CreateProfilingGroup' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: CreateProfilingGroup) 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

-- | Amazon CodeGuru Profiler uses this universally unique identifier (UUID)
-- to prevent the accidental creation of duplicate profiling groups if
-- there are failures and retries.
createProfilingGroup_clientToken :: Lens.Lens' CreateProfilingGroup Prelude.Text
createProfilingGroup_clientToken :: Lens' CreateProfilingGroup Text
createProfilingGroup_clientToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateProfilingGroup' {Text
clientToken :: Text
$sel:clientToken:CreateProfilingGroup' :: CreateProfilingGroup -> Text
clientToken} -> Text
clientToken) (\s :: CreateProfilingGroup
s@CreateProfilingGroup' {} Text
a -> CreateProfilingGroup
s {$sel:clientToken:CreateProfilingGroup' :: Text
clientToken = Text
a} :: CreateProfilingGroup)

-- | The name of the profiling group to create.
createProfilingGroup_profilingGroupName :: Lens.Lens' CreateProfilingGroup Prelude.Text
createProfilingGroup_profilingGroupName :: Lens' CreateProfilingGroup Text
createProfilingGroup_profilingGroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateProfilingGroup' {Text
profilingGroupName :: Text
$sel:profilingGroupName:CreateProfilingGroup' :: CreateProfilingGroup -> Text
profilingGroupName} -> Text
profilingGroupName) (\s :: CreateProfilingGroup
s@CreateProfilingGroup' {} Text
a -> CreateProfilingGroup
s {$sel:profilingGroupName:CreateProfilingGroup' :: Text
profilingGroupName = Text
a} :: CreateProfilingGroup)

instance Core.AWSRequest CreateProfilingGroup where
  type
    AWSResponse CreateProfilingGroup =
      CreateProfilingGroupResponse
  request :: (Service -> Service)
-> CreateProfilingGroup -> Request CreateProfilingGroup
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 CreateProfilingGroup
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CreateProfilingGroup)))
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 ->
          Int -> ProfilingGroupDescription -> CreateProfilingGroupResponse
CreateProfilingGroupResponse'
            forall (f :: * -> *) a b. Functor 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))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall a. FromJSON a => Object -> Either String a
Data.eitherParseJSON Object
x)
      )

instance Prelude.Hashable CreateProfilingGroup where
  hashWithSalt :: Int -> CreateProfilingGroup -> Int
hashWithSalt Int
_salt CreateProfilingGroup' {Maybe (HashMap Text Text)
Maybe AgentOrchestrationConfig
Maybe ComputePlatform
Text
profilingGroupName :: Text
clientToken :: Text
tags :: Maybe (HashMap Text Text)
computePlatform :: Maybe ComputePlatform
agentOrchestrationConfig :: Maybe AgentOrchestrationConfig
$sel:profilingGroupName:CreateProfilingGroup' :: CreateProfilingGroup -> Text
$sel:clientToken:CreateProfilingGroup' :: CreateProfilingGroup -> Text
$sel:tags:CreateProfilingGroup' :: CreateProfilingGroup -> Maybe (HashMap Text Text)
$sel:computePlatform:CreateProfilingGroup' :: CreateProfilingGroup -> Maybe ComputePlatform
$sel:agentOrchestrationConfig:CreateProfilingGroup' :: CreateProfilingGroup -> Maybe AgentOrchestrationConfig
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AgentOrchestrationConfig
agentOrchestrationConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ComputePlatform
computePlatform
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
clientToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
profilingGroupName

instance Prelude.NFData CreateProfilingGroup where
  rnf :: CreateProfilingGroup -> ()
rnf CreateProfilingGroup' {Maybe (HashMap Text Text)
Maybe AgentOrchestrationConfig
Maybe ComputePlatform
Text
profilingGroupName :: Text
clientToken :: Text
tags :: Maybe (HashMap Text Text)
computePlatform :: Maybe ComputePlatform
agentOrchestrationConfig :: Maybe AgentOrchestrationConfig
$sel:profilingGroupName:CreateProfilingGroup' :: CreateProfilingGroup -> Text
$sel:clientToken:CreateProfilingGroup' :: CreateProfilingGroup -> Text
$sel:tags:CreateProfilingGroup' :: CreateProfilingGroup -> Maybe (HashMap Text Text)
$sel:computePlatform:CreateProfilingGroup' :: CreateProfilingGroup -> Maybe ComputePlatform
$sel:agentOrchestrationConfig:CreateProfilingGroup' :: CreateProfilingGroup -> Maybe AgentOrchestrationConfig
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe AgentOrchestrationConfig
agentOrchestrationConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ComputePlatform
computePlatform
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
clientToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
profilingGroupName

instance Data.ToHeaders CreateProfilingGroup where
  toHeaders :: CreateProfilingGroup -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON CreateProfilingGroup where
  toJSON :: CreateProfilingGroup -> Value
toJSON CreateProfilingGroup' {Maybe (HashMap Text Text)
Maybe AgentOrchestrationConfig
Maybe ComputePlatform
Text
profilingGroupName :: Text
clientToken :: Text
tags :: Maybe (HashMap Text Text)
computePlatform :: Maybe ComputePlatform
agentOrchestrationConfig :: Maybe AgentOrchestrationConfig
$sel:profilingGroupName:CreateProfilingGroup' :: CreateProfilingGroup -> Text
$sel:clientToken:CreateProfilingGroup' :: CreateProfilingGroup -> Text
$sel:tags:CreateProfilingGroup' :: CreateProfilingGroup -> Maybe (HashMap Text Text)
$sel:computePlatform:CreateProfilingGroup' :: CreateProfilingGroup -> Maybe ComputePlatform
$sel:agentOrchestrationConfig:CreateProfilingGroup' :: CreateProfilingGroup -> Maybe AgentOrchestrationConfig
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"agentOrchestrationConfig" 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 AgentOrchestrationConfig
agentOrchestrationConfig,
            (Key
"computePlatform" 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 ComputePlatform
computePlatform,
            (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 (HashMap Text Text)
tags,
            forall a. a -> Maybe a
Prelude.Just
              (Key
"profilingGroupName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
profilingGroupName)
          ]
      )

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

instance Data.ToQuery CreateProfilingGroup where
  toQuery :: CreateProfilingGroup -> QueryString
toQuery CreateProfilingGroup' {Maybe (HashMap Text Text)
Maybe AgentOrchestrationConfig
Maybe ComputePlatform
Text
profilingGroupName :: Text
clientToken :: Text
tags :: Maybe (HashMap Text Text)
computePlatform :: Maybe ComputePlatform
agentOrchestrationConfig :: Maybe AgentOrchestrationConfig
$sel:profilingGroupName:CreateProfilingGroup' :: CreateProfilingGroup -> Text
$sel:clientToken:CreateProfilingGroup' :: CreateProfilingGroup -> Text
$sel:tags:CreateProfilingGroup' :: CreateProfilingGroup -> Maybe (HashMap Text Text)
$sel:computePlatform:CreateProfilingGroup' :: CreateProfilingGroup -> Maybe ComputePlatform
$sel:agentOrchestrationConfig:CreateProfilingGroup' :: CreateProfilingGroup -> Maybe AgentOrchestrationConfig
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat [ByteString
"clientToken" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
clientToken]

-- | The structure representing the createProfilingGroupResponse.
--
-- /See:/ 'newCreateProfilingGroupResponse' smart constructor.
data CreateProfilingGroupResponse = CreateProfilingGroupResponse'
  { -- | The response's http status code.
    CreateProfilingGroupResponse -> Int
httpStatus :: Prelude.Int,
    -- | The returned
    -- <https://docs.aws.amazon.com/codeguru/latest/profiler-api/API_ProfilingGroupDescription.html ProfilingGroupDescription>
    -- object that contains information about the created profiling group.
    CreateProfilingGroupResponse -> ProfilingGroupDescription
profilingGroup :: ProfilingGroupDescription
  }
  deriving (CreateProfilingGroupResponse
-> CreateProfilingGroupResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateProfilingGroupResponse
-> CreateProfilingGroupResponse -> Bool
$c/= :: CreateProfilingGroupResponse
-> CreateProfilingGroupResponse -> Bool
== :: CreateProfilingGroupResponse
-> CreateProfilingGroupResponse -> Bool
$c== :: CreateProfilingGroupResponse
-> CreateProfilingGroupResponse -> Bool
Prelude.Eq, ReadPrec [CreateProfilingGroupResponse]
ReadPrec CreateProfilingGroupResponse
Int -> ReadS CreateProfilingGroupResponse
ReadS [CreateProfilingGroupResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateProfilingGroupResponse]
$creadListPrec :: ReadPrec [CreateProfilingGroupResponse]
readPrec :: ReadPrec CreateProfilingGroupResponse
$creadPrec :: ReadPrec CreateProfilingGroupResponse
readList :: ReadS [CreateProfilingGroupResponse]
$creadList :: ReadS [CreateProfilingGroupResponse]
readsPrec :: Int -> ReadS CreateProfilingGroupResponse
$creadsPrec :: Int -> ReadS CreateProfilingGroupResponse
Prelude.Read, Int -> CreateProfilingGroupResponse -> ShowS
[CreateProfilingGroupResponse] -> ShowS
CreateProfilingGroupResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateProfilingGroupResponse] -> ShowS
$cshowList :: [CreateProfilingGroupResponse] -> ShowS
show :: CreateProfilingGroupResponse -> String
$cshow :: CreateProfilingGroupResponse -> String
showsPrec :: Int -> CreateProfilingGroupResponse -> ShowS
$cshowsPrec :: Int -> CreateProfilingGroupResponse -> ShowS
Prelude.Show, forall x.
Rep CreateProfilingGroupResponse x -> CreateProfilingGroupResponse
forall x.
CreateProfilingGroupResponse -> Rep CreateProfilingGroupResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateProfilingGroupResponse x -> CreateProfilingGroupResponse
$cfrom :: forall x.
CreateProfilingGroupResponse -> Rep CreateProfilingGroupResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateProfilingGroupResponse' 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:
--
-- 'httpStatus', 'createProfilingGroupResponse_httpStatus' - The response's http status code.
--
-- 'profilingGroup', 'createProfilingGroupResponse_profilingGroup' - The returned
-- <https://docs.aws.amazon.com/codeguru/latest/profiler-api/API_ProfilingGroupDescription.html ProfilingGroupDescription>
-- object that contains information about the created profiling group.
newCreateProfilingGroupResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'profilingGroup'
  ProfilingGroupDescription ->
  CreateProfilingGroupResponse
newCreateProfilingGroupResponse :: Int -> ProfilingGroupDescription -> CreateProfilingGroupResponse
newCreateProfilingGroupResponse
  Int
pHttpStatus_
  ProfilingGroupDescription
pProfilingGroup_ =
    CreateProfilingGroupResponse'
      { $sel:httpStatus:CreateProfilingGroupResponse' :: Int
httpStatus =
          Int
pHttpStatus_,
        $sel:profilingGroup:CreateProfilingGroupResponse' :: ProfilingGroupDescription
profilingGroup = ProfilingGroupDescription
pProfilingGroup_
      }

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

-- | The returned
-- <https://docs.aws.amazon.com/codeguru/latest/profiler-api/API_ProfilingGroupDescription.html ProfilingGroupDescription>
-- object that contains information about the created profiling group.
createProfilingGroupResponse_profilingGroup :: Lens.Lens' CreateProfilingGroupResponse ProfilingGroupDescription
createProfilingGroupResponse_profilingGroup :: Lens' CreateProfilingGroupResponse ProfilingGroupDescription
createProfilingGroupResponse_profilingGroup = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateProfilingGroupResponse' {ProfilingGroupDescription
profilingGroup :: ProfilingGroupDescription
$sel:profilingGroup:CreateProfilingGroupResponse' :: CreateProfilingGroupResponse -> ProfilingGroupDescription
profilingGroup} -> ProfilingGroupDescription
profilingGroup) (\s :: CreateProfilingGroupResponse
s@CreateProfilingGroupResponse' {} ProfilingGroupDescription
a -> CreateProfilingGroupResponse
s {$sel:profilingGroup:CreateProfilingGroupResponse' :: ProfilingGroupDescription
profilingGroup = ProfilingGroupDescription
a} :: CreateProfilingGroupResponse)

instance Prelude.NFData CreateProfilingGroupResponse where
  rnf :: CreateProfilingGroupResponse -> ()
rnf CreateProfilingGroupResponse' {Int
ProfilingGroupDescription
profilingGroup :: ProfilingGroupDescription
httpStatus :: Int
$sel:profilingGroup:CreateProfilingGroupResponse' :: CreateProfilingGroupResponse -> ProfilingGroupDescription
$sel:httpStatus:CreateProfilingGroupResponse' :: CreateProfilingGroupResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf ProfilingGroupDescription
profilingGroup