{-# 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.SageMaker.CreateWorkteam
-- 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 work team for labeling your data. A work team is defined
-- by one or more Amazon Cognito user pools. You must first create the user
-- pools before you can create a work team.
--
-- You cannot create more than 25 work teams in an account and region.
module Amazonka.SageMaker.CreateWorkteam
  ( -- * Creating a Request
    CreateWorkteam (..),
    newCreateWorkteam,

    -- * Request Lenses
    createWorkteam_notificationConfiguration,
    createWorkteam_tags,
    createWorkteam_workforceName,
    createWorkteam_workteamName,
    createWorkteam_memberDefinitions,
    createWorkteam_description,

    -- * Destructuring the Response
    CreateWorkteamResponse (..),
    newCreateWorkteamResponse,

    -- * Response Lenses
    createWorkteamResponse_workteamArn,
    createWorkteamResponse_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.SageMaker.Types

-- | /See:/ 'newCreateWorkteam' smart constructor.
data CreateWorkteam = CreateWorkteam'
  { -- | Configures notification of workers regarding available or expiring work
    -- items.
    CreateWorkteam -> Maybe NotificationConfiguration
notificationConfiguration :: Prelude.Maybe NotificationConfiguration,
    -- | An array of key-value pairs.
    --
    -- For more information, see
    -- <https://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-resource-tags.html Resource Tag>
    -- and
    -- <https://docs.aws.amazon.com/awsaccountbilling/latest/aboutv2/cost-alloc-tags.html#allocation-what Using Cost Allocation Tags>
    -- in the /Amazon Web Services Billing and Cost Management User Guide/.
    CreateWorkteam -> Maybe [Tag]
tags :: Prelude.Maybe [Tag],
    -- | The name of the workforce.
    CreateWorkteam -> Maybe Text
workforceName :: Prelude.Maybe Prelude.Text,
    -- | The name of the work team. Use this name to identify the work team.
    CreateWorkteam -> Text
workteamName :: Prelude.Text,
    -- | A list of @MemberDefinition@ objects that contains objects that identify
    -- the workers that make up the work team.
    --
    -- Workforces can be created using Amazon Cognito or your own OIDC Identity
    -- Provider (IdP). For private workforces created using Amazon Cognito use
    -- @CognitoMemberDefinition@. For workforces created using your own OIDC
    -- identity provider (IdP) use @OidcMemberDefinition@. Do not provide input
    -- for both of these parameters in a single request.
    --
    -- For workforces created using Amazon Cognito, private work teams
    -- correspond to Amazon Cognito /user groups/ within the user pool used to
    -- create a workforce. All of the @CognitoMemberDefinition@ objects that
    -- make up the member definition must have the same @ClientId@ and
    -- @UserPool@ values. To add a Amazon Cognito user group to an existing
    -- worker pool, see < Adding groups to a User Pool>. For more information
    -- about user pools, see
    -- <https://docs.aws.amazon.com/cognito/latest/developerguide/cognito-user-identity-pools.html Amazon Cognito User Pools>.
    --
    -- For workforces created using your own OIDC IdP, specify the user groups
    -- that you want to include in your private work team in
    -- @OidcMemberDefinition@ by listing those groups in @Groups@.
    CreateWorkteam -> NonEmpty MemberDefinition
memberDefinitions :: Prelude.NonEmpty MemberDefinition,
    -- | A description of the work team.
    CreateWorkteam -> Text
description :: Prelude.Text
  }
  deriving (CreateWorkteam -> CreateWorkteam -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateWorkteam -> CreateWorkteam -> Bool
$c/= :: CreateWorkteam -> CreateWorkteam -> Bool
== :: CreateWorkteam -> CreateWorkteam -> Bool
$c== :: CreateWorkteam -> CreateWorkteam -> Bool
Prelude.Eq, ReadPrec [CreateWorkteam]
ReadPrec CreateWorkteam
Int -> ReadS CreateWorkteam
ReadS [CreateWorkteam]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateWorkteam]
$creadListPrec :: ReadPrec [CreateWorkteam]
readPrec :: ReadPrec CreateWorkteam
$creadPrec :: ReadPrec CreateWorkteam
readList :: ReadS [CreateWorkteam]
$creadList :: ReadS [CreateWorkteam]
readsPrec :: Int -> ReadS CreateWorkteam
$creadsPrec :: Int -> ReadS CreateWorkteam
Prelude.Read, Int -> CreateWorkteam -> ShowS
[CreateWorkteam] -> ShowS
CreateWorkteam -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateWorkteam] -> ShowS
$cshowList :: [CreateWorkteam] -> ShowS
show :: CreateWorkteam -> String
$cshow :: CreateWorkteam -> String
showsPrec :: Int -> CreateWorkteam -> ShowS
$cshowsPrec :: Int -> CreateWorkteam -> ShowS
Prelude.Show, forall x. Rep CreateWorkteam x -> CreateWorkteam
forall x. CreateWorkteam -> Rep CreateWorkteam x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateWorkteam x -> CreateWorkteam
$cfrom :: forall x. CreateWorkteam -> Rep CreateWorkteam x
Prelude.Generic)

-- |
-- Create a value of 'CreateWorkteam' 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:
--
-- 'notificationConfiguration', 'createWorkteam_notificationConfiguration' - Configures notification of workers regarding available or expiring work
-- items.
--
-- 'tags', 'createWorkteam_tags' - An array of key-value pairs.
--
-- For more information, see
-- <https://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-resource-tags.html Resource Tag>
-- and
-- <https://docs.aws.amazon.com/awsaccountbilling/latest/aboutv2/cost-alloc-tags.html#allocation-what Using Cost Allocation Tags>
-- in the /Amazon Web Services Billing and Cost Management User Guide/.
--
-- 'workforceName', 'createWorkteam_workforceName' - The name of the workforce.
--
-- 'workteamName', 'createWorkteam_workteamName' - The name of the work team. Use this name to identify the work team.
--
-- 'memberDefinitions', 'createWorkteam_memberDefinitions' - A list of @MemberDefinition@ objects that contains objects that identify
-- the workers that make up the work team.
--
-- Workforces can be created using Amazon Cognito or your own OIDC Identity
-- Provider (IdP). For private workforces created using Amazon Cognito use
-- @CognitoMemberDefinition@. For workforces created using your own OIDC
-- identity provider (IdP) use @OidcMemberDefinition@. Do not provide input
-- for both of these parameters in a single request.
--
-- For workforces created using Amazon Cognito, private work teams
-- correspond to Amazon Cognito /user groups/ within the user pool used to
-- create a workforce. All of the @CognitoMemberDefinition@ objects that
-- make up the member definition must have the same @ClientId@ and
-- @UserPool@ values. To add a Amazon Cognito user group to an existing
-- worker pool, see < Adding groups to a User Pool>. For more information
-- about user pools, see
-- <https://docs.aws.amazon.com/cognito/latest/developerguide/cognito-user-identity-pools.html Amazon Cognito User Pools>.
--
-- For workforces created using your own OIDC IdP, specify the user groups
-- that you want to include in your private work team in
-- @OidcMemberDefinition@ by listing those groups in @Groups@.
--
-- 'description', 'createWorkteam_description' - A description of the work team.
newCreateWorkteam ::
  -- | 'workteamName'
  Prelude.Text ->
  -- | 'memberDefinitions'
  Prelude.NonEmpty MemberDefinition ->
  -- | 'description'
  Prelude.Text ->
  CreateWorkteam
newCreateWorkteam :: Text -> NonEmpty MemberDefinition -> Text -> CreateWorkteam
newCreateWorkteam
  Text
pWorkteamName_
  NonEmpty MemberDefinition
pMemberDefinitions_
  Text
