{-# 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.UpdateWorkteam
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Updates an existing work team with new member definitions or
-- description.
module Amazonka.SageMaker.UpdateWorkteam
  ( -- * Creating a Request
    UpdateWorkteam (..),
    newUpdateWorkteam,

    -- * Request Lenses
    updateWorkteam_description,
    updateWorkteam_memberDefinitions,
    updateWorkteam_notificationConfiguration,
    updateWorkteam_workteamName,

    -- * Destructuring the Response
    UpdateWorkteamResponse (..),
    newUpdateWorkteamResponse,

    -- * Response Lenses
    updateWorkteamResponse_httpStatus,
    updateWorkteamResponse_workteam,
  )
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:/ 'newUpdateWorkteam' smart constructor.
data UpdateWorkteam = UpdateWorkteam'
  { -- | An updated description for the work team.
    UpdateWorkteam -> Maybe Text
description :: Prelude.Maybe 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@. You should 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@. Be aware
    -- that user groups that are already in the work team must also be listed
    -- in @Groups@ when you make this request to remain on the work team. If
    -- you do not include these user groups, they will no longer be associated
    -- with the work team you update.
    UpdateWorkteam -> Maybe (NonEmpty MemberDefinition)
memberDefinitions :: Prelude.Maybe (Prelude.NonEmpty MemberDefinition),
    -- | Configures SNS topic notifications for available or expiring work items
    UpdateWorkteam -> Maybe NotificationConfiguration
notificationConfiguration :: Prelude.Maybe NotificationConfiguration,
    -- | The name of the work team to update.
    UpdateWorkteam -> Text
workteamName :: Prelude.Text
  }
  deriving (UpdateWorkteam -> UpdateWorkteam -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateWorkteam -> UpdateWorkteam -> Bool
$c/= :: UpdateWorkteam -> UpdateWorkteam -> Bool
== :: UpdateWorkteam -> UpdateWorkteam -> Bool
$c== :: UpdateWorkteam -> UpdateWorkteam -> Bool
Prelude.Eq, ReadPrec [UpdateWorkteam]
ReadPrec UpdateWorkteam
Int -> ReadS UpdateWorkteam
ReadS [UpdateWorkteam]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateWorkteam]
$creadListPrec :: ReadPrec [UpdateWorkteam]
readPrec :: ReadPrec UpdateWorkteam
$creadPrec :: ReadPrec UpdateWorkteam
readList :: ReadS [UpdateWorkteam]
$creadList :: ReadS [UpdateWorkteam]
readsPrec :: Int -> ReadS UpdateWorkteam
$creadsPrec :: Int -> ReadS UpdateWorkteam
Prelude.Read, Int -> UpdateWorkteam -> ShowS
[UpdateWorkteam] -> ShowS
UpdateWorkteam -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateWorkteam] -> ShowS
$cshowList :: [UpdateWorkteam] -> ShowS
show :: UpdateWorkteam -> String
$cshow :: UpdateWorkteam -> String
showsPrec :: Int -> UpdateWorkteam -> ShowS
$cshowsPrec :: Int -> UpdateWorkteam -> ShowS
Prelude.Show, forall x. Rep UpdateWorkteam x -> UpdateWorkteam
forall x. UpdateWorkteam -> Rep UpdateWorkteam x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateWorkteam x -> UpdateWorkteam
$cfrom :: forall x. UpdateWorkteam -> Rep UpdateWorkteam x
Prelude.Generic)

-- |
-- Create a value of 'UpdateWorkteam' 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', 'updateWorkteam_description' - An updated description for the work team.
--
-- 'memberDefinitions', 'updateWorkteam_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@. You should 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@. Be aware
-- that user groups that are already in the work team must also be listed
-- in @Groups@ when you make this request to remain on the work team. If
-- you do not include these user groups, they will no longer be associated
-- with the work team you update.
--
-- 'notificationConfiguration', 'updateWorkteam_notificationConfiguration' - Configures SNS topic notifications for available or expiring work items
--
-- 'workteamName', 'updateWorkteam_workteamName' - The name of the work team to update.
newUpdateWorkteam ::
  -- | 'workteamName'
  Prelude.Text ->
  UpdateWorkteam
newUpdateWorkteam :: Text -> UpdateWorkteam
newUpdateWorkteam Text
pWorkteamName_ =
  UpdateWorkteam'
    { $sel:description:UpdateWorkteam' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:memberDefinitions:UpdateWorkteam' :: Maybe (NonEmpty MemberDefinition)
memberDefinitions = forall a. Maybe a
Prelude.Nothing,
      $sel:notificationConfiguration:UpdateWorkteam' :: Maybe NotificationConfiguration
notificationConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:workteamName:UpdateWorkteam' :: Text
workteamName = Text
pWorkteamName_
    }

-- | An updated description for the work team.
updateWorkteam_description :: Lens.Lens' UpdateWorkteam (Prelude.Maybe Prelude.Text)
updateWorkteam_description :: Lens' UpdateWorkteam (Maybe Text)
updateWorkteam_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateWorkteam' {Maybe Text
description :: Maybe Text
$sel:description:UpdateWorkteam' :: UpdateWorkteam -> Maybe Text
description} -> Maybe Text
description) (\s :: UpdateWorkteam
s@UpdateWorkteam' {} Maybe Text
a -> UpdateWorkteam
s {$sel:description:UpdateWorkteam' :: Maybe Text
description = Maybe Text
a} :: UpdateWorkteam)

-- | 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@. You should 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@. Be aware
-- that user groups that are already in the work team must also be listed
-- in @Groups@ when you make this request to remain on the work team. If
-- you do not include these user groups, they will no longer be associated
-- with the work team you update.
updateWorkteam_memberDefinitions :: Lens.Lens' UpdateWorkteam (Prelude.Maybe (Prelude.NonEmpty MemberDefinition))
updateWorkteam_memberDefinitions :: Lens' UpdateWorkteam (Maybe (NonEmpty MemberDefinition))
updateWorkteam_memberDefinitions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateWorkteam' {Maybe (NonEmpty MemberDefinition)
memberDefinitions :: Maybe (NonEmpty MemberDefinition)
$sel:memberDefinitions:UpdateWorkteam' :: UpdateWorkteam -> Maybe (NonEmpty MemberDefinition)
memberDefinitions} -> Maybe (NonEmpty MemberDefinition)
memberDefinitions) (\s :: UpdateWorkteam
s@UpdateWorkteam' {} Maybe (NonEmpty MemberDefinition)
a -> UpdateWorkteam
s {$sel:memberDefinitions:UpdateWorkteam' :: Maybe (NonEmpty MemberDefinition)
memberDefinitions = Maybe (NonEmpty MemberDefinition)
a} :: UpdateWorkteam) 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

-- | Configures SNS topic notifications for available or expiring work items
updateWorkteam_notificationConfiguration :: Lens.Lens' UpdateWorkteam (Prelude.Maybe NotificationConfiguration)
updateWorkteam_notificationConfiguration :: Lens' UpdateWorkteam (Maybe NotificationConfiguration)
updateWorkteam_notificationConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateWorkteam' {Maybe NotificationConfiguration
notificationConfiguration :: Maybe NotificationConfiguration
$sel:notificationConfiguration:UpdateWorkteam' :: UpdateWorkteam -> Maybe NotificationConfiguration
notificationConfiguration} -> Maybe NotificationConfiguration
notificationConfiguration) (\s :: UpdateWorkteam
s@UpdateWorkteam' {} Maybe NotificationConfiguration
a -> UpdateWorkteam
s {$sel:notificationConfiguration:UpdateWorkteam' :: Maybe NotificationConfiguration
notificationConfiguration = Maybe NotificationConfiguration
a} :: UpdateWorkteam)

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

