{-# 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.EksContainerResourceRequirements -- 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.EksContainerResourceRequirements 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 -- | The type and amount of resources to assign to a container. The supported -- resources include @memory@, @cpu@, and @nvidia.com\/gpu@. For more -- information, see -- <https://kubernetes.io/docs/concepts/configuration/manage-resources-containers/ Resource management for pods and containers> -- in the /Kubernetes documentation/. -- -- /See:/ 'newEksContainerResourceRequirements' smart constructor. data EksContainerResourceRequirements = EksContainerResourceRequirements' { -- | The type and quantity of the resources to reserve for the container. The -- values vary based on the @name@ that\'s specified. Resources can be -- requested using either the @limits@ or the @requests@ objects. -- -- [memory] -- The memory hard limit (in MiB) for the container, using whole -- integers, with a \"Mi\" suffix. If your container attempts to exceed -- the memory specified, the container is terminated. You must specify -- at least 4 MiB of memory for a job. @memory@ can be specified in -- @limits@, @requests@, or both. If @memory@ is specified in both -- places, then the value that\'s specified in @limits@ must be equal -- to the value that\'s specified in @requests@. -- -- To maximize your resource utilization, provide your jobs with as -- much memory as possible for the specific instance type that you are -- using. To learn how, see -- <https://docs.aws.amazon.com/batch/latest/userguide/memory-management.html Memory management> -- in the /Batch User Guide/. -- -- [cpu] -- The number of CPUs that\'s reserved for the container. Values must -- be an even multiple of @0.25@. @cpu@ can be specified in @limits@, -- @requests@, or both. If @cpu@ is specified in both places, then the -- value that\'s specified in @limits@ must be at least as large as the -- value that\'s specified in @requests@. -- -- [nvidia.com\/gpu] -- The number of GPUs that\'s reserved for the container. Values must -- be a whole integer. @memory@ can be specified in @limits@, -- @requests@, or both. If @memory@ is specified in both places, then -- the value that\'s specified in @limits@ must be equal to the value -- that\'s specified in @requests@. EksContainerResourceRequirements -> Maybe (HashMap Text Text) limits :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text), -- | The type and quantity of the resources to request for the container. The -- values vary based on the @name@ that\'s specified. Resources can be -- requested by using either the @limits@ or the @requests@ objects. -- -- [memory] -- The memory hard limit (in MiB) for the container, using whole -- integers, with a \"Mi\" suffix. If your container attempts to exceed -- the memory specified, the container is terminated. You must specify -- at least 4 MiB of memory for a job. @memory@ can be specified in -- @limits@, @requests@, or both. If @memory@ is specified in both, -- then the value that\'s specified in @limits@ must be equal to the -- value that\'s specified in @requests@. -- -- If you\'re trying to maximize your resource utilization by providing -- your jobs as much memory as possible for a particular instance type, -- see -- <https://docs.aws.amazon.com/batch/latest/userguide/memory-management.html Memory management> -- in the /Batch User Guide/. -- -- [cpu] -- The number of CPUs that are reserved for the container. Values must -- be an even multiple of @0.25@. @cpu@ can be specified in @limits@, -- @requests@, or both. If @cpu@ is specified in both, then the value -- that\'s specified in @limits@ must be at least as large as the value -- that\'s specified in @requests@. -- -- [nvidia.com\/gpu] -- The number of GPUs that are reserved for the container. Values must -- be a whole integer. @nvidia.com\/gpu@ can be specified in @limits@, -- @requests@, or both. If @nvidia.com\/gpu@ is specified in both, then -- the value that\'s specified in @limits@ must be equal to the value -- that\'s specified in @requests@. EksContainerResourceRequirements -> Maybe (HashMap Text Text) requests :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text) } deriving (EksContainerResourceRequirements -> EksContainerResourceRequirements -> Bool forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: EksContainerResourceRequirements -> EksContainerResourceRequirements -> Bool $c/= :: EksContainerResourceRequirements -> EksContainerResourceRequirements -> Bool == :: EksContainerResourceRequirements -> EksContainerResourceRequirements -> Bool $c== :: EksContainerResourceRequirements -> EksContainerResourceRequirements -> Bool Prelude.Eq, ReadPrec [EksContainerResourceRequirements] ReadPrec EksContainerResourceRequirements Int -> ReadS EksContainerResourceRequirements ReadS [EksContainerResourceRequirements] forall a. (Int -> ReadS a) -> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a readListPrec :: ReadPrec [EksContainerResourceRequirements] $creadListPrec :: ReadPrec [EksContainerResourceRequirements] readPrec :: ReadPrec EksContainerResourceRequirements $creadPrec :: ReadPrec EksContainerResourceRequirements readList :: ReadS [EksContainerResourceRequirements] $creadList :: ReadS [EksContainerResourceRequirements] readsPrec :: Int -> ReadS EksContainerResourceRequirements $creadsPrec :: Int -> ReadS EksContainerResourceRequirements Prelude.Read, Int -> EksContainerResourceRequirements -> ShowS [EksContainerResourceRequirements] -> ShowS EksContainerResourceRequirements -> String forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [EksContainerResourceRequirements] -> ShowS $cshowList :: [EksContainerResourceRequirements] -> ShowS show :: EksContainerResourceRequirements -> String $cshow :: EksContainerResourceRequirements -> String showsPrec :: Int -> EksContainerResourceRequirements -> ShowS $cshowsPrec :: Int -> EksContainerResourceRequirements -> ShowS Prelude.Show, forall x. Rep EksContainerResourceRequirements x -> EksContainerResourceRequirements forall x. EksContainerResourceRequirements -> Rep EksContainerResourceRequirements x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep EksContainerResourceRequirements x -> EksContainerResourceRequirements $cfrom :: forall x. EksContainerResourceRequirements -> Rep EksContainerResourceRequirements x Prelude.Generic) -- | -- Create a value of 'EksContainerResourceRequirements' 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: -- -- 'limits', 'eksContainerResourceRequirements_limits' - The type and quantity of the resources to reserve for the container. The -- values vary based on the @name@ that\'s specified. Resources can be -- requested using either the @limits@ or the @requests@ objects. -- -- [memory] -- The memory hard limit (in MiB) for the container, using whole -- integers, with a \"Mi\" suffix. If your container attempts to exceed -- the memory specified, the container is terminated. You must specify -- at least 4 MiB of memory for a job. @memory@ can be specified in -- @limits@, @requests@, or both. If @memory@ is specified in both -- places, then the value that\'s specified in @limits@ must be equal -- to the value that\'s specified in @requests@. -- -- To maximize your resource utilization, provide your jobs with as -- much memory as possible for the specific instance type that you are -- using. To learn how, see -- <https://docs.aws.amazon.com/batch/latest/userguide/memory-management.html Memory management> -- in the /Batch User Guide/. -- -- [cpu] -- The number of CPUs that\'s reserved for the container. Values must -- be an even multiple of @0.25@. @cpu@ can be specified in @limits@, -- @requests@, or both. If @cpu@ is specified in both places, then the -- value that\'s specified in @limits@ must be at least as large as the -- value that\'s specified in @requests@. -- -- [nvidia.com\/gpu] -- The number of GPUs that\'s reserved for the container. Values must -- be a whole integer. @memory@ can be specified in @limits@, -- @requests@, or both. If @memory@ is specified in both places, then -- the value that\'s specified in @limits@ must be equal to the value -- that\'s specified in @requests@. -- -- 'requests', 'eksContainerResourceRequirements_requests' - The type and quantity of the resources to request for the container. The -- values vary based on the @name@ that\'s specified. Resources can be -- requested by using either the @limits@ or the @requests@ objects. -- -- [memory] -- The memory hard limit (in MiB) for the container, using whole -- integers, with a \"Mi\" suffix. If your container attempts to exceed -- the memory specified, the container is terminated. You must specify -- at least 4 MiB of memory for a job. @memory@ can be specified in -- @limits@, @requests@, or both. If @memory@ is specified in both, -- then the value that\'s specified in @limits@ must be equal to the -- value that\'s specified in @requests@. -- -- If you\'re trying to maximize your resource utilization by providing -- your jobs as much memory as possible for a particular instance type, -- see -- <https://docs.aws.amazon.com/batch/latest/userguide/memory-management.html Memory management> -- in the /Batch User Guide/. -- -- [cpu] -- The number of CPUs that are reserved for the container. Values must -- be an even multiple of @0.25@. @cpu@ can be specified in @limits@, -- @requests@, or both. If @cpu@ is specified in both, then the value -- that\'s specified in @limits@ must be at least as large as the value -- that\'s specified in @requests@. -- -- [nvidia.com\/gpu] -- The number of GPUs that are reserved for the container. Values must -- be a whole integer. @nvidia.com\/gpu@ can be specified in @limits@, -- @requests@, or both. If @nvidia.com\/gpu@ is specified in both, then -- the value that\'s specified in @limits@ must be equal to the value -- that\'s specified in @requests@. newEksContainerResourceRequirements :: EksContainerResourceRequirements newEksContainerResourceRequirements :: EksContainerResourceRequirements newEksContainerResourceRequirements = EksContainerResourceRequirements' { $sel:limits:EksContainerResourceRequirements' :: Maybe (HashMap Text Text) limits = forall a. Maybe a Prelude.Nothing, $sel:requests:EksContainerResourceRequirements' :: Maybe (HashMap Text Text) requests = forall a. Maybe a Prelude.Nothing } -- | The type and quantity of the resources to reserve for the container. The -- values vary based on the @name@ that\'s specified. Resources can be -- requested using either the @limits@ or the @requests@ objects. -- -- [memory] -- The memory hard limit (in MiB) for the container, using whole -- integers, with a \"Mi\" suffix. If your container attempts to exceed -- the memory specified, the container is terminated. You must specify -- at least 4 MiB of memory for a job. @memory@ can be specified in -- @limits@, @requests@, or both. If @memory@ is specified in both -- places, then the value that\'s specified in @limits@ must be equal -- to the value that\'s specified in @requests@. -- -- To maximize your resource utilization, provide your jobs with as -- much memory as possible for the specific instance type that you are -- using. To learn how, see -- <https://docs.aws.amazon.com/batch/latest/userguide/memory-management.html Memory management> -- in the /Batch User Guide/. -- -- [cpu] -- The number of CPUs that\'s reserved for the container. Values must -- be an even multiple of @0.25@. @cpu@ can be specified in @limits@, -- @requests@, or both. If @cpu@ is specified in both places, then the -- value that\'s specified in @limits@ must be at least as large as the -- value that\'s specified in @requests@. -- -- [nvidia.com\/gpu] -- The number of GPUs that\'s reserved for the container. Values must -- be a whole integer. @memory@ can be specified in @limits@, -- @requests@, or both. If @memory@ is specified in both places, then -- the value that\'s specified in @limits@ must be equal to the value -- that\'s specified in @requests@. eksContainerResourceRequirements_limits :: Lens.Lens' EksContainerResourceRequirements (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text)) eksContainerResourceRequirements_limits :: Lens' EksContainerResourceRequirements (Maybe (HashMap Text Text)) eksContainerResourceRequirements_limits = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b Lens.lens (\EksContainerResourceRequirements' {Maybe (HashMap Text Text) limits :: Maybe (HashMap Text Text) $sel:limits:EksContainerResourceRequirements' :: EksContainerResourceRequirements -> Maybe (HashMap Text Text) limits} -> Maybe (HashMap Text Text) limits) (\s :: EksContainerResourceRequirements s@EksContainerResourceRequirements' {} Maybe (HashMap Text Text) a -> EksContainerResourceRequirements s {$sel:limits:EksContainerResourceRequirements' :: Maybe (HashMap Text Text) limits = Maybe (HashMap Text Text) a} :: EksContainerResourceRequirements) 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 type and quantity of the resources to request for the container. The -- values vary based on the @name@ that\'s specified. Resources can be -- requested by using either the @limits@ or the @requests@ objects. -- -- [memory] -- The memory hard limit (in MiB) for the container, using whole -- integers, with a \"Mi\" suffix. If your container attempts to exceed -- the memory specified, the container is terminated. You must specify -- at least 4 MiB of memory for a job. @memory@ can be specified in -- @limits@, @requests@, or both. If @memory@ is specified in both, -- then the value that\'s specified in @limits@ must be equal to the -- value that\'s specified in @requests@. -- -- If you\'re trying to maximize your resource utilization by providing -- your jobs as much memory as possible for a particular instance type, -- see -- <https://docs.aws.amazon.com/batch/latest/userguide/memory-management.html Memory management> -- in the /Batch User Guide/. -- -- [cpu] -- The number of CPUs that are reserved for the container. Values must -- be an even multiple of @0.25@. @cpu@ can be specified in @limits@, -- @requests@, or both. If @cpu@ is specified in both, then the value -- that\'s specified in @limits@ must be at least as large as the value -- that\'s specified in @requests@. -- -- [nvidia.com\/gpu] -- The number of GPUs that are reserved for the container. Values must -- be a whole integer. @nvidia.com\/gpu@ can be specified in @limits@, -- @requests@, or both. If @nvidia.com\/gpu@ is specified in both, then -- the value that\'s specified in @limits@ must be equal to the value -- that\'s specified in @requests@. eksContainerResourceRequirements_requests :: Lens.Lens' EksContainerResourceRequirements (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text)) eksContainerResourceRequirements_requests :: Lens' EksContainerResourceRequirements (Maybe (HashMap Text Text)) eksContainerResourceRequirements_requests = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b Lens.lens (\EksContainerResourceRequirements' {Maybe (HashMap Text Text) requests :: Maybe (HashMap Text Text) $sel:requests:EksContainerResourceRequirements' :: EksContainerResourceRequirements -> Maybe (HashMap Text Text) requests} -> Maybe (HashMap Text Text) requests) (\s :: EksContainerResourceRequirements s@EksContainerResourceRequirements' {} Maybe (HashMap Text Text) a -> EksContainerResourceRequirements s {$sel:requests:EksContainerResourceRequirements' :: Maybe (HashMap Text Text) requests = Maybe (HashMap Text Text) a} :: EksContainerResourceRequirements) 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 instance Data.FromJSON EksContainerResourceRequirements where parseJSON :: Value -> Parser EksContainerResourceRequirements parseJSON = forall a. String -> (Object -> Parser a) -> Value -> Parser a Data.withObject String "EksContainerResourceRequirements" ( \Object x -> Maybe (HashMap Text Text) -> Maybe (HashMap Text Text) -> EksContainerResourceRequirements EksContainerResourceRequirements' 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 "limits" 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 (Maybe a) Data..:? Key "requests" forall a. Parser (Maybe a) -> a -> Parser a Data..!= forall a. Monoid a => a Prelude.mempty) ) instance Prelude.Hashable EksContainerResourceRequirements where hashWithSalt :: Int -> EksContainerResourceRequirements -> Int hashWithSalt Int _salt EksContainerResourceRequirements' {Maybe (HashMap Text Text) requests :: Maybe (HashMap Text Text) limits :: Maybe (HashMap Text Text) $sel:requests:EksContainerResourceRequirements' :: EksContainerResourceRequirements -> Maybe (HashMap Text Text) $sel:limits:EksContainerResourceRequirements' :: EksContainerResourceRequirements -> Maybe (HashMap Text Text) ..} = Int _salt forall a. Hashable a => Int -> a -> Int `Prelude.hashWithSalt` Maybe (HashMap Text Text) limits forall a. Hashable a => Int -> a -> Int `Prelude.hashWithSalt` Maybe (HashMap Text Text) requests instance Prelude.NFData EksContainerResourceRequirements where rnf :: EksContainerResourceRequirements -> () rnf EksContainerResourceRequirements' {Maybe (HashMap Text Text) requests :: Maybe (HashMap Text Text) limits :: Maybe (HashMap Text Text) $sel:requests:EksContainerResourceRequirements' :: EksContainerResourceRequirements -> Maybe (HashMap Text Text) $sel:limits:EksContainerResourceRequirements' :: EksContainerResourceRequirements -> Maybe (HashMap Text Text) ..} = forall a. NFData a => a -> () Prelude.rnf Maybe (HashMap Text Text) limits seq :: forall a b. a -> b -> b `Prelude.seq` forall a. NFData a => a -> () Prelude.rnf Maybe (HashMap Text Text) requests instance Data.ToJSON EksContainerResourceRequirements where toJSON :: EksContainerResourceRequirements -> Value toJSON EksContainerResourceRequirements' {Maybe (HashMap Text Text) requests :: Maybe (HashMap Text Text) limits :: Maybe (HashMap Text Text) $sel:requests:EksContainerResourceRequirements' :: EksContainerResourceRequirements -> Maybe (HashMap Text Text) $sel:limits:EksContainerResourceRequirements' :: EksContainerResourceRequirements -> Maybe (HashMap Text Text) ..} = [Pair] -> Value Data.object ( forall a. [Maybe a] -> [a] Prelude.catMaybes [ (Key "limits" 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 (HashMap Text Text) limits, (Key "requests" 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 (HashMap Text Text) requests ] )