pDescription_ =
    CreateWorkteam'
      { $sel:notificationConfiguration:CreateWorkteam' :: Maybe NotificationConfiguration
notificationConfiguration =
          forall a. Maybe a
Prelude.Nothing,
        $sel:tags:CreateWorkteam' :: Maybe [Tag]
tags = forall a. Maybe a
Prelude.Nothing,
        $sel:workforceName:CreateWorkteam' :: Maybe Text
workforceName = forall a. Maybe a
Prelude.Nothing,
        $sel:workteamName:CreateWorkteam' :: Text
workteamName = Text
pWorkteamName_,
        $sel:memberDefinitions:CreateWorkteam' :: NonEmpty MemberDefinition
memberDefinitions =
          forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced forall t b. AReview t b -> b -> t
Lens.# NonEmpty MemberDefinition
pMemberDefinitions_,
        $sel:description:CreateWorkteam' :: Text
description = Text
pDescription_
      }

-- | Configures notification of workers regarding available or expiring work
-- items.
createWorkteam_notificationConfiguration :: Lens.Lens' CreateWorkteam (Prelude.Maybe NotificationConfiguration)
createWorkteam_notificationConfiguration :: Lens' CreateWorkteam (Maybe NotificationConfiguration)
createWorkteam_notificationConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateWorkteam' {Maybe NotificationConfiguration
notificationConfiguration :: Maybe NotificationConfiguration
$sel:notificationConfiguration:CreateWorkteam' :: CreateWorkteam -> Maybe NotificationConfiguration
notificationConfiguration} -> Maybe NotificationConfiguration
notificationConfiguration) (\s :: CreateWorkteam
s@CreateWorkteam' {} Maybe NotificationConfiguration
a -> CreateWorkteam
s {$sel:notificationConfiguration:CreateWorkteam' :: Maybe NotificationConfiguration
notificationConfiguration = Maybe NotificationConfiguration
a} :: CreateWorkteam)

-- | An array of key-value pairs.
--
-- For more information, see
-- <https://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-resource-tags.html Resource Tag>
-- and
-- <https://docs.aws.amazon.com/awsaccountbilling/latest/aboutv2/cost-alloc-tags.html#allocation-what Using Cost Allocation Tags>
-- in the /Amazon Web Services Billing and Cost Management User Guide/.
createWorkteam_tags :: Lens.Lens' CreateWorkteam (Prelude.Maybe [Tag])
createWorkteam_tags :: Lens' CreateWorkteam (Maybe [Tag])
createWorkteam_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateWorkteam' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:CreateWorkteam' :: CreateWorkteam -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: CreateWorkteam
s@CreateWorkteam' {} Maybe [Tag]
a -> CreateWorkteam
s {$sel:tags:CreateWorkteam' :: Maybe [Tag]
tags = Maybe [Tag]
a} :: CreateWorkteam) 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 name of the workforce.
createWorkteam_workforceName :: Lens.Lens' CreateWorkteam (Prelude.Maybe Prelude.Text)
createWorkteam_workforceName :: Lens' CreateWorkteam (Maybe Text)
createWorkteam_workforceName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateWorkteam' {Maybe Text
workforceName :: Maybe Text
$sel:workforceName:CreateWorkteam' :: CreateWorkteam -> Maybe Text
workforceName} -> Maybe Text
workforceName) (\s :: CreateWorkteam
s@CreateWorkteam' {} Maybe Text
a -> CreateWorkteam
s {$sel:workforceName:CreateWorkteam' :: Maybe Text
workforceName = Maybe Text
a} :: CreateWorkteam)

-- | The name of the work team. Use this name to identify the work team.
createWorkteam_workteamName :: Lens.Lens' CreateWorkteam Prelude.Text
createWorkteam_workteamName :: Lens' CreateWorkteam Text
createWorkteam_workteamName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateWorkteam' {Text
workteamName :: Text
$sel:workteamName:CreateWorkteam' :: CreateWorkteam -> Text
workteamName} -> Text
workteamName) (\s :: CreateWorkteam
s@CreateWorkteam' {} Text
a -> CreateWorkteam
s {$sel:workteamName:CreateWorkteam' :: Text
workteamName = Text
a} :: CreateWorkteam)