instance Core.AWSRequest UpdateWorkteam where
  type
    AWSResponse UpdateWorkteam =
      UpdateWorkteamResponse
  request :: (Service -> Service) -> UpdateWorkteam -> Request UpdateWorkteam
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 UpdateWorkteam
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse UpdateWorkteam)))
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 -> Workteam -> UpdateWorkteamResponse
UpdateWorkteamResponse'
            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.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"Workteam")
      )

instance Prelude.Hashable UpdateWorkteam where
  hashWithSalt :: Int -> UpdateWorkteam -> Int
hashWithSalt Int
_salt UpdateWorkteam' {Maybe (NonEmpty MemberDefinition)
Maybe Text
Maybe NotificationConfiguration
Text
workteamName :: Text
notificationConfiguration :: Maybe NotificationConfiguration
memberDefinitions :: Maybe (NonEmpty MemberDefinition)
description :: Maybe Text
$sel:workteamName:UpdateWorkteam' :: UpdateWorkteam -> Text
$sel:notificationConfiguration:UpdateWorkteam' :: UpdateWorkteam -> Maybe NotificationConfiguration
$sel:memberDefinitions:UpdateWorkteam' :: UpdateWorkteam -> Maybe (NonEmpty MemberDefinition)
$sel:description:UpdateWorkteam' :: UpdateWorkteam -> 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 (NonEmpty MemberDefinition)
memberDefinitions
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe NotificationConfiguration
notificationConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
workteamName

instance Prelude.NFData UpdateWorkteam where
  rnf :: UpdateWorkteam -> ()
rnf UpdateWorkteam' {Maybe (NonEmpty MemberDefinition)
Maybe Text
Maybe NotificationConfiguration
Text
workteamName :: Text
notificationConfiguration :: Maybe NotificationConfiguration
memberDefinitions :: Maybe (NonEmpty MemberDefinition)
description :: Maybe Text
$sel:workteamName:UpdateWorkteam' :: UpdateWorkteam -> Text
$sel:notificationConfiguration:UpdateWorkteam' :: UpdateWorkteam -> Maybe NotificationConfiguration
$sel:memberDefinitions:UpdateWorkteam' :: UpdateWorkteam -> Maybe (NonEmpty MemberDefinition)
$sel:description:UpdateWorkteam' :: UpdateWorkteam -> 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 (NonEmpty MemberDefinition)
memberDefinitions
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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 Text
workteamName

instance Data.ToHeaders UpdateWorkteam where
  toHeaders :: UpdateWorkteam -> 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.UpdateWorkteam" :: 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 UpdateWorkteam where
  toJSON :: UpdateWorkteam -> Value
toJSON UpdateWorkteam' {Maybe (NonEmpty MemberDefinition)
Maybe Text
Maybe NotificationConfiguration
Text
workteamName :: Text
notificationConfiguration :: Maybe NotificationConfiguration
memberDefinitions :: Maybe (NonEmpty MemberDefinition)
description :: Maybe Text
$sel:workteamName:UpdateWorkteam' :: UpdateWorkteam -> Text
$sel:notificationConfiguration:UpdateWorkteam' :: UpdateWorkteam -> Maybe NotificationConfiguration
$sel:memberDefinitions:UpdateWorkteam' :: UpdateWorkteam -> Maybe (NonEmpty MemberDefinition)
$sel:description:UpdateWorkteam' :: UpdateWorkteam -> 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
"MemberDefinitions" 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 (NonEmpty MemberDefinition)
memberDefinitions,
            (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,
            forall a. a -> Maybe a
Prelude.Just (Key
"WorkteamName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
workteamName)
          ]
      )

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

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

-- | /See:/ 'newUpdateWorkteamResponse' smart constructor.
data UpdateWorkteamResponse = UpdateWorkteamResponse'
  { -- | The response's http status code.
    UpdateWorkteamResponse -> Int
httpStatus :: Prelude.Int,
    -- | A @Workteam@ object that describes the updated work team.
    UpdateWorkteamResponse -> Workteam
workteam :: Workteam
  }
  deriving (UpdateWorkteamResponse -> UpdateWorkteamResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateWorkteamResponse -> UpdateWorkteamResponse -> Bool
$c/= :: UpdateWorkteamResponse -> UpdateWorkteamResponse -> Bool
== :: UpdateWorkteamResponse -> UpdateWorkteamResponse -> Bool
$c== :: UpdateWorkteamResponse -> UpdateWorkteamResponse -> Bool
Prelude.Eq, ReadPrec [UpdateWorkteamResponse]
ReadPrec UpdateWorkteamResponse
Int -> ReadS UpdateWorkteamResponse
ReadS [UpdateWorkteamResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateWorkteamResponse]
$creadListPrec :: ReadPrec [UpdateWorkteamResponse]
readPrec :: ReadPrec UpdateWorkteamResponse
$creadPrec :: ReadPrec UpdateWorkteamResponse
readList :: ReadS [UpdateWorkteamResponse]
$creadList :: ReadS [UpdateWorkteamResponse]
readsPrec :: Int -> ReadS UpdateWorkteamResponse
$creadsPrec :: Int -> ReadS UpdateWorkteamResponse
Prelude.Read, Int -> UpdateWorkteamResponse -> ShowS
[UpdateWorkteamResponse] -> ShowS
UpdateWorkteamResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateWorkteamResponse] -> ShowS
$cshowList :: [UpdateWorkteamResponse] -> ShowS
show :: UpdateWorkteamResponse -> String
$cshow :: UpdateWorkteamResponse -> String
showsPrec :: Int -> UpdateWorkteamResponse -> ShowS
$cshowsPrec :: Int -> UpdateWorkteamResponse -> ShowS
Prelude.Show, forall x. Rep UpdateWorkteamResponse x -> UpdateWorkteamResponse
forall x. UpdateWorkteamResponse -> Rep UpdateWorkteamResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateWorkteamResponse x -> UpdateWorkteamResponse
$cfrom :: forall x. UpdateWorkteamResponse -> Rep UpdateWorkteamResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateWorkteamResponse' 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', 'updateWorkteamResponse_httpStatus' - The response's http status code.
--
-- 'workteam', 'updateWorkteamResponse_workteam' - A @Workteam@ object that describes the updated work team.
newUpdateWorkteamResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'workteam'
  Workteam ->
  UpdateWorkteamResponse
newUpdateWorkteamResponse :: Int -> Workteam -> UpdateWorkteamResponse
newUpdateWorkteamResponse Int
pHttpStatus_ Workteam
pWorkteam_ =
  UpdateWorkteamResponse'
    { $sel:httpStatus:UpdateWorkteamResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:workteam:UpdateWorkteamResponse' :: Workteam
workteam = Workteam
pWorkteam_
    }

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

-- | A @Workteam@ object that describes the updated work team.
updateWorkteamResponse_workteam :: Lens.Lens' UpdateWorkteamResponse Workteam
updateWorkteamResponse_workteam :: Lens' UpdateWorkteamResponse Workteam
updateWorkteamResponse_workteam = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateWorkteamResponse' {Workteam
workteam :: Workteam
$sel:workteam:UpdateWorkteamResponse' :: UpdateWorkteamResponse -> Workteam
workteam} -> Workteam
workteam) (\s :: UpdateWorkteamResponse
s@UpdateWorkteamResponse' {} Workteam
a -> UpdateWorkteamResponse
s {$sel:workteam:UpdateWorkteamResponse' :: Workteam
workteam = Workteam
a} :: UpdateWorkteamResponse)

instance Prelude.NFData UpdateWorkteamResponse where
  rnf :: UpdateWorkteamResponse -> ()
rnf UpdateWorkteamResponse' {Int
Workteam
workteam :: Workteam
httpStatus :: Int
$sel:workteam:UpdateWorkteamResponse' :: UpdateWorkteamResponse -> Workteam
$sel:httpStatus:UpdateWorkteamResponse' :: UpdateWorkteamResponse -> 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 Workteam
workteam