{-# 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.MediaConnect.Types.AddOutputRequest
-- 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.MediaConnect.Types.AddOutputRequest where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.MediaConnect.Types.Encryption
import Amazonka.MediaConnect.Types.MediaStreamOutputConfigurationRequest
import Amazonka.MediaConnect.Types.Protocol
import Amazonka.MediaConnect.Types.VpcInterfaceAttachment
import qualified Amazonka.Prelude as Prelude

-- | The output that you want to add to this flow.
--
-- /See:/ 'newAddOutputRequest' smart constructor.
data AddOutputRequest = AddOutputRequest'
  { -- | The range of IP addresses that should be allowed to initiate output
    -- requests to this flow. These IP addresses should be in the form of a
    -- Classless Inter-Domain Routing (CIDR) block; for example, 10.0.0.0\/16.
    AddOutputRequest -> Maybe [Text]
cidrAllowList :: Prelude.Maybe [Prelude.Text],
    -- | A description of the output. This description appears only on the AWS
    -- Elemental MediaConnect console and will not be seen by the end user.
    AddOutputRequest -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | The IP address from which video will be sent to output destinations.
    AddOutputRequest -> Maybe Text
destination :: Prelude.Maybe Prelude.Text,
    -- | The type of key used for the encryption. If no keyType is provided, the
    -- service will use the default setting (static-key).
    AddOutputRequest -> Maybe Encryption
encryption :: Prelude.Maybe Encryption,
    -- | The maximum latency in milliseconds. This parameter applies only to
    -- RIST-based, Zixi-based, and Fujitsu-based streams.
    AddOutputRequest -> Maybe Int
maxLatency :: Prelude.Maybe Prelude.Int,
    -- | The media streams that are associated with the output, and the
    -- parameters for those associations.
    AddOutputRequest -> Maybe [MediaStreamOutputConfigurationRequest]
mediaStreamOutputConfigurations :: Prelude.Maybe [MediaStreamOutputConfigurationRequest],
    -- | The minimum latency in milliseconds for SRT-based streams. In streams
    -- that use the SRT protocol, this value that you set on your MediaConnect
    -- source or output represents the minimal potential latency of that
    -- connection. The latency of the stream is set to the highest number
    -- between the sender’s minimum latency and the receiver’s minimum latency.
    AddOutputRequest -> Maybe Int
minLatency :: Prelude.Maybe Prelude.Int,
    -- | The name of the output. This value must be unique within the current
    -- flow.
    AddOutputRequest -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | The port to use when content is distributed to this output.
    AddOutputRequest -> Maybe Int
port :: Prelude.Maybe Prelude.Int,
    -- | The remote ID for the Zixi-pull output stream.
    AddOutputRequest -> Maybe Text
remoteId :: Prelude.Maybe Prelude.Text,
    -- | The port that the flow uses to send outbound requests to initiate
    -- connection with the sender.
    AddOutputRequest -> Maybe Int
senderControlPort :: Prelude.Maybe Prelude.Int,
    -- | The smoothing latency in milliseconds for RIST, RTP, and RTP-FEC
    -- streams.
    AddOutputRequest -> Maybe Int
smoothingLatency :: Prelude.Maybe Prelude.Int,
    -- | The stream ID that you want to use for this transport. This parameter
    -- applies only to Zixi-based streams.
    AddOutputRequest -> Maybe Text
streamId :: Prelude.Maybe Prelude.Text,
    -- | The name of the VPC interface attachment to use for this output.
    AddOutputRequest -> Maybe VpcInterfaceAttachment
vpcInterfaceAttachment :: Prelude.Maybe VpcInterfaceAttachment,
    -- | The protocol to use for the output.
    AddOutputRequest -> Protocol
protocol :: Protocol
  }
  deriving (AddOutputRequest -> AddOutputRequest -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AddOutputRequest -> AddOutputRequest -> Bool
$c/= :: AddOutputRequest -> AddOutputRequest -> Bool
== :: AddOutputRequest -> AddOutputRequest -> Bool
$c== :: AddOutputRequest -> AddOutputRequest -> Bool
Prelude.Eq, ReadPrec [AddOutputRequest]
ReadPrec AddOutputRequest
Int -> ReadS AddOutputRequest
ReadS [AddOutputRequest]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AddOutputRequest]
$creadListPrec :: ReadPrec [AddOutputRequest]
readPrec :: ReadPrec AddOutputRequest
$creadPrec :: ReadPrec AddOutputRequest
readList :: ReadS [AddOutputRequest]
$creadList :: ReadS [AddOutputRequest]
readsPrec :: Int -> ReadS AddOutputRequest
$creadsPrec :: Int -> ReadS AddOutputRequest
Prelude.Read, Int -> AddOutputRequest -> ShowS
[AddOutputRequest] -> ShowS
AddOutputRequest -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AddOutputRequest] -> ShowS
$cshowList :: [AddOutputRequest] -> ShowS
show :: AddOutputRequest -> String
$cshow :: AddOutputRequest -> String
showsPrec :: Int -> AddOutputRequest -> ShowS
$cshowsPrec :: Int -> AddOutputRequest -> ShowS
Prelude.Show, forall x. Rep AddOutputRequest x -> AddOutputRequest
forall x. AddOutputRequest -> Rep AddOutputRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AddOutputRequest x -> AddOutputRequest
$cfrom :: forall x. AddOutputRequest -> Rep AddOutputRequest x
Prelude.Generic)

-- |
-- Create a value of 'AddOutputRequest' 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:
--
-- 'cidrAllowList', 'addOutputRequest_cidrAllowList' - The range of IP addresses that should be allowed to initiate output
-- requests to this flow. These IP addresses should be in the form of a
-- Classless Inter-Domain Routing (CIDR) block; for example, 10.0.0.0\/16.
--
-- 'description', 'addOutputRequest_description' - A description of the output. This description appears only on the AWS
-- Elemental MediaConnect console and will not be seen by the end user.
--
-- 'destination', 'addOutputRequest_destination' - The IP address from which video will be sent to output destinations.
--
-- 'encryption', 'addOutputRequest_encryption' - The type of key used for the encryption. If no keyType is provided, the
-- service will use the default setting (static-key).
--
-- 'maxLatency', 'addOutputRequest_maxLatency' - The maximum latency in milliseconds. This parameter applies only to
-- RIST-based, Zixi-based, and Fujitsu-based streams.
--
-- 'mediaStreamOutputConfigurations', 'addOutputRequest_mediaStreamOutputConfigurations' - The media streams that are associated with the output, and the
-- parameters for those associations.
--
-- 'minLatency', 'addOutputRequest_minLatency' - The minimum latency in milliseconds for SRT-based streams. In streams
-- that use the SRT protocol, this value that you set on your MediaConnect
-- source or output represents the minimal potential latency of that
-- connection. The latency of the stream is set to the highest number
-- between the sender’s minimum latency and the receiver’s minimum latency.
--
-- 'name', 'addOutputRequest_name' - The name of the output. This value must be unique within the current
-- flow.
--
-- 'port', 'addOutputRequest_port' - The port to use when content is distributed to this output.
--
-- 'remoteId', 'addOutputRequest_remoteId' - The remote ID for the Zixi-pull output stream.
--
-- 'senderControlPort', 'addOutputRequest_senderControlPort' - The port that the flow uses to send outbound requests to initiate
-- connection with the sender.
--
-- 'smoothingLatency', 'addOutputRequest_smoothingLatency' - The smoothing latency in milliseconds for RIST, RTP, and RTP-FEC
-- streams.
--
-- 'streamId', 'addOutputRequest_streamId' - The stream ID that you want to use for this transport. This parameter
-- applies only to Zixi-based streams.
--
-- 'vpcInterfaceAttachment', 'addOutputRequest_vpcInterfaceAttachment' - The name of the VPC interface attachment to use for this output.
--
-- 'protocol', 'addOutputRequest_protocol' - The protocol to use for the output.
newAddOutputRequest ::
  -- | 'protocol'
  Protocol ->
  AddOutputRequest
newAddOutputRequest :: Protocol -> AddOutputRequest
newAddOutputRequest Protocol
pProtocol_ =
  AddOutputRequest'
    { $sel:cidrAllowList:AddOutputRequest' :: Maybe [Text]
cidrAllowList = forall a. Maybe a
Prelude.Nothing,
      $sel:description:AddOutputRequest' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:destination:AddOutputRequest' :: Maybe Text
destination = forall a. Maybe a
Prelude.Nothing,
      $sel:encryption:AddOutputRequest' :: Maybe Encryption
encryption = forall a. Maybe a
Prelude.Nothing,
      $sel:maxLatency:AddOutputRequest' :: Maybe Int
maxLatency = forall a. Maybe a
Prelude.Nothing,
      $sel:mediaStreamOutputConfigurations:AddOutputRequest' :: Maybe [MediaStreamOutputConfigurationRequest]
mediaStreamOutputConfigurations = forall a. Maybe a
Prelude.Nothing,
      $sel:minLatency:AddOutputRequest' :: Maybe Int
minLatency = forall a. Maybe a
Prelude.Nothing,
      $sel:name:AddOutputRequest' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:port:AddOutputRequest' :: Maybe Int
port = forall a. Maybe a
Prelude.Nothing,
      $sel:remoteId:AddOutputRequest' :: Maybe Text
remoteId = forall a. Maybe a
Prelude.Nothing,
      $sel:senderControlPort:AddOutputRequest' :: Maybe Int
senderControlPort = forall a. Maybe a
Prelude.Nothing,
      $sel:smoothingLatency:AddOutputRequest' :: Maybe Int
smoothingLatency = forall a. Maybe a
Prelude.Nothing,
      $sel:streamId:AddOutputRequest' :: Maybe Text
streamId = forall a. Maybe a
Prelude.Nothing,
      $sel:vpcInterfaceAttachment:AddOutputRequest' :: Maybe VpcInterfaceAttachment
vpcInterfaceAttachment = forall a. Maybe a
Prelude.Nothing,
      $sel:protocol:AddOutputRequest' :: Protocol
protocol = Protocol
pProtocol_
    }

-- | The range of IP addresses that should be allowed to initiate output
-- requests to this flow. These IP addresses should be in the form of a
-- Classless Inter-Domain Routing (CIDR) block; for example, 10.0.0.0\/16.
addOutputRequest_cidrAllowList :: Lens.Lens' AddOutputRequest (Prelude.Maybe [Prelude.Text])
addOutputRequest_cidrAllowList :: Lens' AddOutputRequest (Maybe [Text])
addOutputRequest_cidrAllowList = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AddOutputRequest' {Maybe [Text]
cidrAllowList :: Maybe [Text]
$sel:cidrAllowList:AddOutputRequest' :: AddOutputRequest -> Maybe [Text]
cidrAllowList} -> Maybe [Text]
cidrAllowList) (\s :: AddOutputRequest
s@AddOutputRequest' {} Maybe [Text]
a -> AddOutputRequest
s {$sel:cidrAllowList:AddOutputRequest' :: Maybe [Text]
cidrAllowList = Maybe [Text]
a} :: AddOutputRequest) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | A description of the output. This description appears only on the AWS
-- Elemental MediaConnect console and will not be seen by the end user.
addOutputRequest_description :: Lens.Lens' AddOutputRequest (Prelude.Maybe Prelude.Text)
addOutputRequest_description :: Lens' AddOutputRequest (Maybe Text)
addOutputRequest_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AddOutputRequest' {Maybe Text
description :: Maybe Text
$sel:description:AddOutputRequest' :: AddOutputRequest -> Maybe Text
description} -> Maybe Text
description) (\s :: AddOutputRequest
s@AddOutputRequest' {} Maybe Text
a -> AddOutputRequest
s {$sel:description:AddOutputRequest' :: Maybe Text
description = Maybe Text
a} :: AddOutputRequest)

-- | The IP address from which video will be sent to output destinations.
addOutputRequest_destination :: Lens.Lens' AddOutputRequest (Prelude.Maybe Prelude.Text)
addOutputRequest_destination :: Lens' AddOutputRequest (Maybe Text)
addOutputRequest_destination = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AddOutputRequest' {Maybe Text
destination :: Maybe Text
$sel:destination:AddOutputRequest' :: AddOutputRequest -> Maybe Text
destination} -> Maybe Text
destination) (\s :: AddOutputRequest
s@AddOutputRequest' {} Maybe Text
a -> AddOutputRequest
s {$sel:destination:AddOutputRequest' :: Maybe Text
destination = Maybe Text
a} :: AddOutputRequest)

-- | The type of key used for the encryption. If no keyType is provided, the
-- service will use the default setting (static-key).
addOutputRequest_encryption :: Lens.Lens' AddOutputRequest (Prelude.Maybe Encryption)
addOutputRequest_encryption :: Lens' AddOutputRequest (Maybe Encryption)
addOutputRequest_encryption = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AddOutputRequest' {Maybe Encryption
encryption :: Maybe Encryption
$sel:encryption:AddOutputRequest' :: AddOutputRequest -> Maybe Encryption
encryption} -> Maybe Encryption
encryption) (\s :: AddOutputRequest
s@AddOutputRequest' {} Maybe Encryption
a -> AddOutputRequest
s {$sel:encryption:AddOutputRequest' :: Maybe Encryption
encryption = Maybe Encryption
a} :: AddOutputRequest)

-- | The maximum latency in milliseconds. This parameter applies only to
-- RIST-based, Zixi-based, and Fujitsu-based streams.
addOutputRequest_maxLatency :: Lens.Lens' AddOutputRequest (Prelude.Maybe Prelude.Int)
addOutputRequest_maxLatency :: Lens' AddOutputRequest (Maybe Int)
addOutputRequest_maxLatency = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AddOutputRequest' {Maybe Int
maxLatency :: Maybe Int
$sel:maxLatency:AddOutputRequest' :: AddOutputRequest -> Maybe Int
maxLatency} -> Maybe Int
maxLatency) (\s :: AddOutputRequest
s@AddOutputRequest' {} Maybe Int
a -> AddOutputRequest
s {$sel:maxLatency:AddOutputRequest' :: Maybe Int
maxLatency = Maybe Int
a} :: AddOutputRequest)

-- | The media streams that are associated with the output, and the
-- parameters for those associations.
addOutputRequest_mediaStreamOutputConfigurations :: Lens.Lens' AddOutputRequest (Prelude.Maybe [MediaStreamOutputConfigurationRequest])
addOutputRequest_mediaStreamOutputConfigurations :: Lens'
  AddOutputRequest (Maybe [MediaStreamOutputConfigurationRequest])
addOutputRequest_mediaStreamOutputConfigurations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AddOutputRequest' {Maybe [MediaStreamOutputConfigurationRequest]
mediaStreamOutputConfigurations :: Maybe [MediaStreamOutputConfigurationRequest]
$sel:mediaStreamOutputConfigurations:AddOutputRequest' :: AddOutputRequest -> Maybe [MediaStreamOutputConfigurationRequest]
mediaStreamOutputConfigurations} -> Maybe [MediaStreamOutputConfigurationRequest]
mediaStreamOutputConfigurations) (\s :: AddOutputRequest
s@AddOutputRequest' {} Maybe [MediaStreamOutputConfigurationRequest]
a -> AddOutputRequest
s {$sel:mediaStreamOutputConfigurations:AddOutputRequest' :: Maybe [MediaStreamOutputConfigurationRequest]
mediaStreamOutputConfigurations = Maybe [MediaStreamOutputConfigurationRequest]
a} :: AddOutputRequest) 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 minimum latency in milliseconds for SRT-based streams. In streams
-- that use the SRT protocol, this value that you set on your MediaConnect
-- source or output represents the minimal potential latency of that
-- connection. The latency of the stream is set to the highest number
-- between the sender’s minimum latency and the receiver’s minimum latency.
addOutputRequest_minLatency :: Lens.Lens' AddOutputRequest (Prelude.Maybe Prelude.Int)
addOutputRequest_minLatency :: Lens' AddOutputRequest (Maybe Int)
addOutputRequest_minLatency = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AddOutputRequest' {Maybe Int
minLatency :: Maybe Int
$sel:minLatency:AddOutputRequest' :: AddOutputRequest -> Maybe Int
minLatency} -> Maybe Int
minLatency) (\s :: AddOutputRequest
s@AddOutputRequest' {} Maybe Int
a -> AddOutputRequest
s {$sel:minLatency:AddOutputRequest' :: Maybe Int
minLatency = Maybe Int
a} :: AddOutputRequest)

-- | The name of the output. This value must be unique within the current
-- flow.
addOutputRequest_name :: Lens.Lens' AddOutputRequest (Prelude.Maybe Prelude.Text)
addOutputRequest_name :: Lens' AddOutputRequest (Maybe Text)
addOutputRequest_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AddOutputRequest' {Maybe Text
name :: Maybe Text
$sel:name:AddOutputRequest' :: AddOutputRequest -> Maybe Text
name} -> Maybe Text
name) (\s :: AddOutputRequest
s@AddOutputRequest' {} Maybe Text
a -> AddOutputRequest
s {$sel:name:AddOutputRequest' :: Maybe Text
name = Maybe Text
a} :: AddOutputRequest)

-- | The port to use when content is distributed to this output.
addOutputRequest_port :: Lens.Lens' AddOutputRequest (Prelude.Maybe Prelude.Int)
addOutputRequest_port :: Lens' AddOutputRequest (Maybe Int)
addOutputRequest_port = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AddOutputRequest' {Maybe Int
port :: Maybe Int
$sel:port:AddOutputRequest' :: AddOutputRequest -> Maybe Int
port} -> Maybe Int
port) (\s :: AddOutputRequest
s@AddOutputRequest' {} Maybe Int
a -> AddOutputRequest
s {$sel:port:AddOutputRequest' :: Maybe Int
port = Maybe Int
a} :: AddOutputRequest)

-- | The remote ID for the Zixi-pull output stream.
addOutputRequest_remoteId :: Lens.Lens' AddOutputRequest (Prelude.Maybe Prelude.Text)
addOutputRequest_remoteId :: Lens' AddOutputRequest (Maybe Text)
addOutputRequest_remoteId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AddOutputRequest' {Maybe Text
remoteId :: Maybe Text
$sel:remoteId:AddOutputRequest' :: AddOutputRequest -> Maybe Text
remoteId} -> Maybe Text
remoteId) (\s :: AddOutputRequest
s@AddOutputRequest' {} Maybe Text
a -> AddOutputRequest
s {$sel:remoteId:AddOutputRequest' :: Maybe Text
remoteId = Maybe Text
a} :: AddOutputRequest)

-- | The port that the flow uses to send outbound requests to initiate
-- connection with the sender.
addOutputRequest_senderControlPort :: Lens.Lens' AddOutputRequest (Prelude.Maybe Prelude.Int)
addOutputRequest_senderControlPort :: Lens' AddOutputRequest (Maybe Int)
addOutputRequest_senderControlPort = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AddOutputRequest' {Maybe Int
senderControlPort :: Maybe Int
$sel:senderControlPort:AddOutputRequest' :: AddOutputRequest -> Maybe Int
senderControlPort} -> Maybe Int
senderControlPort) (\s :: AddOutputRequest
s@AddOutputRequest' {} Maybe Int
a -> AddOutputRequest
s {$sel:senderControlPort:AddOutputRequest' :: Maybe Int
senderControlPort = Maybe Int
a} :: AddOutputRequest)