-- | A list of @MemberDefinition@ objects that contains objects that identify
-- the workers that make up the work team.
--
-- Workforces can be created using Amazon Cognito or your own OIDC Identity
-- Provider (IdP). For private workforces created using Amazon Cognito use
-- @CognitoMemberDefinition@. For workforces created using your own OIDC
-- identity provider (IdP) use @OidcMemberDefinition@. Do not provide input
-- for both of these parameters in a single request.
--
-- For workforces created using Amazon Cognito, private work teams
-- correspond to Amazon Cognito /user groups/ within the user pool used to
-- create a workforce. All of the @CognitoMemberDefinition@ objects that
-- make up the member definition must have the same @ClientId@ and
-- @UserPool@ values. To add a Amazon Cognito user group to an existing
-- worker pool, see < Adding groups to a User Pool>. For more information
-- about user pools, see
-- <https://docs.aws.amazon.com/cognito/latest/developerguide/cognito-user-identity-pools.html Amazon Cognito User Pools>.
--
-- For workforces created using your own OIDC IdP, specify the user groups
-- that you want to include in your private work team in
-- @OidcMemberDefinition@ by listing those groups in @Groups@.
createWorkteam_memberDefinitions :: Lens.Lens' CreateWorkteam (Prelude.NonEmpty MemberDefinition)
createWorkteam_memberDefinitions :: Lens' CreateWorkteam (NonEmpty MemberDefinition)
createWorkteam_memberDefinitions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateWorkteam' {NonEmpty MemberDefinition
memberDefinitions :: NonEmpty MemberDefinition
$sel:memberDefinitions:CreateWorkteam' :: CreateWorkteam -> NonEmpty MemberDefinition
memberDefinitions} -> NonEmpty MemberDefinition
memberDefinitions) (\s :: CreateWorkteam
s@CreateWorkteam' {} NonEmpty MemberDefinition
a -> CreateWorkteam
s {$sel:memberDefinitions:CreateWorkteam' :: NonEmpty MemberDefinition
memberDefinitions = NonEmpty MemberDefinition
a} :: CreateWorkteam) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | A description of the work team.
createWorkteam_description :: Lens.Lens' CreateWorkteam Prelude.Text
createWorkteam_description :: Lens' CreateWorkteam Text
createWorkteam_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateWorkteam' {Text
description :: Text
$sel:description:CreateWorkteam' :: CreateWorkteam -> Text
description} -> Text
description) (\s :: CreateWorkteam
s@CreateWorkteam' {} Text
a -> CreateWorkteam
s {$sel:description:CreateWorkteam' :: Text
description = Text
a} :: CreateWorkteam)

instance Core.AWSRequest CreateWorkteam where
  type
    AWSResponse CreateWorkteam =
      CreateWorkteamResponse
  request :: (Service -> Service) -> CreateWorkteam -> Request CreateWorkteam
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 CreateWorkteam
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse CreateWorkteam)))
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 Text -> Int -> CreateWorkteamResponse
CreateWorkteamResponse'
            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
"WorkteamArn")
            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 CreateWorkteam where
  hashWithSalt :: Int -> CreateWorkteam -> Int
