{-# 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.MediaPackage.Types.Channel
-- 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.MediaPackage.Types.Channel where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.MediaPackage.Types.EgressAccessLogs
import Amazonka.MediaPackage.Types.HlsIngest
import Amazonka.MediaPackage.Types.IngressAccessLogs
import qualified Amazonka.Prelude as Prelude

-- | A Channel resource configuration.
--
-- /See:/ 'newChannel' smart constructor.
data Channel = Channel'
  { -- | The Amazon Resource Name (ARN) assigned to the Channel.
    Channel -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
    -- | A short text description of the Channel.
    Channel -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    Channel -> Maybe EgressAccessLogs
egressAccessLogs :: Prelude.Maybe EgressAccessLogs,
    Channel -> Maybe HlsIngest
hlsIngest :: Prelude.Maybe HlsIngest,
    -- | The ID of the Channel.
    Channel -> Maybe Text
id :: Prelude.Maybe Prelude.Text,
    Channel -> Maybe IngressAccessLogs
ingressAccessLogs :: Prelude.Maybe IngressAccessLogs,
    Channel -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text)
  }
  deriving (Channel -> Channel -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Channel -> Channel -> Bool
$c/= :: Channel -> Channel -> Bool
== :: Channel -> Channel -> Bool
$c== :: Channel -> Channel -> Bool
Prelude.Eq, ReadPrec [Channel]
ReadPrec Channel
Int -> ReadS Channel
ReadS [Channel]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Channel]
$creadListPrec :: ReadPrec [Channel]
readPrec :: ReadPrec Channel
$creadPrec :: ReadPrec Channel
readList :: ReadS [Channel]
$creadList :: ReadS [Channel]
readsPrec :: Int -> ReadS Channel
$creadsPrec :: Int -> ReadS Channel
Prelude.Read, Int -> Channel -> ShowS
[Channel] -> ShowS
Channel -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Channel] -> ShowS
$cshowList :: [Channel] -> ShowS
show :: Channel -> String
$cshow :: Channel -> String
showsPrec :: Int -> Channel -> ShowS
$cshowsPrec :: Int -> Channel -> ShowS
Prelude.Show, forall x. Rep Channel x -> Channel
forall x. Channel -> Rep Channel x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Channel x -> Channel
$cfrom :: forall x. Channel -> Rep Channel x
Prelude.Generic)

-- |
-- Create a value of 'Channel' 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:
--
-- 'arn', 'channel_arn' - The Amazon Resource Name (ARN) assigned to the Channel.
--
-- 'description', 'channel_description' - A short text description of the Channel.
--
-- 'egressAccessLogs', 'channel_egressAccessLogs' - Undocumented member.
--
-- 'hlsIngest', 'channel_hlsIngest' - Undocumented member.
--
-- 'id', 'channel_id' - The ID of the Channel.
--
-- 'ingressAccessLogs', 'channel_ingressAccessLogs' - Undocumented member.
--
-- 'tags', 'channel_tags' - Undocumented member.
newChannel ::
  Channel
newChannel :: Channel
newChannel =
  Channel'
    { $sel:arn:Channel' :: Maybe Text
arn = forall a. Maybe a
Prelude.Nothing,
      $sel:description:Channel' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:egressAccessLogs:Channel' :: Maybe EgressAccessLogs
egressAccessLogs = forall a. Maybe a
Prelude.Nothing,
      $sel:hlsIngest:Channel' :: Maybe HlsIngest
hlsIngest = forall a. Maybe a
Prelude.Nothing,
      $sel:id:Channel' :: Maybe Text
id = forall a. Maybe a
Prelude.Nothing,
      $sel:ingressAccessLogs:Channel' :: Maybe IngressAccessLogs
ingressAccessLogs = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:Channel' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing
    }

-- | The Amazon Resource Name (ARN) assigned to the Channel.
channel_arn :: Lens.Lens' Channel (Prelude.Maybe Prelude.Text)
channel_arn :: Lens' Channel (Maybe Text)
channel_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Channel' {Maybe Text
arn :: Maybe Text
$sel:arn:Channel' :: Channel -> Maybe Text
arn} -> Maybe Text
arn) (\s :: Channel
s@Channel' {} Maybe Text
a -> Channel
s {$sel:arn:Channel' :: Maybe Text
arn = Maybe Text
a} :: Channel)

-- | A short text description of the Channel.
channel_description :: Lens.Lens' Channel (Prelude.Maybe Prelude.Text)
channel_description :: Lens' Channel (Maybe Text)
channel_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Channel' {Maybe Text
description :: Maybe Text
$sel:description:Channel' :: Channel -> Maybe Text
description} -> Maybe Text
description) (\s :: Channel
s@Channel' {} Maybe Text
a -> Channel
s {$sel:description:Channel' :: Maybe Text
description = Maybe Text
a} :: Channel)

-- | Undocumented member.
channel_egressAccessLogs :: Lens.Lens' Channel (Prelude.Maybe EgressAccessLogs)
channel_egressAccessLogs :: Lens' Channel (Maybe EgressAccessLogs)
channel_egressAccessLogs = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Channel' {Maybe EgressAccessLogs
egressAccessLogs :: Maybe EgressAccessLogs
$sel:egressAccessLogs:Channel' :: Channel -> Maybe EgressAccessLogs
egressAccessLogs} -> Maybe EgressAccessLogs
egressAccessLogs) (\s :: Channel
s@Channel' {} Maybe EgressAccessLogs
a -> Channel
s {$sel:egressAccessLogs:Channel' :: Maybe EgressAccessLogs
egressAccessLogs = Maybe EgressAccessLogs
a} :: Channel)

-- | Undocumented member.
channel_hlsIngest :: Lens.Lens' Channel (Prelude.Maybe HlsIngest)
channel_hlsIngest :: Lens' Channel (Maybe HlsIngest)
channel_hlsIngest = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Channel' {Maybe HlsIngest
hlsIngest :: Maybe HlsIngest
$sel:hlsIngest:Channel' :: Channel -> Maybe HlsIngest
hlsIngest} -> Maybe HlsIngest
hlsIngest) (\s :: Channel
s@Channel' {} Maybe HlsIngest
a -> Channel
s {$sel:hlsIngest:Channel' :: Maybe HlsIngest
hlsIngest = Maybe HlsIngest
a} :: Channel)

-- | The ID of the Channel.
channel_id :: Lens.Lens' Channel (Prelude.Maybe Prelude.Text)
channel_id :: Lens' Channel (Maybe Text)
channel_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Channel' {Maybe Text
id :: Maybe Text
$sel:id:Channel' :: Channel -> Maybe Text
id} -> Maybe Text
id) (\s :: Channel
s@Channel' {} Maybe Text
a -> Channel
s {$sel:id:Channel' :: Maybe Text
id = Maybe Text
a} :: Channel)

-- | Undocumented member.
channel_ingressAccessLogs :: Lens.Lens' Channel (Prelude.Maybe IngressAccessLogs)
channel_ingressAccessLogs :: Lens' Channel (Maybe IngressAccessLogs)
channel_ingressAccessLogs = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Channel' {Maybe IngressAccessLogs
ingressAccessLogs :: Maybe IngressAccessLogs
$sel:ingressAccessLogs:Channel' :: Channel -> Maybe IngressAccessLogs
ingressAccessLogs} -> Maybe IngressAccessLogs
ingressAccessLogs) (\s :: Channel
s@Channel' {} Maybe IngressAccessLogs
a -> Channel
s {$sel:ingressAccessLogs:Channel' :: Maybe IngressAccessLogs
ingressAccessLogs = Maybe IngressAccessLogs
a} :: Channel)

-- | Undocumented member.
channel_tags :: Lens.Lens' Channel (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
channel_tags :: Lens' Channel (Maybe (HashMap Text Text))
channel_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Channel' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:Channel' :: Channel -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: Channel
s@Channel' {} Maybe (HashMap Text Text)
a -> Channel
s {$sel:tags:Channel' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: Channel) 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

instance Data.FromJSON Channel where
  parseJSON :: Value -> Parser Channel
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"Channel"
      ( \Object
x ->
          Maybe Text
-> Maybe Text
-> Maybe EgressAccessLogs
-> Maybe HlsIngest
-> Maybe Text
-> Maybe IngressAccessLogs
-> Maybe (HashMap Text Text)
-> Channel
Channel'
            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
"description")
            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
"egressAccessLogs")
            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
"hlsIngest")
            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
"ingressAccessLogs")
            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)
      )

instance Prelude.Hashable Channel where
  hashWithSalt :: Int -> Channel -> Int
hashWithSalt Int
_salt Channel' {Maybe Text
Maybe (HashMap Text Text)
Maybe EgressAccessLogs
Maybe HlsIngest
Maybe IngressAccessLogs
tags :: Maybe (HashMap Text Text)
ingressAccessLogs :: Maybe IngressAccessLogs
id :: Maybe Text
hlsIngest :: Maybe HlsIngest
egressAccessLogs :: Maybe EgressAccessLogs
description :: Maybe Text
arn :: Maybe Text
$sel:tags:Channel' :: Channel -> Maybe (HashMap Text Text)
$sel:ingressAccessLogs:Channel' :: Channel -> Maybe IngressAccessLogs
$sel:id:Channel' :: Channel -> Maybe Text
$sel:hlsIngest:Channel' :: Channel -> Maybe HlsIngest
$sel:egressAccessLogs:Channel' :: Channel -> Maybe EgressAccessLogs
$sel:description:Channel' :: Channel -> Maybe Text
$sel:arn:Channel' :: Channel -> 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 Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe EgressAccessLogs
egressAccessLogs
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe HlsIngest
hlsIngest
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
id
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe IngressAccessLogs
ingressAccessLogs
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
tags

instance Prelude.NFData Channel where
  rnf :: Channel -> ()
rnf Channel' {Maybe Text
Maybe (HashMap Text Text)
Maybe EgressAccessLogs
Maybe HlsIngest
Maybe IngressAccessLogs
tags :: Maybe (HashMap Text Text)
ingressAccessLogs :: Maybe IngressAccessLogs
id :: Maybe Text
hlsIngest :: Maybe HlsIngest
egressAccessLogs :: Maybe EgressAccessLogs
description :: Maybe Text
arn :: Maybe Text
$sel:tags:Channel' :: Channel -> Maybe (HashMap Text Text)
$sel:ingressAccessLogs:Channel' :: Channel -> Maybe IngressAccessLogs
$sel:id:Channel' :: Channel -> Maybe Text
$sel:hlsIngest:Channel' :: Channel -> Maybe HlsIngest
$sel:egressAccessLogs:Channel' :: Channel -> Maybe EgressAccessLogs
$sel:description:Channel' :: Channel -> Maybe Text
$sel:arn:Channel' :: Channel -> 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 Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe EgressAccessLogs
egressAccessLogs
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe HlsIngest
hlsIngest
      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 IngressAccessLogs
ingressAccessLogs
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
tags