{-# 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.DrS.Types.Job
-- 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.DrS.Types.Job where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.DrS.Types.InitiatedBy
import Amazonka.DrS.Types.JobStatus
import Amazonka.DrS.Types.JobType
import Amazonka.DrS.Types.ParticipatingServer
import qualified Amazonka.Prelude as Prelude

-- | A job is an asynchronous workflow.
--
-- /See:/ 'newJob' smart constructor.
data Job = Job'
  { -- | The ARN of a Job.
    Job -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
    -- | The date and time of when the Job was created.
    Job -> Maybe Text
creationDateTime :: Prelude.Maybe Prelude.Text,
    -- | The date and time of when the Job ended.
    Job -> Maybe Text
endDateTime :: Prelude.Maybe Prelude.Text,
    -- | A string representing who initiated the Job.
    Job -> Maybe InitiatedBy
initiatedBy :: Prelude.Maybe InitiatedBy,
    -- | A list of servers that the Job is acting upon.
    Job -> Maybe [ParticipatingServer]
participatingServers :: Prelude.Maybe [ParticipatingServer],
    -- | The status of the Job.
    Job -> Maybe JobStatus
status :: Prelude.Maybe JobStatus,
    -- | A list of tags associated with the Job.
    Job -> Maybe (Sensitive (HashMap Text Text))
tags :: Prelude.Maybe (Data.Sensitive (Prelude.HashMap Prelude.Text Prelude.Text)),
    -- | The type of the Job.
    Job -> Maybe JobType
type' :: Prelude.Maybe JobType,
    -- | The ID of the Job.
    Job -> Text
jobID :: Prelude.Text
  }
  deriving (Job -> Job -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Job -> Job -> Bool
$c/= :: Job -> Job -> Bool
== :: Job -> Job -> Bool
$c== :: Job -> Job -> Bool
Prelude.Eq, Int -> Job -> ShowS
[Job] -> ShowS
Job -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Job] -> ShowS
$cshowList :: [Job] -> ShowS
show :: Job -> String
$cshow :: Job -> String
showsPrec :: Int -> Job -> ShowS
$cshowsPrec :: Int -> Job -> ShowS
Prelude.Show, forall x. Rep Job x -> Job
forall x. Job -> Rep Job x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Job x -> Job
$cfrom :: forall x. Job -> Rep Job x
Prelude.Generic)

-- |
-- Create a value of 'Job' 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:
--
-- 'arn', 'job_arn' - The ARN of a Job.
--
-- 'creationDateTime', 'job_creationDateTime' - The date and time of when the Job was created.
--
-- 'endDateTime', 'job_endDateTime' - The date and time of when the Job ended.
--
-- 'initiatedBy', 'job_initiatedBy' - A string representing who initiated the Job.
--
-- 'participatingServers', 'job_participatingServers' - A list of servers that the Job is acting upon.
--
-- 'status', 'job_status' - The status of the Job.
--
-- 'tags', 'job_tags' - A list of tags associated with the Job.
--
-- 'type'', 'job_type' - The type of the Job.
--
-- 'jobID', 'job_jobID' - The ID of the Job.
newJob ::
  -- | 'jobID'
  Prelude.Text ->
  Job
newJob :: Text -> Job
newJob Text
pJobID_ =
  Job'
    { $sel:arn:Job' :: Maybe Text
arn = forall a. Maybe a
Prelude.Nothing,
      $sel:creationDateTime:Job' :: Maybe Text
creationDateTime = forall a. Maybe a
Prelude.Nothing,
      $sel:endDateTime:Job' :: Maybe Text
endDateTime = forall a. Maybe a
Prelude.Nothing,
      $sel:initiatedBy:Job' :: Maybe InitiatedBy
initiatedBy = forall a. Maybe a
Prelude.Nothing,
      $sel:participatingServers:Job' :: Maybe [ParticipatingServer]
participatingServers = forall a. Maybe a
Prelude.Nothing,
      $sel:status:Job' :: Maybe JobStatus
status = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:Job' :: Maybe (Sensitive (HashMap Text Text))
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:type':Job' :: Maybe JobType
type' = forall a. Maybe a
Prelude.Nothing,
      $sel:jobID:Job' :: Text
jobID = Text
pJobID_
    }

-- | The ARN of a Job.
job_arn :: Lens.Lens' Job (Prelude.Maybe Prelude.Text)
job_arn :: Lens' Job (Maybe Text)
job_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe Text
arn :: Maybe Text
$sel:arn:Job' :: Job -> Maybe Text
arn} -> Maybe Text
arn) (\s :: Job
s@Job' {} Maybe Text
a -> Job
s {$sel:arn:Job' :: Maybe Text
arn = Maybe Text
a} :: Job)

-- | The date and time of when the Job was created.
job_creationDateTime :: Lens.Lens' Job (Prelude.Maybe Prelude.Text)
job_creationDateTime :: Lens' Job (Maybe Text)
job_creationDateTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe Text
creationDateTime :: Maybe Text
$sel:creationDateTime:Job' :: Job -> Maybe Text
creationDateTime} -> Maybe Text
creationDateTime) (\s :: Job
s@Job' {} Maybe Text
a -> Job
s {$sel:creationDateTime:Job' :: Maybe Text
creationDateTime = Maybe Text
a} :: Job)

-- | The date and time of when the Job ended.
job_endDateTime :: Lens.Lens' Job (Prelude.Maybe Prelude.Text)
job_endDateTime :: Lens' Job (Maybe Text)
job_endDateTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe Text
endDateTime :: Maybe Text
$sel:endDateTime:Job' :: Job -> Maybe Text
endDateTime} -> Maybe Text
endDateTime) (\s :: Job
s@Job' {} Maybe Text
a -> Job
s {$sel:endDateTime:Job' :: Maybe Text
endDateTime = Maybe Text
a} :: Job)

-- | A string representing who initiated the Job.
job_initiatedBy :: Lens.Lens' Job (Prelude.Maybe InitiatedBy)
job_initiatedBy :: Lens' Job (Maybe InitiatedBy)
job_initiatedBy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe InitiatedBy
initiatedBy :: Maybe InitiatedBy
$sel:initiatedBy:Job' :: Job -> Maybe InitiatedBy
initiatedBy} -> Maybe InitiatedBy
initiatedBy) (\s :: Job
s@Job' {} Maybe InitiatedBy
a -> Job
s {$sel:initiatedBy:Job' :: Maybe InitiatedBy
initiatedBy = Maybe InitiatedBy
a} :: Job)

-- | A list of servers that the Job is acting upon.
job_participatingServers :: Lens.Lens' Job (Prelude.Maybe [ParticipatingServer])
job_participatingServers :: Lens' Job (Maybe [ParticipatingServer])
job_participatingServers = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe [ParticipatingServer]
participatingServers :: Maybe [ParticipatingServer]
$sel:participatingServers:Job' :: Job -> Maybe [ParticipatingServer]
participatingServers} -> Maybe [ParticipatingServer]
participatingServers) (\s :: Job
s@Job' {} Maybe [ParticipatingServer]
a -> Job
s {$sel:participatingServers:Job' :: Maybe [ParticipatingServer]
participatingServers = Maybe [ParticipatingServer]
a} :: Job) 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 status of the Job.
job_status :: Lens.Lens' Job (Prelude.Maybe JobStatus)
job_status :: Lens' Job (Maybe JobStatus)
job_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe JobStatus
status :: Maybe JobStatus
$sel:status:Job' :: Job -> Maybe JobStatus
status} -> Maybe JobStatus
status) (\s :: Job
s@Job' {} Maybe JobStatus
a -> Job
s {$sel:status:Job' :: Maybe JobStatus
status = Maybe JobStatus
a} :: Job)

-- | A list of tags associated with the Job.
job_tags :: Lens.Lens' Job (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
job_tags :: Lens' Job (Maybe (HashMap Text Text))
job_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe (Sensitive (HashMap Text Text))
tags :: Maybe (Sensitive (HashMap Text Text))
$sel:tags:Job' :: Job -> Maybe (Sensitive (HashMap Text Text))
tags} -> Maybe (Sensitive (HashMap Text Text))
tags) (\s :: Job
s@Job' {} Maybe (Sensitive (HashMap Text Text))
a -> Job
s {$sel:tags:Job' :: Maybe (Sensitive (HashMap Text Text))
tags = Maybe (Sensitive (HashMap Text Text))
a} :: Job) 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 a. Iso' (Sensitive a) a
Data._Sensitive forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced)

-- | The type of the Job.
job_type :: Lens.Lens' Job (Prelude.Maybe JobType)
job_type :: Lens' Job (Maybe JobType)
job_type = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe JobType
type' :: Maybe JobType
$sel:type':Job' :: Job -> Maybe JobType
type'} -> Maybe JobType
type') (\s :: Job
s@Job' {} Maybe JobType
a -> Job
s {$sel:type':Job' :: Maybe JobType
type' = Maybe JobType
a} :: Job)

-- | The ID of the Job.
job_jobID :: Lens.Lens' Job Prelude.Text
job_jobID :: Lens' Job Text
job_jobID = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Text
jobID :: Text
$sel:jobID:Job' :: Job -> Text
jobID} -> Text
jobID) (\s :: Job
s@Job' {} Text
a -> Job
s {$sel:jobID:Job' :: Text
jobID = Text
a} :: Job)

instance Data.FromJSON Job where
  parseJSON :: Value -> Parser Job
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"Job"
      ( \Object
x ->
          Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe InitiatedBy
-> Maybe [ParticipatingServer]
-> Maybe JobStatus
-> Maybe (Sensitive (HashMap Text Text))
-> Maybe JobType
-> Text
-> Job
Job'
            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
"arn")
            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
"creationDateTime")
            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
"endDateTime")
            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
"initiatedBy")
            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
"participatingServers"
                            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
"status")
            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
"tags" 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
"type")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"jobID")
      )

instance Prelude.Hashable Job where
  hashWithSalt :: Int -> Job -> Int
hashWithSalt Int
_salt Job' {Maybe [ParticipatingServer]
Maybe Text
Maybe (Sensitive (HashMap Text Text))
Maybe InitiatedBy
Maybe JobStatus
Maybe JobType
Text
jobID :: Text
type' :: Maybe JobType
tags :: Maybe (Sensitive (HashMap Text Text))
status :: Maybe JobStatus
participatingServers :: Maybe [ParticipatingServer]
initiatedBy :: Maybe InitiatedBy
endDateTime :: Maybe Text
creationDateTime :: Maybe Text
arn :: Maybe Text
$sel:jobID:Job' :: Job -> Text
$sel:type':Job' :: Job -> Maybe JobType
$sel:tags:Job' :: Job -> Maybe (Sensitive (HashMap Text Text))
$sel:status:Job' :: Job -> Maybe JobStatus
$sel:participatingServers:Job' :: Job -> Maybe [ParticipatingServer]
$sel:initiatedBy:Job' :: Job -> Maybe InitiatedBy
$sel:endDateTime:Job' :: Job -> Maybe Text
$sel:creationDateTime:Job' :: Job -> Maybe Text
$sel:arn:Job' :: Job -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
arn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
creationDateTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
endDateTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe InitiatedBy
initiatedBy
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [ParticipatingServer]
participatingServers
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe JobStatus
status
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (Sensitive (HashMap Text Text))
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe JobType
type'
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
jobID

instance Prelude.NFData Job where
  rnf :: Job -> ()
rnf Job' {Maybe [ParticipatingServer]
Maybe Text
Maybe (Sensitive (HashMap Text Text))
Maybe InitiatedBy
Maybe JobStatus
Maybe JobType
Text
jobID :: Text
type' :: Maybe JobType
tags :: Maybe (Sensitive (HashMap Text Text))
status :: Maybe JobStatus
participatingServers :: Maybe [ParticipatingServer]
initiatedBy :: Maybe InitiatedBy
endDateTime :: Maybe Text
creationDateTime :: Maybe Text
arn :: Maybe Text
$sel:jobID:Job' :: Job -> Text
$sel:type':Job' :: Job -> Maybe JobType
$sel:tags:Job' :: Job -> Maybe (Sensitive (HashMap Text Text))
$sel:status:Job' :: Job -> Maybe JobStatus
$sel:participatingServers:Job' :: Job -> Maybe [ParticipatingServer]
$sel:initiatedBy:Job' :: Job -> Maybe InitiatedBy
$sel:endDateTime:Job' :: Job -> Maybe Text
$sel:creationDateTime:Job' :: Job -> Maybe Text
$sel:arn:Job' :: Job -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
arn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
creationDateTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
endDateTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe InitiatedBy
initiatedBy
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [ParticipatingServer]
participatingServers
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe JobStatus
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (Sensitive (HashMap Text Text))
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe JobType
type'
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
jobID