hashWithSalt Int
_salt CreateWorkteam' {Maybe [Tag]
Maybe Text
Maybe NotificationConfiguration
NonEmpty MemberDefinition
Text
description :: Text
memberDefinitions :: NonEmpty MemberDefinition
workteamName :: Text
workforceName :: Maybe Text
tags :: Maybe [Tag]
notificationConfiguration :: Maybe NotificationConfiguration
$sel:description:CreateWorkteam' :: CreateWorkteam -> Text
$sel:memberDefinitions:CreateWorkteam' :: CreateWorkteam -> NonEmpty MemberDefinition
$sel:workteamName:CreateWorkteam' :: CreateWorkteam -> Text
$sel:workforceName:CreateWorkteam' :: CreateWorkteam -> Maybe Text
$sel:tags:CreateWorkteam' :: CreateWorkteam -> Maybe [Tag]
$sel:notificationConfiguration:CreateWorkteam' :: CreateWorkteam -> Maybe NotificationConfiguration
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe NotificationConfiguration
notificationConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Tag]
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
workforceName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
workteamName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` NonEmpty MemberDefinition
memberDefinitions
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
description

instance Prelude.NFData CreateWorkteam where
  rnf :: CreateWorkteam -> ()
rnf CreateWorkteam' {Maybe [Tag]
Maybe Text
Maybe NotificationConfiguration
NonEmpty MemberDefinition
Text
description :: Text
memberDefinitions :: NonEmpty MemberDefinition
workteamName :: Text
workforceName :: Maybe Text
tags :: Maybe [Tag]
notificationConfiguration :: Maybe NotificationConfiguration
$sel:description:CreateWorkteam' :: CreateWorkteam -> Text
$sel:memberDefinitions:CreateWorkteam' :: CreateWorkteam -> NonEmpty MemberDefinition
$sel:workteamName:CreateWorkteam' :: CreateWorkteam -> Text
$sel:workforceName:CreateWorkteam' :: CreateWorkteam -> Maybe Text
$sel:tags:CreateWorkteam' :: CreateWorkteam -> Maybe [Tag]
$sel:notificationConfiguration:CreateWorkteam' :: CreateWorkteam -> Maybe NotificationConfiguration
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe NotificationConfiguration
notificationConfiguration
      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 Maybe Text
workforceName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
workteamName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf NonEmpty MemberDefinition
memberDefinitions
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
description

instance Data.ToHeaders CreateWorkteam where
  toHeaders :: CreateWorkteam -> 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
"SageMaker.CreateWorkteam" :: 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 CreateWorkteam where
  toJSON :: CreateWorkteam -> Value
toJSON CreateWorkteam' {Maybe [Tag]
Maybe Text
Maybe NotificationConfiguration
NonEmpty MemberDefinition
Text
description :: Text
memberDefinitions :: NonEmpty MemberDefinition
workteamName :: Text
workforceName :: Maybe Text
tags :: Maybe [Tag]
notificationConfiguration :: Maybe NotificationConfiguration
$sel:description:CreateWorkteam' :: CreateWorkteam -> Text
$sel:memberDefinitions:CreateWorkteam' :: CreateWorkteam -> NonEmpty MemberDefinition
$sel:workteamName:CreateWorkteam' :: CreateWorkteam -> Text
$sel:workforceName:CreateWorkteam' :: CreateWorkteam -> Maybe Text
$sel:tags:CreateWorkteam' :: CreateWorkteam -> Maybe [Tag]
$sel:notificationConfiguration:CreateWorkteam' :: CreateWorkteam -> Maybe NotificationConfiguration
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"NotificationConfiguration" 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 NotificationConfiguration
notificationConfiguration,
            (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,
            (Key
"WorkforceName" 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
workforceName,
            forall a. a -> Maybe a
Prelude.Just (Key
"WorkteamName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
workteamName),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"MemberDefinitions" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= NonEmpty MemberDefinition
memberDefinitions),
            forall a. a -> Maybe a
Prelude.Just (Key
"Description" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
description)
          ]
      )

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

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

-- | /See:/ 'newCreateWorkteamResponse' smart constructor.
data CreateWorkteamResponse = CreateWorkteamResponse'
  { -- | The Amazon Resource Name (ARN) of the work team. You can use this ARN to
    -- identify the work team.
    CreateWorkteamResponse -> Maybe Text
workteamArn :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    CreateWorkteamResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateWorkteamResponse -> CreateWorkteamResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateWorkteamResponse -> CreateWorkteamResponse -> Bool
$c/= :: CreateWorkteamResponse -> CreateWorkteamResponse -> Bool
== :: CreateWorkteamResponse -> CreateWorkteamResponse -> Bool
$c== :: CreateWorkteamResponse -> CreateWorkteamResponse -> Bool
Prelude.Eq, ReadPrec [CreateWorkteamResponse]
ReadPrec CreateWorkteamResponse
Int -> ReadS CreateWorkteamResponse
ReadS [CreateWorkteamResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateWorkteamResponse]
$creadListPrec :: ReadPrec [CreateWorkteamResponse]
readPrec :: ReadPrec CreateWorkteamResponse
$creadPrec :: ReadPrec CreateWorkteamResponse
readList :: ReadS [CreateWorkteamResponse]
$creadList :: ReadS [CreateWorkteamResponse]
readsPrec :: Int -> ReadS CreateWorkteamResponse
$creadsPrec :: Int -> ReadS CreateWorkteamResponse
Prelude.Read, Int -> CreateWorkteamResponse -> ShowS
[CreateWorkteamResponse] -> ShowS
CreateWorkteamResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateWorkteamResponse] -> ShowS
$cshowList :: [CreateWorkteamResponse] -> ShowS
show :: CreateWorkteamResponse -> String
$cshow :: CreateWorkteamResponse -> String
showsPrec :: Int -> CreateWorkteamResponse -> ShowS
$cshowsPrec :: Int -> CreateWorkteamResponse -> ShowS
Prelude.Show, forall x. Rep CreateWorkteamResponse x -> CreateWorkteamResponse
forall x. CreateWorkteamResponse -> Rep CreateWorkteamResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateWorkteamResponse x -> CreateWorkteamResponse
$cfrom :: forall x. CreateWorkteamResponse -> Rep CreateWorkteamResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateWorkteamResponse' 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:
--
-- 'workteamArn', 'createWorkteamResponse_workteamArn' - The Amazon Resource Name (ARN) of the work team. You can use this ARN to
-- identify the work team.
--
-- 'httpStatus', 'createWorkteamResponse_httpStatus' - The response's http status code.
newCreateWorkteamResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateWorkteamResponse
newCreateWorkteamResponse :: Int -> CreateWorkteamResponse
newCreateWorkteamResponse Int
pHttpStatus_ =
  CreateWorkteamResponse'
    { $sel:workteamArn:CreateWorkteamResponse' :: Maybe Text
workteamArn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateWorkteamResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The Amazon Resource Name (ARN) of the work team. You can use this ARN to
-- identify the work team.
createWorkteamResponse_workteamArn :: Lens.Lens' CreateWorkteamResponse (Prelude.Maybe Prelude.Text)
createWorkteamResponse_workteamArn :: Lens' CreateWorkteamResponse (Maybe Text)
createWorkteamResponse_workteamArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateWorkteamResponse' {Maybe Text
workteamArn :: Maybe Text
$sel:workteamArn:CreateWorkteamResponse' :: CreateWorkteamResponse -> Maybe Text
workteamArn} -> Maybe Text
workteamArn) (\s :: CreateWorkteamResponse
s@CreateWorkteamResponse' {} Maybe Text
a -> CreateWorkteamResponse
s {$sel:workteamArn:CreateWorkteamResponse' :: Maybe Text
workteamArn = Maybe Text
a} :: CreateWorkteamResponse)

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

instance Prelude.NFData CreateWorkteamResponse where
  rnf :: CreateWorkteamResponse -> ()
rnf CreateWorkteamResponse' {Int
Maybe Text
httpStatus :: Int
workteamArn :: Maybe Text
$sel:httpStatus:CreateWorkteamResponse' :: CreateWorkteamResponse -> Int
$sel:workteamArn:CreateWorkteamResponse' :: CreateWorkteamResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
workteamArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus