{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.ElasticTranscoder.CreateJob
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- When you create a job, Elastic Transcoder returns JSON data that
-- includes the values that you specified plus information about the job
-- that is created.
--
-- If you have specified more than one output for your jobs (for example,
-- one output for the Kindle Fire and another output for the Apple iPhone
-- 4s), you currently must use the Elastic Transcoder API to list the jobs
-- (as opposed to the AWS Console).
module Amazonka.ElasticTranscoder.CreateJob
  ( -- * Creating a Request
    CreateJob (..),
    newCreateJob,

    -- * Request Lenses
    createJob_input,
    createJob_inputs,
    createJob_output,
    createJob_outputKeyPrefix,
    createJob_outputs,
    createJob_playlists,
    createJob_userMetadata,
    createJob_pipelineId,

    -- * Destructuring the Response
    CreateJobResponse (..),
    newCreateJobResponse,

    -- * Response Lenses
    createJobResponse_job,
    createJobResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.ElasticTranscoder.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | The @CreateJobRequest@ structure.
--
-- /See:/ 'newCreateJob' smart constructor.
data CreateJob = CreateJob'
  { -- | A section of the request body that provides information about the file
    -- that is being transcoded.
    CreateJob -> Maybe JobInput
input :: Prelude.Maybe JobInput,
    -- | A section of the request body that provides information about the files
    -- that are being transcoded.
    CreateJob -> Maybe [JobInput]
inputs :: Prelude.Maybe [JobInput],
    -- | A section of the request body that provides information about the
    -- transcoded (target) file. We strongly recommend that you use the
    -- @Outputs@ syntax instead of the @Output@ syntax.
    CreateJob -> Maybe CreateJobOutput
output :: Prelude.Maybe CreateJobOutput,
    -- | The value, if any, that you want Elastic Transcoder to prepend to the
    -- names of all files that this job creates, including output files,
    -- thumbnails, and playlists.
    CreateJob -> Maybe Text
outputKeyPrefix :: Prelude.Maybe Prelude.Text,
    -- | A section of the request body that provides information about the
    -- transcoded (target) files. We recommend that you use the @Outputs@
    -- syntax instead of the @Output@ syntax.
    CreateJob -> Maybe [CreateJobOutput]
outputs :: Prelude.Maybe [CreateJobOutput],
    -- | If you specify a preset in @PresetId@ for which the value of @Container@
    -- is fmp4 (Fragmented MP4) or ts (MPEG-TS), Playlists contains information
    -- about the master playlists that you want Elastic Transcoder to create.
    --
    -- The maximum number of master playlists in a job is 30.
    CreateJob -> Maybe [CreateJobPlaylist]
playlists :: Prelude.Maybe [CreateJobPlaylist],
    -- | User-defined metadata that you want to associate with an Elastic
    -- Transcoder job. You specify metadata in @key\/value@ pairs, and you can
    -- add up to 10 @key\/value@ pairs per job. Elastic Transcoder does not
    -- guarantee that @key\/value@ pairs are returned in the same order in
    -- which you specify them.
    CreateJob -> Maybe (HashMap Text Text)
userMetadata :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The @Id@ of the pipeline that you want Elastic Transcoder to use for
    -- transcoding. The pipeline determines several settings, including the
    -- Amazon S3 bucket from which Elastic Transcoder gets the files to
    -- transcode and the bucket into which Elastic Transcoder puts the
    -- transcoded files.
    CreateJob -> Text
pipelineId :: Prelude.Text
  }
  deriving (CreateJob -> CreateJob -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateJob -> CreateJob -> Bool
$c/= :: CreateJob -> CreateJob -> Bool
== :: CreateJob -> CreateJob -> Bool
$c== :: CreateJob -> CreateJob -> Bool
Prelude.Eq, ReadPrec [CreateJob]
ReadPrec CreateJob
Int -> ReadS CreateJob
ReadS [CreateJob]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateJob]
$creadListPrec :: ReadPrec [CreateJob]
readPrec :: ReadPrec CreateJob
$creadPrec :: ReadPrec CreateJob
readList :: ReadS [CreateJob]
$creadList :: ReadS [CreateJob]
readsPrec :: Int -> ReadS CreateJob
$creadsPrec :: Int -> ReadS CreateJob
Prelude.Read, Int -> CreateJob -> ShowS
[CreateJob] -> ShowS
CreateJob -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateJob] -> ShowS
$cshowList :: [CreateJob] -> ShowS
show :: CreateJob -> String
$cshow :: CreateJob -> String
showsPrec :: Int -> CreateJob -> ShowS
$cshowsPrec :: Int -> CreateJob -> ShowS
Prelude.Show, forall x. Rep CreateJob x -> CreateJob
forall x. CreateJob -> Rep CreateJob x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateJob x -> CreateJob
$cfrom :: forall x. CreateJob -> Rep CreateJob x
Prelude.Generic)

-- |
-- Create a value of 'CreateJob' 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:
--
-- 'input', 'createJob_input' - A section of the request body that provides information about the file
-- that is being transcoded.
--
-- 'inputs', 'createJob_inputs' - A section of the request body that provides information about the files
-- that are being transcoded.
--
-- 'output', 'createJob_output' - A section of the request body that provides information about the
-- transcoded (target) file. We strongly recommend that you use the
-- @Outputs@ syntax instead of the @Output@ syntax.
--
-- 'outputKeyPrefix', 'createJob_outputKeyPrefix' - The value, if any, that you want Elastic Transcoder to prepend to the
-- names of all files that this job creates, including output files,
-- thumbnails, and playlists.
--
-- 'outputs', 'createJob_outputs' - A section of the request body that provides information about the
-- transcoded (target) files. We recommend that you use the @Outputs@
-- syntax instead of the @Output@ syntax.
--
-- 'playlists', 'createJob_playlists' - If you specify a preset in @PresetId@ for which the value of @Container@
-- is fmp4 (Fragmented MP4) or ts (MPEG-TS), Playlists contains information
-- about the master playlists that you want Elastic Transcoder to create.
--
-- The maximum number of master playlists in a job is 30.
--
-- 'userMetadata', 'createJob_userMetadata' - User-defined metadata that you want to associate with an Elastic
-- Transcoder job. You specify metadata in @key\/value@ pairs, and you can
-- add up to 10 @key\/value@ pairs per job. Elastic Transcoder does not
-- guarantee that @key\/value@ pairs are returned in the same order in
-- which you specify them.
--
-- 'pipelineId', 'createJob_pipelineId' - The @Id@ of the pipeline that you want Elastic Transcoder to use for
-- transcoding. The pipeline determines several settings, including the
-- Amazon S3 bucket from which Elastic Transcoder gets the files to
-- transcode and the bucket into which Elastic Transcoder puts the
-- transcoded files.
newCreateJob ::
  -- | 'pipelineId'
  Prelude.Text ->
  CreateJob
newCreateJob :: Text -> CreateJob
newCreateJob Text
pPipelineId_ =
  CreateJob'
    { $sel:input:CreateJob' :: Maybe JobInput
input = forall a. Maybe a
Prelude.Nothing,
      $sel:inputs:CreateJob' :: Maybe [JobInput]
inputs = forall a. Maybe a
Prelude.Nothing,
      $sel:output:CreateJob' :: Maybe CreateJobOutput
output = forall a. Maybe a
Prelude.Nothing,
      $sel:outputKeyPrefix:CreateJob' :: Maybe Text
outputKeyPrefix = forall a. Maybe a
Prelude.Nothing,
      $sel:outputs:CreateJob' :: Maybe [CreateJobOutput]
outputs = forall a. Maybe a
Prelude.Nothing,
      $sel:playlists:CreateJob' :: Maybe [CreateJobPlaylist]
playlists = forall a. Maybe a
Prelude.Nothing,
      $sel:userMetadata:CreateJob' :: Maybe (HashMap Text Text)
userMetadata = forall a. Maybe a
Prelude.Nothing,
      $sel:pipelineId:CreateJob' :: Text
pipelineId = Text
pPipelineId_
    }

-- | A section of the request body that provides information about the file
-- that is being transcoded.
createJob_input :: Lens.Lens' CreateJob (Prelude.Maybe JobInput)
createJob_input :: Lens' CreateJob (Maybe JobInput)
createJob_input = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateJob' {Maybe JobInput
input :: Maybe JobInput
$sel:input:CreateJob' :: CreateJob -> Maybe JobInput
input} -> Maybe JobInput
input) (\s :: CreateJob
s@CreateJob' {} Maybe JobInput
a -> CreateJob
s {$sel:input:CreateJob' :: Maybe JobInput
input = Maybe JobInput
a} :: CreateJob)

-- | A section of the request body that provides information about the files
-- that are being transcoded.
createJob_inputs :: Lens.Lens' CreateJob (Prelude.Maybe [JobInput])
createJob_inputs :: Lens' CreateJob (Maybe [JobInput])
createJob_inputs = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateJob' {Maybe [JobInput]
inputs :: Maybe [JobInput]
$sel:inputs:CreateJob' :: CreateJob -> Maybe [JobInput]
inputs} -> Maybe [JobInput]
inputs) (\s :: CreateJob
s@CreateJob' {} Maybe [JobInput]
a -> CreateJob
s {$sel:inputs:CreateJob' :: Maybe [JobInput]
inputs = Maybe [JobInput]
a} :: CreateJob) 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 section of the request body that provides information about the
-- transcoded (target) file. We strongly recommend that you use the
-- @Outputs@ syntax instead of the @Output@ syntax.
createJob_output :: Lens.Lens' CreateJob (Prelude.Maybe CreateJobOutput)
createJob_output :: Lens' CreateJob (Maybe CreateJobOutput)
createJob_output = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateJob' {Maybe CreateJobOutput
output :: Maybe CreateJobOutput
$sel:output:CreateJob' :: CreateJob -> Maybe CreateJobOutput
output} -> Maybe CreateJobOutput
output) (\s :: CreateJob
s@CreateJob' {} Maybe CreateJobOutput
a -> CreateJob
s {$sel:output:CreateJob' :: Maybe CreateJobOutput
output = Maybe CreateJobOutput
a} :: CreateJob)

-- | The value, if any, that you want Elastic Transcoder to prepend to the
-- names of all files that this job creates, including output files,
-- thumbnails, and playlists.
createJob_outputKeyPrefix :: Lens.Lens' CreateJob (Prelude.Maybe Prelude.Text)
createJob_outputKeyPrefix :: Lens' CreateJob (Maybe Text)
createJob_outputKeyPrefix = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateJob' {Maybe Text
outputKeyPrefix :: Maybe Text
$sel:outputKeyPrefix:CreateJob' :: CreateJob -> Maybe Text
outputKeyPrefix} -> Maybe Text
outputKeyPrefix) (\s :: CreateJob
s@CreateJob' {} Maybe Text
a -> CreateJob
s {$sel:outputKeyPrefix:CreateJob' :: Maybe Text
outputKeyPrefix = Maybe Text
a} :: CreateJob)

-- | A section of the request body that provides information about the
-- transcoded (target) files. We recommend that you use the @Outputs@
-- syntax instead of the @Output@ syntax.
createJob_outputs :: Lens.Lens' CreateJob (Prelude.Maybe [CreateJobOutput])
createJob_outputs :: Lens' CreateJob (Maybe [CreateJobOutput])
createJob_outputs = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateJob' {Maybe [CreateJobOutput]
outputs :: Maybe [CreateJobOutput]
$sel:outputs:CreateJob' :: CreateJob -> Maybe [CreateJobOutput]
outputs} -> Maybe [CreateJobOutput]
outputs) (\s :: CreateJob
s@CreateJob' {} Maybe [CreateJobOutput]
a -> CreateJob
s {$sel:outputs:CreateJob' :: Maybe [CreateJobOutput]
outputs = Maybe [CreateJobOutput]
a} :: CreateJob) 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

