{-# 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.ElasticTranscoder.Types.Pipeline
-- 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.ElasticTranscoder.Types.Pipeline 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.Notifications
import Amazonka.ElasticTranscoder.Types.PipelineOutputConfig
import qualified Amazonka.Prelude as Prelude

-- | The pipeline (queue) that is used to manage jobs.
--
-- /See:/ 'newPipeline' smart constructor.
data Pipeline = Pipeline'
  { -- | The Amazon Resource Name (ARN) for the pipeline.
    Pipeline -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
    -- | The AWS Key Management Service (AWS KMS) key that you want to use with
    -- this pipeline.
    --
    -- If you use either @s3@ or @s3-aws-kms@ as your @Encryption:Mode@, you
    -- don\'t need to provide a key with your job because a default key, known
    -- as an AWS-KMS key, is created for you automatically. You need to provide
    -- an AWS-KMS key only if you want to use a non-default AWS-KMS key, or if
    -- you are using an @Encryption:Mode@ of @aes-cbc-pkcs7@, @aes-ctr@, or
    -- @aes-gcm@.
    Pipeline -> Maybe Text
awsKmsKeyArn :: Prelude.Maybe Prelude.Text,
    -- | Information about the Amazon S3 bucket in which you want Elastic
    -- Transcoder to save transcoded files and playlists. Either you specify
    -- both @ContentConfig@ and @ThumbnailConfig@, or you specify
    -- @OutputBucket@.
    --
    -- -   __Bucket__: The Amazon S3 bucket in which you want Elastic
    --     Transcoder to save transcoded files and playlists.
    --
    -- -   __Permissions__: A list of the users and\/or predefined Amazon S3
    --     groups you want to have access to transcoded files and playlists,
    --     and the type of access that you want them to have.
    --
    --     -   GranteeType: The type of value that appears in the @Grantee@
    --         object:
    --
    --         -   @Canonical@: Either the canonical user ID for an AWS account
    --             or an origin access identity for an Amazon CloudFront
    --             distribution.
    --
    --         -   @Email@: The registered email address of an AWS account.
    --
    --         -   @Group@: One of the following predefined Amazon S3 groups:
    --             @AllUsers@, @AuthenticatedUsers@, or @LogDelivery@.
    --
    --     -   @Grantee@: The AWS user or group that you want to have access to
    --         transcoded files and playlists.
    --
    --     -   @Access@: The permission that you want to give to the AWS user
    --         that is listed in @Grantee@. Valid values include:
    --
    --         -   @READ@: The grantee can read the objects and metadata for
    --             objects that Elastic Transcoder adds to the Amazon S3
    --             bucket.
    --
    --         -   @READ_ACP@: The grantee can read the object ACL for objects
    --             that Elastic Transcoder adds to the Amazon S3 bucket.
    --
    --         -   @WRITE_ACP@: The grantee can write the ACL for the objects
    --             that Elastic Transcoder adds to the Amazon S3 bucket.
    --
    --         -   @FULL_CONTROL@: The grantee has @READ@, @READ_ACP@, and
    --             @WRITE_ACP@ permissions for the objects that Elastic
    --             Transcoder adds to the Amazon S3 bucket.
    --
    -- -   __StorageClass__: The Amazon S3 storage class, Standard or
    --     ReducedRedundancy, that you want Elastic Transcoder to assign to the
    --     video files and playlists that it stores in your Amazon S3 bucket.
    Pipeline -> Maybe PipelineOutputConfig
contentConfig :: Prelude.Maybe PipelineOutputConfig,
    -- | The identifier for the pipeline. You use this value to identify the
    -- pipeline in which you want to perform a variety of operations, such as
    -- creating a job or a preset.
    Pipeline -> Maybe Text
id :: Prelude.Maybe Prelude.Text,
    -- | The Amazon S3 bucket from which Elastic Transcoder gets media files for
    -- transcoding and the graphics files, if any, that you want to use for
    -- watermarks.
    Pipeline -> Maybe Text
inputBucket :: Prelude.Maybe Prelude.Text,
    -- | The name of the pipeline. We recommend that the name be unique within
    -- the AWS account, but uniqueness is not enforced.
    --
    -- Constraints: Maximum 40 characters
    Pipeline -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Simple Notification Service (Amazon SNS) topic that you want
    -- to notify to report job status.
    --
    -- To receive notifications, you must also subscribe to the new topic in
    -- the Amazon SNS console.
    --
    -- -   __Progressing__ (optional): The Amazon Simple Notification Service
    --     (Amazon SNS) topic that you want to notify when Elastic Transcoder
    --     has started to process the job.
    --
    -- -   __Complete__ (optional): The Amazon SNS topic that you want to
    --     notify when Elastic Transcoder has finished processing the job.
    --
    -- -   __Warning__ (optional): The Amazon SNS topic that you want to notify
    --     when Elastic Transcoder encounters a warning condition.
    --
    -- -   __Error__ (optional): The Amazon SNS topic that you want to notify
    --     when Elastic Transcoder encounters an error condition.
    Pipeline -> Maybe Notifications
notifications :: Prelude.Maybe Notifications,
    -- | The Amazon S3 bucket in which you want Elastic Transcoder to save
    -- transcoded files, thumbnails, and playlists. Either you specify this
    -- value, or you specify both @ContentConfig@ and @ThumbnailConfig@.
    Pipeline -> Maybe Text
outputBucket :: Prelude.Maybe Prelude.Text,
    -- | The IAM Amazon Resource Name (ARN) for the role that Elastic Transcoder
    -- uses to transcode jobs for this pipeline.
    Pipeline -> Maybe Text
role' :: Prelude.Maybe Prelude.Text,
    -- | The current status of the pipeline:
    --
    -- -   @Active@: The pipeline is processing jobs.
    --
    -- -   @Paused@: The pipeline is not currently processing jobs.
    Pipeline -> Maybe Text
status :: Prelude.Maybe Prelude.Text,
    -- | Information about the Amazon S3 bucket in which you want Elastic
    -- Transcoder to save thumbnail files. Either you specify both
    -- @ContentConfig@ and @ThumbnailConfig@, or you specify @OutputBucket@.
    --
    -- -   @Bucket@: The Amazon S3 bucket in which you want Elastic Transcoder
    --     to save thumbnail files.
    --
    -- -   @Permissions@: A list of the users and\/or predefined Amazon S3
    --     groups you want to have access to thumbnail files, and the type of
    --     access that you want them to have.
    --
    --     -   GranteeType: The type of value that appears in the Grantee
    --         object:
    --
    --         -   @Canonical@: Either the canonical user ID for an AWS account
    --             or an origin access identity for an Amazon CloudFront
    --             distribution.
    --
    --             A canonical user ID is not the same as an AWS account
    --             number.
    --
    --         -   @Email@: The registered email address of an AWS account.
    --
    --         -   @Group@: One of the following predefined Amazon S3 groups:
    --             @AllUsers@, @AuthenticatedUsers@, or @LogDelivery@.
    --
    --     -   @Grantee@: The AWS user or group that you want to have access to
    --         thumbnail files.
    --
    --     -   Access: The permission that you want to give to the AWS user
    --         that is listed in Grantee. Valid values include:
    --
    --         -   @READ@: The grantee can read the thumbnails and metadata for
    --             thumbnails that Elastic Transcoder adds to the Amazon S3
    --             bucket.
    --
    --         -   @READ_ACP@: The grantee can read the object ACL for
    --             thumbnails that Elastic Transcoder adds to the Amazon S3
    --             bucket.
    --
    --         -   @WRITE_ACP@: The grantee can write the ACL for the
    --             thumbnails that Elastic Transcoder adds to the Amazon S3
    --             bucket.
    --
    --         -   @FULL_CONTROL@: The grantee has READ, READ_ACP, and
    --             WRITE_ACP permissions for the thumbnails that Elastic
    --             Transcoder adds to the Amazon S3 bucket.
    --
    -- -   @StorageClass@: The Amazon S3 storage class, @Standard@ or
    --     @ReducedRedundancy@, that you want Elastic Transcoder to assign to
    --     the thumbnails that it stores in your Amazon S3 bucket.
    Pipeline -> Maybe PipelineOutputConfig
thumbnailConfig :: Prelude.Maybe PipelineOutputConfig
  }
  deriving (Pipeline -> Pipeline -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Pipeline -> Pipeline -> Bool
$c/= :: Pipeline -> Pipeline -> Bool
== :: Pipeline -> Pipeline -> Bool
$c== :: Pipeline -> Pipeline -> Bool
Prelude.Eq, ReadPrec [Pipeline]
ReadPrec Pipeline
Int -> ReadS Pipeline
ReadS [Pipeline]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Pipeline]
$creadListPrec :: ReadPrec [Pipeline]
readPrec :: ReadPrec Pipeline
$creadPrec :: ReadPrec Pipeline
readList :: ReadS [Pipeline]
$creadList :: ReadS [Pipeline]
readsPrec :: Int -> ReadS Pipeline
$creadsPrec :: Int -> ReadS Pipeline
Prelude.Read, Int -> Pipeline -> ShowS
[Pipeline] -> ShowS
Pipeline -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Pipeline] -> ShowS
$cshowList :: [Pipeline] -> ShowS
show :: Pipeline -> String
$cshow :: Pipeline -> String
showsPrec :: Int -> Pipeline -> ShowS
$cshowsPrec :: Int -> Pipeline -> ShowS
Prelude.Show, forall x. Rep Pipeline x -> Pipeline
forall x. Pipeline -> Rep Pipeline x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Pipeline x -> Pipeline
$cfrom :: forall x. Pipeline -> Rep Pipeline x
Prelude.Generic)

-- |
-- Create a value of 'Pipeline' 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', 'pipeline_arn' - The Amazon Resource Name (ARN) for the pipeline.
--
-- 'awsKmsKeyArn', 'pipeline_awsKmsKeyArn' - The AWS Key Management Service (AWS KMS) key that you want to use with
-- this pipeline.
--
-- If you use either @s3@ or @s3-aws-kms@ as your @Encryption:Mode@, you
-- don\'t need to provide a key with your job because a default key, known
-- as an AWS-KMS key, is created for you automatically. You need to provide
-- an AWS-KMS key only if you want to use a non-default AWS-KMS key, or if
-- you are using an @Encryption:Mode@ of @aes-cbc-pkcs7@, @aes-ctr@, or
-- @aes-gcm@.
--
-- 'contentConfig', 'pipeline_contentConfig' - Information about the Amazon S3 bucket in which you want Elastic
-- Transcoder to save transcoded files and playlists. Either you specify
-- both @ContentConfig@ and @ThumbnailConfig@, or you specify
-- @OutputBucket@.
--
-- -   __Bucket__: The Amazon S3 bucket in which you want Elastic
--     Transcoder to save transcoded files and playlists.
--
-- -   __Permissions__: A list of the users and\/or predefined Amazon S3
--     groups you want to have access to transcoded files and playlists,
--     and the type of access that you want them to have.
--
--     -   GranteeType: The type of value that appears in the @Grantee@
--         object:
--
--         -   @Canonical@: Either the canonical user ID for an AWS account
--             or an origin access identity for an Amazon CloudFront
--             distribution.
--
--         -   @Email@: The registered email address of an AWS account.
--
--         -   @Group@: One of the following predefined Amazon S3 groups:
--             @AllUsers@, @AuthenticatedUsers@, or @LogDelivery@.
--
--     -   @Grantee@: The AWS user or group that you want to have access to
--         transcoded files and playlists.
--
--     -   @Access@: The permission that you want to give to the AWS user
--         that is listed in @Grantee@. Valid values include:
--
--         -   @READ@: The grantee can read the objects and metadata for
--             objects that Elastic Transcoder adds to the Amazon S3
--             bucket.
--
--         -   @READ_ACP@: The grantee can read the object ACL for objects
--             that Elastic Transcoder adds to the Amazon S3 bucket.
--
--         -   @WRITE_ACP@: The grantee can write the ACL for the objects
--             that Elastic Transcoder adds to the Amazon S3 bucket.
--
--         -   @FULL_CONTROL@: The grantee has @READ@, @READ_ACP@, and
--             @WRITE_ACP@ permissions for the objects that Elastic
--             Transcoder adds to the Amazon S3 bucket.
--
-- -   __StorageClass__: The Amazon S3 storage class, Standard or
--     ReducedRedundancy, that you want Elastic Transcoder to assign to the
--     video files and playlists that it stores in your Amazon S3 bucket.
--
-- 'id', 'pipeline_id' - The identifier for the pipeline. You use this value to identify the
-- pipeline in which you want to perform a variety of operations, such as
-- creating a job or a preset.
--
-- 'inputBucket', 'pipeline_inputBucket' - The Amazon S3 bucket from which Elastic Transcoder gets media files for
-- transcoding and the graphics files, if any, that you want to use for
-- watermarks.
--
-- 'name', 'pipeline_name' - The name of the pipeline. We recommend that the name be unique within
-- the AWS account, but uniqueness is not enforced.
--
-- Constraints: Maximum 40 characters
--
-- 'notifications', 'pipeline_notifications' - The Amazon Simple Notification Service (Amazon SNS) topic that you want
-- to notify to report job status.
--
-- To receive notifications, you must also subscribe to the new topic in
-- the Amazon SNS console.
--
-- -   __Progressing__ (optional): The Amazon Simple Notification Service
--     (Amazon SNS) topic that you want to notify when Elastic Transcoder
--     has started to process the job.
--
-- -   __Complete__ (optional): The Amazon SNS topic that you want to
--     notify when Elastic Transcoder has finished processing the job.
--
-- -   __Warning__ (optional): The Amazon SNS topic that you want to notify
--     when Elastic Transcoder encounters a warning condition.
--
-- -   __Error__ (optional): The Amazon SNS topic that you want to notify
--     when Elastic Transcoder encounters an error condition.
--
-- 'outputBucket', 'pipeline_outputBucket' - The Amazon S3 bucket in which you want Elastic Transcoder to save
-- transcoded files, thumbnails, and playlists. Either you specify this
-- value, or you specify both @ContentConfig@ and @ThumbnailConfig@.
--
-- 'role'', 'pipeline_role' - The IAM Amazon Resource Name (ARN) for the role that Elastic Transcoder
-- uses to transcode jobs for this pipeline.
--
-- 'status', 'pipeline_status' - The current status of the pipeline:
--
-- -   @Active@: The pipeline is processing jobs.
--
-- -   @Paused@: The pipeline is not currently processing jobs.
--
-- 'thumbnailConfig', 'pipeline_thumbnailConfig' - Information about the Amazon S3 bucket in which you want Elastic
-- Transcoder to save thumbnail files. Either you specify both
-- @ContentConfig@ and @ThumbnailConfig@, or you specify @OutputBucket@.
--
-- -   @Bucket@: The Amazon S3 bucket in which you want Elastic Transcoder
--     to save thumbnail files.
--
-- -   @Permissions@: A list of the users and\/or predefined Amazon S3
--     groups you want to have access to thumbnail files, and the type of
--     access that you want them to have.
--
--     -   GranteeType: The type of value that appears in the Grantee
--         object:
--
--         -   @Canonical@: Either the canonical user ID for an AWS account
--             or an origin access identity for an Amazon CloudFront
--             distribution.
--
--             A canonical user ID is not the same as an AWS account
--             number.
--
--         -   @Email@: The registered email address of an AWS account.
--
--         -   @Group@: One of the following predefined Amazon S3 groups:
--             @AllUsers@, @AuthenticatedUsers@, or @LogDelivery@.
--
--     -   @Grantee@: The AWS user or group that you want to have access to
--         thumbnail files.
--
--     -   Access: The permission that you want to give to the AWS user
--         that is listed in Grantee. Valid values include:
--
--         -   @READ@: The grantee can read the thumbnails and metadata for
--             thumbnails that Elastic Transcoder adds to the Amazon S3
--             bucket.
--
--         -   @READ_ACP@: The grantee can read the object ACL for
--             thumbnails that Elastic Transcoder adds to the Amazon S3
--             bucket.
--
--         -   @WRITE_ACP@: The grantee can write the ACL for the
--             thumbnails that Elastic Transcoder adds to the Amazon S3
--             bucket.
--
--         -   @FULL_CONTROL@: The grantee has READ, READ_ACP, and
--             WRITE_ACP permissions for the thumbnails that Elastic
--             Transcoder adds to the Amazon S3 bucket.
--
-- -   @StorageClass@: The Amazon S3 storage class, @Standard@ or
--     @ReducedRedundancy@, that you want Elastic Transcoder to assign to
--     the thumbnails that it stores in your Amazon S3 bucket.
newPipeline ::
  Pipeline
newPipeline :: Pipeline
newPipeline =
  Pipeline'
    { $sel:arn:Pipeline' :: Maybe Text
arn = forall a. Maybe a
Prelude.Nothing,
      $sel:awsKmsKeyArn:Pipeline' :: Maybe Text
awsKmsKeyArn = forall a. Maybe a
Prelude.Nothing,
      $sel:contentConfig:Pipeline' :: Maybe PipelineOutputConfig
contentConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:id:Pipeline' :: Maybe Text
id = forall a. Maybe a
Prelude.Nothing,
      $sel:inputBucket:Pipeline' :: Maybe Text
inputBucket = forall a. Maybe a
Prelude.Nothing,
      $sel:name:Pipeline' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:notifications:Pipeline' :: Maybe Notifications
notifications = forall a. Maybe a
Prelude.Nothing,
      $sel:outputBucket:Pipeline' :: Maybe Text
outputBucket = forall a. Maybe a
Prelude.Nothing,
      $sel:role':Pipeline' :: Maybe Text
role' = forall a. Maybe a
Prelude.Nothing,
      $sel:status:Pipeline' :: Maybe Text
status = forall a. Maybe a
Prelude.Nothing,
      $sel:thumbnailConfig:Pipeline' :: Maybe PipelineOutputConfig
thumbnailConfig = forall a. Maybe a
Prelude.Nothing
    }

-- | The Amazon Resource Name (ARN) for the pipeline.
pipeline_arn :: Lens.Lens' Pipeline (Prelude.Maybe Prelude.Text)
pipeline_arn :: Lens' Pipeline (Maybe Text)
pipeline_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Pipeline' {Maybe Text
arn :: Maybe Text
$sel:arn:Pipeline' :: Pipeline -> Maybe Text
arn} -> Maybe Text
arn) (\s :: Pipeline
s@Pipeline' {} Maybe Text
a -> Pipeline
s {$sel:arn:Pipeline' :: Maybe Text
arn = Maybe Text
a} :: Pipeline)

-- | The AWS Key Management Service (AWS KMS) key that you want to use with
-- this pipeline.
--
-- If you use either @s3@ or @s3-aws-kms@ as your @Encryption:Mode@, you
-- don\'t need to provide a key with your job because a default key, known
-- as an AWS-KMS key, is created for you automatically. You need to provide
-- an AWS-KMS key only if you want to use a non-default AWS-KMS key, or if
-- you are using an @Encryption:Mode@ of @aes-cbc-pkcs7@, @aes-ctr@, or
-- @aes-gcm@.
pipeline_awsKmsKeyArn :: Lens.Lens' Pipeline (Prelude.Maybe Prelude.Text)
pipeline_awsKmsKeyArn :: Lens' Pipeline (Maybe Text)
pipeline_awsKmsKeyArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Pipeline' {Maybe Text
awsKmsKeyArn :: Maybe Text
$sel:awsKmsKeyArn:Pipeline' :: Pipeline -> Maybe Text
awsKmsKeyArn} -> Maybe Text
awsKmsKeyArn) (\s :: Pipeline
s@Pipeline' {} Maybe Text
a -> Pipeline
s {$sel:awsKmsKeyArn:Pipeline' :: Maybe Text
awsKmsKeyArn = Maybe Text
a} :: Pipeline)

-- | Information about the Amazon S3 bucket in which you want Elastic
-- Transcoder to save transcoded files and playlists. Either you specify
-- both @ContentConfig@ and @ThumbnailConfig@, or you specify
-- @OutputBucket@.
--
-- -   __Bucket__: The Amazon S3 bucket in which you want Elastic
--     Transcoder to save transcoded files and playlists.
--
-- -   __Permissions__: A list of the users and\/or predefined Amazon S3
--     groups you want to have access to transcoded files and playlists,
--     and the type of access that you want them to have.
--
--     -   GranteeType: The type of value that appears in the @Grantee@
--         object:
--
--         -   @Canonical@: Either the canonical user ID for an AWS account
--             or an origin access identity for an Amazon CloudFront
--             distribution.
--
--         -   @Email@: The registered email address of an AWS account.
--
--         -   @Group@: One of the following predefined Amazon S3 groups:
--             @AllUsers@, @AuthenticatedUsers@, or @LogDelivery@.
--
--     -   @Grantee@: The AWS user or group that you want to have access to
--         transcoded files and playlists.
--
--     -   @Access@: The permission that you want to give to the AWS user
--         that is listed in @Grantee@. Valid values include:
--
--         -   @READ@: The grantee can read the objects and metadata for
--             objects that Elastic Transcoder adds to the Amazon S3
--             bucket.
--
--         -   @READ_ACP@: The grantee can read the object ACL for objects
--             that Elastic Transcoder adds to the Amazon S3 bucket.
--
--         -   @WRITE_ACP@: The grantee can write the ACL for the objects
--             that Elastic Transcoder adds to the Amazon S3 bucket.
--
--         -   @FULL_CONTROL@: The grantee has @READ@, @READ_ACP@, and
--             @WRITE_ACP@ permissions for the objects that Elastic
--             Transcoder adds to the Amazon S3 bucket.
--
-- -   __StorageClass__: The Amazon S3 storage class, Standard or
--     ReducedRedundancy, that you want Elastic Transcoder to assign to the
--     video files and playlists that it stores in your Amazon S3 bucket.
pipeline_contentConfig :: Lens.Lens' Pipeline (Prelude.Maybe PipelineOutputConfig)
pipeline_contentConfig :: Lens' Pipeline (Maybe PipelineOutputConfig)
pipeline_contentConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Pipeline' {Maybe PipelineOutputConfig
contentConfig :: Maybe PipelineOutputConfig
$sel:contentConfig:Pipeline' :: Pipeline -> Maybe PipelineOutputConfig
contentConfig} -> Maybe PipelineOutputConfig
contentConfig) (\s :: Pipeline
s@Pipeline' {} Maybe PipelineOutputConfig
a -> Pipeline
s {$sel:contentConfig:Pipeline' :: Maybe PipelineOutputConfig
contentConfig = Maybe PipelineOutputConfig
a} :: Pipeline)

-- | The identifier for the pipeline. You use this value to identify the
-- pipeline in which you want to perform a variety of operations, such as
-- creating a job or a preset.
pipeline_id :: Lens.Lens' Pipeline (Prelude.Maybe Prelude.Text)
pipeline_id :: Lens' Pipeline (Maybe Text)
pipeline_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Pipeline' {Maybe Text
id :: Maybe Text
$sel:id:Pipeline' :: Pipeline -> Maybe Text
id} -> Maybe Text
id) (\s :: Pipeline
s@Pipeline' {} Maybe Text
a -> Pipeline
s {$sel:id:Pipeline' :: Maybe Text
id = Maybe Text
a} :: Pipeline)

-- | The Amazon S3 bucket from which Elastic Transcoder gets media files for
-- transcoding and the graphics files, if any, that you want to use for
-- watermarks.
pipeline_inputBucket :: Lens.Lens' Pipeline (Prelude.Maybe Prelude.Text)
pipeline_inputBucket :: Lens' Pipeline (Maybe Text)
pipeline_inputBucket = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Pipeline' {Maybe Text
inputBucket :: Maybe Text
$sel:inputBucket:Pipeline' :: Pipeline -> Maybe Text
inputBucket} -> Maybe Text
inputBucket) (\s :: Pipeline
s@Pipeline' {} Maybe Text
a -> Pipeline
s {$sel:inputBucket:Pipeline' :: Maybe Text
inputBucket = Maybe Text
a} :: Pipeline)

-- | The name of the pipeline. We recommend that the name be unique within
-- the AWS account, but uniqueness is not enforced.
--
-- Constraints: Maximum 40 characters
pipeline_name :: Lens.Lens' Pipeline (Prelude.Maybe Prelude.Text)
pipeline_name :: Lens' Pipeline (Maybe Text)
pipeline_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Pipeline' {Maybe Text
name :: Maybe Text
$sel:name:Pipeline' :: Pipeline -> Maybe Text
name} -> Maybe Text
name) (\s :: Pipeline
s@Pipeline' {} Maybe Text
a -> Pipeline
s {$sel:name:Pipeline' :: Maybe Text
name = Maybe Text
a} :: Pipeline)

-- | The Amazon Simple Notification Service (Amazon SNS) topic that you want
-- to notify to report job status.
--
-- To receive notifications, you must also subscribe to the new topic in
-- the Amazon SNS console.
--
-- -   __Progressing__ (optional): The Amazon Simple Notification Service
--     (Amazon SNS) topic that you want to notify when Elastic Transcoder
--     has started to process the job.
--
-- -   __Complete__ (optional): The Amazon SNS topic that you want to
--     notify when Elastic Transcoder has finished processing the job.
--
-- -   __Warning__ (optional): The Amazon SNS topic that you want to notify
--     when Elastic Transcoder encounters a warning condition.
--
-- -   __Error__ (optional): The Amazon SNS topic that you want to notify
--     when Elastic Transcoder encounters an error condition.
pipeline_notifications :: Lens.Lens' Pipeline (Prelude.Maybe Notifications)
pipeline_notifications :: Lens' Pipeline (Maybe Notifications)
pipeline_notifications = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Pipeline' {Maybe Notifications
notifications :: Maybe Notifications
$sel:notifications:Pipeline' :: Pipeline -> Maybe Notifications
notifications} -> Maybe Notifications
notifications) (\s :: Pipeline
s@Pipeline' {} Maybe Notifications
a -> Pipeline
s {$sel:notifications:Pipeline' :: Maybe Notifications
notifications = Maybe Notifications
a} :: Pipeline)

-- | The Amazon S3 bucket in which you want Elastic Transcoder to save
-- transcoded files, thumbnails, and playlists. Either you specify this
-- value, or you specify both @ContentConfig@ and @ThumbnailConfig@.
pipeline_outputBucket :: Lens.Lens' Pipeline (Prelude.Maybe Prelude.Text)
pipeline_outputBucket :: Lens' Pipeline (Maybe Text)
pipeline_outputBucket = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Pipeline' {Maybe Text
outputBucket :: Maybe Text
$sel:outputBucket:Pipeline' :: Pipeline -> Maybe Text
outputBucket} -> Maybe Text
outputBucket) (\s :: Pipeline
s@Pipeline' {} Maybe Text
a -> Pipeline
s {$sel:outputBucket:Pipeline' :: Maybe Text
outputBucket = Maybe Text
a} :: Pipeline)

-- | The IAM Amazon Resource Name (ARN) for the role that Elastic Transcoder
-- uses to transcode jobs for this pipeline.
pipeline_role :: Lens.Lens' Pipeline (Prelude.Maybe Prelude.Text)
pipeline_role :: Lens' Pipeline (Maybe Text)
pipeline_role = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Pipeline' {Maybe Text
role' :: Maybe Text
$sel:role':Pipeline' :: Pipeline -> Maybe Text
role'} -> Maybe Text
role') (\s :: Pipeline
s@Pipeline' {} Maybe Text
a -> Pipeline
s {$sel:role':Pipeline' :: Maybe Text
role' = Maybe Text
a} :: Pipeline)

-- | The current status of the pipeline:
--
-- -   @Active@: The pipeline is processing jobs.
--
-- -   @Paused@: The pipeline is not currently processing jobs.
pipeline_status :: Lens.Lens' Pipeline (Prelude.Maybe Prelude.Text)
pipeline_status :: Lens' Pipeline (Maybe Text)
pipeline_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Pipeline' {Maybe Text
status :: Maybe Text
$sel:status:Pipeline' :: Pipeline -> Maybe Text
status} -> Maybe Text
status) (\s :: Pipeline
s@Pipeline' {} Maybe Text
a -> Pipeline
s {$sel:status:Pipeline' :: Maybe Text
status = Maybe Text
a} :: Pipeline)

-- | Information about the Amazon S3 bucket in which you want Elastic
-- Transcoder to save thumbnail files. Either you specify both
-- @ContentConfig@ and @ThumbnailConfig@, or you specify @OutputBucket@.
--
-- -   @Bucket@: The Amazon S3 bucket in which you want Elastic Transcoder
--     to save thumbnail files.
--
-- -   @Permissions@: A list of the users and\/or predefined Amazon S3
--     groups you want to have access to thumbnail files, and the type of
--     access that you want them to have.
--
--     -   GranteeType: The type of value that appears in the Grantee
--         object:
--
--         -   @Canonical@: Either the canonical user ID for an AWS account
--             or an origin access identity for an Amazon CloudFront
--             distribution.
--
--             A canonical user ID is not the same as an AWS account
--             number.
--
--         -   @Email@: The registered email address of an AWS account.
--
--         -   @Group@: One of the following predefined Amazon S3 groups:
--             @AllUsers@, @AuthenticatedUsers@, or @LogDelivery@.
--
--     -   @Grantee@: The AWS user or group that you want to have access to
--         thumbnail files.
--
--     -   Access: The permission that you want to give to the AWS user
--         that is listed in Grantee. Valid values include:
--
--         -   @READ@: The grantee can read the thumbnails and metadata for
--             thumbnails that Elastic Transcoder adds to the Amazon S3
--             bucket.
--
--         -   @READ_ACP@: The grantee can read the object ACL for
--             thumbnails that Elastic Transcoder adds to the Amazon S3
--             bucket.
--
--         -   @WRITE_ACP@: The grantee can write the ACL for the
--             thumbnails that Elastic Transcoder adds to the Amazon S3
--             bucket.
--
--         -   @FULL_CONTROL@: The grantee has READ, READ_ACP, and
--             WRITE_ACP permissions for the thumbnails that Elastic
--             Transcoder adds to the Amazon S3 bucket.
--
-- -   @StorageClass@: The Amazon S3 storage class, @Standard@ or
--     @ReducedRedundancy@, that you want Elastic Transcoder to assign to
--     the thumbnails that it stores in your Amazon S3 bucket.
pipeline_thumbnailConfig :: Lens.Lens' Pipeline (Prelude.Maybe PipelineOutputConfig)
pipeline_thumbnailConfig :: Lens' Pipeline (Maybe PipelineOutputConfig)
pipeline_thumbnailConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Pipeline' {Maybe PipelineOutputConfig
thumbnailConfig :: Maybe PipelineOutputConfig
$sel:thumbnailConfig:Pipeline' :: Pipeline -> Maybe PipelineOutputConfig
thumbnailConfig} -> Maybe PipelineOutputConfig
thumbnailConfig) (\s :: Pipeline
s@Pipeline' {} Maybe PipelineOutputConfig
a -> Pipeline
s {$sel:thumbnailConfig:Pipeline' :: Maybe PipelineOutputConfig
thumbnailConfig = Maybe PipelineOutputConfig
a} :: Pipeline)

instance Data.FromJSON Pipeline where
  parseJSON :: Value -> Parser Pipeline
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"Pipeline"
      ( \Object
x ->
          Maybe Text
-> Maybe Text
-> Maybe PipelineOutputConfig
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Notifications
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe PipelineOutputConfig
-> Pipeline
Pipeline'
            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
"AwsKmsKeyArn")
            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
"ContentConfig")
            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
"InputBucket")
            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
"Notifications")
            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
"OutputBucket")
            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
"Role")
            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
"ThumbnailConfig")
      )

instance Prelude.Hashable Pipeline where
  hashWithSalt :: Int -> Pipeline -> Int
hashWithSalt Int
_salt Pipeline' {Maybe Text
Maybe Notifications
Maybe PipelineOutputConfig
thumbnailConfig :: Maybe PipelineOutputConfig
status :: Maybe Text
role' :: Maybe Text
outputBucket :: Maybe Text
notifications :: Maybe Notifications
name :: Maybe Text
inputBucket :: Maybe Text
id :: Maybe Text
contentConfig :: Maybe PipelineOutputConfig
awsKmsKeyArn :: Maybe Text
arn :: Maybe Text
$sel:thumbnailConfig:Pipeline' :: Pipeline -> Maybe PipelineOutputConfig
$sel:status:Pipeline' :: Pipeline -> Maybe Text
$sel:role':Pipeline' :: Pipeline -> Maybe Text
$sel:outputBucket:Pipeline' :: Pipeline -> Maybe Text
$sel:notifications:Pipeline' :: Pipeline -> Maybe Notifications
$sel:name:Pipeline' :: Pipeline -> Maybe Text
$sel:inputBucket:Pipeline' :: Pipeline -> Maybe Text
$sel:id:Pipeline' :: Pipeline -> Maybe Text
$sel:contentConfig:Pipeline' :: Pipeline -> Maybe PipelineOutputConfig
$sel:awsKmsKeyArn:Pipeline' :: Pipeline -> Maybe Text
$sel:arn:Pipeline' :: Pipeline -> 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
awsKmsKeyArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe PipelineOutputConfig
contentConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
id
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
inputBucket
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Notifications
notifications
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
outputBucket
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
role'
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
status
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe PipelineOutputConfig
thumbnailConfig

instance Prelude.NFData Pipeline where
  rnf :: Pipeline -> ()
rnf Pipeline' {Maybe Text
Maybe Notifications
Maybe PipelineOutputConfig
thumbnailConfig :: Maybe PipelineOutputConfig
status :: Maybe Text
role' :: Maybe Text
outputBucket :: Maybe Text
notifications :: Maybe Notifications
name :: Maybe Text
inputBucket :: Maybe Text
id :: Maybe Text
contentConfig :: Maybe PipelineOutputConfig
awsKmsKeyArn :: Maybe Text
arn :: Maybe Text
$sel:thumbnailConfig:Pipeline' :: Pipeline -> Maybe PipelineOutputConfig
$sel:status:Pipeline' :: Pipeline -> Maybe Text
$sel:role':Pipeline' :: Pipeline -> Maybe Text
$sel:outputBucket:Pipeline' :: Pipeline -> Maybe Text
$sel:notifications:Pipeline' :: Pipeline -> Maybe Notifications
$sel:name:Pipeline' :: Pipeline -> Maybe Text
$sel:inputBucket:Pipeline' :: Pipeline -> Maybe Text
$sel:id:Pipeline' :: Pipeline -> Maybe Text
$sel:contentConfig:Pipeline' :: Pipeline -> Maybe PipelineOutputConfig
$sel:awsKmsKeyArn:Pipeline' :: Pipeline -> Maybe Text
$sel:arn:Pipeline' :: Pipeline -> 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
awsKmsKeyArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe PipelineOutputConfig
contentConfig
      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
inputBucket
      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 Notifications
notifications
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
outputBucket
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
role'
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe PipelineOutputConfig
thumbnailConfig