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

import Amazonka.Batch.Types.NetworkInterface
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 attempt.
--
-- /See:/ 'newAttemptContainerDetail' smart constructor.
data AttemptContainerDetail = AttemptContainerDetail'
  { -- | The Amazon Resource Name (ARN) of the Amazon ECS container instance that
    -- hosts the job attempt.
    AttemptContainerDetail -> Maybe Text
containerInstanceArn :: Prelude.Maybe Prelude.Text,
    -- | The exit code for the job attempt. A non-zero exit code is considered
    -- failed.
    AttemptContainerDetail -> Maybe Int
exitCode :: Prelude.Maybe Prelude.Int,
    -- | The name of the 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.
    AttemptContainerDetail -> Maybe Text
logStreamName :: Prelude.Maybe Prelude.Text,
    -- | The network interfaces that are associated with the job attempt.
    AttemptContainerDetail -> Maybe [NetworkInterface]
networkInterfaces :: Prelude.Maybe [NetworkInterface],
    -- | A short (255 max characters) human-readable string to provide additional
    -- details for a running or stopped container.
    AttemptContainerDetail -> Maybe Text
reason :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the Amazon ECS task that\'s associated
    -- with the job attempt. Each container attempt receives a task ARN when
    -- they reach the @STARTING@ status.
    AttemptContainerDetail -> Maybe Text
taskArn :: Prelude.Maybe Prelude.Text
  }
  deriving (AttemptContainerDetail -> AttemptContainerDetail -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AttemptContainerDetail -> AttemptContainerDetail -> Bool
$c/= :: AttemptContainerDetail -> AttemptContainerDetail -> Bool
== :: AttemptContainerDetail -> AttemptContainerDetail -> Bool
$c== :: AttemptContainerDetail -> AttemptContainerDetail -> Bool
Prelude.Eq, ReadPrec [AttemptContainerDetail]
ReadPrec AttemptContainerDetail
Int -> ReadS AttemptContainerDetail
ReadS [AttemptContainerDetail]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AttemptContainerDetail]
$creadListPrec :: ReadPrec [AttemptContainerDetail]
readPrec :: ReadPrec AttemptContainerDetail
$creadPrec :: ReadPrec AttemptContainerDetail
readList :: ReadS [AttemptContainerDetail]
$creadList :: ReadS [AttemptContainerDetail]
readsPrec :: Int -> ReadS AttemptContainerDetail
$creadsPrec :: Int -> ReadS AttemptContainerDetail
Prelude.Read, Int -> AttemptContainerDetail -> ShowS
[AttemptContainerDetail] -> ShowS
AttemptContainerDetail -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AttemptContainerDetail] -> ShowS
$cshowList :: [AttemptContainerDetail] -> ShowS
show :: AttemptContainerDetail -> String
$cshow :: AttemptContainerDetail -> String
showsPrec :: Int -> AttemptContainerDetail -> ShowS
$cshowsPrec :: Int -> AttemptContainerDetail -> ShowS
Prelude.Show, forall x. Rep AttemptContainerDetail x -> AttemptContainerDetail
forall x. AttemptContainerDetail -> Rep AttemptContainerDetail x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AttemptContainerDetail x -> AttemptContainerDetail
$cfrom :: forall x. AttemptContainerDetail -> Rep AttemptContainerDetail x
Prelude.Generic)

-- |
-- Create a value of 'AttemptContainerDetail' 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:
--
-- 'containerInstanceArn', 'attemptContainerDetail_containerInstanceArn' - The Amazon Resource Name (ARN) of the Amazon ECS container instance that
-- hosts the job attempt.
--
-- 'exitCode', 'attemptContainerDetail_exitCode' - The exit code for the job attempt. A non-zero exit code is considered
-- failed.
--
-- 'logStreamName', 'attemptContainerDetail_logStreamName' - The name of the 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.
--
-- 'networkInterfaces', 'attemptContainerDetail_networkInterfaces' - The network interfaces that are associated with the job attempt.
--
-- 'reason', 'attemptContainerDetail_reason' - A short (255 max characters) human-readable string to provide additional
-- details for a running or stopped container.
--
-- 'taskArn', 'attemptContainerDetail_taskArn' - The Amazon Resource Name (ARN) of the Amazon ECS task that\'s associated
-- with the job attempt. Each container attempt receives a task ARN when
-- they reach the @STARTING@ status.
newAttemptContainerDetail ::
  AttemptContainerDetail
newAttemptContainerDetail :: AttemptContainerDetail
newAttemptContainerDetail =
  AttemptContainerDetail'
    { $sel:containerInstanceArn:AttemptContainerDetail' :: Maybe Text
containerInstanceArn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:exitCode:AttemptContainerDetail' :: Maybe Int
exitCode = forall a. Maybe a
Prelude.Nothing,
      $sel:logStreamName:AttemptContainerDetail' :: Maybe Text
logStreamName = forall a. Maybe a
Prelude.Nothing,
      $sel:networkInterfaces:AttemptContainerDetail' :: Maybe [NetworkInterface]
networkInterfaces = forall a. Maybe a
Prelude.Nothing,
      $sel:reason:AttemptContainerDetail' :: Maybe Text
reason = forall a. Maybe a
Prelude.Nothing,
      $sel:taskArn:AttemptContainerDetail' :: Maybe Text
taskArn = forall a. Maybe a
Prelude.Nothing
    }

-- | The Amazon Resource Name (ARN) of the Amazon ECS container instance that
-- hosts the job attempt.
attemptContainerDetail_containerInstanceArn :: Lens.Lens' AttemptContainerDetail (Prelude.Maybe Prelude.Text)
attemptContainerDetail_containerInstanceArn :: Lens' AttemptContainerDetail (Maybe Text)
attemptContainerDetail_containerInstanceArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AttemptContainerDetail' {Maybe Text
containerInstanceArn :: Maybe Text
$sel:containerInstanceArn:AttemptContainerDetail' :: AttemptContainerDetail -> Maybe Text
containerInstanceArn} -> Maybe Text
containerInstanceArn) (\s :: AttemptContainerDetail
s@AttemptContainerDetail' {} Maybe Text
a -> AttemptContainerDetail
s {$sel:containerInstanceArn:AttemptContainerDetail' :: Maybe Text
containerInstanceArn = Maybe Text
a} :: AttemptContainerDetail)

-- | The exit code for the job attempt. A non-zero exit code is considered
-- failed.
attemptContainerDetail_exitCode :: Lens.Lens' AttemptContainerDetail (Prelude.Maybe Prelude.Int)
attemptContainerDetail_exitCode :: Lens' AttemptContainerDetail (Maybe Int)
attemptContainerDetail_exitCode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AttemptContainerDetail' {Maybe Int
exitCode :: Maybe Int
$sel:exitCode:AttemptContainerDetail' :: AttemptContainerDetail -> Maybe Int
exitCode} -> Maybe Int
exitCode) (\s :: AttemptContainerDetail
s@AttemptContainerDetail' {} Maybe Int
a -> AttemptContainerDetail
s {$sel:exitCode:AttemptContainerDetail' :: Maybe Int
exitCode = Maybe Int
a} :: AttemptContainerDetail)

-- | The name of the 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.
attemptContainerDetail_logStreamName :: Lens.Lens' AttemptContainerDetail (Prelude.Maybe Prelude.Text)
attemptContainerDetail_logStreamName :: Lens' AttemptContainerDetail (Maybe Text)
attemptContainerDetail_logStreamName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AttemptContainerDetail' {Maybe Text
logStreamName :: Maybe Text
$sel:logStreamName:AttemptContainerDetail' :: AttemptContainerDetail -> Maybe Text
logStreamName} -> Maybe Text
logStreamName) (\s :: AttemptContainerDetail
s@AttemptContainerDetail' {} Maybe Text
a -> AttemptContainerDetail
s {$sel:logStreamName:AttemptContainerDetail' :: Maybe Text
logStreamName = Maybe Text
a} :: AttemptContainerDetail)

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

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

-- | The Amazon Resource Name (ARN) of the Amazon ECS task that\'s associated
-- with the job attempt. Each container attempt receives a task ARN when
-- they reach the @STARTING@ status.
attemptContainerDetail_taskArn :: Lens.Lens' AttemptContainerDetail (Prelude.Maybe Prelude.Text)
attemptContainerDetail_taskArn :: Lens' AttemptContainerDetail (Maybe Text)
attemptContainerDetail_taskArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AttemptContainerDetail' {Maybe Text
taskArn :: Maybe Text
$sel:taskArn:AttemptContainerDetail' :: AttemptContainerDetail -> Maybe Text
taskArn} -> Maybe Text
taskArn) (\s :: AttemptContainerDetail
s@AttemptContainerDetail' {} Maybe Text
a -> AttemptContainerDetail
s {$sel:taskArn:AttemptContainerDetail' :: Maybe Text
taskArn = Maybe Text
a} :: AttemptContainerDetail)

instance Data.FromJSON AttemptContainerDetail where
  parseJSON :: Value -> Parser AttemptContainerDetail
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"AttemptContainerDetail"
      ( \Object
x ->
          Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe [NetworkInterface]
-> Maybe Text
-> Maybe Text
-> AttemptContainerDetail
AttemptContainerDetail'
            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
"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
"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
"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
"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
"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
"taskArn")
      )

instance Prelude.Hashable AttemptContainerDetail where
  hashWithSalt :: Int -> AttemptContainerDetail -> Int
hashWithSalt Int
_salt AttemptContainerDetail' {Maybe Int
Maybe [NetworkInterface]
Maybe Text
taskArn :: Maybe Text
reason :: Maybe Text
networkInterfaces :: Maybe [NetworkInterface]
logStreamName :: Maybe Text
exitCode :: Maybe Int
containerInstanceArn :: Maybe Text
$sel:taskArn:AttemptContainerDetail' :: AttemptContainerDetail -> Maybe Text
$sel:reason:AttemptContainerDetail' :: AttemptContainerDetail -> Maybe Text
$sel:networkInterfaces:AttemptContainerDetail' :: AttemptContainerDetail -> Maybe [NetworkInterface]
$sel:logStreamName:AttemptContainerDetail' :: AttemptContainerDetail -> Maybe Text
$sel:exitCode:AttemptContainerDetail' :: AttemptContainerDetail -> Maybe Int
$sel:containerInstanceArn:AttemptContainerDetail' :: AttemptContainerDetail -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
containerInstanceArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
exitCode
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
logStreamName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [NetworkInterface]
networkInterfaces
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
reason
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
taskArn

instance Prelude.NFData AttemptContainerDetail where
  rnf :: AttemptContainerDetail -> ()
rnf AttemptContainerDetail' {Maybe Int
Maybe [NetworkInterface]
Maybe Text
taskArn :: Maybe Text
reason :: Maybe Text
networkInterfaces :: Maybe [NetworkInterface]
logStreamName :: Maybe Text
exitCode :: Maybe Int
containerInstanceArn :: Maybe Text
$sel:taskArn:AttemptContainerDetail' :: AttemptContainerDetail -> Maybe Text
$sel:reason:AttemptContainerDetail' :: AttemptContainerDetail -> Maybe Text
$sel:networkInterfaces:AttemptContainerDetail' :: AttemptContainerDetail -> Maybe [NetworkInterface]
$sel:logStreamName:AttemptContainerDetail' :: AttemptContainerDetail -> Maybe Text
$sel:exitCode:AttemptContainerDetail' :: AttemptContainerDetail -> Maybe Int
$sel:containerInstanceArn:AttemptContainerDetail' :: AttemptContainerDetail -> Maybe Text
..} =
    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 Int
exitCode
      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 [NetworkInterface]
networkInterfaces
      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 Text
taskArn