{-# 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.ContainerDetail
-- 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.ContainerDetail where

import Amazonka.Batch.Types.FargatePlatformConfiguration
import Amazonka.Batch.Types.KeyValuePair
import Amazonka.Batch.Types.LinuxParameters
import Amazonka.Batch.Types.LogConfiguration
import Amazonka.Batch.Types.MountPoint
import Amazonka.Batch.Types.NetworkConfiguration
import Amazonka.Batch.Types.NetworkInterface
import Amazonka.Batch.Types.ResourceRequirement
import Amazonka.Batch.Types.Secret
import Amazonka.Batch.Types.Ulimit
import Amazonka.Batch.Types.Volume
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 of a container that\'s part of a
-- job.
--
-- /See:/ 'newContainerDetail' smart constructor.
data ContainerDetail = ContainerDetail'
  { -- | The command that\'s passed to the container.
    ContainerDetail -> Maybe [Text]
command :: Prelude.Maybe [Prelude.Text],
    -- | The Amazon Resource Name (ARN) of the container instance that the
    -- container is running on.
    ContainerDetail -> Maybe Text
containerInstanceArn :: Prelude.Maybe Prelude.Text,
    -- | The environment variables to pass to a container.
    --
    -- Environment variables cannot start with \"@AWS_BATCH@\". This naming
    -- convention is reserved for variables that Batch sets.
    ContainerDetail -> Maybe [KeyValuePair]
environment :: Prelude.Maybe [KeyValuePair],
    -- | The Amazon Resource Name (ARN) of the execution role that Batch can
    -- assume. For more information, see
    -- <https://docs.aws.amazon.com/batch/latest/userguide/execution-IAM-role.html Batch execution IAM role>
    -- in the /Batch User Guide/.
    ContainerDetail -> Maybe Text
executionRoleArn :: Prelude.Maybe Prelude.Text,
    -- | The exit code to return upon completion.
    ContainerDetail -> Maybe Int
exitCode :: Prelude.Maybe Prelude.Int,
    -- | The platform configuration for jobs that are running on Fargate
    -- resources. Jobs that are running on EC2 resources must not specify this
    -- parameter.
    ContainerDetail -> Maybe FargatePlatformConfiguration
fargatePlatformConfiguration :: Prelude.Maybe FargatePlatformConfiguration,
    -- | The image used to start the container.
    ContainerDetail -> Maybe Text
image :: Prelude.Maybe Prelude.Text,
    -- | The instance type of the underlying host infrastructure of a multi-node
    -- parallel job.
    --
    -- This parameter isn\'t applicable to jobs that are running on Fargate
    -- resources.
    ContainerDetail -> Maybe Text
instanceType :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) that\'s associated with the job when run.
    ContainerDetail -> Maybe Text
jobRoleArn :: Prelude.Maybe Prelude.Text,
    -- | Linux-specific modifications that are applied to the container, such as
    -- details for device mappings.
    ContainerDetail -> Maybe LinuxParameters
linuxParameters :: Prelude.Maybe LinuxParameters,
    -- | The log configuration specification for the container.
    --
    -- This parameter maps to @LogConfig@ in the
    -- <https://docs.docker.com/engine/api/v1.23/#create-a-container Create a container>
    -- section of the
    -- <https://docs.docker.com/engine/api/v1.23/ Docker Remote API> and the
    -- @--log-driver@ option to
    -- <https://docs.docker.com/engine/reference/run/ docker run>. By default,
    -- containers use the same logging driver that the Docker daemon uses.
    -- However, the container might use a different logging driver than the
    -- Docker daemon by specifying a log driver with this parameter in the
    -- container definition. To use a different logging driver for a container,
    -- the log system must be configured properly on the container instance.
    -- Or, alternatively, it must be configured on a different log server for
    -- remote logging options. For more information on the options for
    -- different supported log drivers, see
    -- <https://docs.docker.com/engine/admin/logging/overview/ Configure logging drivers>
    -- in the Docker documentation.
    --
    -- Batch currently supports a subset of the logging drivers available to
    -- the Docker daemon (shown in the LogConfiguration data type). Additional
    -- log drivers might be available in future releases of the Amazon ECS
    -- container agent.
    --
    -- This parameter requires version 1.18 of the Docker Remote API or greater
    -- on your container instance. To check the Docker Remote API version on
    -- your container instance, log in to your container instance and run the
    -- following command: @sudo docker version | grep \"Server API version\"@
    --
    -- The Amazon ECS container agent running on a container instance must
    -- register the logging drivers available on that instance with the
    -- @ECS_AVAILABLE_LOGGING_DRIVERS@ environment variable before containers
    -- placed on that instance can use these log configuration options. For
    -- more information, see
    -- <https://docs.aws.amazon.com/AmazonECS/latest/developerguide/ecs-agent-config.html Amazon ECS container agent configuration>
    -- in the /Amazon Elastic Container Service Developer Guide/.
    ContainerDetail -> Maybe LogConfiguration
logConfiguration :: Prelude.Maybe LogConfiguration,
    -- | The name of the Amazon CloudWatch Logs log stream that\'s associated
    -- with the container. The log group for Batch jobs is @\/aws\/batch\/job@.
    -- Each container attempt receives a log stream name when they reach the
    -- @RUNNING@ status.
    ContainerDetail -> Maybe Text
logStreamName :: Prelude.Maybe Prelude.Text,
    -- | For jobs running on EC2 resources that didn\'t specify memory
    -- requirements using @resourceRequirements@, the number of MiB of memory
    -- reserved for the job. For other jobs, including all run on Fargate
    -- resources, see @resourceRequirements@.
    ContainerDetail -> Maybe Int
memory :: Prelude.Maybe Prelude.Int,
    -- | The mount points for data volumes in your container.
    ContainerDetail -> Maybe [MountPoint]
mountPoints :: Prelude.Maybe [MountPoint],
    -- | The network configuration for jobs that are running on Fargate
    -- resources. Jobs that are running on EC2 resources must not specify this
    -- parameter.
    ContainerDetail -> Maybe NetworkConfiguration
networkConfiguration :: Prelude.Maybe NetworkConfiguration,
    -- | The network interfaces that are associated with the job.
    ContainerDetail -> Maybe [NetworkInterface]
networkInterfaces :: Prelude.Maybe [NetworkInterface],
    -- | When this parameter is true, the container is given elevated permissions
    -- on the host container instance (similar to the @root@ user). The default
    -- value is @false@.
    --
    -- This parameter isn\'t applicable to jobs that are running on Fargate
    -- resources and shouldn\'t be provided, or specified as @false@.
    ContainerDetail -> Maybe Bool
privileged :: Prelude.Maybe Prelude.Bool,
    -- | When this parameter is true, the container is given read-only access to
    -- its root file system. This parameter maps to @ReadonlyRootfs@ in the
    -- <https://docs.docker.com/engine/api/v1.23/#create-a-container Create a container>
    -- section of the
    -- <https://docs.docker.com/engine/api/v1.23/ Docker Remote API> and the
    -- @--read-only@ option to
    -- <https://docs.docker.com/engine/reference/commandline/run/ docker run> .
    ContainerDetail -> Maybe Bool
readonlyRootFilesystem :: Prelude.Maybe Prelude.Bool,
    -- | A short (255 max characters) human-readable string to provide additional
    -- details for a running or stopped container.
    ContainerDetail -> Maybe Text
reason :: Prelude.Maybe Prelude.Text,
    -- | The type and amount of resources to assign to a container. The supported
    -- resources include @GPU@, @MEMORY@, and @VCPU@.
    ContainerDetail -> Maybe [ResourceRequirement]
resourceRequirements :: Prelude.Maybe [ResourceRequirement],
    -- | The secrets to pass to the container. For more information, see
    -- <https://docs.aws.amazon.com/batch/latest/userguide/specifying-sensitive-data.html Specifying sensitive data>
    -- in the /Batch User Guide/.
    ContainerDetail -> Maybe [Secret]
secrets :: Prelude.Maybe [Secret],
    -- | The Amazon Resource Name (ARN) of the Amazon ECS task that\'s associated
    -- with the container job. Each container attempt receives a task ARN when
    -- they reach the @STARTING@ status.
    ContainerDetail -> Maybe Text
taskArn :: Prelude.Maybe Prelude.Text,
    -- | A list of @ulimit@ values to set in the container. This parameter maps
    -- to @Ulimits@ in the
    -- <https://docs.docker.com/engine/api/v1.23/#create-a-container Create a container>
    -- section of the
    -- <https://docs.docker.com/engine/api/v1.23/ Docker Remote API> and the
    -- @--ulimit@ option to
    -- <https://docs.docker.com/engine/reference/run/ docker run>.
    --
    -- This parameter isn\'t applicable to jobs that are running on Fargate
    -- resources.
    ContainerDetail -> Maybe [Ulimit]
ulimits :: Prelude.Maybe [Ulimit],
    -- | The user name to use inside the container. This parameter maps to @User@
    -- in the
    -- <https://docs.docker.com/engine/api/v1.23/#create-a-container Create a container>
    -- section of the
    -- <https://docs.docker.com/engine/api/v1.23/ Docker Remote API> and the
    -- @--user@ option to
    -- <https://docs.docker.com/engine/reference/run/ docker run>.
    ContainerDetail -> Maybe Text
user :: Prelude.Maybe Prelude.Text,
    -- | The number of vCPUs reserved for the container. For jobs that run on EC2
    -- resources, you can specify the vCPU requirement for the job using
    -- @resourceRequirements@, but you can\'t specify the vCPU requirements in
    -- both the @vcpus@ and @resourceRequirements@ object. This parameter maps
    -- to @CpuShares@ in the
    -- <https://docs.docker.com/engine/api/v1.23/#create-a-container Create a container>
    -- section of the
    -- <https://docs.docker.com/engine/api/v1.23/ Docker Remote API> and the
    -- @--cpu-shares@ option to
    -- <https://docs.docker.com/engine/reference/run/ docker run>. Each vCPU is
    -- equivalent to 1,024 CPU shares. You must specify at least one vCPU. This
    -- is required but can be specified in several places. It must be specified
    -- for each node at least once.
    --
    -- This parameter isn\'t applicable to jobs that run on Fargate resources.
    -- For jobs that run on Fargate resources, you must specify the vCPU
    -- requirement for the job using @resourceRequirements@.
    ContainerDetail -> Maybe Int
vcpus :: Prelude.Maybe Prelude.Int,
    -- | A list of volumes that are associated with the job.
    ContainerDetail -> Maybe [Volume]
volumes :: Prelude.Maybe [Volume]
  }
  deriving (ContainerDetail -> ContainerDetail -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ContainerDetail -> ContainerDetail -> Bool
$c/= :: ContainerDetail -> ContainerDetail -> Bool
== :: ContainerDetail -> ContainerDetail -> Bool
$c== :: ContainerDetail -> ContainerDetail -> Bool
Prelude.Eq, ReadPrec [ContainerDetail]
ReadPrec ContainerDetail
Int -> ReadS ContainerDetail
ReadS [ContainerDetail]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ContainerDetail]
$creadListPrec :: ReadPrec [ContainerDetail]
readPrec :: ReadPrec ContainerDetail
$creadPrec :: ReadPrec ContainerDetail
readList :: ReadS [ContainerDetail]
$creadList :: ReadS [ContainerDetail]
readsPrec :: Int -> ReadS ContainerDetail
$creadsPrec :: Int -> ReadS ContainerDetail
Prelude.Read, Int -> ContainerDetail -> ShowS
[ContainerDetail] -> ShowS
ContainerDetail -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ContainerDetail] -> ShowS
$cshowList :: [ContainerDetail] -> ShowS
show :: ContainerDetail -> String
$cshow :: ContainerDetail -> String
showsPrec :: Int -> ContainerDetail -> ShowS
$cshowsPrec :: Int -> ContainerDetail -> ShowS
Prelude.Show, forall x. Rep ContainerDetail x -> ContainerDetail
forall x. ContainerDetail -> Rep ContainerDetail x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ContainerDetail x -> ContainerDetail
$cfrom :: forall x. ContainerDetail -> Rep ContainerDetail x
Prelude.Generic)

-- |
-- Create a value of 'ContainerDetail' 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:
--
-- 'command', 'containerDetail_command' - The command that\'s passed to the container.
--
-- 'containerInstanceArn', 'containerDetail_containerInstanceArn' - The Amazon Resource Name (ARN) of the container instance that the
-- container is running on.
--
-- 'environment', 'containerDetail_environment' - The environment variables to pass to a container.
--
-- Environment variables cannot start with \"@AWS_BATCH@\". This naming
-- convention is reserved for variables that Batch sets.
--
-- 'executionRoleArn', 'containerDetail_executionRoleArn' - The Amazon Resource Name (ARN) of the execution role that Batch can
-- assume. For more information, see
-- <https://docs.aws.amazon.com/batch/latest/userguide/execution-IAM-role.html Batch execution IAM role>
-- in the /Batch User Guide/.
--
-- 'exitCode', 'containerDetail_exitCode' - The exit code to return upon completion.
--
-- 'fargatePlatformConfiguration', 'containerDetail_fargatePlatformConfiguration' - The platform configuration for jobs that are running on Fargate
-- resources. Jobs that are running on EC2 resources must not specify this
-- parameter.
--
-- 'image', 'containerDetail_image' - The image used to start the container.
--
-- 'instanceType', 'containerDetail_instanceType' - The instance type of the underlying host infrastructure of a multi-node
-- parallel job.
--
-- This parameter isn\'t applicable to jobs that are running on Fargate
-- resources.
--
-- 'jobRoleArn', 'containerDetail_jobRoleArn' - The Amazon Resource Name (ARN) that\'s associated with the job when run.
--
-- 'linuxParameters', 'containerDetail_linuxParameters' - Linux-specific modifications that are applied to the container, such as
-- details for device mappings.
--
-- 'logConfiguration', 'containerDetail_logConfiguration' - The log configuration specification for the container.
--
-- This parameter maps to @LogConfig@ in the
-- <https://docs.docker.com/engine/api/v1.23/#create-a-container Create a container>
-- section of the
-- <https://docs.docker.com/engine/api/v1.23/ Docker Remote API> and the
-- @--log-driver@ option to
-- <https://docs.docker.com/engine/reference/run/ docker run>. By default,
-- containers use the same logging driver that the Docker daemon uses.
-- However, the container might use a different logging driver than the
-- Docker daemon by specifying a log driver with this parameter in the
-- container definition. To use a different logging driver for a container,
-- the log system must be configured properly on the container instance.
-- Or, alternatively, it must be configured on a different log server for
-- remote logging options. For more information on the options for
-- different supported log drivers, see
-- <https://docs.docker.com/engine/admin/logging/overview/ Configure logging drivers>
-- in the Docker documentation.
--
-- Batch currently supports a subset of the logging drivers available to
-- the Docker daemon (shown in the LogConfiguration data type). Additional
-- log drivers might be available in future releases of the Amazon ECS
-- container agent.
--
-- This parameter requires version 1.18 of the Docker Remote API or greater
-- on your container instance. To check the Docker Remote API version on
-- your container instance, log in to your container instance and run the
-- following command: @sudo docker version | grep \"Server API version\"@
--
-- The Amazon ECS container agent running on a container instance must
-- register the logging drivers available on that instance with the
-- @ECS_AVAILABLE_LOGGING_DRIVERS@ environment variable before containers
-- placed on that instance can use these log configuration options. For
-- more information, see
-- <https://docs.aws.amazon.com/AmazonECS/latest/developerguide/ecs-agent-config.html Amazon ECS container agent configuration>
-- in the /Amazon Elastic Container Service Developer Guide/.
--
-- 'logStreamName', 'containerDetail_logStreamName' - The name of the Amazon CloudWatch Logs log stream that\'s associated
-- with the container. The log group for Batch jobs is @\/aws\/batch\/job@.
-- Each container attempt receives a log stream name when they reach the
-- @RUNNING@ status.
--
-- 'memory', 'containerDetail_memory' - For jobs running on EC2 resources that didn\'t specify memory
-- requirements using @resourceRequirements@, the number of MiB of memory
-- reserved for the job. For other jobs, including all run on Fargate
-- resources, see @resourceRequirements@.
--
-- 'mountPoints', 'containerDetail_mountPoints' - The mount points for data volumes in your container.
--
-- 'networkConfiguration', 'containerDetail_networkConfiguration' - The network configuration for jobs that are running on Fargate
-- resources. Jobs that are running on EC2 resources must not specify this
-- parameter.
--
-- 'networkInterfaces', 'containerDetail_networkInterfaces' - The network interfaces that are associated with the job.
--
-- 'privileged', 'containerDetail_privileged' - When this parameter is true, the container is given elevated permissions
-- on the host container instance (similar to the @root@ user). The default
-- value is @false@.
--
-- This parameter isn\'t applicable to jobs that are running on Fargate
-- resources and shouldn\'t be provided, or specified as @false@.
--
-- 'readonlyRootFilesystem', 'containerDetail_readonlyRootFilesystem' - When this parameter is true, the container is given read-only access to
-- its root file system. This parameter maps to @ReadonlyRootfs@ in the
-- <https://docs.docker.com/engine/api/v1.23/#create-a-container Create a container>
-- section of the
-- <https://docs.docker.com/engine/api/v1.23/ Docker Remote API> and the
-- @--read-only@ option to
-- <https://docs.docker.com/engine/reference/commandline/run/ docker run> .
--
-- 'reason', 'containerDetail_reason' - A short (255 max characters) human-readable string to provide additional
-- details for a running or stopped container.
--
-- 'resourceRequirements', 'containerDetail_resourceRequirements' - The type and amount of resources to assign to a container. The supported
-- resources include @GPU@, @MEMORY@, and @VCPU@.
--
-- 'secrets', 'containerDetail_secrets' - The secrets to pass to the container. For more information, see
-- <https://docs.aws.amazon.com/batch/latest/userguide/specifying-sensitive-data.html Specifying sensitive data>
-- in the /Batch User Guide/.
--
-- 'taskArn', 'containerDetail_taskArn' - The Amazon Resource Name (ARN) of the Amazon ECS task that\'s associated
-- with the container job. Each container attempt receives a task ARN when
-- they reach the @STARTING@ status.
--
-- 'ulimits', 'containerDetail_ulimits' - A list of @ulimit@ values to set in the container. This parameter maps
-- to @Ulimits@ in the
-- <https://docs.docker.com/engine/api/v1.23/#create-a-container Create a container>
-- section of the
-- <https://docs.docker.com/engine/api/v1.23/ Docker Remote API> and the
-- @--ulimit@ option to
-- <https://docs.docker.com/engine/reference/run/ docker run>.
--
-- This parameter isn\'t applicable to jobs that are running on Fargate
-- resources.
--
-- 'user', 'containerDetail_user' - The user name to use inside the container. This parameter maps to @User@
-- in the
-- <https://docs.docker.com/engine/api/v1.23/#create-a-container Create a container>
-- section of the
-- <https://docs.docker.com/engine/api/v1.23/ Docker Remote API> and the
-- @--user@ option to
-- <https://docs.docker.com/engine/reference/run/ docker run>.
--
-- 'vcpus', 'containerDetail_vcpus' - The number of vCPUs reserved for the container. For jobs that run on EC2
-- resources, you can specify the vCPU requirement for the job using
-- @resourceRequirements@, but you can\'t specify the vCPU requirements in
-- both the @vcpus@ and @resourceRequirements@ object. This parameter maps
-- to @CpuShares@ in the
-- <https://docs.docker.com/engine/api/v1.23/#create-a-container Create a container>
-- section of the
-- <https://docs.docker.com/engine/api/v1.23/ Docker Remote API> and the
-- @--cpu-shares@ option to
-- <https://docs.docker.com/engine/reference/run/ docker run>. Each vCPU is
-- equivalent to 1,024 CPU shares. You must specify at least one vCPU. This
-- is required but can be specified in several places. It must be specified
-- for each node at least once.
--
-- This parameter isn\'t applicable to jobs that run on Fargate resources.
-- For jobs that run on Fargate resources, you must specify the vCPU
-- requirement for the job using @resourceRequirements@.
--
-- 'volumes', 'containerDetail_volumes' - A list of volumes that are associated with the job.
newContainerDetail ::
  ContainerDetail
newContainerDetail :: ContainerDetail
newContainerDetail =
  ContainerDetail'
    { $sel:command:ContainerDetail' :: Maybe [Text]
command = forall a. Maybe a
Prelude.Nothing,
      $sel:containerInstanceArn:ContainerDetail' :: Maybe Text
containerInstanceArn = forall a. Maybe a
Prelude.Nothing,
      $sel:environment:ContainerDetail' :: Maybe [KeyValuePair]
environment = forall a. Maybe a
Prelude.Nothing,
      $sel:executionRoleArn:ContainerDetail' :: Maybe Text
executionRoleArn = forall a. Maybe a
Prelude.Nothing,
      $sel:exitCode:ContainerDetail' :: Maybe Int
exitCode = forall a. Maybe a
Prelude.Nothing,
      $sel:fargatePlatformConfiguration:ContainerDetail' :: Maybe FargatePlatformConfiguration
fargatePlatformConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:image:ContainerDetail' :: Maybe Text
image = forall a. Maybe a
Prelude.Nothing,
      $sel:instanceType:ContainerDetail' :: Maybe Text
instanceType = forall a. Maybe a
Prelude.Nothing,
      $sel:jobRoleArn:ContainerDetail' :: Maybe Text
jobRoleArn = forall a. Maybe a
Prelude.Nothing,
      $sel:linuxParameters:ContainerDetail' :: Maybe LinuxParameters
linuxParameters = forall a. Maybe a
Prelude.Nothing,
      $sel:logConfiguration:ContainerDetail' :: Maybe LogConfiguration
logConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:logStreamName:ContainerDetail' :: Maybe Text
logStreamName = forall a. Maybe a
Prelude.Nothing,
      $sel:memory:ContainerDetail' :: Maybe Int
memory = forall a. Maybe a
Prelude.Nothing,
      $sel:mountPoints:ContainerDetail' :: Maybe [MountPoint]
mountPoints = forall a. Maybe a
Prelude.Nothing,
      $sel:networkConfiguration:ContainerDetail' :: Maybe NetworkConfiguration
networkConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:networkInterfaces:ContainerDetail' :: Maybe [NetworkInterface]
networkInterfaces = forall a. Maybe a
Prelude.Nothing,
      $sel:privileged:ContainerDetail' :: Maybe Bool
privileged = forall a. Maybe a
Prelude.Nothing,
      $sel:readonlyRootFilesystem:ContainerDetail' :: Maybe Bool
readonlyRootFilesystem = forall a. Maybe a
Prelude.Nothing,
      $sel:reason:ContainerDetail' :: Maybe Text
reason = forall a. Maybe a
Prelude.Nothing,
      $sel:resourceRequirements:ContainerDetail' :: Maybe [ResourceRequirement]
resourceRequirements = forall a. Maybe a
Prelude.Nothing,
      $sel:secrets:ContainerDetail' :: Maybe [Secret]
secrets = forall a. Maybe a
Prelude.Nothing,
      $sel:taskArn:ContainerDetail' :: Maybe Text
taskArn = forall a. Maybe a
Prelude.Nothing,
      $sel:ulimits:ContainerDetail' :: Maybe [Ulimit]
ulimits = forall a. Maybe a
Prelude.Nothing,
      $sel:user:ContainerDetail' :: Maybe Text
user = forall a. Maybe a
Prelude.Nothing,
      $sel:vcpus:ContainerDetail' :: Maybe Int
vcpus = forall a. Maybe a
Prelude.Nothing,
      $sel:volumes:ContainerDetail' :: Maybe [Volume]
volumes = forall a. Maybe a
Prelude.Nothing
    }

-- | The command that\'s passed to the container.
containerDetail_command :: Lens.Lens' ContainerDetail (Prelude.Maybe [Prelude.Text])
containerDetail_command :: Lens' ContainerDetail (Maybe [Text])
containerDetail_command = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ContainerDetail' {Maybe [Text]
command :: Maybe [Text]
$sel:command:ContainerDetail' :: ContainerDetail -> Maybe [Text]
command} -> Maybe [Text]
command) (\s :: ContainerDetail
s@ContainerDetail' {} Maybe [Text]
a -> ContainerDetail
s {$sel:command:ContainerDetail' :: Maybe [Text]
command = Maybe [Text]
a} :: ContainerDetail) 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 Amazon Resource Name (ARN) of the container instance that the
-- container is running on.
containerDetail_containerInstanceArn :: Lens.Lens' ContainerDetail (Prelude.Maybe Prelude.Text)
containerDetail_containerInstanceArn :: Lens' ContainerDetail (Maybe Text)
containerDetail_containerInstanceArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ContainerDetail' {Maybe Text
containerInstanceArn :: Maybe Text
$sel:containerInstanceArn:ContainerDetail' :: ContainerDetail -> Maybe Text
containerInstanceArn} -> Maybe Text
containerInstanceArn) (\s :: ContainerDetail
s@ContainerDetail' {} Maybe Text
a -> ContainerDetail
s {$sel:containerInstanceArn:ContainerDetail' :: Maybe Text
containerInstanceArn = Maybe Text
a} :: ContainerDetail)

-- | The environment variables to pass to a container.
--
-- Environment variables cannot start with \"@AWS_BATCH@\". This naming
-- convention is reserved for variables that Batch sets.
containerDetail_environment :: Lens.Lens' ContainerDetail (Prelude.Maybe [KeyValuePair])
containerDetail_environment :: Lens' ContainerDetail (Maybe [KeyValuePair])
containerDetail_environment = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ContainerDetail' {Maybe [KeyValuePair]
environment :: Maybe [KeyValuePair]
$sel:environment:ContainerDetail' :: ContainerDetail -> Maybe [KeyValuePair]
environment} -> Maybe [KeyValuePair]
environment) (\s :: ContainerDetail
s@ContainerDetail' {} Maybe [KeyValuePair]
a -> ContainerDetail
s {$sel:environment:ContainerDetail' :: Maybe [KeyValuePair]
environment = Maybe [KeyValuePair]
a} :: ContainerDetail) 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 Amazon Resource Name (ARN) of the execution role that Batch can
-- assume. For more information, see
-- <https://docs.aws.amazon.com/batch/latest/userguide/execution-IAM-role.html Batch execution IAM role>
-- in the /Batch User Guide/.
containerDetail_executionRoleArn :: Lens.Lens' ContainerDetail (Prelude.Maybe Prelude.Text)
containerDetail_executionRoleArn :: Lens' ContainerDetail (Maybe Text)
containerDetail_executionRoleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ContainerDetail' {Maybe Text
executionRoleArn :: Maybe Text
$sel:executionRoleArn:ContainerDetail' :: ContainerDetail -> Maybe Text
executionRoleArn} -> Maybe Text
executionRoleArn) (\s :: ContainerDetail
s@ContainerDetail' {} Maybe Text
a -> ContainerDetail
s {$sel:executionRoleArn:ContainerDetail' :: Maybe Text
executionRoleArn = Maybe Text
a} :: ContainerDetail)

-- | The exit code to return upon completion.
containerDetail_exitCode :: Lens.Lens' ContainerDetail (Prelude.Maybe Prelude.Int)
containerDetail_exitCode :: Lens' ContainerDetail (Maybe Int)
containerDetail_exitCode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ContainerDetail' {Maybe Int
exitCode :: Maybe Int
$sel:exitCode:ContainerDetail' :: ContainerDetail -> Maybe Int
exitCode} -> Maybe Int
exitCode) (\s :: ContainerDetail
s@ContainerDetail' {} Maybe Int
a -> ContainerDetail
s {$sel:exitCode:ContainerDetail' :: Maybe Int
exitCode = Maybe Int
a} :: ContainerDetail)

-- | The platform configuration for jobs that are running on Fargate
-- resources. Jobs that are running on EC2 resources must not specify this
-- parameter.
containerDetail_fargatePlatformConfiguration :: Lens.Lens' ContainerDetail (Prelude.Maybe FargatePlatformConfiguration)
containerDetail_fargatePlatformConfiguration :: Lens' ContainerDetail (Maybe FargatePlatformConfiguration)
containerDetail_fargatePlatformConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ContainerDetail' {Maybe FargatePlatformConfiguration
fargatePlatformConfiguration :: Maybe FargatePlatformConfiguration
$sel:fargatePlatformConfiguration:ContainerDetail' :: ContainerDetail -> Maybe FargatePlatformConfiguration
fargatePlatformConfiguration} -> Maybe FargatePlatformConfiguration
fargatePlatformConfiguration) (\s :: ContainerDetail
s@ContainerDetail' {} Maybe FargatePlatformConfiguration
a -> ContainerDetail
s {$sel:fargatePlatformConfiguration:ContainerDetail' :: Maybe FargatePlatformConfiguration
fargatePlatformConfiguration = Maybe FargatePlatformConfiguration
a} :: ContainerDetail)

-- | The image used to start the container.
containerDetail_image :: Lens.Lens' ContainerDetail (Prelude.Maybe Prelude.Text)
containerDetail_image :: Lens' ContainerDetail (Maybe Text)
containerDetail_image = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ContainerDetail' {Maybe Text
image :: Maybe Text
$sel:image:ContainerDetail' :: ContainerDetail -> Maybe Text
image} -> Maybe Text
image) (\s :: ContainerDetail
s@ContainerDetail' {} Maybe Text
a -> ContainerDetail
s {$sel:image:ContainerDetail' :: Maybe Text
image = Maybe Text
a} :: ContainerDetail)

-- | The instance type of the underlying host infrastructure of a multi-node
-- parallel job.
--
-- This parameter isn\'t applicable to jobs that are running on Fargate
-- resources.
containerDetail_instanceType :: Lens.Lens' ContainerDetail (Prelude.Maybe Prelude.Text)
containerDetail_instanceType :: Lens' ContainerDetail (Maybe Text)
containerDetail_instanceType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ContainerDetail' {Maybe Text
instanceType :: Maybe Text
$sel:instanceType:ContainerDetail' :: ContainerDetail -> Maybe Text
instanceType} -> Maybe Text
instanceType) (\s :: ContainerDetail
s@ContainerDetail' {} Maybe Text
a -> ContainerDetail
s {$sel:instanceType:ContainerDetail' :: Maybe Text
instanceType = Maybe Text
a} :: ContainerDetail)

-- | The Amazon Resource Name (ARN) that\'s associated with the job when run.
containerDetail_jobRoleArn :: Lens.Lens' ContainerDetail (Prelude.Maybe Prelude.Text)
containerDetail_jobRoleArn :: Lens' ContainerDetail (Maybe Text)
containerDetail_jobRoleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ContainerDetail' {Maybe Text
jobRoleArn :: Maybe Text
$sel:jobRoleArn:ContainerDetail' :: ContainerDetail -> Maybe Text
jobRoleArn} -> Maybe Text
jobRoleArn) (\s :: ContainerDetail
s@ContainerDetail' {} Maybe Text
a -> ContainerDetail
s {$sel:jobRoleArn:ContainerDetail' :: Maybe Text
jobRoleArn = Maybe Text
a} :: ContainerDetail)

-- | Linux-specific modifications that are applied to the container, such as
-- details for device mappings.
containerDetail_linuxParameters :: Lens.Lens' ContainerDetail (Prelude.Maybe LinuxParameters)
containerDetail_linuxParameters :: Lens' ContainerDetail (Maybe LinuxParameters)
containerDetail_linuxParameters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ContainerDetail' {Maybe LinuxParameters
linuxParameters :: Maybe LinuxParameters
$sel:linuxParameters:ContainerDetail' :: ContainerDetail -> Maybe LinuxParameters
linuxParameters} -> Maybe LinuxParameters
linuxParameters) (\s :: ContainerDetail
s@ContainerDetail' {} Maybe LinuxParameters
a -> ContainerDetail
s {$sel:linuxParameters:ContainerDetail' :: Maybe LinuxParameters
linuxParameters = Maybe LinuxParameters
a} :: ContainerDetail)

-- | The log configuration specification for the container.
--
-- This parameter maps to @LogConfig@ in the
-- <https://docs.docker.com/engine/api/v1.23/#create-a-container Create a container>
-- section of the
-- <https://docs.docker.com/engine/api/v1.23/ Docker Remote API> and the
-- @--log-driver@ option to
-- <https://docs.docker.com/engine/reference/run/ docker run>. By default,
-- containers use the same logging driver that the Docker daemon uses.
-- However, the container might use a different logging driver than the
-- Docker daemon by specifying a log driver with this parameter in the
-- container definition. To use a different logging driver for a container,
-- the log system must be configured properly on the container instance.
-- Or, alternatively, it must be configured on a different log server for
-- remote logging options. For more information on the options for
-- different supported log drivers, see
-- <https://docs.docker.com/engine/admin/logging/overview/ Configure logging drivers>
-- in the Docker documentation.
--
-- Batch currently supports a subset of the logging drivers available to
-- the Docker daemon (shown in the LogConfiguration data type). Additional
-- log drivers might be available in future releases of the Amazon ECS
-- container agent.
--
-- This parameter requires version 1.18 of the Docker Remote API or greater
-- on your container instance. To check the Docker Remote API version on
-- your container instance, log in to your container instance and run the
-- following command: @sudo docker version | grep \"Server API version\"@
--
-- The Amazon ECS container agent running on a container instance must
-- register the logging drivers available on that instance with the
-- @ECS_AVAILABLE_LOGGING_DRIVERS@ environment variable before containers
-- placed on that instance can use these log configuration options. For
-- more information, see
-- <https://docs.aws.amazon.com/AmazonECS/latest/developerguide/ecs-agent-config.html Amazon ECS container agent configuration>
-- in the /Amazon Elastic Container Service Developer Guide/.
containerDetail_logConfiguration :: Lens.Lens' ContainerDetail (Prelude.Maybe LogConfiguration)
containerDetail_logConfiguration :: Lens' ContainerDetail (Maybe LogConfiguration)
containerDetail_logConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ContainerDetail' {Maybe LogConfiguration
logConfiguration :: Maybe LogConfiguration
$sel:logConfiguration:ContainerDetail' :: ContainerDetail -> Maybe LogConfiguration
logConfiguration} -> Maybe LogConfiguration
logConfiguration) (\s :: ContainerDetail
s@ContainerDetail' {} Maybe LogConfiguration
a -> ContainerDetail
s {$sel:logConfiguration:ContainerDetail' :: Maybe LogConfiguration
logConfiguration = Maybe LogConfiguration
a} :: ContainerDetail)

-- | The name of the Amazon CloudWatch Logs log stream that\'s associated
-- with the container. The log group for Batch jobs is @\/aws\/batch\/job@.
-- Each container attempt receives a log stream name when they reach the
-- @RUNNING@ status.
containerDetail_logStreamName :: Lens.Lens' ContainerDetail (Prelude.Maybe Prelude.Text)
containerDetail_logStreamName :: Lens' ContainerDetail (Maybe Text)
containerDetail_logStreamName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ContainerDetail' {Maybe Text
logStreamName :: Maybe Text
$sel:logStreamName:ContainerDetail' :: ContainerDetail -> Maybe Text
logStreamName} -> Maybe Text
logStreamName) (\s :: ContainerDetail
s@ContainerDetail' {} Maybe Text
a -> ContainerDetail
s {$sel:logStreamName:ContainerDetail' :: Maybe Text
logStreamName = Maybe Text
a} :: ContainerDetail)

-- | For jobs running on EC2 resources that didn\'t specify memory
-- requirements using @resourceRequirements@, the number of MiB of memory
-- reserved for the job. For other jobs, including all run on Fargate
-- resources, see @resourceRequirements@.
containerDetail_memory :: Lens.Lens' ContainerDetail (Prelude.Maybe Prelude.Int)
containerDetail_memory :: Lens' ContainerDetail (Maybe Int)
containerDetail_memory = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ContainerDetail' {Maybe Int
memory :: Maybe Int
$sel:memory:ContainerDetail' :: ContainerDetail -> Maybe Int
memory} -> Maybe Int
memory) (\s :: ContainerDetail
s@ContainerDetail' {} Maybe Int
a -> ContainerDetail
s {$sel:memory:ContainerDetail' :: Maybe Int
memory = Maybe Int
a} :: ContainerDetail)

-- | The mount points for data volumes in your container.
containerDetail_mountPoints :: Lens.Lens' ContainerDetail (Prelude.Maybe [MountPoint])
containerDetail_mountPoints :: Lens' ContainerDetail (Maybe [MountPoint])
containerDetail_mountPoints = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ContainerDetail' {Maybe [MountPoint]
mountPoints :: Maybe [MountPoint]
$sel:mountPoints:ContainerDetail' :: ContainerDetail -> Maybe [MountPoint]
mountPoints} -> Maybe [MountPoint]
mountPoints) (\s :: ContainerDetail
s@ContainerDetail' {} Maybe [MountPoint]
a -> ContainerDetail
s {$sel:mountPoints:ContainerDetail' :: Maybe [MountPoint]
mountPoints = Maybe [MountPoint]
a} :: ContainerDetail) 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 network configuration for jobs that are running on Fargate
-- resources. Jobs that are running on EC2 resources must not specify this
-- parameter.
containerDetail_networkConfiguration :: Lens.Lens' ContainerDetail (Prelude.Maybe NetworkConfiguration)
containerDetail_networkConfiguration :: Lens' ContainerDetail (Maybe NetworkConfiguration)
containerDetail_networkConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ContainerDetail' {Maybe NetworkConfiguration
networkConfiguration :: Maybe NetworkConfiguration
$sel:networkConfiguration:ContainerDetail' :: ContainerDetail -> Maybe NetworkConfiguration
networkConfiguration} -> Maybe NetworkConfiguration
networkConfiguration) (\s :: ContainerDetail
s@ContainerDetail' {} Maybe NetworkConfiguration
a -> ContainerDetail
s {$sel:networkConfiguration:ContainerDetail' :: Maybe NetworkConfiguration
networkConfiguration = Maybe NetworkConfiguration
a} :: ContainerDetail)

-- | The network interfaces that are associated with the job.
containerDetail_networkInterfaces :: Lens.Lens' ContainerDetail (Prelude.Maybe [NetworkInterface])
containerDetail_networkInterfaces :: Lens' ContainerDetail (Maybe [NetworkInterface])
containerDetail_networkInterfaces = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ContainerDetail' {Maybe [NetworkInterface]
networkInterfaces :: Maybe [NetworkInterface]
$sel:networkInterfaces:ContainerDetail' :: ContainerDetail -> Maybe [NetworkInterface]
networkInterfaces} -> Maybe [NetworkInterface]
networkInterfaces) (\s :: ContainerDetail
s@ContainerDetail' {} Maybe [NetworkInterface]
a -> ContainerDetail
s {$sel:networkInterfaces:ContainerDetail' :: Maybe [NetworkInterface]
networkInterfaces = Maybe [NetworkInterface]
a} :: ContainerDetail) 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

-- | When this parameter is true, the container is given elevated permissions
-- on the host container instance (similar to the @root@ user). The default
-- value is @false@.
--
-- This parameter isn\'t applicable to jobs that are running on Fargate
-- resources and shouldn\'t be provided, or specified as @false@.
containerDetail_privileged :: Lens.Lens' ContainerDetail (Prelude.Maybe Prelude.Bool)
containerDetail_privileged :: Lens' ContainerDetail (Maybe Bool)
containerDetail_privileged = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ContainerDetail' {Maybe Bool
privileged :: Maybe Bool
$sel:privileged:ContainerDetail' :: ContainerDetail -> Maybe Bool
privileged} -> Maybe Bool
privileged) (\s :: ContainerDetail
s@ContainerDetail' {} Maybe Bool
a -> ContainerDetail
s {$sel:privileged:ContainerDetail' :: Maybe Bool
privileged = Maybe Bool
a} :: ContainerDetail)

-- | When this parameter is true, the container is given read-only access to
-- its root file system. This parameter maps to @ReadonlyRootfs@ in the
-- <https://docs.docker.com/engine/api/v1.23/#create-a-container Create a container>
-- section of the
-- <https://docs.docker.com/engine/api/v1.23/ Docker Remote API> and the
-- @--read-only@ option to
-- <https://docs.docker.com/engine/reference/commandline/run/ docker run> .
containerDetail_readonlyRootFilesystem :: Lens.Lens' ContainerDetail (Prelude.Maybe Prelude.Bool)
containerDetail_readonlyRootFilesystem :: Lens' ContainerDetail (Maybe Bool)
containerDetail_readonlyRootFilesystem = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ContainerDetail' {Maybe Bool
readonlyRootFilesystem :: Maybe Bool
$sel:readonlyRootFilesystem:ContainerDetail' :: ContainerDetail -> Maybe Bool
readonlyRootFilesystem} -> Maybe Bool
readonlyRootFilesystem) (\s :: ContainerDetail
s@ContainerDetail' {} Maybe Bool
a -> ContainerDetail
s {$sel:readonlyRootFilesystem:ContainerDetail' :: Maybe Bool
readonlyRootFilesystem = Maybe Bool
a} :: ContainerDetail)

-- | A short (255 max characters) human-readable string to provide additional
-- details for a running or stopped container.
containerDetail_reason :: Lens.Lens' ContainerDetail (Prelude.Maybe Prelude.Text)
containerDetail_reason :: Lens' ContainerDetail (Maybe Text)
containerDetail_reason = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ContainerDetail' {Maybe Text
reason :: Maybe Text
$sel:reason:ContainerDetail' :: ContainerDetail -> Maybe Text
reason} -> Maybe Text
reason) (\s :: ContainerDetail
s@ContainerDetail' {} Maybe Text
a -> ContainerDetail
s {$sel:reason:ContainerDetail' :: Maybe Text
reason = Maybe Text
a} :: ContainerDetail)

-- | The type and amount of resources to assign to a container. The supported
-- resources include @GPU@, @MEMORY@, and @VCPU@.
containerDetail_resourceRequirements :: Lens.Lens' ContainerDetail (Prelude.Maybe [ResourceRequirement])
containerDetail_resourceRequirements :: Lens' ContainerDetail (Maybe [ResourceRequirement])
containerDetail_resourceRequirements = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ContainerDetail' {Maybe [ResourceRequirement]
resourceRequirements :: Maybe [ResourceRequirement]
$sel:resourceRequirements:ContainerDetail' :: ContainerDetail -> Maybe [ResourceRequirement]
resourceRequirements} -> Maybe [ResourceRequirement]
resourceRequirements) (\s :: ContainerDetail
s@ContainerDetail' {} Maybe [ResourceRequirement]
a -> ContainerDetail
s {$sel:resourceRequirements:ContainerDetail' :: Maybe [ResourceRequirement]
resourceRequirements = Maybe [ResourceRequirement]
a} :: ContainerDetail) 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 secrets to pass to the container. For more information, see
-- <https://docs.aws.amazon.com/batch/latest/userguide/specifying-sensitive-data.html Specifying sensitive data>
-- in the /Batch User Guide/.
containerDetail_secrets :: Lens.Lens' ContainerDetail (Prelude.Maybe [Secret])
containerDetail_secrets :: Lens' ContainerDetail (Maybe [Secret])
containerDetail_secrets = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ContainerDetail' {Maybe [Secret]
secrets :: Maybe [Secret]
$sel:secrets:ContainerDetail' :: ContainerDetail -> Maybe [Secret]
secrets} -> Maybe [Secret]
secrets) (\s :: ContainerDetail
s@ContainerDetail' {} Maybe [Secret]
a -> ContainerDetail
s {$sel:secrets:ContainerDetail' :: Maybe [Secret]
secrets = Maybe [Secret]
a} :: ContainerDetail) 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 Amazon Resource Name (ARN) of the Amazon ECS task that\'s associated
-- with the container job. Each container attempt receives a task ARN when
-- they reach the @STARTING@ status.
containerDetail_taskArn :: Lens.Lens' ContainerDetail (Prelude.Maybe Prelude.Text)
containerDetail_taskArn :: Lens' ContainerDetail (Maybe Text)
containerDetail_taskArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ContainerDetail' {Maybe Text
taskArn :: Maybe Text
$sel:taskArn:ContainerDetail' :: ContainerDetail -> Maybe Text
taskArn} -> Maybe Text
taskArn) (\s :: ContainerDetail
s@ContainerDetail' {} Maybe Text
a -> ContainerDetail
s {$sel:taskArn:ContainerDetail' :: Maybe Text
taskArn = Maybe Text
a} :: ContainerDetail)

-- | A list of @ulimit@ values to set in the container. This parameter maps
-- to @Ulimits@ in the
-- <https://docs.docker.com/engine/api/v1.23/#create-a-container Create a container>
-- section of the
-- <https://docs.docker.com/engine/api/v1.23/ Docker Remote API> and the
-- @--ulimit@ option to
-- <https://docs.docker.com/engine/reference/run/ docker run>.
--
-- This parameter isn\'t applicable to jobs that are running on Fargate
-- resources.
containerDetail_ulimits :: Lens.Lens' ContainerDetail (Prelude.Maybe [Ulimit])
containerDetail_ulimits :: Lens' ContainerDetail (Maybe [Ulimit])
containerDetail_ulimits = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ContainerDetail' {Maybe [Ulimit]
ulimits :: Maybe [Ulimit]
$sel:ulimits:ContainerDetail' :: ContainerDetail -> Maybe [Ulimit]
ulimits} -> Maybe [Ulimit]
ulimits) (\s :: ContainerDetail
s@ContainerDetail' {} Maybe [Ulimit]
a -> ContainerDetail
s {$sel:ulimits:ContainerDetail' :: Maybe [Ulimit]
ulimits = Maybe [Ulimit]
a} :: ContainerDetail) 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 user name to use inside the container. This parameter maps to @User@
-- in the
-- <https://docs.docker.com/engine/api/v1.23/#create-a-container Create a container>
-- section of the
-- <https://docs.docker.com/engine/api/v1.23/ Docker Remote API> and the
-- @--user@ option to
-- <https://docs.docker.com/engine/reference/run/ docker run>.
containerDetail_user :: Lens.Lens' ContainerDetail (Prelude.Maybe Prelude.Text)
containerDetail_user :: Lens' ContainerDetail (Maybe Text)
containerDetail_user = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ContainerDetail' {Maybe Text
user :: Maybe Text
$sel:user:ContainerDetail' :: ContainerDetail -> Maybe Text
user} -> Maybe Text
user) (\s :: ContainerDetail
s@ContainerDetail' {} Maybe Text
a -> ContainerDetail
s {$sel:user:ContainerDetail' :: Maybe Text
user = Maybe Text
a} :: ContainerDetail)

-- | The number of vCPUs reserved for the container. For jobs that run on EC2
-- resources, you can specify the vCPU requirement for the job using
-- @resourceRequirements@, but you can\'t specify the vCPU requirements in
-- both the @vcpus@ and @resourceRequirements@ object. This parameter maps
-- to @CpuShares@ in the
-- <https://docs.docker.com/engine/api/v1.23/#create-a-container Create a container>
-- section of the
-- <https://docs.docker.com/engine/api/v1.23/ Docker Remote API> and the
-- @--cpu-shares@ option to
-- <https://docs.docker.com/engine/reference/run/ docker run>. Each vCPU is
-- equivalent to 1,024 CPU shares. You must specify at least one vCPU. This
-- is required but can be specified in several places. It must be specified
-- for each node at least once.
--
-- This parameter isn\'t applicable to jobs that run on Fargate resources.
-- For jobs that run on Fargate resources, you must specify the vCPU
-- requirement for the job using @resourceRequirements@.
containerDetail_vcpus :: Lens.Lens' ContainerDetail (Prelude.Maybe Prelude.Int)
containerDetail_vcpus :: Lens' ContainerDetail (Maybe Int)
containerDetail_vcpus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ContainerDetail' {Maybe Int
vcpus :: Maybe Int
$sel:vcpus:ContainerDetail' :: ContainerDetail -> Maybe Int
vcpus} -> Maybe Int
vcpus) (\s :: ContainerDetail
s@ContainerDetail' {} Maybe Int
a -> ContainerDetail
s {$sel:vcpus:ContainerDetail' :: Maybe Int
vcpus = Maybe Int
a} :: ContainerDetail)

-- | A list of volumes that are associated with the job.
containerDetail_volumes :: Lens.Lens' ContainerDetail (Prelude.Maybe [Volume])
containerDetail_volumes :: Lens' ContainerDetail (Maybe [Volume])
containerDetail_volumes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ContainerDetail' {Maybe [Volume]
volumes :: Maybe [Volume]
$sel:volumes:ContainerDetail' :: ContainerDetail -> Maybe [Volume]
volumes} -> Maybe [Volume]
volumes) (\s :: ContainerDetail
s@ContainerDetail' {} Maybe [Volume]
a -> ContainerDetail
s {$sel:volumes:ContainerDetail' :: Maybe [Volume]
volumes = Maybe [Volume]
a} :: ContainerDetail) 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 ContainerDetail where
  parseJSON :: Value -> Parser ContainerDetail
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"ContainerDetail"
      ( \Object
x ->
          Maybe [Text]
-> Maybe Text
-> Maybe [KeyValuePair]
-> Maybe Text
-> Maybe Int
-> Maybe FargatePlatformConfiguration
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe LinuxParameters
-> Maybe LogConfiguration
-> Maybe Text
-> Maybe Int
-> Maybe [MountPoint]
-> Maybe NetworkConfiguration
-> Maybe [NetworkInterface]
-> Maybe Bool
-> Maybe Bool
-> Maybe Text
-> Maybe [ResourceRequirement]
-> Maybe [Secret]
-> Maybe Text
-> Maybe [Ulimit]
-> Maybe Text
-> Maybe Int
-> Maybe [Volume]
-> ContainerDetail
ContainerDetail'
            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
"command" 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
"containerInstanceArn")
            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
"environment" 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
"executionRoleArn")
            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
"exitCode")
            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
"fargatePlatformConfiguration")
            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
"image")
            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
"instanceType")
            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
"jobRoleArn")
            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
"linuxParameters")
            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
"logConfiguration")
            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
"logStreamName")
            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
"memory")
            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
"mountPoints" 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
"networkConfiguration")
            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
"networkInterfaces"
                            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
"privileged")
            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
"readonlyRootFilesystem")
            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
"reason")
            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
"resourceRequirements"
                            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
"secrets" 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
"taskArn")
            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
"ulimits" 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
"user")
            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
"vcpus")
            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
"volumes" forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty)
      )

instance Prelude.Hashable ContainerDetail where
  hashWithSalt :: Int -> ContainerDetail -> Int
hashWithSalt Int
_salt ContainerDetail' {Maybe Bool
Maybe Int
Maybe [Text]
Maybe [KeyValuePair]
Maybe [MountPoint]
Maybe [NetworkInterface]
Maybe [ResourceRequirement]
Maybe [Secret]
Maybe [Ulimit]
Maybe [Volume]
Maybe Text
Maybe FargatePlatformConfiguration
Maybe NetworkConfiguration
Maybe LogConfiguration
Maybe LinuxParameters
volumes :: Maybe [Volume]
vcpus :: Maybe Int
user :: Maybe Text
ulimits :: Maybe [Ulimit]
taskArn :: Maybe Text
secrets :: Maybe [Secret]
resourceRequirements :: Maybe [ResourceRequirement]
reason :: Maybe Text
readonlyRootFilesystem :: Maybe Bool
privileged :: Maybe Bool
networkInterfaces :: Maybe [NetworkInterface]
networkConfiguration :: Maybe NetworkConfiguration
mountPoints :: Maybe [MountPoint]
memory :: Maybe Int
logStreamName :: Maybe Text
logConfiguration :: Maybe LogConfiguration
linuxParameters :: Maybe LinuxParameters
jobRoleArn :: Maybe Text
instanceType :: Maybe Text
image :: Maybe Text
fargatePlatformConfiguration :: Maybe FargatePlatformConfiguration
exitCode :: Maybe Int
executionRoleArn :: Maybe Text
environment :: Maybe [KeyValuePair]
containerInstanceArn :: Maybe Text
command :: Maybe [Text]
$sel:volumes:ContainerDetail' :: ContainerDetail -> Maybe [Volume]
$sel:vcpus:ContainerDetail' :: ContainerDetail -> Maybe Int
$sel:user:ContainerDetail' :: ContainerDetail -> Maybe Text
$sel:ulimits:ContainerDetail' :: ContainerDetail -> Maybe [Ulimit]
$sel:taskArn:ContainerDetail' :: ContainerDetail -> Maybe Text
$sel:secrets:ContainerDetail' :: ContainerDetail -> Maybe [Secret]
$sel:resourceRequirements:ContainerDetail' :: ContainerDetail -> Maybe [ResourceRequirement]
$sel:reason:ContainerDetail' :: ContainerDetail -> Maybe Text
$sel:readonlyRootFilesystem:ContainerDetail' :: ContainerDetail -> Maybe Bool
$sel:privileged:ContainerDetail' :: ContainerDetail -> Maybe Bool
$sel:networkInterfaces:ContainerDetail' :: ContainerDetail -> Maybe [NetworkInterface]
$sel:networkConfiguration:ContainerDetail' :: ContainerDetail -> Maybe NetworkConfiguration
$sel:mountPoints:ContainerDetail' :: ContainerDetail -> Maybe [MountPoint]
$sel:memory:ContainerDetail' :: ContainerDetail -> Maybe Int
$sel:logStreamName:ContainerDetail' :: ContainerDetail -> Maybe Text
$sel:logConfiguration:ContainerDetail' :: ContainerDetail -> Maybe LogConfiguration
$sel:linuxParameters:ContainerDetail' :: ContainerDetail -> Maybe LinuxParameters
$sel:jobRoleArn:ContainerDetail' :: ContainerDetail -> Maybe Text
$sel:instanceType:ContainerDetail' :: ContainerDetail -> Maybe Text
$sel:image:ContainerDetail' :: ContainerDetail -> Maybe Text
$sel:fargatePlatformConfiguration:ContainerDetail' :: ContainerDetail -> Maybe FargatePlatformConfiguration
$sel:exitCode:ContainerDetail' :: ContainerDetail -> Maybe Int
$sel:executionRoleArn:ContainerDetail' :: ContainerDetail -> Maybe Text
$sel:environment:ContainerDetail' :: ContainerDetail -> Maybe [KeyValuePair]
$sel:containerInstanceArn:ContainerDetail' :: ContainerDetail -> Maybe Text
$sel:command:ContainerDetail' :: ContainerDetail -> Maybe [Text]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
command
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
containerInstanceArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [KeyValuePair]
environment
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
executionRoleArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
exitCode
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe FargatePlatformConfiguration
fargatePlatformConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
image
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
instanceType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
jobRoleArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe LinuxParameters
linuxParameters
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe LogConfiguration
logConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
logStreamName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
memory
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [MountPoint]
mountPoints
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe NetworkConfiguration
networkConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [NetworkInterface]
networkInterfaces
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
privileged
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
readonlyRootFilesystem
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
reason
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [ResourceRequirement]
resourceRequirements
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Secret]
secrets
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
taskArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Ulimit]
ulimits
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
user
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
vcpus
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Volume]
volumes

instance Prelude.NFData ContainerDetail where
  rnf :: ContainerDetail -> ()
rnf ContainerDetail' {Maybe Bool
Maybe Int
Maybe [Text]
Maybe [KeyValuePair]
Maybe [MountPoint]
Maybe [NetworkInterface]
Maybe [ResourceRequirement]
Maybe [Secret]
Maybe [Ulimit]
Maybe [Volume]
Maybe Text
Maybe FargatePlatformConfiguration
Maybe NetworkConfiguration
Maybe LogConfiguration
Maybe LinuxParameters
volumes :: Maybe [Volume]
vcpus :: Maybe Int
user :: Maybe Text
ulimits :: Maybe [Ulimit]
taskArn :: Maybe Text
secrets :: Maybe [Secret]
resourceRequirements :: Maybe [ResourceRequirement]
reason :: Maybe Text
readonlyRootFilesystem :: Maybe Bool
privileged :: Maybe Bool
networkInterfaces :: Maybe [NetworkInterface]
networkConfiguration :: Maybe NetworkConfiguration
mountPoints :: Maybe [MountPoint]
memory :: Maybe Int
logStreamName :: Maybe Text
logConfiguration :: Maybe LogConfiguration
linuxParameters :: Maybe LinuxParameters
jobRoleArn :: Maybe Text
instanceType :: Maybe Text
image :: Maybe Text
fargatePlatformConfiguration :: Maybe FargatePlatformConfiguration
exitCode :: Maybe Int
executionRoleArn :: Maybe Text
environment :: Maybe [KeyValuePair]
containerInstanceArn :: Maybe Text
command :: Maybe [Text]
$sel:volumes:ContainerDetail' :: ContainerDetail -> Maybe [Volume]
$sel:vcpus:ContainerDetail' :: ContainerDetail -> Maybe Int
$sel:user:ContainerDetail' :: ContainerDetail -> Maybe Text
$sel:ulimits:ContainerDetail' :: ContainerDetail -> Maybe [Ulimit]
$sel:taskArn:ContainerDetail' :: ContainerDetail -> Maybe Text
$sel:secrets:ContainerDetail' :: ContainerDetail -> Maybe [Secret]
$sel:resourceRequirements:ContainerDetail' :: ContainerDetail -> Maybe [ResourceRequirement]
$sel:reason:ContainerDetail' :: ContainerDetail -> Maybe Text
$sel:readonlyRootFilesystem:ContainerDetail' :: ContainerDetail -> Maybe Bool
$sel:privileged:ContainerDetail' :: ContainerDetail -> Maybe Bool
$sel:networkInterfaces:ContainerDetail' :: ContainerDetail -> Maybe [NetworkInterface]
$sel:networkConfiguration:ContainerDetail' :: ContainerDetail -> Maybe NetworkConfiguration
$sel:mountPoints:ContainerDetail' :: ContainerDetail -> Maybe [MountPoint]
$sel:memory:ContainerDetail' :: ContainerDetail -> Maybe Int
$sel:logStreamName:ContainerDetail' :: ContainerDetail -> Maybe Text
$sel:logConfiguration:ContainerDetail' :: ContainerDetail -> Maybe LogConfiguration
$sel:linuxParameters:ContainerDetail' :: ContainerDetail -> Maybe LinuxParameters
$sel:jobRoleArn:ContainerDetail' :: ContainerDetail -> Maybe Text
$sel:instanceType:ContainerDetail' :: ContainerDetail -> Maybe Text
$sel:image:ContainerDetail' :: ContainerDetail -> Maybe Text
$sel:fargatePlatformConfiguration:ContainerDetail' :: ContainerDetail -> Maybe FargatePlatformConfiguration
$sel:exitCode:ContainerDetail' :: ContainerDetail -> Maybe Int
$sel:executionRoleArn:ContainerDetail' :: ContainerDetail -> Maybe Text
$sel:environment:ContainerDetail' :: ContainerDetail -> Maybe [KeyValuePair]
$sel:containerInstanceArn:ContainerDetail' :: ContainerDetail -> Maybe Text
$sel:command:ContainerDetail' :: ContainerDetail -> Maybe [Text]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
command
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
containerInstanceArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [KeyValuePair]
environment
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
executionRoleArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
exitCode
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe FargatePlatformConfiguration
fargatePlatformConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
image
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
instanceType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
jobRoleArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe LinuxParameters
linuxParameters
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe LogConfiguration
logConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
logStreamName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
memory
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [MountPoint]
mountPoints
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe NetworkConfiguration
networkConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [NetworkInterface]
networkInterfaces
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
privileged
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
readonlyRootFilesystem
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
reason
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe [ResourceRequirement]
resourceRequirements
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Secret]
secrets
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
taskArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Ulimit]
ulimits
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
user
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
vcpus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe [Volume]
volumes