{-# 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.MediaConvert.CreateQueue
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Create a new transcoding queue. For information about queues, see
-- Working With Queues in the User Guide at
-- https:\/\/docs.aws.amazon.com\/mediaconvert\/latest\/ug\/working-with-queues.html
module Amazonka.MediaConvert.CreateQueue
  ( -- * Creating a Request
    CreateQueue (..),
    newCreateQueue,

    -- * Request Lenses
    createQueue_description,
    createQueue_pricingPlan,
    createQueue_reservationPlanSettings,
    createQueue_status,
    createQueue_tags,
    createQueue_name,

    -- * Destructuring the Response
    CreateQueueResponse (..),
    newCreateQueueResponse,

    -- * Response Lenses
    createQueueResponse_queue,
    createQueueResponse_httpStatus,
  )
where

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

-- | /See:/ 'newCreateQueue' smart constructor.
data CreateQueue = CreateQueue'
  { -- | Optional. A description of the queue that you are creating.
    CreateQueue -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | Specifies whether the pricing plan for the queue is on-demand or
    -- reserved. For on-demand, you pay per minute, billed in increments of .01
    -- minute. For reserved, you pay for the transcoding capacity of the entire
    -- queue, regardless of how much or how little you use it. Reserved pricing
    -- requires a 12-month commitment. When you use the API to create a queue,
    -- the default is on-demand.
    CreateQueue -> Maybe PricingPlan
pricingPlan :: Prelude.Maybe PricingPlan,
    -- | Details about the pricing plan for your reserved queue. Required for
    -- reserved queues and not applicable to on-demand queues.
    CreateQueue -> Maybe ReservationPlanSettings
reservationPlanSettings :: Prelude.Maybe ReservationPlanSettings,
    -- | Initial state of the queue. If you create a paused queue, then jobs in
    -- that queue won\'t begin.
    CreateQueue -> Maybe QueueStatus
status :: Prelude.Maybe QueueStatus,
    -- | The tags that you want to add to the resource. You can tag resources
    -- with a key-value pair or with only a key.
    CreateQueue -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The name of the queue that you are creating.
    CreateQueue -> Text
name :: Prelude.Text
  }
  deriving (CreateQueue -> CreateQueue -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateQueue -> CreateQueue -> Bool
$c/= :: CreateQueue -> CreateQueue -> Bool
== :: CreateQueue -> CreateQueue -> Bool
$c== :: CreateQueue -> CreateQueue -> Bool
Prelude.Eq, ReadPrec [CreateQueue]
ReadPrec CreateQueue
Int -> ReadS CreateQueue
ReadS [CreateQueue]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateQueue]
$creadListPrec :: ReadPrec [CreateQueue]
readPrec :: ReadPrec CreateQueue
$creadPrec :: ReadPrec CreateQueue
readList :: ReadS [CreateQueue]
$creadList :: ReadS [CreateQueue]
readsPrec :: Int -> ReadS CreateQueue
$creadsPrec :: Int -> ReadS CreateQueue
Prelude.Read, Int -> CreateQueue -> ShowS
[CreateQueue] -> ShowS
CreateQueue -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateQueue] -> ShowS
$cshowList :: [CreateQueue] -> ShowS
show :: CreateQueue -> String
$cshow :: CreateQueue -> String
showsPrec :: Int -> CreateQueue -> ShowS
$cshowsPrec :: Int -> CreateQueue -> ShowS
Prelude.Show, forall x. Rep CreateQueue x -> CreateQueue
forall x. CreateQueue -> Rep CreateQueue x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateQueue x -> CreateQueue
$cfrom :: forall x. CreateQueue -> Rep CreateQueue x
Prelude.Generic)

-- |
-- Create a value of 'CreateQueue' 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:
--
-- 'description', 'createQueue_description' - Optional. A description of the queue that you are creating.
--
-- 'pricingPlan', 'createQueue_pricingPlan' - Specifies whether the pricing plan for the queue is on-demand or
-- reserved. For on-demand, you pay per minute, billed in increments of .01
-- minute. For reserved, you pay for the transcoding capacity of the entire
-- queue, regardless of how much or how little you use it. Reserved pricing
-- requires a 12-month commitment. When you use the API to create a queue,
-- the default is on-demand.
--
-- 'reservationPlanSettings', 'createQueue_reservationPlanSettings' - Details about the pricing plan for your reserved queue. Required for
-- reserved queues and not applicable to on-demand queues.
--
-- 'status', 'createQueue_status' - Initial state of the queue. If you create a paused queue, then jobs in
-- that queue won\'t begin.
--
-- 'tags', 'createQueue_tags' - The tags that you want to add to the resource. You can tag resources
-- with a key-value pair or with only a key.
--
-- 'name', 'createQueue_name' - The name of the queue that you are creating.
newCreateQueue ::
  -- | 'name'
  Prelude.Text ->
  CreateQueue
newCreateQueue :: Text -> CreateQueue
newCreateQueue Text
pName_ =
  CreateQueue'
    { $sel:description:CreateQueue' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:pricingPlan:CreateQueue' :: Maybe PricingPlan
pricingPlan = forall a. Maybe a
Prelude.Nothing,
      $sel:reservationPlanSettings:CreateQueue' :: Maybe ReservationPlanSettings
reservationPlanSettings = forall a. Maybe a
Prelude.Nothing,
      $sel:status:CreateQueue' :: Maybe QueueStatus
status = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:CreateQueue' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:name:CreateQueue' :: Text
name = Text
pName_
    }

-- | Optional. A description of the queue that you are creating.
createQueue_description :: Lens.Lens' CreateQueue (Prelude.Maybe Prelude.Text)
createQueue_description :: Lens' CreateQueue (Maybe Text)
createQueue_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateQueue' {Maybe Text
description :: Maybe Text
$sel:description:CreateQueue' :: CreateQueue -> Maybe Text
description} -> Maybe Text
description) (\s :: CreateQueue
s@CreateQueue' {} Maybe Text
a -> CreateQueue
s {$sel:description:CreateQueue' :: Maybe Text
description = Maybe Text
a} :: CreateQueue)

-- | Specifies whether the pricing plan for the queue is on-demand or
-- reserved. For on-demand, you pay per minute, billed in increments of .01
-- minute. For reserved, you pay for the transcoding capacity of the entire
-- queue, regardless of how much or how little you use it. Reserved pricing
-- requires a 12-month commitment. When you use the API to create a queue,
-- the default is on-demand.
createQueue_pricingPlan :: Lens.Lens' CreateQueue (Prelude.Maybe PricingPlan)
createQueue_pricingPlan :: Lens' CreateQueue (Maybe PricingPlan)
createQueue_pricingPlan = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateQueue' {Maybe PricingPlan
pricingPlan :: Maybe PricingPlan
$sel:pricingPlan:CreateQueue' :: CreateQueue -> Maybe PricingPlan
pricingPlan} -> Maybe PricingPlan
pricingPlan) (\s :: CreateQueue
s@CreateQueue' {} Maybe PricingPlan
a -> CreateQueue
s {$sel:pricingPlan:CreateQueue' :: Maybe PricingPlan
pricingPlan = Maybe PricingPlan
a} :: CreateQueue)

-- | Details about the pricing plan for your reserved queue. Required for
-- reserved queues and not applicable to on-demand queues.
createQueue_reservationPlanSettings :: Lens.Lens' CreateQueue (Prelude.Maybe ReservationPlanSettings)
createQueue_reservationPlanSettings :: Lens' CreateQueue (Maybe ReservationPlanSettings)
createQueue_reservationPlanSettings = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateQueue' {Maybe ReservationPlanSettings
reservationPlanSettings :: Maybe ReservationPlanSettings
$sel:reservationPlanSettings:CreateQueue' :: CreateQueue -> Maybe ReservationPlanSettings
reservationPlanSettings} -> Maybe ReservationPlanSettings
reservationPlanSettings) (\s :: CreateQueue
s@CreateQueue' {} Maybe ReservationPlanSettings
a -> CreateQueue
s {$sel:reservationPlanSettings:CreateQueue' :: Maybe ReservationPlanSettings
reservationPlanSettings = Maybe ReservationPlanSettings
a} :: CreateQueue)

-- | Initial state of the queue. If you create a paused queue, then jobs in
-- that queue won\'t begin.
createQueue_status :: Lens.Lens' CreateQueue (Prelude.Maybe QueueStatus)
createQueue_status :: Lens' CreateQueue (Maybe QueueStatus)
createQueue_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateQueue' {Maybe QueueStatus
status :: Maybe QueueStatus
$sel:status:CreateQueue' :: CreateQueue -> Maybe QueueStatus
status} -> Maybe QueueStatus
status) (\s :: CreateQueue
s@CreateQueue' {} Maybe QueueStatus
a -> CreateQueue
s {$sel:status:CreateQueue' :: Maybe QueueStatus
status = Maybe QueueStatus
a} :: CreateQueue)

-- | The tags that you want to add to the resource. You can tag resources
-- with a key-value pair or with only a key.
createQueue_tags :: Lens.Lens' CreateQueue (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
createQueue_tags :: Lens' CreateQueue (Maybe (HashMap Text Text))
createQueue_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateQueue' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:CreateQueue' :: CreateQueue -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: CreateQueue
s@CreateQueue' {} Maybe (HashMap Text Text)
a -> CreateQueue
s {$sel:tags:CreateQueue' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: CreateQueue) 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 name of the queue that you are creating.
createQueue_name :: Lens.Lens' CreateQueue Prelude.Text
createQueue_name :: Lens' CreateQueue Text
createQueue_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateQueue' {Text
name :: Text
$sel:name:CreateQueue' :: CreateQueue -> Text
name} -> Text
name) (\s :: CreateQueue
s@CreateQueue' {} Text
a -> CreateQueue
s {$sel:name:CreateQueue' :: Text
name = Text
a} :: CreateQueue)

instance Core.AWSRequest CreateQueue where
  type AWSResponse CreateQueue = CreateQueueResponse
  request :: (Service -> Service) -> CreateQueue -> Request CreateQueue
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 CreateQueue
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse CreateQueue)))
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 Queue -> Int -> CreateQueueResponse
CreateQueueResponse'
            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
"queue")
            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 CreateQueue where
  hashWithSalt :: Int -> CreateQueue -> Int
hashWithSalt Int
_salt CreateQueue' {Maybe Text
Maybe (HashMap Text Text)
Maybe PricingPlan
Maybe QueueStatus
Maybe ReservationPlanSettings
Text
name :: Text
tags :: Maybe (HashMap Text Text)
status :: Maybe QueueStatus
reservationPlanSettings :: Maybe ReservationPlanSettings
pricingPlan :: Maybe PricingPlan
description :: Maybe Text
$sel:name:CreateQueue' :: CreateQueue -> Text
$sel:tags:CreateQueue' :: CreateQueue -> Maybe (HashMap Text Text)
$sel:status:CreateQueue' :: CreateQueue -> Maybe QueueStatus
$sel:reservationPlanSettings:CreateQueue' :: CreateQueue -> Maybe ReservationPlanSettings
$sel:pricingPlan:CreateQueue' :: CreateQueue -> Maybe PricingPlan
$sel:description:CreateQueue' :: CreateQueue -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe PricingPlan
pricingPlan
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ReservationPlanSettings
reservationPlanSettings
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe QueueStatus
status
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name

instance Prelude.NFData CreateQueue where
  rnf :: CreateQueue -> ()
rnf CreateQueue' {Maybe Text
Maybe (HashMap Text Text)
Maybe PricingPlan
Maybe QueueStatus
Maybe ReservationPlanSettings
Text
name :: Text
tags :: Maybe (HashMap Text Text)
status :: Maybe QueueStatus
reservationPlanSettings :: Maybe ReservationPlanSettings
pricingPlan :: Maybe PricingPlan
description :: Maybe Text
$sel:name:CreateQueue' :: CreateQueue -> Text
$sel:tags:CreateQueue' :: CreateQueue -> Maybe (HashMap Text Text)
$sel:status:CreateQueue' :: CreateQueue -> Maybe QueueStatus
$sel:reservationPlanSettings:CreateQueue' :: CreateQueue -> Maybe ReservationPlanSettings
$sel:pricingPlan:CreateQueue' :: CreateQueue -> Maybe PricingPlan
$sel:description:CreateQueue' :: CreateQueue -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe PricingPlan
pricingPlan
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ReservationPlanSettings
reservationPlanSettings
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe QueueStatus
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
name

instance Data.ToHeaders CreateQueue where
  toHeaders :: CreateQueue -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON CreateQueue where
  toJSON :: CreateQueue -> Value
toJSON CreateQueue' {Maybe Text
Maybe (HashMap Text Text)
Maybe PricingPlan
Maybe QueueStatus
Maybe ReservationPlanSettings
Text
name :: Text
tags :: Maybe (HashMap Text Text)
status :: Maybe QueueStatus
reservationPlanSettings :: Maybe ReservationPlanSettings
pricingPlan :: Maybe PricingPlan
description :: Maybe Text
$sel:name:CreateQueue' :: CreateQueue -> Text
$sel:tags:CreateQueue' :: CreateQueue -> Maybe (HashMap Text Text)
$sel:status:CreateQueue' :: CreateQueue -> Maybe QueueStatus
$sel:reservationPlanSettings:CreateQueue' :: CreateQueue -> Maybe ReservationPlanSettings
$sel:pricingPlan:CreateQueue' :: CreateQueue -> Maybe PricingPlan
$sel:description:CreateQueue' :: CreateQueue -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"description" 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
description,
            (Key
"pricingPlan" 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 PricingPlan
pricingPlan,
            (Key
"reservationPlanSettings" 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 ReservationPlanSettings
reservationPlanSettings,
            (Key
"status" 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 QueueStatus
status,
            (Key
"tags" 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)
tags,
            forall a. a -> Maybe a
Prelude.Just (Key
"name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
name)
          ]
      )

instance Data.ToPath CreateQueue where
  toPath :: CreateQueue -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/2017-08-29/queues"

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

-- | /See:/ 'newCreateQueueResponse' smart constructor.
data CreateQueueResponse = CreateQueueResponse'
  { -- | You can use queues to manage the resources that are available to your
    -- AWS account for running multiple transcoding jobs at the same time. If
    -- you don\'t specify a queue, the service sends all jobs through the
    -- default queue. For more information, see
    -- https:\/\/docs.aws.amazon.com\/mediaconvert\/latest\/ug\/working-with-queues.html.
    CreateQueueResponse -> Maybe Queue
queue :: Prelude.Maybe Queue,
    -- | The response's http status code.
    CreateQueueResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateQueueResponse -> CreateQueueResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateQueueResponse -> CreateQueueResponse -> Bool
$c/= :: CreateQueueResponse -> CreateQueueResponse -> Bool
== :: CreateQueueResponse -> CreateQueueResponse -> Bool
$c== :: CreateQueueResponse -> CreateQueueResponse -> Bool
Prelude.Eq, ReadPrec [CreateQueueResponse]
ReadPrec CreateQueueResponse
Int -> ReadS CreateQueueResponse
ReadS [CreateQueueResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateQueueResponse]
$creadListPrec :: ReadPrec [CreateQueueResponse]
readPrec :: ReadPrec CreateQueueResponse
$creadPrec :: ReadPrec CreateQueueResponse
readList :: ReadS [CreateQueueResponse]
$creadList :: ReadS [CreateQueueResponse]
readsPrec :: Int -> ReadS CreateQueueResponse
$creadsPrec :: Int -> ReadS CreateQueueResponse
Prelude.Read, Int -> CreateQueueResponse -> ShowS
[CreateQueueResponse] -> ShowS
CreateQueueResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateQueueResponse] -> ShowS
$cshowList :: [CreateQueueResponse] -> ShowS
show :: CreateQueueResponse -> String
$cshow :: CreateQueueResponse -> String
showsPrec :: Int -> CreateQueueResponse -> ShowS
$cshowsPrec :: Int -> CreateQueueResponse -> ShowS
Prelude.Show, forall x. Rep CreateQueueResponse x -> CreateQueueResponse
forall x. CreateQueueResponse -> Rep CreateQueueResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateQueueResponse x -> CreateQueueResponse
$cfrom :: forall x. CreateQueueResponse -> Rep CreateQueueResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateQueueResponse' 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:
--
-- 'queue', 'createQueueResponse_queue' - You can use queues to manage the resources that are available to your
-- AWS account for running multiple transcoding jobs at the same time. If
-- you don\'t specify a queue, the service sends all jobs through the
-- default queue. For more information, see
-- https:\/\/docs.aws.amazon.com\/mediaconvert\/latest\/ug\/working-with-queues.html.
--
-- 'httpStatus', 'createQueueResponse_httpStatus' - The response's http status code.
newCreateQueueResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateQueueResponse
newCreateQueueResponse :: Int -> CreateQueueResponse
newCreateQueueResponse Int
pHttpStatus_ =
  CreateQueueResponse'
    { $sel:queue:CreateQueueResponse' :: Maybe Queue
queue = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateQueueResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | You can use queues to manage the resources that are available to your
-- AWS account for running multiple transcoding jobs at the same time. If
-- you don\'t specify a queue, the service sends all jobs through the
-- default queue. For more information, see
-- https:\/\/docs.aws.amazon.com\/mediaconvert\/latest\/ug\/working-with-queues.html.
createQueueResponse_queue :: Lens.Lens' CreateQueueResponse (Prelude.Maybe Queue)
createQueueResponse_queue :: Lens' CreateQueueResponse (Maybe Queue)
createQueueResponse_queue = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateQueueResponse' {Maybe Queue
queue :: Maybe Queue
$sel:queue:CreateQueueResponse' :: CreateQueueResponse -> Maybe Queue
queue} -> Maybe Queue
queue) (\s :: CreateQueueResponse
s@CreateQueueResponse' {} Maybe Queue
a -> CreateQueueResponse
s {$sel:queue:CreateQueueResponse' :: Maybe Queue
queue = Maybe Queue
a} :: CreateQueueResponse)

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

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