{-# 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.Braket.Types.JobStoppingCondition
-- 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.Braket.Types.JobStoppingCondition 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

-- | Specifies limits for how long an Amazon Braket job can run.
--
-- /See:/ 'newJobStoppingCondition' smart constructor.
data JobStoppingCondition = JobStoppingCondition'
  { -- | The maximum length of time, in seconds, that an Amazon Braket job can
    -- run.
    JobStoppingCondition -> Maybe Natural
maxRuntimeInSeconds :: Prelude.Maybe Prelude.Natural
  }
  deriving (JobStoppingCondition -> JobStoppingCondition -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: JobStoppingCondition -> JobStoppingCondition -> Bool
$c/= :: JobStoppingCondition -> JobStoppingCondition -> Bool
== :: JobStoppingCondition -> JobStoppingCondition -> Bool
$c== :: JobStoppingCondition -> JobStoppingCondition -> Bool
Prelude.Eq, ReadPrec [JobStoppingCondition]
ReadPrec JobStoppingCondition
Int -> ReadS JobStoppingCondition
ReadS [JobStoppingCondition]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [JobStoppingCondition]
$creadListPrec :: ReadPrec [JobStoppingCondition]
readPrec :: ReadPrec JobStoppingCondition
$creadPrec :: ReadPrec JobStoppingCondition
readList :: ReadS [JobStoppingCondition]
$creadList :: ReadS [JobStoppingCondition]
readsPrec :: Int -> ReadS JobStoppingCondition
$creadsPrec :: Int -> ReadS JobStoppingCondition
Prelude.Read, Int -> JobStoppingCondition -> ShowS
[JobStoppingCondition] -> ShowS
JobStoppingCondition -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [JobStoppingCondition] -> ShowS
$cshowList :: [JobStoppingCondition] -> ShowS
show :: JobStoppingCondition -> String
$cshow :: JobStoppingCondition -> String
showsPrec :: Int -> JobStoppingCondition -> ShowS
$cshowsPrec :: Int -> JobStoppingCondition -> ShowS
Prelude.Show, forall x. Rep JobStoppingCondition x -> JobStoppingCondition
forall x. JobStoppingCondition -> Rep JobStoppingCondition x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep JobStoppingCondition x -> JobStoppingCondition
$cfrom :: forall x. JobStoppingCondition -> Rep JobStoppingCondition x
Prelude.Generic)

-- |
-- Create a value of 'JobStoppingCondition' 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:
--
-- 'maxRuntimeInSeconds', 'jobStoppingCondition_maxRuntimeInSeconds' - The maximum length of time, in seconds, that an Amazon Braket job can
-- run.
newJobStoppingCondition ::
  JobStoppingCondition
newJobStoppingCondition :: JobStoppingCondition
newJobStoppingCondition =
  JobStoppingCondition'
    { $sel:maxRuntimeInSeconds:JobStoppingCondition' :: Maybe Natural
maxRuntimeInSeconds =
        forall a. Maybe a
Prelude.Nothing
    }

-- | The maximum length of time, in seconds, that an Amazon Braket job can
-- run.
jobStoppingCondition_maxRuntimeInSeconds :: Lens.Lens' JobStoppingCondition (Prelude.Maybe Prelude.Natural)
jobStoppingCondition_maxRuntimeInSeconds :: Lens' JobStoppingCondition (Maybe Natural)
jobStoppingCondition_maxRuntimeInSeconds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobStoppingCondition' {Maybe Natural
maxRuntimeInSeconds :: Maybe Natural
$sel:maxRuntimeInSeconds:JobStoppingCondition' :: JobStoppingCondition -> Maybe Natural
maxRuntimeInSeconds} -> Maybe Natural
maxRuntimeInSeconds) (\s :: JobStoppingCondition
s@JobStoppingCondition' {} Maybe Natural
a -> JobStoppingCondition
s {$sel:maxRuntimeInSeconds:JobStoppingCondition' :: Maybe Natural
maxRuntimeInSeconds = Maybe Natural
a} :: JobStoppingCondition)

instance Data.FromJSON JobStoppingCondition where
  parseJSON :: Value -> Parser JobStoppingCondition
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"JobStoppingCondition"
      ( \Object
x ->
          Maybe Natural -> JobStoppingCondition
JobStoppingCondition'
            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
"maxRuntimeInSeconds")
      )

instance Prelude.Hashable JobStoppingCondition where
  hashWithSalt :: Int -> JobStoppingCondition -> Int
hashWithSalt Int
_salt JobStoppingCondition' {Maybe Natural
maxRuntimeInSeconds :: Maybe Natural
$sel:maxRuntimeInSeconds:JobStoppingCondition' :: JobStoppingCondition -> Maybe Natural
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maxRuntimeInSeconds

instance Prelude.NFData JobStoppingCondition where
  rnf :: JobStoppingCondition -> ()
rnf JobStoppingCondition' {Maybe Natural
maxRuntimeInSeconds :: Maybe Natural
$sel:maxRuntimeInSeconds:JobStoppingCondition' :: JobStoppingCondition -> Maybe Natural
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
maxRuntimeInSeconds

instance Data.ToJSON JobStoppingCondition where
  toJSON :: JobStoppingCondition -> Value
toJSON JobStoppingCondition' {Maybe Natural
maxRuntimeInSeconds :: Maybe Natural
$sel:maxRuntimeInSeconds:JobStoppingCondition' :: JobStoppingCondition -> Maybe Natural
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"maxRuntimeInSeconds" 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 Natural
maxRuntimeInSeconds
          ]
      )