{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# 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.Types.Workforce
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.SageMaker.Types.Workforce 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 Amazonka.SageMaker.Types.CognitoConfig
import Amazonka.SageMaker.Types.OidcConfigForResponse
import Amazonka.SageMaker.Types.SourceIpConfig
import Amazonka.SageMaker.Types.WorkforceStatus
import Amazonka.SageMaker.Types.WorkforceVpcConfigResponse

-- | A single private workforce, which is automatically created when you
-- create your first private work team. You can create one private work
-- force in each Amazon Web Services Region. By default, any
-- workforce-related API operation used in a specific region will apply to
-- the workforce created in that region. To learn how to create a private
-- workforce, see
-- <https://docs.aws.amazon.com/sagemaker/latest/dg/sms-workforce-create-private.html Create a Private Workforce>.
--
-- /See:/ 'newWorkforce' smart constructor.
data Workforce = Workforce'
  { -- | The configuration of an Amazon Cognito workforce. A single Cognito
    -- workforce is created using and corresponds to a single
    -- <https://docs.aws.amazon.com/cognito/latest/developerguide/cognito-user-identity-pools.html Amazon Cognito user pool>.
    Workforce -> Maybe CognitoConfig
cognitoConfig :: Prelude.Maybe CognitoConfig,
    -- | The date that the workforce is created.
    Workforce -> Maybe POSIX
createDate :: Prelude.Maybe Data.POSIX,
    -- | The reason your workforce failed.
    Workforce -> Maybe Text
failureReason :: Prelude.Maybe Prelude.Text,
    -- | The most recent date that was used to successfully add one or more IP
    -- address ranges
    -- (<https://docs.aws.amazon.com/vpc/latest/userguide/VPC_Subnets.html CIDRs>)
    -- to a private workforce\'s allow list.
    Workforce -> Maybe POSIX
lastUpdatedDate :: Prelude.Maybe Data.POSIX,
    -- | The configuration of an OIDC Identity Provider (IdP) private workforce.
    Workforce -> Maybe OidcConfigForResponse
oidcConfig :: Prelude.Maybe OidcConfigForResponse,
    -- | A list of one to ten IP address ranges
    -- (<https://docs.aws.amazon.com/vpc/latest/userguide/VPC_Subnets.html CIDRs>)
    -- to be added to the workforce allow list. By default, a workforce isn\'t
    -- restricted to specific IP addresses.
    Workforce -> Maybe SourceIpConfig
sourceIpConfig :: Prelude.Maybe SourceIpConfig,
    -- | The status of your workforce.
    Workforce -> Maybe WorkforceStatus
status :: Prelude.Maybe WorkforceStatus,
    -- | The subdomain for your OIDC Identity Provider.
    Workforce -> Maybe Text
subDomain :: Prelude.Maybe Prelude.Text,
    -- | The configuration of a VPC workforce.
    Workforce -> Maybe WorkforceVpcConfigResponse
workforceVpcConfig :: Prelude.Maybe WorkforceVpcConfigResponse,
    -- | The name of the private workforce.
    Workforce -> Text
workforceName :: Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the private workforce.
    Workforce -> Text
workforceArn :: Prelude.Text
  }
  deriving (Workforce -> Workforce -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Workforce -> Workforce -> Bool
$c/= :: Workforce -> Workforce -> Bool
== :: Workforce -> Workforce -> Bool
$c== :: Workforce -> Workforce -> Bool
Prelude.Eq, ReadPrec [Workforce]
ReadPrec Workforce
Int -> ReadS Workforce
ReadS [Workforce]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Workforce]
$creadListPrec :: ReadPrec [Workforce]
readPrec :: ReadPrec Workforce
$creadPrec :: ReadPrec Workforce
readList :: ReadS [Workforce]
$creadList :: ReadS [Workforce]
readsPrec :: Int -> ReadS Workforce
$creadsPrec :: Int -> ReadS Workforce
Prelude.Read, Int -> Workforce -> ShowS
[Workforce] -> ShowS
Workforce -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Workforce] -> ShowS
$cshowList :: [Workforce] -> ShowS
show :: Workforce -> String
$cshow :: Workforce -> String
showsPrec :: Int -> Workforce -> ShowS
$cshowsPrec :: Int -> Workforce -> ShowS
Prelude.Show, forall x. Rep Workforce x -> Workforce
forall x. Workforce -> Rep Workforce x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Workforce x -> Workforce
$cfrom :: forall x. Workforce -> Rep Workforce x
Prelude.Generic)

-- |
-- Create a value of 'Workforce' 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:
--
-- 'cognitoConfig', 'workforce_cognitoConfig' - The configuration of an Amazon Cognito workforce. A single Cognito
-- workforce is created using and corresponds to a single
-- <https://docs.aws.amazon.com/cognito/latest/developerguide/cognito-user-identity-pools.html Amazon Cognito user pool>.
--
-- 'createDate', 'workforce_createDate' - The date that the workforce is created.
--
-- 'failureReason', 'workforce_failureReason' - The reason your workforce failed.
--
-- 'lastUpdatedDate', 'workforce_lastUpdatedDate' - The most recent date that was used to successfully add one or more IP
-- address ranges
-- (<https://docs.aws.amazon.com/vpc/latest/userguide/VPC_Subnets.html CIDRs>)
-- to a private workforce\'s allow list.
--
-- 'oidcConfig', 'workforce_oidcConfig' - The configuration of an OIDC Identity Provider (IdP) private workforce.
--
-- 'sourceIpConfig', 'workforce_sourceIpConfig' - A list of one to ten IP address ranges
-- (<https://docs.aws.amazon.com/vpc/latest/userguide/VPC_Subnets.html CIDRs>)
-- to be added to the workforce allow list. By default, a workforce isn\'t
-- restricted to specific IP addresses.
--
-- 'status', 'workforce_status' - The status of your workforce.
--
-- 'subDomain', 'workforce_subDomain' - The subdomain for your OIDC Identity Provider.
--
-- 'workforceVpcConfig', 'workforce_workforceVpcConfig' - The configuration of a VPC workforce.
--
-- 'workforceName', 'workforce_workforceName' - The name of the private workforce.
--
-- 'workforceArn', 'workforce_workforceArn' - The Amazon Resource Name (ARN) of the private workforce.
newWorkforce ::
  -- | 'workforceName'
  Prelude.Text ->
  -- | 'workforceArn'
  Prelude.Text ->
  Workforce
newWorkforce :: Text -> Text -> Workforce
newWorkforce Text
pWorkforceName_ Text
pWorkforceArn_ =
  Workforce'
    { $sel:cognitoConfig:Workforce' :: Maybe CognitoConfig
cognitoConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:createDate:Workforce' :: Maybe POSIX
createDate = forall a. Maybe a
Prelude.Nothing,
      $sel:failureReason:Workforce' :: Maybe Text
failureReason = forall a. Maybe a
Prelude.Nothing,
      $sel:lastUpdatedDate:Workforce' :: Maybe POSIX
lastUpdatedDate = forall a. Maybe a
Prelude.Nothing,
      $sel:oidcConfig:Workforce' :: Maybe OidcConfigForResponse
oidcConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:sourceIpConfig:Workforce' :: Maybe SourceIpConfig
sourceIpConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:status:Workforce' :: Maybe WorkforceStatus
status = forall a. Maybe a
Prelude.Nothing,
      $sel:subDomain:Workforce' :: Maybe Text
subDomain = forall a. Maybe a
Prelude.Nothing,
      $sel:workforceVpcConfig:Workforce' :: Maybe WorkforceVpcConfigResponse
workforceVpcConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:workforceName:Workforce' :: Text
workforceName = Text
pWorkforceName_,
      $sel:workforceArn:Workforce' :: Text
workforceArn = Text
pWorkforceArn_
    }

-- | The configuration of an Amazon Cognito workforce. A single Cognito
-- workforce is created using and corresponds to a single
-- <https://docs.aws.amazon.com/cognito/latest/developerguide/cognito-user-identity-pools.html Amazon Cognito user pool>.
workforce_cognitoConfig :: Lens.Lens' Workforce (Prelude.Maybe CognitoConfig)
workforce_cognitoConfig :: Lens' Workforce (Maybe CognitoConfig)
workforce_cognitoConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Workforce' {Maybe CognitoConfig
cognitoConfig :: Maybe CognitoConfig
$sel:cognitoConfig:Workforce' :: Workforce -> Maybe CognitoConfig
cognitoConfig} -> Maybe CognitoConfig
cognitoConfig) (\s :: Workforce
s@Workforce' {} Maybe CognitoConfig
a -> Workforce
s {$sel:cognitoConfig:Workforce' :: Maybe CognitoConfig
cognitoConfig = Maybe CognitoConfig
a} :: Workforce)

-- | The date that the workforce is created.
workforce_createDate :: Lens.Lens' Workforce (Prelude.Maybe Prelude.UTCTime)
workforce_createDate :: Lens' Workforce (Maybe UTCTime)
workforce_createDate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Workforce' {Maybe POSIX
createDate :: Maybe POSIX
$sel:createDate:Workforce' :: Workforce -> Maybe POSIX
createDate} -> Maybe POSIX
createDate) (\s :: Workforce
s@Workforce' {} Maybe POSIX
a -> Workforce
s {$sel:createDate:Workforce' :: Maybe POSIX
createDate = Maybe POSIX
a} :: Workforce) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The reason your workforce failed.
workforce_failureReason :: Lens.Lens' Workforce (Prelude.Maybe Prelude.Text)
workforce_failureReason :: Lens' Workforce (Maybe Text)
workforce_failureReason = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Workforce' {Maybe Text
failureReason :: Maybe Text
$sel:failureReason:Workforce' :: Workforce -> Maybe Text
failureReason} -> Maybe Text
failureReason) (\s :: Workforce
s@Workforce' {} Maybe Text
a -> Workforce
s {$sel:failureReason:Workforce' :: Maybe Text
failureReason = Maybe Text
a} :: Workforce)

