{-# 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 #-}
module Amazonka.MediaLive.Types.ChannelSummary 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.CdiInputSpecification
import Amazonka.MediaLive.Types.ChannelClass
import Amazonka.MediaLive.Types.ChannelEgressEndpoint
import Amazonka.MediaLive.Types.ChannelState
import Amazonka.MediaLive.Types.InputAttachment
import Amazonka.MediaLive.Types.InputSpecification
import Amazonka.MediaLive.Types.LogLevel
import Amazonka.MediaLive.Types.MaintenanceStatus
import Amazonka.MediaLive.Types.OutputDestination
import Amazonka.MediaLive.Types.VpcOutputSettingsDescription
import qualified Amazonka.Prelude as Prelude
data ChannelSummary = ChannelSummary'
{
ChannelSummary -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
ChannelSummary -> Maybe CdiInputSpecification
cdiInputSpecification :: Prelude.Maybe CdiInputSpecification,
ChannelSummary -> Maybe ChannelClass
channelClass :: Prelude.Maybe ChannelClass,
ChannelSummary -> Maybe [OutputDestination]
destinations :: Prelude.Maybe [OutputDestination],
ChannelSummary -> Maybe [ChannelEgressEndpoint]
egressEndpoints :: Prelude.Maybe [ChannelEgressEndpoint],
ChannelSummary -> Maybe Text
id :: Prelude.Maybe Prelude.Text,
ChannelSummary -> Maybe [InputAttachment]
inputAttachments :: Prelude.Maybe [InputAttachment],
ChannelSummary -> Maybe InputSpecification
inputSpecification :: Prelude.Maybe InputSpecification,
ChannelSummary -> Maybe LogLevel
logLevel :: Prelude.Maybe LogLevel,
ChannelSummary -> Maybe MaintenanceStatus
maintenance :: Prelude.Maybe MaintenanceStatus,
ChannelSummary -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
ChannelSummary -> Maybe Int
pipelinesRunningCount :: Prelude.Maybe Prelude.Int,
ChannelSummary -> Maybe Text
roleArn :: Prelude.Maybe Prelude.Text,
ChannelSummary -> Maybe ChannelState
state :: Prelude.Maybe ChannelState,
ChannelSummary -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
ChannelSummary -> Maybe VpcOutputSettingsDescription
vpc :: Prelude.Maybe VpcOutputSettingsDescription
}
deriving (ChannelSummary -> ChannelSummary -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ChannelSummary -> ChannelSummary -> Bool
$c/= :: ChannelSummary -> ChannelSummary -> Bool
== :: ChannelSummary -> ChannelSummary -> Bool
$c== :: ChannelSummary -> ChannelSummary -> Bool
Prelude.Eq, ReadPrec [ChannelSummary]
ReadPrec ChannelSummary
Int -> ReadS ChannelSummary
ReadS [ChannelSummary]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ChannelSummary]
$creadListPrec :: ReadPrec [ChannelSummary]
readPrec :: ReadPrec ChannelSummary
$creadPrec :: ReadPrec ChannelSummary
readList :: ReadS [ChannelSummary]
$creadList :: ReadS [ChannelSummary]
readsPrec :: Int -> ReadS ChannelSummary
$creadsPrec :: Int -> ReadS ChannelSummary
Prelude.Read, Int -> ChannelSummary -> ShowS
[ChannelSummary] -> ShowS
ChannelSummary -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ChannelSummary] -> ShowS
$cshowList :: [ChannelSummary] -> ShowS
show :: ChannelSummary -> String
$cshow :: ChannelSummary -> String
showsPrec :: Int -> ChannelSummary -> ShowS
$cshowsPrec :: Int -> ChannelSummary -> ShowS
Prelude.Show, forall x. Rep ChannelSummary x -> ChannelSummary
forall x. ChannelSummary -> Rep ChannelSummary x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ChannelSummary x -> ChannelSummary
$cfrom :: forall x. ChannelSummary -> Rep ChannelSummary x
Prelude.Generic)
newChannelSummary ::
ChannelSummary
newChannelSummary :: ChannelSummary
newChannelSummary =
ChannelSummary'
{ $sel:arn:ChannelSummary' :: Maybe Text
arn = forall a. Maybe a
Prelude.Nothing,
$sel:cdiInputSpecification:ChannelSummary' :: Maybe CdiInputSpecification
cdiInputSpecification = forall a. Maybe a
Prelude.Nothing,
$sel:channelClass:ChannelSummary' :: Maybe ChannelClass
channelClass = forall a. Maybe a
Prelude.Nothing,
$sel:destinations:ChannelSummary' :: Maybe [OutputDestination]
destinations = forall a. Maybe a
Prelude.Nothing,
$sel:egressEndpoints:ChannelSummary' :: Maybe [ChannelEgressEndpoint]
egressEndpoints = forall a. Maybe a
Prelude.Nothing,
$sel:id:ChannelSummary' :: Maybe Text
id = forall a. Maybe a
Prelude.Nothing,
$sel:inputAttachments:ChannelSummary' :: Maybe [InputAttachment]
inputAttachments = forall a. Maybe a
Prelude.Nothing,
$sel:inputSpecification:ChannelSummary' :: Maybe InputSpecification
inputSpecification = forall a. Maybe a
Prelude.Nothing,
$sel:logLevel:ChannelSummary' :: Maybe LogLevel
logLevel = forall a. Maybe a
Prelude.Nothing,
$sel:maintenance:ChannelSummary' :: Maybe MaintenanceStatus
maintenance = forall a. Maybe a
Prelude.Nothing,
$sel:name:ChannelSummary' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
$sel:pipelinesRunningCount:ChannelSummary' :: Maybe Int
pipelinesRunningCount = forall a. Maybe a
Prelude.Nothing,
$sel:roleArn:ChannelSummary' :: Maybe Text
roleArn = forall a. Maybe a
Prelude.Nothing,
$sel:state:ChannelSummary' :: Maybe ChannelState
state = forall a. Maybe a
Prelude.Nothing,
$sel:tags:ChannelSummary' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
$sel:vpc:ChannelSummary' :: Maybe VpcOutputSettingsDescription
vpc = forall a. Maybe a
Prelude.Nothing
}
channelSummary_arn :: Lens.Lens' ChannelSummary (Prelude.Maybe Prelude.Text)
channelSummary_arn :: Lens' ChannelSummary (Maybe Text)
channelSummary_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ChannelSummary' {Maybe Text
arn :: Maybe Text
$sel:arn:ChannelSummary' :: ChannelSummary -> Maybe Text
arn} -> Maybe Text
arn) (\s :: ChannelSummary
s@ChannelSummary' {} Maybe Text
a -> ChannelSummary
s {$sel:arn:ChannelSummary' :: Maybe Text
arn = Maybe Text
a} :: ChannelSummary)
channelSummary_cdiInputSpecification :: Lens.Lens' ChannelSummary (Prelude.Maybe CdiInputSpecification)
channelSummary_cdiInputSpecification :: Lens' ChannelSummary (Maybe CdiInputSpecification)
channelSummary_cdiInputSpecification = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ChannelSummary' {Maybe CdiInputSpecification
cdiInputSpecification :: Maybe CdiInputSpecification
$sel:cdiInputSpecification:ChannelSummary' :: ChannelSummary -> Maybe CdiInputSpecification
cdiInputSpecification} -> Maybe CdiInputSpecification
cdiInputSpecification) (\s :: ChannelSummary
s@ChannelSummary' {} Maybe CdiInputSpecification
a -> ChannelSummary
s {$sel:cdiInputSpecification:ChannelSummary' :: Maybe CdiInputSpecification
cdiInputSpecification = Maybe CdiInputSpecification
a} :: ChannelSummary)
channelSummary_channelClass :: Lens.Lens' ChannelSummary (Prelude.Maybe ChannelClass)
channelSummary_channelClass :: Lens' ChannelSummary (Maybe ChannelClass)
channelSummary_channelClass = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ChannelSummary' {Maybe ChannelClass
channelClass :: Maybe ChannelClass
$sel:channelClass:ChannelSummary' :: ChannelSummary -> Maybe ChannelClass
channelClass} -> Maybe ChannelClass
channelClass) (\s :: ChannelSummary
s@ChannelSummary' {} Maybe ChannelClass
a -> ChannelSummary
s {$sel:channelClass:ChannelSummary' :: Maybe ChannelClass
channelClass = Maybe ChannelClass
a} :: ChannelSummary)
channelSummary_destinations :: Lens.Lens' ChannelSummary (Prelude.Maybe [OutputDestination])
channelSummary_destinations :: Lens' ChannelSummary (Maybe [OutputDestination])
channelSummary_destinations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ChannelSummary' {Maybe [OutputDestination]
destinations :: Maybe [OutputDestination]
$sel:destinations:ChannelSummary' :: ChannelSummary -> Maybe [OutputDestination]
destinations} -> Maybe [OutputDestination]
destinations) (\s :: ChannelSummary
s@ChannelSummary' {} Maybe [OutputDestination]
a -> ChannelSummary
s {$sel:destinations:ChannelSummary' :: Maybe [OutputDestination]
destinations = Maybe [OutputDestination]
a} :: ChannelSummary) 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
channelSummary_egressEndpoints :: Lens.Lens' ChannelSummary (Prelude.Maybe [ChannelEgressEndpoint])
channelSummary_egressEndpoints :: Lens' ChannelSummary (Maybe [ChannelEgressEndpoint])
channelSummary_egressEndpoints = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ChannelSummary' {Maybe [ChannelEgressEndpoint]
egressEndpoints :: Maybe [ChannelEgressEndpoint]
$sel:egressEndpoints:ChannelSummary' :: ChannelSummary -> Maybe [ChannelEgressEndpoint]
egressEndpoints} -> Maybe [ChannelEgressEndpoint]
egressEndpoints) (\s :: ChannelSummary
s@ChannelSummary' {} Maybe [ChannelEgressEndpoint]
a -> ChannelSummary
s {$sel:egressEndpoints:ChannelSummary' :: Maybe [ChannelEgressEndpoint]
egressEndpoints = Maybe [ChannelEgressEndpoint]
a} :: ChannelSummary) 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
channelSummary_id :: Lens.Lens' ChannelSummary (Prelude.Maybe Prelude.Text)
channelSummary_id :: Lens' ChannelSummary (Maybe Text)
channelSummary_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ChannelSummary' {Maybe Text
id :: Maybe Text
$sel:id:ChannelSummary' :: ChannelSummary -> Maybe Text
id} -> Maybe Text
id) (\s :: ChannelSummary
s@ChannelSummary' {} Maybe Text
a -> ChannelSummary
s {$sel:id:ChannelSummary' :: Maybe Text
id = Maybe Text
a} :: ChannelSummary)
channelSummary_inputAttachments :: Lens.Lens' ChannelSummary (Prelude.Maybe [InputAttachment])
channelSummary_inputAttachments :: Lens' ChannelSummary (Maybe [InputAttachment])
channelSummary_inputAttachments = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ChannelSummary' {Maybe [InputAttachment]
inputAttachments :: Maybe [InputAttachment]
$sel:inputAttachments:ChannelSummary' :: ChannelSummary -> Maybe [InputAttachment]
inputAttachments} -> Maybe [InputAttachment]
inputAttachments) (\s :: ChannelSummary
s@ChannelSummary' {} Maybe [InputAttachment]
a -> ChannelSummary
s {$sel:inputAttachments:ChannelSummary' :: Maybe [InputAttachment]
inputAttachments = Maybe [InputAttachment]
a} :: ChannelSummary) 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
channelSummary_inputSpecification :: Lens.Lens' ChannelSummary (Prelude.Maybe InputSpecification)
channelSummary_inputSpecification :: Lens' ChannelSummary (Maybe InputSpecification)
channelSummary_inputSpecification = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ChannelSummary' {Maybe InputSpecification
inputSpecification :: Maybe InputSpecification
$sel:inputSpecification:ChannelSummary' :: ChannelSummary -> Maybe InputSpecification
inputSpecification} -> Maybe InputSpecification
inputSpecification) (\s :: ChannelSummary
s@ChannelSummary' {} Maybe InputSpecification
a -> ChannelSummary
s {$sel:inputSpecification:ChannelSummary' :: Maybe InputSpecification
inputSpecification = Maybe InputSpecification
a} :: ChannelSummary)
channelSummary_logLevel :: Lens.Lens' ChannelSummary (Prelude.Maybe LogLevel)
channelSummary_logLevel :: Lens' ChannelSummary (Maybe LogLevel)
channelSummary_logLevel = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ChannelSummary' {Maybe LogLevel
logLevel :: Maybe LogLevel
$sel:logLevel:ChannelSummary' :: ChannelSummary -> Maybe LogLevel
logLevel} -> Maybe LogLevel
logLevel) (\s :: ChannelSummary
s@ChannelSummary' {} Maybe LogLevel
a -> ChannelSummary
s {$sel:logLevel:ChannelSummary' :: Maybe LogLevel
logLevel = Maybe LogLevel
a} :: ChannelSummary)
channelSummary_maintenance :: Lens.Lens' ChannelSummary (Prelude.Maybe MaintenanceStatus)
channelSummary_maintenance :: Lens' ChannelSummary (Maybe MaintenanceStatus)
channelSummary_maintenance = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ChannelSummary' {Maybe MaintenanceStatus
maintenance :: Maybe MaintenanceStatus
$sel:maintenance:ChannelSummary' :: ChannelSummary -> Maybe MaintenanceStatus
maintenance} -> Maybe MaintenanceStatus
maintenance) (\s :: ChannelSummary
s@ChannelSummary' {} Maybe MaintenanceStatus
a -> ChannelSummary
s {$sel:maintenance:ChannelSummary' :: Maybe MaintenanceStatus
maintenance = Maybe MaintenanceStatus
a} :: ChannelSummary)
channelSummary_name :: Lens.Lens' ChannelSummary (Prelude.Maybe Prelude.Text)
channelSummary_name :: Lens' ChannelSummary (Maybe Text)
channelSummary_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ChannelSummary' {Maybe Text
name :: Maybe Text
$sel:name:ChannelSummary' :: ChannelSummary -> Maybe Text
name} -> Maybe Text
name) (\s :: ChannelSummary
s@ChannelSummary' {} Maybe Text
a -> ChannelSummary
s {$sel:name:ChannelSummary' :: Maybe Text
name = Maybe Text
a} :: ChannelSummary)
channelSummary_pipelinesRunningCount :: Lens.Lens' ChannelSummary (Prelude.Maybe Prelude.Int)
channelSummary_pipelinesRunningCount :: Lens' ChannelSummary (Maybe Int)
channelSummary_pipelinesRunningCount = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ChannelSummary' {Maybe Int
pipelinesRunningCount :: Maybe Int
$sel:pipelinesRunningCount:ChannelSummary' :: ChannelSummary -> Maybe Int
pipelinesRunningCount} -> Maybe Int
pipelinesRunningCount) (\s :: ChannelSummary
s@ChannelSummary' {} Maybe Int
a -> ChannelSummary
s {$sel:pipelinesRunningCount:ChannelSummary' :: Maybe Int
pipelinesRunningCount = Maybe Int
a} :: ChannelSummary)
channelSummary_roleArn :: Lens.Lens' ChannelSummary (Prelude.Maybe Prelude.Text)
channelSummary_roleArn :: Lens' ChannelSummary (Maybe Text)
channelSummary_roleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ChannelSummary' {Maybe Text
roleArn :: Maybe Text
$sel:roleArn:ChannelSummary' :: ChannelSummary -> Maybe Text
roleArn} -> Maybe Text
roleArn) (\s :: ChannelSummary
s@ChannelSummary' {} Maybe Text
a -> ChannelSummary
s {$sel:roleArn:ChannelSummary' :: Maybe Text
roleArn = Maybe Text
a} :: ChannelSummary)
channelSummary_state :: Lens.Lens' ChannelSummary (Prelude.Maybe ChannelState)
channelSummary_state :: Lens' ChannelSummary (Maybe ChannelState)
channelSummary_state = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ChannelSummary' {Maybe ChannelState
state :: Maybe ChannelState
$sel:state:ChannelSummary' :: ChannelSummary -> Maybe ChannelState
state} -> Maybe ChannelState
state) (\s :: ChannelSummary
s@ChannelSummary' {} Maybe ChannelState
a -> ChannelSummary
s {$sel:state:ChannelSummary' :: Maybe ChannelState
state = Maybe ChannelState
a} :: ChannelSummary)
channelSummary_tags :: Lens.Lens' ChannelSummary (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
channelSummary_tags :: Lens' ChannelSummary (Maybe (HashMap Text Text))
channelSummary_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ChannelSummary' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:ChannelSummary' :: ChannelSummary -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: ChannelSummary
s@ChannelSummary' {} Maybe (HashMap Text Text)
a -> ChannelSummary
s {$sel:tags:ChannelSummary' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: ChannelSummary) 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
channelSummary_vpc :: Lens.Lens' ChannelSummary (Prelude.Maybe VpcOutputSettingsDescription)
channelSummary_vpc :: Lens' ChannelSummary (Maybe VpcOutputSettingsDescription)
channelSummary_vpc = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ChannelSummary' {Maybe VpcOutputSettingsDescription
vpc :: Maybe VpcOutputSettingsDescription
$sel:vpc:ChannelSummary' :: ChannelSummary -> Maybe VpcOutputSettingsDescription
vpc} -> Maybe VpcOutputSettingsDescription
vpc) (\s :: ChannelSummary
s@ChannelSummary' {} Maybe VpcOutputSettingsDescription
a -> ChannelSummary
s {$sel:vpc:ChannelSummary' :: Maybe VpcOutputSettingsDescription
vpc = Maybe VpcOutputSettingsDescription
a} :: ChannelSummary)
instance Data.FromJSON ChannelSummary where
parseJSON :: Value -> Parser ChannelSummary
parseJSON =
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
String
"ChannelSummary"
( \Object
x ->
Maybe Text
-> Maybe CdiInputSpecification
-> Maybe ChannelClass
-> Maybe [OutputDestination]
-> Maybe [ChannelEgressEndpoint]
-> Maybe Text
-> Maybe [InputAttachment]
-> Maybe InputSpecification
-> Maybe LogLevel
-> Maybe MaintenanceStatus
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe ChannelState
-> Maybe (HashMap Text Text)
-> Maybe VpcOutputSettingsDescription
-> ChannelSummary
ChannelSummary'
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"arn")
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"cdiInputSpecification")
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"channelClass")
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"destinations" forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( Object
x
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"egressEndpoints"
forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty
)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"id")
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( Object
x
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"inputAttachments"
forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty
)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"inputSpecification")
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"logLevel")
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"maintenance")
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"name")
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"pipelinesRunningCount")
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"roleArn")
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"state")
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"tags" forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"vpc")
)
instance Prelude.Hashable ChannelSummary where
hashWithSalt :: Int -> ChannelSummary -> Int
hashWithSalt Int
_salt ChannelSummary' {Maybe Int
Maybe [ChannelEgressEndpoint]
Maybe [OutputDestination]
Maybe [InputAttachment]
Maybe Text
Maybe (HashMap Text Text)
Maybe CdiInputSpecification
Maybe ChannelClass
Maybe ChannelState
Maybe InputSpecification
Maybe LogLevel
Maybe MaintenanceStatus
Maybe VpcOutputSettingsDescription
vpc :: Maybe VpcOutputSettingsDescription
tags :: Maybe (HashMap Text Text)
state :: Maybe ChannelState
roleArn :: Maybe Text
pipelinesRunningCount :: Maybe Int
name :: Maybe Text
maintenance :: Maybe MaintenanceStatus
logLevel :: Maybe LogLevel
inputSpecification :: Maybe InputSpecification
inputAttachments :: Maybe [InputAttachment]
id :: Maybe Text
egressEndpoints :: Maybe [ChannelEgressEndpoint]
destinations :: Maybe [OutputDestination]
channelClass :: Maybe ChannelClass
cdiInputSpecification :: Maybe CdiInputSpecification
arn :: Maybe Text
$sel:vpc:ChannelSummary' :: ChannelSummary -> Maybe VpcOutputSettingsDescription
$sel:tags:ChannelSummary' :: ChannelSummary -> Maybe (HashMap Text Text)
$sel:state:ChannelSummary' :: ChannelSummary -> Maybe ChannelState
$sel:roleArn:ChannelSummary' :: ChannelSummary -> Maybe Text
$sel:pipelinesRunningCount:ChannelSummary' :: ChannelSummary -> Maybe Int
$sel:name:ChannelSummary' :: ChannelSummary -> Maybe Text
$sel:maintenance:ChannelSummary' :: ChannelSummary -> Maybe MaintenanceStatus
$sel:logLevel:ChannelSummary' :: ChannelSummary -> Maybe LogLevel
$sel:inputSpecification:ChannelSummary' :: ChannelSummary -> Maybe InputSpecification
$sel:inputAttachments:ChannelSummary' :: ChannelSummary -> Maybe [InputAttachment]
$sel:id:ChannelSummary' :: ChannelSummary -> Maybe Text
$sel:egressEndpoints:ChannelSummary' :: ChannelSummary -> Maybe [ChannelEgressEndpoint]
$sel:destinations:ChannelSummary' :: ChannelSummary -> Maybe [OutputDestination]
$sel:channelClass:ChannelSummary' :: ChannelSummary -> Maybe ChannelClass
$sel:cdiInputSpecification:ChannelSummary' :: ChannelSummary -> Maybe CdiInputSpecification
$sel:arn:ChannelSummary' :: ChannelSummary -> Maybe Text
..} =
Int
_salt
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
arn
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe CdiInputSpecification
cdiInputSpecification
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ChannelClass
channelClass
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [OutputDestination]
destinations
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [ChannelEgressEndpoint]
egressEndpoints
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
id
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [InputAttachment]
inputAttachments
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe InputSpecification
inputSpecification
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe LogLevel
logLevel
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe MaintenanceStatus
maintenance
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
name
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
pipelinesRunningCount
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
roleArn
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ChannelState
state
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
tags
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe VpcOutputSettingsDescription
vpc
instance Prelude.NFData ChannelSummary where
rnf :: ChannelSummary -> ()
rnf ChannelSummary' {Maybe Int
Maybe [ChannelEgressEndpoint]
Maybe [OutputDestination]
Maybe [InputAttachment]
Maybe Text
Maybe (HashMap Text Text)
Maybe CdiInputSpecification
Maybe ChannelClass
Maybe ChannelState
Maybe InputSpecification
Maybe LogLevel
Maybe MaintenanceStatus
Maybe VpcOutputSettingsDescription
vpc :: Maybe VpcOutputSettingsDescription
tags :: Maybe (HashMap Text Text)
state :: Maybe ChannelState
roleArn :: Maybe Text
pipelinesRunningCount :: Maybe Int
name :: Maybe Text
maintenance :: Maybe MaintenanceStatus
logLevel :: Maybe LogLevel
inputSpecification :: Maybe InputSpecification
inputAttachments :: Maybe [InputAttachment]
id :: Maybe Text
egressEndpoints :: Maybe [ChannelEgressEndpoint]
destinations :: Maybe [OutputDestination]
channelClass :: Maybe ChannelClass
cdiInputSpecification :: Maybe CdiInputSpecification
arn :: Maybe Text
$sel:vpc:ChannelSummary' :: ChannelSummary -> Maybe VpcOutputSettingsDescription
$sel:tags:ChannelSummary' :: ChannelSummary -> Maybe (HashMap Text Text)
$sel:state:ChannelSummary' :: ChannelSummary -> Maybe ChannelState
$sel:roleArn:ChannelSummary' :: ChannelSummary -> Maybe Text
$sel:pipelinesRunningCount:ChannelSummary' :: ChannelSummary -> Maybe Int
$sel:name:ChannelSummary' :: ChannelSummary -> Maybe Text
$sel:maintenance:ChannelSummary' :: ChannelSummary -> Maybe MaintenanceStatus
$sel:logLevel:ChannelSummary' :: ChannelSummary -> Maybe LogLevel
$sel:inputSpecification:ChannelSummary' :: ChannelSummary -> Maybe InputSpecification
$sel:inputAttachments:ChannelSummary' :: ChannelSummary -> Maybe [InputAttachment]
$sel:id:ChannelSummary' :: ChannelSummary -> Maybe Text
$sel:egressEndpoints:ChannelSummary' :: ChannelSummary -> Maybe [ChannelEgressEndpoint]
$sel:destinations:ChannelSummary' :: ChannelSummary -> Maybe [OutputDestination]
$sel:channelClass:ChannelSummary' :: ChannelSummary -> Maybe ChannelClass
$sel:cdiInputSpecification:ChannelSummary' :: ChannelSummary -> Maybe CdiInputSpecification
$sel:arn:ChannelSummary' :: ChannelSummary -> Maybe Text
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
arn
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe CdiInputSpecification
cdiInputSpecification
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ChannelClass
channelClass
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [OutputDestination]
destinations
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [ChannelEgressEndpoint]
egressEndpoints
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
id
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [InputAttachment]
inputAttachments
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe InputSpecification
inputSpecification
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe LogLevel
logLevel
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe MaintenanceStatus
maintenance
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
pipelinesRunningCount
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
roleArn
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ChannelState
state
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 Maybe VpcOutputSettingsDescription
vpc