-- | If you specify a preset in @PresetId@ for which the value of @Container@
-- is fmp4 (Fragmented MP4) or ts (MPEG-TS), Playlists contains information
-- about the master playlists that you want Elastic Transcoder to create.
--
-- The maximum number of master playlists in a job is 30.
createJob_playlists :: Lens.Lens' CreateJob (Prelude.Maybe [CreateJobPlaylist])
createJob_playlists :: Lens' CreateJob (Maybe [CreateJobPlaylist])
createJob_playlists = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateJob' {Maybe [CreateJobPlaylist]
playlists :: Maybe [CreateJobPlaylist]
$sel:playlists:CreateJob' :: CreateJob -> Maybe [CreateJobPlaylist]
playlists} -> Maybe [CreateJobPlaylist]
playlists) (\s :: CreateJob
s@CreateJob' {} Maybe [CreateJobPlaylist]
a -> CreateJob
s {$sel:playlists:CreateJob' :: Maybe [CreateJobPlaylist]
playlists = Maybe [CreateJobPlaylist]
a} :: CreateJob) 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

-- | User-defined metadata that you want to associate with an Elastic
-- Transcoder job. You specify metadata in @key\/value@ pairs, and you can
-- add up to 10 @key\/value@ pairs per job. Elastic Transcoder does not
-- guarantee that @key\/value@ pairs are returned in the same order in
-- which you specify them.
createJob_userMetadata :: Lens.Lens' CreateJob (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
createJob_userMetadata :: Lens' CreateJob (Maybe (HashMap Text Text))
createJob_userMetadata = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateJob' {Maybe (HashMap Text Text)
userMetadata :: Maybe (HashMap Text Text)
$sel:userMetadata:CreateJob' :: CreateJob -> Maybe (HashMap Text Text)
userMetadata} -> Maybe (HashMap Text Text)
userMetadata) (\s :: CreateJob
s@CreateJob' {} Maybe (HashMap Text Text)
a -> CreateJob
s {$sel:userMetadata:CreateJob' :: Maybe (HashMap Text Text)
userMetadata = Maybe (HashMap Text Text)
a} :: CreateJob) 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 @Id@ of the pipeline that you want Elastic Transcoder to use for
-- transcoding. The pipeline determines several settings, including the
-- Amazon S3 bucket from which Elastic Transcoder gets the files to
-- transcode and the bucket into which Elastic Transcoder puts the
-- transcoded files.
createJob_pipelineId :: Lens.Lens' CreateJob Prelude.Text
createJob_pipelineId :: Lens' CreateJob Text
createJob_pipelineId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateJob' {Text
pipelineId :: Text
$sel:pipelineId:CreateJob' :: CreateJob -> Text
pipelineId} -> Text
pipelineId) (\s :: CreateJob
s@CreateJob' {} Text
a -> CreateJob
s {$sel:pipelineId:CreateJob' :: Text
pipelineId = Text
a} :: CreateJob)

instance Core.AWSRequest CreateJob where
  type AWSResponse CreateJob = CreateJobResponse
  request :: (Service -> Service) -> CreateJob -> Request CreateJob
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy CreateJob
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse CreateJob)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe Job -> Int -> CreateJobResponse
CreateJobResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"Job")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable CreateJob where
  hashWithSalt :: Int -> CreateJob -> Int
hashWithSalt Int
_salt CreateJob' {Maybe [CreateJobPlaylist]
Maybe [JobInput]
Maybe [CreateJobOutput]
Maybe Text
Maybe (HashMap Text Text)
Maybe JobInput
Maybe CreateJobOutput
Text
pipelineId :: Text
userMetadata :: Maybe (HashMap Text Text)
playlists :: Maybe [CreateJobPlaylist]
outputs :: Maybe [CreateJobOutput]
outputKeyPrefix :: Maybe Text
output :: Maybe CreateJobOutput
inputs :: Maybe [JobInput]
input :: Maybe JobInput
$sel:pipelineId:CreateJob' :: CreateJob -> Text
$sel:userMetadata:CreateJob' :: CreateJob -> Maybe (HashMap Text Text)
$sel:playlists:CreateJob' :: CreateJob -> Maybe [CreateJobPlaylist]
$sel:outputs:CreateJob' :: CreateJob -> Maybe [CreateJobOutput]
$sel:outputKeyPrefix:CreateJob' :: CreateJob -> Maybe Text
$sel:output:CreateJob' :: CreateJob -> Maybe CreateJobOutput
$sel:inputs:CreateJob' :: CreateJob -> Maybe [JobInput]
$sel:input:CreateJob' :: CreateJob -> Maybe JobInput
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe JobInput
input
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [JobInput]
inputs
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe CreateJobOutput
output
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
outputKeyPrefix
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [CreateJobOutput]
outputs
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [CreateJobPlaylist]
playlists
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
userMetadata
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
pipelineId

instance Prelude.NFData CreateJob where
  rnf :: CreateJob -> ()
rnf CreateJob' {Maybe [CreateJobPlaylist]
Maybe [JobInput]
Maybe [CreateJobOutput]
Maybe Text
Maybe (HashMap Text Text)
Maybe JobInput
Maybe CreateJobOutput
Text
pipelineId :: Text
userMetadata :: Maybe (HashMap Text Text)
playlists :: Maybe [CreateJobPlaylist]
outputs :: Maybe [CreateJobOutput]
outputKeyPrefix :: Maybe Text
output :: Maybe CreateJobOutput
inputs :: Maybe [JobInput]
input :: Maybe JobInput
$sel:pipelineId:CreateJob' :: CreateJob -> Text
$sel:userMetadata:CreateJob' :: CreateJob -> Maybe (HashMap Text Text)
$sel:playlists:CreateJob' :: CreateJob -> Maybe [CreateJobPlaylist]
$sel:outputs:CreateJob' :: CreateJob -> Maybe [CreateJobOutput]
$sel:outputKeyPrefix:CreateJob' :: CreateJob -> Maybe Text
$sel:output:CreateJob' :: CreateJob -> Maybe CreateJobOutput
$sel:inputs:CreateJob' :: CreateJob -> Maybe [JobInput]
$sel:input:CreateJob' :: CreateJob -> Maybe JobInput
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe JobInput
input
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [JobInput]
inputs
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe CreateJobOutput
output
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
outputKeyPrefix
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [CreateJobOutput]
outputs
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [CreateJobPlaylist]
playlists
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
userMetadata
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
pipelineId

instance Data.ToHeaders CreateJob where
  toHeaders :: CreateJob -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

instance Data.ToJSON CreateJob where
  toJSON :: CreateJob -> Value
toJSON CreateJob' {Maybe [CreateJobPlaylist]
Maybe [JobInput]
Maybe [CreateJobOutput]
Maybe Text
Maybe (HashMap Text Text)
Maybe JobInput
Maybe CreateJobOutput
Text
pipelineId :: Text
userMetadata :: Maybe (HashMap Text Text)
playlists :: Maybe [CreateJobPlaylist]
outputs :: Maybe [CreateJobOutput]
outputKeyPrefix :: Maybe Text
output :: Maybe CreateJobOutput
inputs :: Maybe [JobInput]
input :: Maybe JobInput
$sel:pipelineId:CreateJob' :: CreateJob -> Text
$sel:userMetadata:CreateJob' :: CreateJob -> Maybe (HashMap Text Text)
$sel:playlists:CreateJob' :: CreateJob -> Maybe [CreateJobPlaylist]
$sel:outputs:CreateJob' :: CreateJob -> Maybe [CreateJobOutput]
$sel:outputKeyPrefix:CreateJob' :: CreateJob -> Maybe Text
$sel:output:CreateJob' :: CreateJob -> Maybe CreateJobOutput
$sel:inputs:CreateJob' :: CreateJob -> Maybe [JobInput]
$sel:input:CreateJob' :: CreateJob -> Maybe JobInput
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Input" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe JobInput
input,
            (Key
"Inputs" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [JobInput]
inputs,
            (Key
"Output" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe CreateJobOutput
output,
            (Key
"OutputKeyPrefix" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
outputKeyPrefix,
            (Key
"Outputs" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [CreateJobOutput]
outputs,
            (Key
"Playlists" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [CreateJobPlaylist]
playlists,
            (Key
"UserMetadata" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (HashMap Text Text)
userMetadata,
            forall a. a -> Maybe a
Prelude.Just (Key
"PipelineId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
pipelineId)
          ]
      )

instance Data.ToPath CreateJob where
  toPath :: CreateJob -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/2012-09-25/jobs"

instance Data.ToQuery CreateJob where
  toQuery :: CreateJob -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | The CreateJobResponse structure.
--
-- /See:/ 'newCreateJobResponse' smart constructor.
data CreateJobResponse = CreateJobResponse'
  { -- | A section of the response body that provides information about the job
    -- that is created.
    CreateJobResponse -> Maybe Job
job :: Prelude.Maybe Job,
    -- | The response's http status code.
    CreateJobResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateJobResponse -> CreateJobResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateJobResponse -> CreateJobResponse -> Bool
$c/= :: CreateJobResponse -> CreateJobResponse -> Bool
== :: CreateJobResponse -> CreateJobResponse -> Bool
$c== :: CreateJobResponse -> CreateJobResponse -> Bool
Prelude.Eq, ReadPrec [CreateJobResponse]
ReadPrec CreateJobResponse
Int -> ReadS CreateJobResponse
ReadS [CreateJobResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateJobResponse]
$creadListPrec :: ReadPrec [CreateJobResponse]
readPrec :: ReadPrec CreateJobResponse
$creadPrec :: ReadPrec CreateJobResponse
readList :: ReadS [CreateJobResponse]
$creadList :: ReadS [CreateJobResponse]
readsPrec :: Int -> ReadS CreateJobResponse
$creadsPrec :: Int -> ReadS CreateJobResponse
Prelude.Read, Int -> CreateJobResponse -> ShowS
[CreateJobResponse] -> ShowS
CreateJobResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateJobResponse] -> ShowS
$cshowList :: [CreateJobResponse] -> ShowS
show :: CreateJobResponse -> String
$cshow :: CreateJobResponse -> String
showsPrec :: Int -> CreateJobResponse -> ShowS
$cshowsPrec :: Int -> CreateJobResponse -> ShowS
Prelude.Show, forall x. Rep CreateJobResponse x -> CreateJobResponse
forall x. CreateJobResponse -> Rep CreateJobResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateJobResponse x -> CreateJobResponse
$cfrom :: forall x. CreateJobResponse -> Rep CreateJobResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateJobResponse' 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:
--
-- 'job', 'createJobResponse_job' - A section of the response body that provides information about the job
-- that is created.
--
-- 'httpStatus', 'createJobResponse_httpStatus' - The response's http status code.
newCreateJobResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateJobResponse
newCreateJobResponse :: Int -> CreateJobResponse
newCreateJobResponse Int
pHttpStatus_ =
  CreateJobResponse'
    { $sel:job:CreateJobResponse' :: Maybe Job
job = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateJobResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A section of the response body that provides information about the job
-- that is created.
createJobResponse_job :: Lens.Lens' CreateJobResponse (Prelude.Maybe Job)
createJobResponse_job :: Lens' CreateJobResponse (Maybe Job)
createJobResponse_job = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateJobResponse' {Maybe Job
job :: Maybe Job
$sel:job:CreateJobResponse' :: CreateJobResponse -> Maybe Job
job} -> Maybe Job
job) (\s :: CreateJobResponse
s@CreateJobResponse' {} Maybe Job
a -> CreateJobResponse
s {$sel:job:CreateJobResponse' :: Maybe Job
job = Maybe Job
a} :: CreateJobResponse)

-- | The response's http status code.
createJobResponse_httpStatus :: Lens.Lens' CreateJobResponse Prelude.Int
createJobResponse_httpStatus :: Lens' CreateJobResponse Int
createJobResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateJobResponse' {Int
httpStatus :: Int
$sel:httpStatus:CreateJobResponse' :: CreateJobResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: CreateJobResponse
s@CreateJobResponse' {} Int
a -> CreateJobResponse
s {$sel:httpStatus:CreateJobResponse' :: Int
httpStatus = Int
a} :: CreateJobResponse)

instance Prelude.NFData CreateJobResponse where
  rnf :: CreateJobResponse -> ()
rnf CreateJobResponse' {Int
Maybe Job
httpStatus :: Int
job :: Maybe Job
$sel:httpStatus:CreateJobResponse' :: CreateJobResponse -> Int
$sel:job:CreateJobResponse' :: CreateJobResponse -> Maybe Job
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Job
job
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus