{-# 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.Batch.Types.JobQueueDetail
-- 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.Batch.Types.JobQueueDetail where

import Amazonka.Batch.Types.ComputeEnvironmentOrder
import Amazonka.Batch.Types.JQState
import Amazonka.Batch.Types.JQStatus
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

-- | An object that represents the details for an Batch job queue.
--
-- /See:/ 'newJobQueueDetail' smart constructor.
data JobQueueDetail = JobQueueDetail'
  { -- | The Amazon Resource Name (ARN) of the scheduling policy. The format is
    -- @aws:@/@Partition@/@:batch:@/@Region@/@:@/@Account@/@:scheduling-policy\/@/@Name@/@ @.
    -- For example,
    -- @aws:aws:batch:us-west-2:123456789012:scheduling-policy\/MySchedulingPolicy@.
    JobQueueDetail -> Maybe Text
schedulingPolicyArn :: Prelude.Maybe Prelude.Text,
    -- | The status of the job queue (for example, @CREATING@ or @VALID@).
    JobQueueDetail -> Maybe JQStatus
status :: Prelude.Maybe JQStatus,
    -- | A short, human-readable string to provide additional details for the
    -- current status of the job queue.
    JobQueueDetail -> Maybe Text
statusReason :: Prelude.Maybe Prelude.Text,
    -- | The tags that are applied to the job queue. For more information, see
    -- <https://docs.aws.amazon.com/batch/latest/userguide/using-tags.html Tagging your Batch resources>
    -- in /Batch User Guide/.
    JobQueueDetail -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The job queue name.
    JobQueueDetail -> Text
jobQueueName :: Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the job queue.
    JobQueueDetail -> Text
jobQueueArn :: Prelude.Text,
    -- | Describes the ability of the queue to accept new jobs. If the job queue
    -- state is @ENABLED@, it can accept jobs. If the job queue state is
    -- @DISABLED@, new jobs can\'t be added to the queue, but jobs already in
    -- the queue can finish.
    JobQueueDetail -> JQState
state :: JQState,
    -- | The priority of the job queue. Job queues with a higher priority (or a
    -- higher integer value for the @priority@ parameter) are evaluated first
    -- when associated with the same compute environment. Priority is
    -- determined in descending order. For example, a job queue with a priority
    -- value of @10@ is given scheduling preference over a job queue with a
    -- priority value of @1@. All of the compute environments must be either
    -- EC2 (@EC2@ or @SPOT@) or Fargate (@FARGATE@ or @FARGATE_SPOT@). EC2 and
    -- Fargate compute environments can\'t be mixed.
    JobQueueDetail -> Int
priority :: Prelude.Int,
    -- | The compute environments that are attached to the job queue and the
    -- order that job placement is preferred. Compute environments are selected
    -- for job placement in ascending order.
    JobQueueDetail -> [ComputeEnvironmentOrder]
computeEnvironmentOrder :: [ComputeEnvironmentOrder]
  }
  deriving (JobQueueDetail -> JobQueueDetail -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: JobQueueDetail -> JobQueueDetail -> Bool
$c/= :: JobQueueDetail -> JobQueueDetail -> Bool
== :: JobQueueDetail -> JobQueueDetail -> Bool
$c== :: JobQueueDetail -> JobQueueDetail -> Bool
Prelude.Eq, ReadPrec [JobQueueDetail]
ReadPrec JobQueueDetail
Int -> ReadS JobQueueDetail
ReadS [JobQueueDetail]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [JobQueueDetail]
$creadListPrec :: ReadPrec [JobQueueDetail]
readPrec :: ReadPrec JobQueueDetail
$creadPrec :: ReadPrec JobQueueDetail
readList :: ReadS [JobQueueDetail]
$creadList :: ReadS [JobQueueDetail]
readsPrec :: Int -> ReadS JobQueueDetail
$creadsPrec :: Int -> ReadS JobQueueDetail
Prelude.Read, Int -> JobQueueDetail -> ShowS
[JobQueueDetail] -> ShowS
JobQueueDetail -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [JobQueueDetail] -> ShowS
$cshowList :: [JobQueueDetail] -> ShowS
show :: JobQueueDetail -> String
$cshow :: JobQueueDetail -> String
showsPrec :: Int -> JobQueueDetail -> ShowS
$cshowsPrec :: Int -> JobQueueDetail -> ShowS
Prelude.Show, forall x. Rep JobQueueDetail x -> JobQueueDetail
forall x. JobQueueDetail -> Rep JobQueueDetail x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep JobQueueDetail x -> JobQueueDetail
$cfrom :: forall x. JobQueueDetail -> Rep JobQueueDetail x
Prelude.Generic)

-- |
-- Create a value of 'JobQueueDetail' 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:
--
-- 'schedulingPolicyArn', 'jobQueueDetail_schedulingPolicyArn' - The Amazon Resource Name (ARN) of the scheduling policy. The format is
-- @aws:@/@Partition@/@:batch:@/@Region@/@:@/@Account@/@:scheduling-policy\/@/@Name@/@ @.
-- For example,
-- @aws:aws:batch:us-west-2:123456789012:scheduling-policy\/MySchedulingPolicy@.
--
-- 'status', 'jobQueueDetail_status' - The status of the job queue (for example, @CREATING@ or @VALID@).
--
-- 'statusReason', 'jobQueueDetail_statusReason' - A short, human-readable string to provide additional details for the
-- current status of the job queue.
--
-- 'tags', 'jobQueueDetail_tags' - The tags that are applied to the job queue. For more information, see
-- <https://docs.aws.amazon.com/batch/latest/userguide/using-tags.html Tagging your Batch resources>
-- in /Batch User Guide/.
--
-- 'jobQueueName', 'jobQueueDetail_jobQueueName' - The job queue name.
--
-- 'jobQueueArn', 'jobQueueDetail_jobQueueArn' - The Amazon Resource Name (ARN) of the job queue.
--
-- 'state', 'jobQueueDetail_state' - Describes the ability of the queue to accept new jobs. If the job queue
-- state is @ENABLED@, it can accept jobs. If the job queue state is
-- @DISABLED@, new jobs can\'t be added to the queue, but jobs already in
-- the queue can finish.
--
-- 'priority', 'jobQueueDetail_priority' - The priority of the job queue. Job queues with a higher priority (or a
-- higher integer value for the @priority@ parameter) are evaluated first
-- when associated with the same compute environment. Priority is
-- determined in descending order. For example, a job queue with a priority
-- value of @10@ is given scheduling preference over a job queue with a
-- priority value of @1@. All of the compute environments must be either
-- EC2 (@EC2@ or @SPOT@) or Fargate (@FARGATE@ or @FARGATE_SPOT@). EC2 and
-- Fargate compute environments can\'t be mixed.
--
-- 'computeEnvironmentOrder', 'jobQueueDetail_computeEnvironmentOrder' - The compute environments that are attached to the job queue and the
-- order that job placement is preferred. Compute environments are selected
-- for job placement in ascending order.
newJobQueueDetail ::
  -- | 'jobQueueName'
  Prelude.Text ->
  -- | 'jobQueueArn'
  Prelude.Text ->
  -- | 'state'
  JQState ->
  -- | 'priority'
  Prelude.Int ->
  JobQueueDetail
newJobQueueDetail :: Text -> Text -> JQState -> Int -> JobQueueDetail
newJobQueueDetail
  Text
pJobQueueName_
  Text
pJobQueueArn_
  JQState
pState_
  Int
pPriority_ =
    JobQueueDetail'
      { $sel:schedulingPolicyArn:JobQueueDetail' :: Maybe Text
schedulingPolicyArn =
          forall a. Maybe a
Prelude.Nothing,
        $sel:status:JobQueueDetail' :: Maybe JQStatus
status = forall a. Maybe a
Prelude.Nothing,
        $sel:statusReason:JobQueueDetail' :: Maybe Text
statusReason = forall a. Maybe a
Prelude.Nothing,
        $sel:tags:JobQueueDetail' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
        $sel:jobQueueName:JobQueueDetail' :: Text
jobQueueName = Text
pJobQueueName_,
        $sel:jobQueueArn:JobQueueDetail' :: Text
jobQueueArn = Text
pJobQueueArn_,
        $sel:state:JobQueueDetail' :: JQState
state = JQState
pState_,
        $sel:priority:JobQueueDetail' :: Int
priority = Int
pPriority_,
        $sel:computeEnvironmentOrder:JobQueueDetail' :: [ComputeEnvironmentOrder]
computeEnvironmentOrder = forall a. Monoid a => a
Prelude.mempty
      }

-- | The Amazon Resource Name (ARN) of the scheduling policy. The format is
-- @aws:@/@Partition@/@:batch:@/@Region@/@:@/@Account@/@:scheduling-policy\/@/@Name@/@ @.
-- For example,
-- @aws:aws:batch:us-west-2:123456789012:scheduling-policy\/MySchedulingPolicy@.
jobQueueDetail_schedulingPolicyArn :: Lens.Lens' JobQueueDetail (Prelude.Maybe Prelude.Text)
jobQueueDetail_schedulingPolicyArn :: Lens' JobQueueDetail (Maybe Text)
jobQueueDetail_schedulingPolicyArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobQueueDetail' {Maybe Text
schedulingPolicyArn :: Maybe Text
$sel:schedulingPolicyArn:JobQueueDetail' :: JobQueueDetail -> Maybe Text
schedulingPolicyArn} -> Maybe Text
schedulingPolicyArn) (\s :: JobQueueDetail
s@JobQueueDetail' {} Maybe Text
a -> JobQueueDetail
s {$sel:schedulingPolicyArn:JobQueueDetail' :: Maybe Text
schedulingPolicyArn = Maybe Text
a} :: JobQueueDetail)

-- | The status of the job queue (for example, @CREATING@ or @VALID@).
jobQueueDetail_status :: Lens.Lens' JobQueueDetail (Prelude.Maybe JQStatus)
jobQueueDetail_status :: Lens' JobQueueDetail (Maybe JQStatus)
jobQueueDetail_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobQueueDetail' {Maybe JQStatus
status :: Maybe JQStatus
$sel:status:JobQueueDetail' :: JobQueueDetail -> Maybe JQStatus
status} -> Maybe JQStatus
status) (\s :: JobQueueDetail
s@JobQueueDetail' {} Maybe JQStatus
a -> JobQueueDetail
s {$sel:status:JobQueueDetail' :: Maybe JQStatus
status = Maybe JQStatus
a} :: JobQueueDetail)

-- | A short, human-readable string to provide additional details for the
-- current status of the job queue.
jobQueueDetail_statusReason :: Lens.Lens' JobQueueDetail (Prelude.Maybe Prelude.Text)
jobQueueDetail_statusReason :: Lens' JobQueueDetail (Maybe Text)
jobQueueDetail_statusReason = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobQueueDetail' {Maybe Text
statusReason :: Maybe Text
$sel:statusReason:JobQueueDetail' :: JobQueueDetail -> Maybe Text
statusReason} -> Maybe Text
statusReason) (\s :: JobQueueDetail
s@JobQueueDetail' {} Maybe Text
a -> JobQueueDetail
s {$sel:statusReason:JobQueueDetail' :: Maybe Text
statusReason = Maybe Text
a} :: JobQueueDetail)