-- | The most recent date that was used to successfully add one or more IP
-- address ranges
-- (<https://docs.aws.amazon.com/vpc/latest/userguide/VPC_Subnets.html CIDRs>)
-- to a private workforce\'s allow list.
workforce_lastUpdatedDate :: Lens.Lens' Workforce (Prelude.Maybe Prelude.UTCTime)
workforce_lastUpdatedDate :: Lens' Workforce (Maybe UTCTime)
workforce_lastUpdatedDate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Workforce' {Maybe POSIX
lastUpdatedDate :: Maybe POSIX
$sel:lastUpdatedDate:Workforce' :: Workforce -> Maybe POSIX
lastUpdatedDate} -> Maybe POSIX
lastUpdatedDate) (\s :: Workforce
s@Workforce' {} Maybe POSIX
a -> Workforce
s {$sel:lastUpdatedDate:Workforce' :: Maybe POSIX
lastUpdatedDate = Maybe POSIX
a} :: Workforce) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The configuration of an OIDC Identity Provider (IdP) private workforce.
workforce_oidcConfig :: Lens.Lens' Workforce (Prelude.Maybe OidcConfigForResponse)
workforce_oidcConfig :: Lens' Workforce (Maybe OidcConfigForResponse)
workforce_oidcConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Workforce' {Maybe OidcConfigForResponse
oidcConfig :: Maybe OidcConfigForResponse
$sel:oidcConfig:Workforce' :: Workforce -> Maybe OidcConfigForResponse
oidcConfig} -> Maybe OidcConfigForResponse
oidcConfig) (\s :: Workforce
s@Workforce' {} Maybe OidcConfigForResponse
a -> Workforce
s {$sel:oidcConfig:Workforce' :: Maybe OidcConfigForResponse
oidcConfig = Maybe OidcConfigForResponse
a} :: Workforce)

-- | A list of one to ten IP address ranges
-- (<https://docs.aws.amazon.com/vpc/latest/userguide/VPC_Subnets.html CIDRs>)
-- to be added to the workforce allow list. By default, a workforce isn\'t
-- restricted to specific IP addresses.
workforce_sourceIpConfig :: Lens.Lens' Workforce (Prelude.Maybe SourceIpConfig)
workforce_sourceIpConfig :: Lens' Workforce (Maybe SourceIpConfig)
workforce_sourceIpConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Workforce' {Maybe SourceIpConfig
sourceIpConfig :: Maybe SourceIpConfig
$sel:sourceIpConfig:Workforce' :: Workforce -> Maybe SourceIpConfig
sourceIpConfig} -> Maybe SourceIpConfig
sourceIpConfig) (\s :: Workforce
s@Workforce' {} Maybe SourceIpConfig
a -> Workforce
s {$sel:sourceIpConfig:Workforce' :: Maybe SourceIpConfig
sourceIpConfig = Maybe SourceIpConfig
a} :: Workforce)

-- | The status of your workforce.
workforce_status :: Lens.Lens' Workforce (Prelude.Maybe WorkforceStatus)
workforce_status :: Lens' Workforce (Maybe WorkforceStatus)
workforce_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Workforce' {Maybe WorkforceStatus
status :: Maybe WorkforceStatus
$sel:status:Workforce' :: Workforce -> Maybe WorkforceStatus
status} -> Maybe WorkforceStatus
status) (\s :: Workforce
s@Workforce' {} Maybe WorkforceStatus
a -> Workforce
s {$sel:status:Workforce' :: Maybe WorkforceStatus
status = Maybe WorkforceStatus
a} :: Workforce)

-- | The subdomain for your OIDC Identity Provider.
workforce_subDomain :: Lens.Lens' Workforce (Prelude.Maybe Prelude.Text)
workforce_subDomain :: Lens' Workforce (Maybe Text)
workforce_subDomain = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Workforce' {Maybe Text
subDomain :: Maybe Text
$sel:subDomain:Workforce' :: Workforce -> Maybe Text
subDomain} -> Maybe Text
subDomain) (\s :: Workforce
s@Workforce' {} Maybe Text
a -> Workforce
s {$sel:subDomain:Workforce' :: Maybe Text
subDomain = Maybe Text
a} :: Workforce)

-- | The configuration of a VPC workforce.
workforce_workforceVpcConfig :: Lens.Lens' Workforce (Prelude.Maybe WorkforceVpcConfigResponse)
workforce_workforceVpcConfig :: Lens' Workforce (Maybe WorkforceVpcConfigResponse)
workforce_workforceVpcConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Workforce' {Maybe WorkforceVpcConfigResponse
workforceVpcConfig :: Maybe WorkforceVpcConfigResponse
$sel:workforceVpcConfig:Workforce' :: Workforce -> Maybe WorkforceVpcConfigResponse
workforceVpcConfig} -> Maybe WorkforceVpcConfigResponse
workforceVpcConfig) (\s :: Workforce
s@Workforce' {} Maybe WorkforceVpcConfigResponse
a -> Workforce
s {$sel:workforceVpcConfig:Workforce' :: Maybe WorkforceVpcConfigResponse
workforceVpcConfig = Maybe WorkforceVpcConfigResponse
a} :: Workforce)

-- | The name of the private workforce.
workforce_workforceName :: Lens.Lens' Workforce Prelude.Text
workforce_workforceName :: Lens' Workforce Text
workforce_workforceName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Workforce' {Text
workforceName :: Text
$sel:workforceName:Workforce' :: Workforce -> Text
workforceName} -> Text
workforceName) (\s :: Workforce
s@Workforce' {} Text
a -> Workforce
s {$sel:workforceName:Workforce' :: Text
workforceName = Text
a} :: Workforce)

-- | The Amazon Resource Name (ARN) of the private workforce.
workforce_workforceArn :: Lens.Lens' Workforce Prelude.Text
workforce_workforceArn :: Lens' Workforce Text
workforce_workforceArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Workforce' {Text
workforceArn :: Text
$sel:workforceArn:Workforce' :: Workforce -> Text
workforceArn} -> Text
workforceArn) (\s :: Workforce
s@Workforce' {} Text
a -> Workforce
s {$sel:workforceArn:Workforce' :: Text
workforceArn = Text
a} :: Workforce)

instance Data.FromJSON Workforce where
  parseJSON :: Value -> Parser Workforce
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"Workforce"
      ( \Object
x ->
          Maybe CognitoConfig
-> Maybe POSIX
-> Maybe Text
-> Maybe POSIX
-> Maybe OidcConfigForResponse
-> Maybe SourceIpConfig
-> Maybe WorkforceStatus
-> Maybe Text
-> Maybe WorkforceVpcConfigResponse
-> Text
-> Text
-> Workforce
Workforce'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"CognitoConfig")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"CreateDate")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"FailureReason")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"LastUpdatedDate")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"OidcConfig")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"SourceIpConfig")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"Status")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"SubDomain")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"WorkforceVpcConfig")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"WorkforceName")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"WorkforceArn")
      )

instance Prelude.Hashable Workforce where
  hashWithSalt :: Int -> Workforce -> Int
hashWithSalt Int
_salt Workforce' {Maybe Text
Maybe POSIX
Maybe CognitoConfig
Maybe OidcConfigForResponse
Maybe SourceIpConfig
Maybe WorkforceStatus
Maybe WorkforceVpcConfigResponse
Text
workforceArn :: Text
workforceName :: Text
workforceVpcConfig :: Maybe WorkforceVpcConfigResponse
subDomain :: Maybe Text
status :: Maybe WorkforceStatus
sourceIpConfig :: Maybe SourceIpConfig
oidcConfig :: Maybe OidcConfigForResponse
lastUpdatedDate :: Maybe POSIX
failureReason :: Maybe Text
createDate :: Maybe POSIX
cognitoConfig :: Maybe CognitoConfig
$sel:workforceArn:Workforce' :: Workforce -> Text
$sel:workforceName:Workforce' :: Workforce -> Text
$sel:workforceVpcConfig:Workforce' :: Workforce -> Maybe WorkforceVpcConfigResponse
$sel:subDomain:Workforce' :: Workforce -> Maybe Text
$sel:status:Workforce' :: Workforce -> Maybe WorkforceStatus
$sel:sourceIpConfig:Workforce' :: Workforce -> Maybe SourceIpConfig
$sel:oidcConfig:Workforce' :: Workforce -> Maybe OidcConfigForResponse
$sel:lastUpdatedDate:Workforce' :: Workforce -> Maybe POSIX
$sel:failureReason:Workforce' :: Workforce -> Maybe Text
$sel:createDate:Workforce' :: Workforce -> Maybe POSIX
$sel:cognitoConfig:Workforce' :: Workforce -> Maybe CognitoConfig
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe CognitoConfig
cognitoConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
createDate
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
failureReason
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
lastUpdatedDate
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe OidcConfigForResponse
oidcConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe SourceIpConfig
sourceIpConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe WorkforceStatus
status
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
subDomain
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe WorkforceVpcConfigResponse
workforceVpcConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
workforceName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
workforceArn

instance Prelude.NFData Workforce where
  rnf :: Workforce -> ()
rnf Workforce' {Maybe Text
Maybe POSIX
Maybe CognitoConfig
Maybe OidcConfigForResponse
Maybe SourceIpConfig
Maybe WorkforceStatus
Maybe WorkforceVpcConfigResponse
Text
workforceArn :: Text
workforceName :: Text
workforceVpcConfig :: Maybe WorkforceVpcConfigResponse
subDomain :: Maybe Text
status :: Maybe WorkforceStatus
sourceIpConfig :: Maybe SourceIpConfig
oidcConfig :: Maybe OidcConfigForResponse
lastUpdatedDate :: Maybe POSIX
failureReason :: Maybe Text
createDate :: Maybe POSIX
cognitoConfig :: Maybe CognitoConfig
$sel:workforceArn:Workforce' :: Workforce -> Text
$sel:workforceName:Workforce' :: Workforce -> Text
$sel:workforceVpcConfig:Workforce' :: Workforce -> Maybe WorkforceVpcConfigResponse
$sel:subDomain:Workforce' :: Workforce -> Maybe Text
$sel:status:Workforce' :: Workforce -> Maybe WorkforceStatus
$sel:sourceIpConfig:Workforce' :: Workforce -> Maybe SourceIpConfig
$sel:oidcConfig:Workforce' :: Workforce -> Maybe OidcConfigForResponse
$sel:lastUpdatedDate:Workforce' :: Workforce -> Maybe POSIX
$sel:failureReason:Workforce' :: Workforce -> Maybe Text
$sel:createDate:Workforce' :: Workforce -> Maybe POSIX
$sel:cognitoConfig:Workforce' :: Workforce -> Maybe CognitoConfig
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe CognitoConfig
cognitoConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
createDate
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
failureReason
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
lastUpdatedDate
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe OidcConfigForResponse
oidcConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe SourceIpConfig
sourceIpConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe WorkforceStatus
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
subDomain
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe WorkforceVpcConfigResponse
workforceVpcConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
workforceName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
workforceArn