-- | The smoothing latency in milliseconds for RIST, RTP, and RTP-FEC
-- streams.
addOutputRequest_smoothingLatency :: Lens.Lens' AddOutputRequest (Prelude.Maybe Prelude.Int)
addOutputRequest_smoothingLatency :: Lens' AddOutputRequest (Maybe Int)
addOutputRequest_smoothingLatency = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AddOutputRequest' {Maybe Int
smoothingLatency :: Maybe Int
$sel:smoothingLatency:AddOutputRequest' :: AddOutputRequest -> Maybe Int
smoothingLatency} -> Maybe Int
smoothingLatency) (\s :: AddOutputRequest
s@AddOutputRequest' {} Maybe Int
a -> AddOutputRequest
s {$sel:smoothingLatency:AddOutputRequest' :: Maybe Int
smoothingLatency = Maybe Int
a} :: AddOutputRequest)

-- | The stream ID that you want to use for this transport. This parameter
-- applies only to Zixi-based streams.
addOutputRequest_streamId :: Lens.Lens' AddOutputRequest (Prelude.Maybe Prelude.Text)
addOutputRequest_streamId :: Lens' AddOutputRequest (Maybe Text)
addOutputRequest_streamId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AddOutputRequest' {Maybe Text
streamId :: Maybe Text
$sel:streamId:AddOutputRequest' :: AddOutputRequest -> Maybe Text
streamId} -> Maybe Text
streamId) (\s :: AddOutputRequest
s@AddOutputRequest' {} Maybe Text
a -> AddOutputRequest
s {$sel:streamId:AddOutputRequest' :: Maybe Text
streamId = Maybe Text
a} :: AddOutputRequest)

-- | The name of the VPC interface attachment to use for this output.
addOutputRequest_vpcInterfaceAttachment :: Lens.Lens' AddOutputRequest (Prelude.Maybe VpcInterfaceAttachment)
addOutputRequest_vpcInterfaceAttachment :: Lens' AddOutputRequest (Maybe VpcInterfaceAttachment)
addOutputRequest_vpcInterfaceAttachment = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AddOutputRequest' {Maybe VpcInterfaceAttachment
vpcInterfaceAttachment :: Maybe VpcInterfaceAttachment
$sel:vpcInterfaceAttachment:AddOutputRequest' :: AddOutputRequest -> Maybe VpcInterfaceAttachment
vpcInterfaceAttachment} -> Maybe VpcInterfaceAttachment
vpcInterfaceAttachment) (\s :: AddOutputRequest
s@AddOutputRequest' {} Maybe VpcInterfaceAttachment
a -> AddOutputRequest
s {$sel:vpcInterfaceAttachment:AddOutputRequest' :: Maybe VpcInterfaceAttachment
vpcInterfaceAttachment = Maybe VpcInterfaceAttachment
a} :: AddOutputRequest)

-- | The protocol to use for the output.
addOutputRequest_protocol :: Lens.Lens' AddOutputRequest Protocol
addOutputRequest_protocol :: Lens' AddOutputRequest Protocol
addOutputRequest_protocol = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AddOutputRequest' {Protocol
protocol :: Protocol
$sel:protocol:AddOutputRequest' :: AddOutputRequest -> Protocol
protocol} -> Protocol
protocol) (\s :: AddOutputRequest
s@AddOutputRequest' {} Protocol
a -> AddOutputRequest
s {$sel:protocol:AddOutputRequest' :: Protocol
protocol = Protocol
a} :: AddOutputRequest)

instance Prelude.Hashable AddOutputRequest where
  hashWithSalt :: Int -> AddOutputRequest -> Int
hashWithSalt Int
_salt AddOutputRequest' {Maybe Int
Maybe [Text]
Maybe [MediaStreamOutputConfigurationRequest]
Maybe Text
Maybe Encryption
Maybe VpcInterfaceAttachment
Protocol
protocol :: Protocol
vpcInterfaceAttachment :: Maybe VpcInterfaceAttachment
streamId :: Maybe Text
smoothingLatency :: Maybe Int
senderControlPort :: Maybe Int
remoteId :: Maybe Text
port :: Maybe Int
name :: Maybe Text
minLatency :: Maybe Int
mediaStreamOutputConfigurations :: Maybe [MediaStreamOutputConfigurationRequest]
maxLatency :: Maybe Int
encryption :: Maybe Encryption
destination :: Maybe Text
description :: Maybe Text
cidrAllowList :: Maybe [Text]
$sel:protocol:AddOutputRequest' :: AddOutputRequest -> Protocol
$sel:vpcInterfaceAttachment:AddOutputRequest' :: AddOutputRequest -> Maybe VpcInterfaceAttachment
$sel:streamId:AddOutputRequest' :: AddOutputRequest -> Maybe Text
$sel:smoothingLatency:AddOutputRequest' :: AddOutputRequest -> Maybe Int
$sel:senderControlPort:AddOutputRequest' :: AddOutputRequest -> Maybe Int
$sel:remoteId:AddOutputRequest' :: AddOutputRequest -> Maybe Text
$sel:port:AddOutputRequest' :: AddOutputRequest -> Maybe Int
$sel:name:AddOutputRequest' :: AddOutputRequest -> Maybe Text
$sel:minLatency:AddOutputRequest' :: AddOutputRequest -> Maybe Int
$sel:mediaStreamOutputConfigurations:AddOutputRequest' :: AddOutputRequest -> Maybe [MediaStreamOutputConfigurationRequest]
$sel:maxLatency:AddOutputRequest' :: AddOutputRequest -> Maybe Int
$sel:encryption:AddOutputRequest' :: AddOutputRequest -> Maybe Encryption
$sel:destination:AddOutputRequest' :: AddOutputRequest -> Maybe Text
$sel:description:AddOutputRequest' :: AddOutputRequest -> Maybe Text
$sel:cidrAllowList:AddOutputRequest' :: AddOutputRequest -> Maybe [Text]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
cidrAllowList
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
destination
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Encryption
encryption
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
maxLatency
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [MediaStreamOutputConfigurationRequest]
mediaStreamOutputConfigurations
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
minLatency
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
port
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
remoteId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
senderControlPort
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
smoothingLatency
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
streamId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe VpcInterfaceAttachment
vpcInterfaceAttachment
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Protocol
protocol

instance Prelude.NFData AddOutputRequest where
  rnf :: AddOutputRequest -> ()
rnf AddOutputRequest' {Maybe Int
Maybe [Text]
Maybe [MediaStreamOutputConfigurationRequest]
Maybe Text
Maybe Encryption
Maybe VpcInterfaceAttachment
Protocol
protocol :: Protocol
vpcInterfaceAttachment :: Maybe VpcInterfaceAttachment
streamId :: Maybe Text
smoothingLatency :: Maybe Int
senderControlPort :: Maybe Int
remoteId :: Maybe Text
port :: Maybe Int
name :: Maybe Text
minLatency :: Maybe Int
mediaStreamOutputConfigurations :: Maybe [MediaStreamOutputConfigurationRequest]
maxLatency :: Maybe Int
encryption :: Maybe Encryption
destination :: Maybe Text
description :: Maybe Text
cidrAllowList :: Maybe [Text]
$sel:protocol:AddOutputRequest' :: AddOutputRequest -> Protocol
$sel:vpcInterfaceAttachment:AddOutputRequest' :: AddOutputRequest -> Maybe VpcInterfaceAttachment
$sel:streamId:AddOutputRequest' :: AddOutputRequest -> Maybe Text
$sel:smoothingLatency:AddOutputRequest' :: AddOutputRequest -> Maybe Int
$sel:senderControlPort:AddOutputRequest' :: AddOutputRequest -> Maybe Int
$sel:remoteId:AddOutputRequest' :: AddOutputRequest -> Maybe Text
$sel:port:AddOutputRequest' :: AddOutputRequest -> Maybe Int
$sel:name:AddOutputRequest' :: AddOutputRequest -> Maybe Text
$sel:minLatency:AddOutputRequest' :: AddOutputRequest -> Maybe Int
$sel:mediaStreamOutputConfigurations:AddOutputRequest' :: AddOutputRequest -> Maybe [MediaStreamOutputConfigurationRequest]
$sel:maxLatency:AddOutputRequest' :: AddOutputRequest -> Maybe Int
$sel:encryption:AddOutputRequest' :: AddOutputRequest -> Maybe Encryption
$sel:destination:AddOutputRequest' :: AddOutputRequest -> Maybe Text
$sel:description:AddOutputRequest' :: AddOutputRequest -> Maybe Text
$sel:cidrAllowList:AddOutputRequest' :: AddOutputRequest -> Maybe [Text]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
cidrAllowList
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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 Text
destination
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Encryption
encryption
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
maxLatency
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [MediaStreamOutputConfigurationRequest]
mediaStreamOutputConfigurations
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
minLatency
      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 Int
port
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
remoteId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
senderControlPort
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
smoothingLatency
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
streamId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe VpcInterfaceAttachment
vpcInterfaceAttachment
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Protocol
protocol

instance Data.ToJSON AddOutputRequest where
  toJSON :: AddOutputRequest -> Value
toJSON AddOutputRequest' {Maybe Int
Maybe [Text]
Maybe [MediaStreamOutputConfigurationRequest]
Maybe Text
Maybe Encryption
Maybe VpcInterfaceAttachment
Protocol
protocol :: Protocol
vpcInterfaceAttachment :: Maybe VpcInterfaceAttachment
streamId :: Maybe Text
smoothingLatency :: Maybe Int
senderControlPort :: Maybe Int
remoteId :: Maybe Text
port :: Maybe Int
name :: Maybe Text
minLatency :: Maybe Int
mediaStreamOutputConfigurations :: Maybe [MediaStreamOutputConfigurationRequest]
maxLatency :: Maybe Int
encryption :: Maybe Encryption
destination :: Maybe Text
description :: Maybe Text
cidrAllowList :: Maybe [Text]
$sel:protocol:AddOutputRequest' :: AddOutputRequest -> Protocol
$sel:vpcInterfaceAttachment:AddOutputRequest' :: AddOutputRequest -> Maybe VpcInterfaceAttachment
$sel:streamId:AddOutputRequest' :: AddOutputRequest -> Maybe Text
$sel:smoothingLatency:AddOutputRequest' :: AddOutputRequest -> Maybe Int
$sel:senderControlPort:AddOutputRequest' :: AddOutputRequest -> Maybe Int
$sel:remoteId:AddOutputRequest' :: AddOutputRequest -> Maybe Text
$sel:port:AddOutputRequest' :: AddOutputRequest -> Maybe Int
$sel:name:AddOutputRequest' :: AddOutputRequest -> Maybe Text
$sel:minLatency:AddOutputRequest' :: AddOutputRequest -> Maybe Int
$sel:mediaStreamOutputConfigurations:AddOutputRequest' :: AddOutputRequest -> Maybe [MediaStreamOutputConfigurationRequest]
$sel:maxLatency:AddOutputRequest' :: AddOutputRequest -> Maybe Int
$sel:encryption:AddOutputRequest' :: AddOutputRequest -> Maybe Encryption
$sel:destination:AddOutputRequest' :: AddOutputRequest -> Maybe Text
$sel:description:AddOutputRequest' :: AddOutputRequest -> Maybe Text
$sel:cidrAllowList:AddOutputRequest' :: AddOutputRequest -> Maybe [Text]
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"cidrAllowList" 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]
cidrAllowList,
            (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
"destination" 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
destination,
            (Key
"encryption" 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 Encryption
encryption,
            (Key
"maxLatency" 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 Int
maxLatency,
            (Key
"mediaStreamOutputConfigurations" 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 [MediaStreamOutputConfigurationRequest]
mediaStreamOutputConfigurations,
            (Key
"minLatency" 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 Int
minLatency,
            (Key
"name" 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
name,
            (Key
"port" 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 Int
port,
            (Key
"remoteId" 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
remoteId,
            (Key
"senderControlPort" 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 Int
senderControlPort,
            (Key
"smoothingLatency" 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 Int
smoothingLatency,
            (Key
"streamId" 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
streamId,
            (Key
"vpcInterfaceAttachment" 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 VpcInterfaceAttachment
vpcInterfaceAttachment,
            forall a. a -> Maybe a
Prelude.Just (Key
"protocol" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Protocol
protocol)
          ]
      )