-- | The tags that are applied to the job queue. For more information, see
-- <https://docs.aws.amazon.com/batch/latest/userguide/using-tags.html Tagging your Batch resources>
-- in /Batch User Guide/.
jobQueueDetail_tags :: Lens.Lens' JobQueueDetail (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
jobQueueDetail_tags :: Lens' JobQueueDetail (Maybe (HashMap Text Text))
jobQueueDetail_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobQueueDetail' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:JobQueueDetail' :: JobQueueDetail -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: JobQueueDetail
s@JobQueueDetail' {} Maybe (HashMap Text Text)
a -> JobQueueDetail
s {$sel:tags:JobQueueDetail' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: JobQueueDetail) 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 job queue name.
jobQueueDetail_jobQueueName :: Lens.Lens' JobQueueDetail Prelude.Text
jobQueueDetail_jobQueueName :: Lens' JobQueueDetail Text
jobQueueDetail_jobQueueName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobQueueDetail' {Text
jobQueueName :: Text
$sel:jobQueueName:JobQueueDetail' :: JobQueueDetail -> Text
jobQueueName} -> Text
jobQueueName) (\s :: JobQueueDetail
s@JobQueueDetail' {} Text
a -> JobQueueDetail
s {$sel:jobQueueName:JobQueueDetail' :: Text
jobQueueName = Text
a} :: JobQueueDetail)

