{-# 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.ReadPipeline
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- The ReadPipeline operation gets detailed information about a pipeline.
module Amazonka.ElasticTranscoder.ReadPipeline
  ( -- * Creating a Request
    ReadPipeline (..),
    newReadPipeline,

    -- * Request Lenses
    readPipeline_id,

    -- * Destructuring the Response
    ReadPipelineResponse (..),
    newReadPipelineResponse,

    -- * Response Lenses
    readPipelineResponse_pipeline,
    readPipelineResponse_warnings,
    readPipelineResponse_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 @ReadPipelineRequest@ structure.
--
-- /See:/ 'newReadPipeline' smart constructor.
data ReadPipeline = ReadPipeline'
  { -- | The identifier of the pipeline to read.
    ReadPipeline -> Text
id :: Prelude.Text
  }
  deriving (ReadPipeline -> ReadPipeline -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ReadPipeline -> ReadPipeline -> Bool
$c/= :: ReadPipeline -> ReadPipeline -> Bool
== :: ReadPipeline -> ReadPipeline -> Bool
$c== :: ReadPipeline -> ReadPipeline -> Bool
Prelude.Eq, ReadPrec [ReadPipeline]
ReadPrec ReadPipeline
Int -> ReadS ReadPipeline
ReadS [ReadPipeline]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ReadPipeline]
$creadListPrec :: ReadPrec [ReadPipeline]
readPrec :: ReadPrec ReadPipeline
$creadPrec :: ReadPrec ReadPipeline
readList :: ReadS [ReadPipeline]
$creadList :: ReadS [ReadPipeline]
readsPrec :: Int -> ReadS ReadPipeline
$creadsPrec :: Int -> ReadS ReadPipeline
Prelude.Read, Int -> ReadPipeline -> ShowS
[ReadPipeline] -> ShowS
ReadPipeline -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ReadPipeline] -> ShowS
$cshowList :: [ReadPipeline] -> ShowS
show :: ReadPipeline -> String
$cshow :: ReadPipeline -> String
showsPrec :: Int -> ReadPipeline -> ShowS
$cshowsPrec :: Int -> ReadPipeline -> ShowS
Prelude.Show, forall x. Rep ReadPipeline x -> ReadPipeline
forall x. ReadPipeline -> Rep ReadPipeline x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ReadPipeline x -> ReadPipeline
$cfrom :: forall x. ReadPipeline -> Rep ReadPipeline x
Prelude.Generic)

-- |
-- Create a value of 'ReadPipeline' 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:
--
-- 'id', 'readPipeline_id' - The identifier of the pipeline to read.
newReadPipeline ::
  -- | 'id'
  Prelude.Text ->
  ReadPipeline
newReadPipeline :: Text -> ReadPipeline
newReadPipeline Text
pId_ = ReadPipeline' {$sel:id:ReadPipeline' :: Text
id = Text
pId_}

-- | The identifier of the pipeline to read.
readPipeline_id :: Lens.Lens' ReadPipeline Prelude.Text
readPipeline_id :: Lens' ReadPipeline Text
readPipeline_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ReadPipeline' {Text
id :: Text
$sel:id:ReadPipeline' :: ReadPipeline -> Text
id} -> Text
id) (\s :: ReadPipeline
s@ReadPipeline' {} Text
a -> ReadPipeline
s {$sel:id:ReadPipeline' :: Text
id = Text
a} :: ReadPipeline)

instance Core.AWSRequest ReadPipeline where
  type AWSResponse ReadPipeline = ReadPipelineResponse
  request :: (Service -> Service) -> ReadPipeline -> Request ReadPipeline
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.get (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy ReadPipeline
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ReadPipeline)))
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 Pipeline -> Maybe [Warning] -> Int -> ReadPipelineResponse
ReadPipelineResponse'
            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
"Pipeline")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"Warnings" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
            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 ReadPipeline where
  hashWithSalt :: Int -> ReadPipeline -> Int
hashWithSalt Int
_salt ReadPipeline' {Text
id :: Text
$sel:id:ReadPipeline' :: ReadPipeline -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
id

instance Prelude.NFData ReadPipeline where
  rnf :: ReadPipeline -> ()
rnf ReadPipeline' {Text
id :: Text
$sel:id:ReadPipeline' :: ReadPipeline -> Text
..} = forall a. NFData a => a -> ()
Prelude.rnf Text
id

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

instance Data.ToPath ReadPipeline where
  toPath :: ReadPipeline -> ByteString
toPath ReadPipeline' {Text
id :: Text
$sel:id:ReadPipeline' :: ReadPipeline -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/2012-09-25/pipelines/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
id]

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

-- | The @ReadPipelineResponse@ structure.
--
-- /See:/ 'newReadPipelineResponse' smart constructor.
data ReadPipelineResponse = ReadPipelineResponse'
  { -- | A section of the response body that provides information about the
    -- pipeline.
    ReadPipelineResponse -> Maybe Pipeline
pipeline :: Prelude.Maybe Pipeline,
    -- | Elastic Transcoder returns a warning if the resources used by your
    -- pipeline are not in the same region as the pipeline.
    --
    -- Using resources in the same region, such as your Amazon S3 buckets,
    -- Amazon SNS notification topics, and AWS KMS key, reduces processing time
    -- and prevents cross-regional charges.
    ReadPipelineResponse -> Maybe [Warning]
warnings :: Prelude.Maybe [Warning],
    -- | The response's http status code.
    ReadPipelineResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ReadPipelineResponse -> ReadPipelineResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ReadPipelineResponse -> ReadPipelineResponse -> Bool
$c/= :: ReadPipelineResponse -> ReadPipelineResponse -> Bool
== :: ReadPipelineResponse -> ReadPipelineResponse -> Bool
$c== :: ReadPipelineResponse -> ReadPipelineResponse -> Bool
Prelude.Eq, ReadPrec [ReadPipelineResponse]
ReadPrec ReadPipelineResponse
Int -> ReadS ReadPipelineResponse
ReadS [ReadPipelineResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ReadPipelineResponse]
$creadListPrec :: ReadPrec [ReadPipelineResponse]
readPrec :: ReadPrec ReadPipelineResponse
$creadPrec :: ReadPrec ReadPipelineResponse
readList :: ReadS [ReadPipelineResponse]
$creadList :: ReadS [ReadPipelineResponse]
readsPrec :: Int -> ReadS ReadPipelineResponse
$creadsPrec :: Int -> ReadS ReadPipelineResponse
Prelude.Read, Int -> ReadPipelineResponse -> ShowS
[ReadPipelineResponse] -> ShowS
ReadPipelineResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ReadPipelineResponse] -> ShowS
$cshowList :: [ReadPipelineResponse] -> ShowS
show :: ReadPipelineResponse -> String
$cshow :: ReadPipelineResponse -> String
showsPrec :: Int -> ReadPipelineResponse -> ShowS
$cshowsPrec :: Int -> ReadPipelineResponse -> ShowS
Prelude.Show, forall x. Rep ReadPipelineResponse x -> ReadPipelineResponse
forall x. ReadPipelineResponse -> Rep ReadPipelineResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ReadPipelineResponse x -> ReadPipelineResponse
$cfrom :: forall x. ReadPipelineResponse -> Rep ReadPipelineResponse x
Prelude.Generic)

-- |
-- Create a value of 'ReadPipelineResponse' 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:
--
-- 'pipeline', 'readPipelineResponse_pipeline' - A section of the response body that provides information about the
-- pipeline.
--
-- 'warnings', 'readPipelineResponse_warnings' - Elastic Transcoder returns a warning if the resources used by your
-- pipeline are not in the same region as the pipeline.
--
-- Using resources in the same region, such as your Amazon S3 buckets,
-- Amazon SNS notification topics, and AWS KMS key, reduces processing time
-- and prevents cross-regional charges.
--
-- 'httpStatus', 'readPipelineResponse_httpStatus' - The response's http status code.
newReadPipelineResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ReadPipelineResponse
newReadPipelineResponse :: Int -> ReadPipelineResponse
newReadPipelineResponse Int
pHttpStatus_ =
  ReadPipelineResponse'
    { $sel:pipeline:ReadPipelineResponse' :: Maybe Pipeline
pipeline = forall a. Maybe a
Prelude.Nothing,
      $sel:warnings:ReadPipelineResponse' :: Maybe [Warning]
warnings = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ReadPipelineResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A section of the response body that provides information about the
-- pipeline.
readPipelineResponse_pipeline :: Lens.Lens' ReadPipelineResponse (Prelude.Maybe Pipeline)
readPipelineResponse_pipeline :: Lens' ReadPipelineResponse (Maybe Pipeline)
readPipelineResponse_pipeline = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ReadPipelineResponse' {Maybe Pipeline
pipeline :: Maybe Pipeline
$sel:pipeline:ReadPipelineResponse' :: ReadPipelineResponse -> Maybe Pipeline
pipeline} -> Maybe Pipeline
pipeline) (\s :: ReadPipelineResponse
s@ReadPipelineResponse' {} Maybe Pipeline
a -> ReadPipelineResponse
s {$sel:pipeline:ReadPipelineResponse' :: Maybe Pipeline
pipeline = Maybe Pipeline
a} :: ReadPipelineResponse)

-- | Elastic Transcoder returns a warning if the resources used by your
-- pipeline are not in the same region as the pipeline.
--
-- Using resources in the same region, such as your Amazon S3 buckets,
-- Amazon SNS notification topics, and AWS KMS key, reduces processing time
-- and prevents cross-regional charges.
readPipelineResponse_warnings :: Lens.Lens' ReadPipelineResponse (Prelude.Maybe [Warning])
readPipelineResponse_warnings :: Lens' ReadPipelineResponse (Maybe [Warning])
readPipelineResponse_warnings = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ReadPipelineResponse' {Maybe [Warning]
warnings :: Maybe [Warning]
$sel:warnings:ReadPipelineResponse' :: ReadPipelineResponse -> Maybe [Warning]
warnings} -> Maybe [Warning]
warnings) (\s :: ReadPipelineResponse
s@ReadPipelineResponse' {} Maybe [Warning]
a -> ReadPipelineResponse
s {$sel:warnings:ReadPipelineResponse' :: Maybe [Warning]
warnings = Maybe [Warning]
a} :: ReadPipelineResponse) 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 response's http status code.
readPipelineResponse_httpStatus :: Lens.Lens' ReadPipelineResponse Prelude.Int
readPipelineResponse_httpStatus :: Lens' ReadPipelineResponse Int
readPipelineResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ReadPipelineResponse' {Int
httpStatus :: Int
$sel:httpStatus:ReadPipelineResponse' :: ReadPipelineResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ReadPipelineResponse
s@ReadPipelineResponse' {} Int
a -> ReadPipelineResponse
s {$sel:httpStatus:ReadPipelineResponse' :: Int
httpStatus = Int
a} :: ReadPipelineResponse)

instance Prelude.NFData ReadPipelineResponse where
  rnf :: ReadPipelineResponse -> ()
rnf ReadPipelineResponse' {Int
Maybe [Warning]
Maybe Pipeline
httpStatus :: Int
warnings :: Maybe [Warning]
pipeline :: Maybe Pipeline
$sel:httpStatus:ReadPipelineResponse' :: ReadPipelineResponse -> Int
$sel:warnings:ReadPipelineResponse' :: ReadPipelineResponse -> Maybe [Warning]
$sel:pipeline:ReadPipelineResponse' :: ReadPipelineResponse -> Maybe Pipeline
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Pipeline
pipeline
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Warning]
warnings
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus