{-# 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.MediaLive.CreateMultiplexProgram
-- 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 program in the multiplex.
module Amazonka.MediaLive.CreateMultiplexProgram
  ( -- * Creating a Request
    CreateMultiplexProgram' (..),
    newCreateMultiplexProgram',

    -- * Request Lenses
    createMultiplexProgram'_multiplexId,
    createMultiplexProgram'_requestId,
    createMultiplexProgram'_multiplexProgramSettings,
    createMultiplexProgram'_programName,

    -- * Destructuring the Response
    CreateMultiplexProgramResponse (..),
    newCreateMultiplexProgramResponse,

    -- * Response Lenses
    createMultiplexProgramResponse_multiplexProgram,
    createMultiplexProgramResponse_httpStatus,
  )
where

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

-- | A request to create a program in a multiplex.
--
-- /See:/ 'newCreateMultiplexProgram'' smart constructor.
data CreateMultiplexProgram' = CreateMultiplexProgram''
  { -- | ID of the multiplex where the program is to be created.
    CreateMultiplexProgram' -> Text
multiplexId :: Prelude.Text,
    -- | Unique request ID. This prevents retries from creating multiple
    -- resources.
    CreateMultiplexProgram' -> Text
requestId :: Prelude.Text,
    -- | The settings for this multiplex program.
    CreateMultiplexProgram' -> MultiplexProgramSettings
multiplexProgramSettings :: MultiplexProgramSettings,
    -- | Name of multiplex program.
    CreateMultiplexProgram' -> Text
programName :: Prelude.Text
  }
  deriving (CreateMultiplexProgram' -> CreateMultiplexProgram' -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateMultiplexProgram' -> CreateMultiplexProgram' -> Bool
$c/= :: CreateMultiplexProgram' -> CreateMultiplexProgram' -> Bool
== :: CreateMultiplexProgram' -> CreateMultiplexProgram' -> Bool
$c== :: CreateMultiplexProgram' -> CreateMultiplexProgram' -> Bool
Prelude.Eq, ReadPrec [CreateMultiplexProgram']
ReadPrec CreateMultiplexProgram'
Int -> ReadS CreateMultiplexProgram'
ReadS [CreateMultiplexProgram']
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateMultiplexProgram']
$creadListPrec :: ReadPrec [CreateMultiplexProgram']
readPrec :: ReadPrec CreateMultiplexProgram'
$creadPrec :: ReadPrec CreateMultiplexProgram'
readList :: ReadS [CreateMultiplexProgram']
$creadList :: ReadS [CreateMultiplexProgram']
readsPrec :: Int -> ReadS CreateMultiplexProgram'
$creadsPrec :: Int -> ReadS CreateMultiplexProgram'
Prelude.Read, Int -> CreateMultiplexProgram' -> ShowS
[CreateMultiplexProgram'] -> ShowS
CreateMultiplexProgram' -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateMultiplexProgram'] -> ShowS
$cshowList :: [CreateMultiplexProgram'] -> ShowS
show :: CreateMultiplexProgram' -> String
$cshow :: CreateMultiplexProgram' -> String
showsPrec :: Int -> CreateMultiplexProgram' -> ShowS
$cshowsPrec :: Int -> CreateMultiplexProgram' -> ShowS
Prelude.Show, forall x. Rep CreateMultiplexProgram' x -> CreateMultiplexProgram'
forall x. CreateMultiplexProgram' -> Rep CreateMultiplexProgram' x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateMultiplexProgram' x -> CreateMultiplexProgram'
$cfrom :: forall x. CreateMultiplexProgram' -> Rep CreateMultiplexProgram' x
Prelude.Generic)

-- |
-- Create a value of 'CreateMultiplexProgram'' 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:
--
-- 'multiplexId', 'createMultiplexProgram'_multiplexId' - ID of the multiplex where the program is to be created.
--
-- 'requestId', 'createMultiplexProgram'_requestId' - Unique request ID. This prevents retries from creating multiple
-- resources.
--
-- 'multiplexProgramSettings', 'createMultiplexProgram'_multiplexProgramSettings' - The settings for this multiplex program.
--
-- 'programName', 'createMultiplexProgram'_programName' - Name of multiplex program.
newCreateMultiplexProgram' ::
  -- | 'multiplexId'
  Prelude.Text ->
  -- | 'requestId'
  Prelude.Text ->
  -- | 'multiplexProgramSettings'
  MultiplexProgramSettings ->
  -- | 'programName'
  Prelude.Text ->
  CreateMultiplexProgram'
newCreateMultiplexProgram' :: Text
-> Text
-> MultiplexProgramSettings
-> Text
-> CreateMultiplexProgram'
newCreateMultiplexProgram'
  Text
pMultiplexId_
  Text
pRequestId_
  MultiplexProgramSettings
pMultiplexProgramSettings_
  Text
pProgramName_ =
    CreateMultiplexProgram''
      { $sel:multiplexId:CreateMultiplexProgram'' :: Text
multiplexId =
          Text
pMultiplexId_,
        $sel:requestId:CreateMultiplexProgram'' :: Text
requestId = Text
pRequestId_,
        $sel:multiplexProgramSettings:CreateMultiplexProgram'' :: MultiplexProgramSettings
multiplexProgramSettings =
          MultiplexProgramSettings
pMultiplexProgramSettings_,
        $sel:programName:CreateMultiplexProgram'' :: Text
programName = Text
pProgramName_
      }

-- | ID of the multiplex where the program is to be created.
createMultiplexProgram'_multiplexId :: Lens.Lens' CreateMultiplexProgram' Prelude.Text
createMultiplexProgram'_multiplexId :: Lens' CreateMultiplexProgram' Text
createMultiplexProgram'_multiplexId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateMultiplexProgram'' {Text
multiplexId :: Text
$sel:multiplexId:CreateMultiplexProgram'' :: CreateMultiplexProgram' -> Text
multiplexId} -> Text
multiplexId) (\s :: CreateMultiplexProgram'
s@CreateMultiplexProgram'' {} Text
a -> CreateMultiplexProgram'
s {$sel:multiplexId:CreateMultiplexProgram'' :: Text
multiplexId = Text
a} :: CreateMultiplexProgram')

-- | Unique request ID. This prevents retries from creating multiple
-- resources.
createMultiplexProgram'_requestId :: Lens.Lens' CreateMultiplexProgram' Prelude.Text
createMultiplexProgram'_requestId :: Lens' CreateMultiplexProgram' Text
createMultiplexProgram'_requestId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateMultiplexProgram'' {Text
requestId :: Text
$sel:requestId:CreateMultiplexProgram'' :: CreateMultiplexProgram' -> Text
requestId} -> Text
requestId) (\s :: CreateMultiplexProgram'
s@CreateMultiplexProgram'' {} Text
a -> CreateMultiplexProgram'
s {$sel:requestId:CreateMultiplexProgram'' :: Text
requestId = Text
a} :: CreateMultiplexProgram')

-- | The settings for this multiplex program.
createMultiplexProgram'_multiplexProgramSettings :: Lens.Lens' CreateMultiplexProgram' MultiplexProgramSettings
createMultiplexProgram'_multiplexProgramSettings :: Lens' CreateMultiplexProgram' MultiplexProgramSettings
createMultiplexProgram'_multiplexProgramSettings = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateMultiplexProgram'' {MultiplexProgramSettings
multiplexProgramSettings :: MultiplexProgramSettings
$sel:multiplexProgramSettings:CreateMultiplexProgram'' :: CreateMultiplexProgram' -> MultiplexProgramSettings
multiplexProgramSettings} -> MultiplexProgramSettings
multiplexProgramSettings) (\s :: CreateMultiplexProgram'
s@CreateMultiplexProgram'' {} MultiplexProgramSettings
a -> CreateMultiplexProgram'
s {$sel:multiplexProgramSettings:CreateMultiplexProgram'' :: MultiplexProgramSettings
multiplexProgramSettings = MultiplexProgramSettings
a} :: CreateMultiplexProgram')

-- | Name of multiplex program.
createMultiplexProgram'_programName :: Lens.Lens' CreateMultiplexProgram' Prelude.Text
createMultiplexProgram'_programName :: Lens' CreateMultiplexProgram' Text
createMultiplexProgram'_programName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateMultiplexProgram'' {Text
programName :: Text
$sel:programName:CreateMultiplexProgram'' :: CreateMultiplexProgram' -> Text
programName} -> Text
programName) (\s :: CreateMultiplexProgram'
s@CreateMultiplexProgram'' {} Text
a -> CreateMultiplexProgram'
s {$sel:programName:CreateMultiplexProgram'' :: Text
programName = Text
a} :: CreateMultiplexProgram')

instance Core.AWSRequest CreateMultiplexProgram' where
  type
    AWSResponse CreateMultiplexProgram' =
      CreateMultiplexProgramResponse
  request :: (Service -> Service)
-> CreateMultiplexProgram' -> Request CreateMultiplexProgram'
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 CreateMultiplexProgram'
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CreateMultiplexProgram')))
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 MultiplexProgram -> Int -> CreateMultiplexProgramResponse
CreateMultiplexProgramResponse'
            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
"multiplexProgram")
            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 CreateMultiplexProgram' where
  hashWithSalt :: Int -> CreateMultiplexProgram' -> Int
hashWithSalt Int
_salt CreateMultiplexProgram'' {Text
MultiplexProgramSettings
programName :: Text
multiplexProgramSettings :: MultiplexProgramSettings
requestId :: Text
multiplexId :: Text
$sel:programName:CreateMultiplexProgram'' :: CreateMultiplexProgram' -> Text
$sel:multiplexProgramSettings:CreateMultiplexProgram'' :: CreateMultiplexProgram' -> MultiplexProgramSettings
$sel:requestId:CreateMultiplexProgram'' :: CreateMultiplexProgram' -> Text
$sel:multiplexId:CreateMultiplexProgram'' :: CreateMultiplexProgram' -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
multiplexId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
requestId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` MultiplexProgramSettings
multiplexProgramSettings
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
programName

instance Prelude.NFData CreateMultiplexProgram' where
  rnf :: CreateMultiplexProgram' -> ()
rnf CreateMultiplexProgram'' {Text
MultiplexProgramSettings
programName :: Text
multiplexProgramSettings :: MultiplexProgramSettings
requestId :: Text
multiplexId :: Text
$sel:programName:CreateMultiplexProgram'' :: CreateMultiplexProgram' -> Text
$sel:multiplexProgramSettings:CreateMultiplexProgram'' :: CreateMultiplexProgram' -> MultiplexProgramSettings
$sel:requestId:CreateMultiplexProgram'' :: CreateMultiplexProgram' -> Text
$sel:multiplexId:CreateMultiplexProgram'' :: CreateMultiplexProgram' -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
multiplexId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
requestId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf MultiplexProgramSettings
multiplexProgramSettings
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
programName

instance Data.ToHeaders CreateMultiplexProgram' where
  toHeaders :: CreateMultiplexProgram' -> 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 CreateMultiplexProgram' where
  toJSON :: CreateMultiplexProgram' -> Value
toJSON CreateMultiplexProgram'' {Text
MultiplexProgramSettings
programName :: Text
multiplexProgramSettings :: MultiplexProgramSettings
requestId :: Text
multiplexId :: Text
$sel:programName:CreateMultiplexProgram'' :: CreateMultiplexProgram' -> Text
$sel:multiplexProgramSettings:CreateMultiplexProgram'' :: CreateMultiplexProgram' -> MultiplexProgramSettings
$sel:requestId:CreateMultiplexProgram'' :: CreateMultiplexProgram' -> Text
$sel:multiplexId:CreateMultiplexProgram'' :: CreateMultiplexProgram' -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just (Key
"requestId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
requestId),
            forall a. a -> Maybe a
Prelude.Just
              ( Key
"multiplexProgramSettings"
                  forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= MultiplexProgramSettings
multiplexProgramSettings
              ),
            forall a. a -> Maybe a
Prelude.Just (Key
"programName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
programName)
          ]
      )

instance Data.ToPath CreateMultiplexProgram' where
  toPath :: CreateMultiplexProgram' -> ByteString
toPath CreateMultiplexProgram'' {Text
MultiplexProgramSettings
programName :: Text
multiplexProgramSettings :: MultiplexProgramSettings
requestId :: Text
multiplexId :: Text
$sel:programName:CreateMultiplexProgram'' :: CreateMultiplexProgram' -> Text
$sel:multiplexProgramSettings:CreateMultiplexProgram'' :: CreateMultiplexProgram' -> MultiplexProgramSettings
$sel:requestId:CreateMultiplexProgram'' :: CreateMultiplexProgram' -> Text
$sel:multiplexId:CreateMultiplexProgram'' :: CreateMultiplexProgram' -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/prod/multiplexes/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
multiplexId,
        ByteString
"/programs"
      ]

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

-- | Placeholder documentation for CreateMultiplexProgramResponse
--
-- /See:/ 'newCreateMultiplexProgramResponse' smart constructor.
data CreateMultiplexProgramResponse = CreateMultiplexProgramResponse'
  { -- | The newly created multiplex program.
    CreateMultiplexProgramResponse -> Maybe MultiplexProgram
multiplexProgram :: Prelude.Maybe MultiplexProgram,
    -- | The response's http status code.
    CreateMultiplexProgramResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateMultiplexProgramResponse
-> CreateMultiplexProgramResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateMultiplexProgramResponse
-> CreateMultiplexProgramResponse -> Bool
$c/= :: CreateMultiplexProgramResponse
-> CreateMultiplexProgramResponse -> Bool
== :: CreateMultiplexProgramResponse
-> CreateMultiplexProgramResponse -> Bool
$c== :: CreateMultiplexProgramResponse
-> CreateMultiplexProgramResponse -> Bool
Prelude.Eq, ReadPrec [CreateMultiplexProgramResponse]
ReadPrec CreateMultiplexProgramResponse
Int -> ReadS CreateMultiplexProgramResponse
ReadS [CreateMultiplexProgramResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateMultiplexProgramResponse]
$creadListPrec :: ReadPrec [CreateMultiplexProgramResponse]
readPrec :: ReadPrec CreateMultiplexProgramResponse
$creadPrec :: ReadPrec CreateMultiplexProgramResponse
readList :: ReadS [CreateMultiplexProgramResponse]
$creadList :: ReadS [CreateMultiplexProgramResponse]
readsPrec :: Int -> ReadS CreateMultiplexProgramResponse
$creadsPrec :: Int -> ReadS CreateMultiplexProgramResponse
Prelude.Read, Int -> CreateMultiplexProgramResponse -> ShowS
[CreateMultiplexProgramResponse] -> ShowS
CreateMultiplexProgramResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateMultiplexProgramResponse] -> ShowS
$cshowList :: [CreateMultiplexProgramResponse] -> ShowS
show :: CreateMultiplexProgramResponse -> String
$cshow :: CreateMultiplexProgramResponse -> String
showsPrec :: Int -> CreateMultiplexProgramResponse -> ShowS
$cshowsPrec :: Int -> CreateMultiplexProgramResponse -> ShowS
Prelude.Show, forall x.
Rep CreateMultiplexProgramResponse x
-> CreateMultiplexProgramResponse
forall x.
CreateMultiplexProgramResponse
-> Rep CreateMultiplexProgramResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateMultiplexProgramResponse x
-> CreateMultiplexProgramResponse
$cfrom :: forall x.
CreateMultiplexProgramResponse
-> Rep CreateMultiplexProgramResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateMultiplexProgramResponse' 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:
--
-- 'multiplexProgram', 'createMultiplexProgramResponse_multiplexProgram' - The newly created multiplex program.
--
-- 'httpStatus', 'createMultiplexProgramResponse_httpStatus' - The response's http status code.
newCreateMultiplexProgramResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateMultiplexProgramResponse
newCreateMultiplexProgramResponse :: Int -> CreateMultiplexProgramResponse
newCreateMultiplexProgramResponse Int
pHttpStatus_ =
  CreateMultiplexProgramResponse'
    { $sel:multiplexProgram:CreateMultiplexProgramResponse' :: Maybe MultiplexProgram
multiplexProgram =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateMultiplexProgramResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The newly created multiplex program.
createMultiplexProgramResponse_multiplexProgram :: Lens.Lens' CreateMultiplexProgramResponse (Prelude.Maybe MultiplexProgram)
createMultiplexProgramResponse_multiplexProgram :: Lens' CreateMultiplexProgramResponse (Maybe MultiplexProgram)
createMultiplexProgramResponse_multiplexProgram = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateMultiplexProgramResponse' {Maybe MultiplexProgram
multiplexProgram :: Maybe MultiplexProgram
$sel:multiplexProgram:CreateMultiplexProgramResponse' :: CreateMultiplexProgramResponse -> Maybe MultiplexProgram
multiplexProgram} -> Maybe MultiplexProgram
multiplexProgram) (\s :: CreateMultiplexProgramResponse
s@CreateMultiplexProgramResponse' {} Maybe MultiplexProgram
a -> CreateMultiplexProgramResponse
s {$sel:multiplexProgram:CreateMultiplexProgramResponse' :: Maybe MultiplexProgram
multiplexProgram = Maybe MultiplexProgram
a} :: CreateMultiplexProgramResponse)

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

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