-- | The Amazon Resource Name (ARN) of the job queue.
jobQueueDetail_jobQueueArn :: Lens.Lens' JobQueueDetail Prelude.Text
jobQueueDetail_jobQueueArn :: Lens' JobQueueDetail Text
jobQueueDetail_jobQueueArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobQueueDetail' {Text
jobQueueArn :: Text
$sel:jobQueueArn:JobQueueDetail' :: JobQueueDetail -> Text
jobQueueArn} -> Text
jobQueueArn) (\s :: JobQueueDetail
s@JobQueueDetail' {} Text
a -> JobQueueDetail
s {$sel:jobQueueArn:JobQueueDetail' :: Text
jobQueueArn = Text
a} :: JobQueueDetail)

-- | Describes the ability of the queue to accept new jobs. If the job queue
-- state is @ENABLED@, it can accept jobs. If the job queue state is
-- @DISABLED@, new jobs can\'t be added to the queue, but jobs already in
-- the queue can finish.
jobQueueDetail_state :: Lens.Lens' JobQueueDetail JQState
jobQueueDetail_state :: Lens' JobQueueDetail JQState
jobQueueDetail_state = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobQueueDetail' {JQState
state :: JQState
$sel:state:JobQueueDetail' :: JobQueueDetail -> JQState
state} -> JQState
state) (\s :: JobQueueDetail
s@JobQueueDetail' {} JQState
a -> JobQueueDetail
s {$sel:state:JobQueueDetail' :: JQState
state = JQState
a} :: JobQueueDetail)

-- | The priority of the job queue. Job queues with a higher priority (or a
-- higher integer value for the @priority@ parameter) are evaluated first
-- when associated with the same compute environment. Priority is
-- determined in descending order. For example, a job queue with a priority
-- value of @10@ is given scheduling preference over a job queue with a
-- priority value of @1@. All of the compute environments must be either
-- EC2 (@EC2@ or @SPOT@) or Fargate (@FARGATE@ or @FARGATE_SPOT@). EC2 and
-- Fargate compute environments can\'t be mixed.
jobQueueDetail_priority :: Lens.Lens' JobQueueDetail Prelude.Int
jobQueueDetail_priority :: Lens' JobQueueDetail Int
jobQueueDetail_priority = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobQueueDetail' {Int
priority :: Int
$sel:priority:JobQueueDetail' :: JobQueueDetail -> Int
priority} -> Int
priority) (\s :: JobQueueDetail
s@JobQueueDetail' {} Int
a -> JobQueueDetail
s {$sel:priority:JobQueueDetail' :: Int
priority = Int
a} :: JobQueueDetail)

-- | The compute environments that are attached to the job queue and the
-- order that job placement is preferred. Compute environments are selected
-- for job placement in ascending order.
jobQueueDetail_computeEnvironmentOrder :: Lens.Lens' JobQueueDetail [ComputeEnvironmentOrder]
jobQueueDetail_computeEnvironmentOrder :: Lens' JobQueueDetail [ComputeEnvironmentOrder]
jobQueueDetail_computeEnvironmentOrder = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobQueueDetail' {[ComputeEnvironmentOrder]
computeEnvironmentOrder :: [ComputeEnvironmentOrder]
$sel:computeEnvironmentOrder:JobQueueDetail' :: JobQueueDetail -> [ComputeEnvironmentOrder]
computeEnvironmentOrder} -> [ComputeEnvironmentOrder]
computeEnvironmentOrder) (\s :: JobQueueDetail
s@JobQueueDetail' {} [ComputeEnvironmentOrder]
a -> JobQueueDetail
s {$sel:computeEnvironmentOrder:JobQueueDetail' :: [ComputeEnvironmentOrder]
computeEnvironmentOrder = [ComputeEnvironmentOrder]
a} :: JobQueueDetail) 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

