{-# 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.EMR.Types.StepSummary
-- 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.EMR.Types.StepSummary where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.EMR.Types.ActionOnFailure
import Amazonka.EMR.Types.HadoopStepConfig
import Amazonka.EMR.Types.StepStatus
import qualified Amazonka.Prelude as Prelude

-- | The summary of the cluster step.
--
-- /See:/ 'newStepSummary' smart constructor.
data StepSummary = StepSummary'
  { -- | The action to take when the cluster step fails. Possible values are
    -- TERMINATE_CLUSTER, CANCEL_AND_WAIT, and CONTINUE. TERMINATE_JOB_FLOW is
    -- available for backward compatibility.
    StepSummary -> Maybe ActionOnFailure
actionOnFailure :: Prelude.Maybe ActionOnFailure,
    -- | The Hadoop job configuration of the cluster step.
    StepSummary -> Maybe HadoopStepConfig
config :: Prelude.Maybe HadoopStepConfig,
    -- | The identifier of the cluster step.
    StepSummary -> Maybe Text
id :: Prelude.Maybe Prelude.Text,
    -- | The name of the cluster step.
    StepSummary -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | The current execution status details of the cluster step.
    StepSummary -> Maybe StepStatus
status :: Prelude.Maybe StepStatus
  }
  deriving (StepSummary -> StepSummary -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StepSummary -> StepSummary -> Bool
$c/= :: StepSummary -> StepSummary -> Bool
== :: StepSummary -> StepSummary -> Bool
$c== :: StepSummary -> StepSummary -> Bool
Prelude.Eq, ReadPrec [StepSummary]
ReadPrec StepSummary
Int -> ReadS StepSummary
ReadS [StepSummary]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StepSummary]
$creadListPrec :: ReadPrec [StepSummary]
readPrec :: ReadPrec StepSummary
$creadPrec :: ReadPrec StepSummary
readList :: ReadS [StepSummary]
$creadList :: ReadS [StepSummary]
readsPrec :: Int -> ReadS StepSummary
$creadsPrec :: Int -> ReadS StepSummary
Prelude.Read, Int -> StepSummary -> ShowS
[StepSummary] -> ShowS
StepSummary -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StepSummary] -> ShowS
$cshowList :: [StepSummary] -> ShowS
show :: StepSummary -> String
$cshow :: StepSummary -> String
showsPrec :: Int -> StepSummary -> ShowS
$cshowsPrec :: Int -> StepSummary -> ShowS
Prelude.Show, forall x. Rep StepSummary x -> StepSummary
forall x. StepSummary -> Rep StepSummary x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StepSummary x -> StepSummary
$cfrom :: forall x. StepSummary -> Rep StepSummary x
Prelude.Generic)

-- |
-- Create a value of 'StepSummary' 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:
--
-- 'actionOnFailure', 'stepSummary_actionOnFailure' - The action to take when the cluster step fails. Possible values are
-- TERMINATE_CLUSTER, CANCEL_AND_WAIT, and CONTINUE. TERMINATE_JOB_FLOW is
-- available for backward compatibility.
--
-- 'config', 'stepSummary_config' - The Hadoop job configuration of the cluster step.
--
-- 'id', 'stepSummary_id' - The identifier of the cluster step.
--
-- 'name', 'stepSummary_name' - The name of the cluster step.
--
-- 'status', 'stepSummary_status' - The current execution status details of the cluster step.
newStepSummary ::
  StepSummary
newStepSummary :: StepSummary
newStepSummary =
  StepSummary'
    { $sel:actionOnFailure:StepSummary' :: Maybe ActionOnFailure
actionOnFailure = forall a. Maybe a
Prelude.Nothing,
      $sel:config:StepSummary' :: Maybe HadoopStepConfig
config = forall a. Maybe a
Prelude.Nothing,
      $sel:id:StepSummary' :: Maybe Text
id = forall a. Maybe a
Prelude.Nothing,
      $sel:name:StepSummary' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:status:StepSummary' :: Maybe StepStatus
status = forall a. Maybe a
Prelude.Nothing
    }

-- | The action to take when the cluster step fails. Possible values are
-- TERMINATE_CLUSTER, CANCEL_AND_WAIT, and CONTINUE. TERMINATE_JOB_FLOW is
-- available for backward compatibility.
stepSummary_actionOnFailure :: Lens.Lens' StepSummary (Prelude.Maybe ActionOnFailure)
stepSummary_actionOnFailure :: Lens' StepSummary (Maybe ActionOnFailure)
stepSummary_actionOnFailure = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StepSummary' {Maybe ActionOnFailure
actionOnFailure :: Maybe ActionOnFailure
$sel:actionOnFailure:StepSummary' :: StepSummary -> Maybe ActionOnFailure
actionOnFailure} -> Maybe ActionOnFailure
actionOnFailure) (\s :: StepSummary
s@StepSummary' {} Maybe ActionOnFailure
a -> StepSummary
s {$sel:actionOnFailure:StepSummary' :: Maybe ActionOnFailure
actionOnFailure = Maybe ActionOnFailure
a} :: StepSummary)

-- | The Hadoop job configuration of the cluster step.
stepSummary_config :: Lens.Lens' StepSummary (Prelude.Maybe HadoopStepConfig)
stepSummary_config :: Lens' StepSummary (Maybe HadoopStepConfig)
stepSummary_config = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StepSummary' {Maybe HadoopStepConfig
config :: Maybe HadoopStepConfig
$sel:config:StepSummary' :: StepSummary -> Maybe HadoopStepConfig
config} -> Maybe HadoopStepConfig
config) (\s :: StepSummary
s@StepSummary' {} Maybe HadoopStepConfig
a -> StepSummary
s {$sel:config:StepSummary' :: Maybe HadoopStepConfig
config = Maybe HadoopStepConfig
a} :: StepSummary)

-- | The identifier of the cluster step.
stepSummary_id :: Lens.Lens' StepSummary (Prelude.Maybe Prelude.Text)
stepSummary_id :: Lens' StepSummary (Maybe Text)
stepSummary_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StepSummary' {Maybe Text
id :: Maybe Text
$sel:id:StepSummary' :: StepSummary -> Maybe Text
id} -> Maybe Text
id) (\s :: StepSummary
s@StepSummary' {} Maybe Text
a -> StepSummary
s {$sel:id:StepSummary' :: Maybe Text
id = Maybe Text
a} :: StepSummary)

-- | The name of the cluster step.
stepSummary_name :: Lens.Lens' StepSummary (Prelude.Maybe Prelude.Text)
stepSummary_name :: Lens' StepSummary (Maybe Text)
stepSummary_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StepSummary' {Maybe Text
name :: Maybe Text
$sel:name:StepSummary' :: StepSummary -> Maybe Text
name} -> Maybe Text
name) (\s :: StepSummary
s@StepSummary' {} Maybe Text
a -> StepSummary
s {$sel:name:StepSummary' :: Maybe Text
name = Maybe Text
a} :: StepSummary)

-- | The current execution status details of the cluster step.
stepSummary_status :: Lens.Lens' StepSummary (Prelude.Maybe StepStatus)
stepSummary_status :: Lens' StepSummary (Maybe StepStatus)
stepSummary_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StepSummary' {Maybe StepStatus
status :: Maybe StepStatus
$sel:status:StepSummary' :: StepSummary -> Maybe StepStatus
status} -> Maybe StepStatus
status) (\s :: StepSummary
s@StepSummary' {} Maybe StepStatus
a -> StepSummary
s {$sel:status:StepSummary' :: Maybe StepStatus
status = Maybe StepStatus
a} :: StepSummary)

instance Data.FromJSON StepSummary where
  parseJSON :: Value -> Parser StepSummary
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"StepSummary"
      ( \Object
x ->
          Maybe ActionOnFailure
-> Maybe HadoopStepConfig
-> Maybe Text
-> Maybe Text
-> Maybe StepStatus
-> StepSummary
StepSummary'
            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
"ActionOnFailure")
            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
"Config")
            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
"Id")
            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
"Name")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"Status")
      )

instance Prelude.Hashable StepSummary where
  hashWithSalt :: Int -> StepSummary -> Int
hashWithSalt Int
_salt StepSummary' {Maybe Text
Maybe ActionOnFailure
Maybe HadoopStepConfig
Maybe StepStatus
status :: Maybe StepStatus
name :: Maybe Text
id :: Maybe Text
config :: Maybe HadoopStepConfig
actionOnFailure :: Maybe ActionOnFailure
$sel:status:StepSummary' :: StepSummary -> Maybe StepStatus
$sel:name:StepSummary' :: StepSummary -> Maybe Text
$sel:id:StepSummary' :: StepSummary -> Maybe Text
$sel:config:StepSummary' :: StepSummary -> Maybe HadoopStepConfig
$sel:actionOnFailure:StepSummary' :: StepSummary -> Maybe ActionOnFailure
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ActionOnFailure
actionOnFailure
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe HadoopStepConfig
config
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
id
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe StepStatus
status

instance Prelude.NFData StepSummary where
  rnf :: StepSummary -> ()
rnf StepSummary' {Maybe Text
Maybe ActionOnFailure
Maybe HadoopStepConfig
Maybe StepStatus
status :: Maybe StepStatus
name :: Maybe Text
id :: Maybe Text
config :: Maybe HadoopStepConfig
actionOnFailure :: Maybe ActionOnFailure
$sel:status:StepSummary' :: StepSummary -> Maybe StepStatus
$sel:name:StepSummary' :: StepSummary -> Maybe Text
$sel:id:StepSummary' :: StepSummary -> Maybe Text
$sel:config:StepSummary' :: StepSummary -> Maybe HadoopStepConfig
$sel:actionOnFailure:StepSummary' :: StepSummary -> Maybe ActionOnFailure
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe ActionOnFailure
actionOnFailure
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe HadoopStepConfig
config
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
id
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe StepStatus
status