instance Data.FromJSON JobQueueDetail where
  parseJSON :: Value -> Parser JobQueueDetail
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"JobQueueDetail"
      ( \Object
x ->
          Maybe Text
-> Maybe JQStatus
-> Maybe Text
-> Maybe (HashMap Text Text)
-> Text
-> Text
-> JQState
-> Int
-> [ComputeEnvironmentOrder]
-> JobQueueDetail
JobQueueDetail'
            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
"schedulingPolicyArn")
            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
"statusReason")
            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
"tags" forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty)
            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
"jobQueueName")
            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
"jobQueueArn")
            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
"state")
            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
"priority")
            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
"computeEnvironmentOrder"
                            forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty
                        )
      )

instance Prelude.Hashable JobQueueDetail where
  hashWithSalt :: Int -> JobQueueDetail -> Int
hashWithSalt Int
_salt JobQueueDetail' {Int
[ComputeEnvironmentOrder]
Maybe Text
Maybe (HashMap Text Text)
Maybe JQStatus
Text
JQState
computeEnvironmentOrder :: [ComputeEnvironmentOrder]
priority :: Int
state :: JQState
jobQueueArn :: Text
jobQueueName :: Text
tags :: Maybe (HashMap Text Text)
statusReason :: Maybe Text
status :: Maybe JQStatus
schedulingPolicyArn :: Maybe Text
$sel:computeEnvironmentOrder:JobQueueDetail' :: JobQueueDetail -> [ComputeEnvironmentOrder]
$sel:priority:JobQueueDetail' :: JobQueueDetail -> Int
$sel:state:JobQueueDetail' :: JobQueueDetail -> JQState
$sel:jobQueueArn:JobQueueDetail' :: JobQueueDetail -> Text
$sel:jobQueueName:JobQueueDetail' :: JobQueueDetail -> Text
$sel:tags:JobQueueDetail' :: JobQueueDetail -> Maybe (HashMap Text Text)
$sel:statusReason:JobQueueDetail' :: JobQueueDetail -> Maybe Text
$sel:status:JobQueueDetail' :: JobQueueDetail -> Maybe JQStatus
$sel:schedulingPolicyArn:JobQueueDetail' :: JobQueueDetail -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
schedulingPolicyArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe JQStatus
status
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
statusReason
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
jobQueueName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
jobQueueArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` JQState
state
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Int
priority
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [ComputeEnvironmentOrder]
computeEnvironmentOrder

instance Prelude.NFData JobQueueDetail where
  rnf :: JobQueueDetail -> ()
rnf JobQueueDetail' {Int
[ComputeEnvironmentOrder]
Maybe Text
Maybe (HashMap Text Text)
Maybe JQStatus
Text
JQState
computeEnvironmentOrder :: [ComputeEnvironmentOrder]
priority :: Int
state :: JQState
jobQueueArn :: Text
jobQueueName :: Text
tags :: Maybe (HashMap Text Text)
statusReason :: Maybe Text
status :: Maybe JQStatus
schedulingPolicyArn :: Maybe Text
$sel:computeEnvironmentOrder:JobQueueDetail' :: JobQueueDetail -> [ComputeEnvironmentOrder]
$sel:priority:JobQueueDetail' :: JobQueueDetail -> Int
$sel:state:JobQueueDetail' :: JobQueueDetail -> JQState
$sel:jobQueueArn:JobQueueDetail' :: JobQueueDetail -> Text
$sel:jobQueueName:JobQueueDetail' :: JobQueueDetail -> Text
$sel:tags:JobQueueDetail' :: JobQueueDetail -> Maybe (HashMap Text Text)
$sel:statusReason:JobQueueDetail' :: JobQueueDetail -> Maybe Text
$sel:status:JobQueueDetail' :: JobQueueDetail -> Maybe JQStatus
$sel:schedulingPolicyArn:JobQueueDetail' :: JobQueueDetail -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
schedulingPolicyArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe JQStatus
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
statusReason
      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
jobQueueName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
jobQueueArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf JQState
state
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
priority
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [ComputeEnvironmentOrder]
computeEnvironmentOrder