{-# 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.MediaTailor.Types.PrefetchSchedule
-- 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.MediaTailor.Types.PrefetchSchedule where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.MediaTailor.Types.PrefetchConsumption
import Amazonka.MediaTailor.Types.PrefetchRetrieval
import qualified Amazonka.Prelude as Prelude

-- | A prefetch schedule allows you to tell MediaTailor to fetch and prepare
-- certain ads before an ad break happens. For more information about ad
-- prefetching, see
-- <https://docs.aws.amazon.com/mediatailor/latest/ug/prefetching-ads.html Using ad prefetching>
-- in the /MediaTailor User Guide/.
--
-- /See:/ 'newPrefetchSchedule' smart constructor.
data PrefetchSchedule = PrefetchSchedule'
  { -- | An optional stream identifier that you can specify in order to prefetch
    -- for multiple streams that use the same playback configuration.
    PrefetchSchedule -> Maybe Text
streamId :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the prefetch schedule.
    PrefetchSchedule -> Text
arn :: Prelude.Text,
    -- | Consumption settings determine how, and when, MediaTailor places the
    -- prefetched ads into ad breaks. Ad consumption occurs within a span of
    -- time that you define, called a /consumption window/. You can designate
    -- which ad breaks that MediaTailor fills with prefetch ads by setting
    -- avail matching criteria.
    PrefetchSchedule -> PrefetchConsumption
consumption :: PrefetchConsumption,
    -- | The name of the prefetch schedule. The name must be unique among all
    -- prefetch schedules that are associated with the specified playback
    -- configuration.
    PrefetchSchedule -> Text
name :: Prelude.Text,
    -- | The name of the playback configuration to create the prefetch schedule
    -- for.
    PrefetchSchedule -> Text
playbackConfigurationName :: Prelude.Text,
    -- | A complex type that contains settings for prefetch retrieval from the ad
    -- decision server (ADS).
    PrefetchSchedule -> PrefetchRetrieval
retrieval :: PrefetchRetrieval
  }
  deriving (PrefetchSchedule -> PrefetchSchedule -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PrefetchSchedule -> PrefetchSchedule -> Bool
$c/= :: PrefetchSchedule -> PrefetchSchedule -> Bool
== :: PrefetchSchedule -> PrefetchSchedule -> Bool
$c== :: PrefetchSchedule -> PrefetchSchedule -> Bool
Prelude.Eq, ReadPrec [PrefetchSchedule]
ReadPrec PrefetchSchedule
Int -> ReadS PrefetchSchedule
ReadS [PrefetchSchedule]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PrefetchSchedule]
$creadListPrec :: ReadPrec [PrefetchSchedule]
readPrec :: ReadPrec PrefetchSchedule
$creadPrec :: ReadPrec PrefetchSchedule
readList :: ReadS [PrefetchSchedule]
$creadList :: ReadS [PrefetchSchedule]
readsPrec :: Int -> ReadS PrefetchSchedule
$creadsPrec :: Int -> ReadS PrefetchSchedule
Prelude.Read, Int -> PrefetchSchedule -> ShowS
[PrefetchSchedule] -> ShowS
PrefetchSchedule -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PrefetchSchedule] -> ShowS
$cshowList :: [PrefetchSchedule] -> ShowS
show :: PrefetchSchedule -> String
$cshow :: PrefetchSchedule -> String
showsPrec :: Int -> PrefetchSchedule -> ShowS
$cshowsPrec :: Int -> PrefetchSchedule -> ShowS
Prelude.Show, forall x. Rep PrefetchSchedule x -> PrefetchSchedule
forall x. PrefetchSchedule -> Rep PrefetchSchedule x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PrefetchSchedule x -> PrefetchSchedule
$cfrom :: forall x. PrefetchSchedule -> Rep PrefetchSchedule x
Prelude.Generic)

-- |
-- Create a value of 'PrefetchSchedule' 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:
--
-- 'streamId', 'prefetchSchedule_streamId' - An optional stream identifier that you can specify in order to prefetch
-- for multiple streams that use the same playback configuration.
--
-- 'arn', 'prefetchSchedule_arn' - The Amazon Resource Name (ARN) of the prefetch schedule.
--
-- 'consumption', 'prefetchSchedule_consumption' - Consumption settings determine how, and when, MediaTailor places the
-- prefetched ads into ad breaks. Ad consumption occurs within a span of
-- time that you define, called a /consumption window/. You can designate
-- which ad breaks that MediaTailor fills with prefetch ads by setting
-- avail matching criteria.
--
-- 'name', 'prefetchSchedule_name' - The name of the prefetch schedule. The name must be unique among all
-- prefetch schedules that are associated with the specified playback
-- configuration.
--
-- 'playbackConfigurationName', 'prefetchSchedule_playbackConfigurationName' - The name of the playback configuration to create the prefetch schedule
-- for.
--
-- 'retrieval', 'prefetchSchedule_retrieval' - A complex type that contains settings for prefetch retrieval from the ad
-- decision server (ADS).
newPrefetchSchedule ::
  -- | 'arn'
  Prelude.Text ->
  -- | 'consumption'
  PrefetchConsumption ->
  -- | 'name'
  Prelude.Text ->
  -- | 'playbackConfigurationName'
  Prelude.Text ->
  -- | 'retrieval'
  PrefetchRetrieval ->
  PrefetchSchedule
newPrefetchSchedule :: Text
-> PrefetchConsumption
-> Text
-> Text
-> PrefetchRetrieval
-> PrefetchSchedule
newPrefetchSchedule
  Text
pArn_
  PrefetchConsumption
pConsumption_
  Text
pName_
  Text
pPlaybackConfigurationName_
  PrefetchRetrieval
pRetrieval_ =
    PrefetchSchedule'
      { $sel:streamId:PrefetchSchedule' :: Maybe Text
streamId = forall a. Maybe a
Prelude.Nothing,
        $sel:arn:PrefetchSchedule' :: Text
arn = Text
pArn_,
        $sel:consumption:PrefetchSchedule' :: PrefetchConsumption
consumption = PrefetchConsumption
pConsumption_,
        $sel:name:PrefetchSchedule' :: Text
name = Text
pName_,
        $sel:playbackConfigurationName:PrefetchSchedule' :: Text
playbackConfigurationName =
          Text
pPlaybackConfigurationName_,
        $sel:retrieval:PrefetchSchedule' :: PrefetchRetrieval
retrieval = PrefetchRetrieval
pRetrieval_
      }

-- | An optional stream identifier that you can specify in order to prefetch
-- for multiple streams that use the same playback configuration.
prefetchSchedule_streamId :: Lens.Lens' PrefetchSchedule (Prelude.Maybe Prelude.Text)
prefetchSchedule_streamId :: Lens' PrefetchSchedule (Maybe Text)
prefetchSchedule_streamId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PrefetchSchedule' {Maybe Text
streamId :: Maybe Text
$sel:streamId:PrefetchSchedule' :: PrefetchSchedule -> Maybe Text
streamId} -> Maybe Text
streamId) (\s :: PrefetchSchedule
s@PrefetchSchedule' {} Maybe Text
a -> PrefetchSchedule
s {$sel:streamId:PrefetchSchedule' :: Maybe Text
streamId = Maybe Text
a} :: PrefetchSchedule)

-- | The Amazon Resource Name (ARN) of the prefetch schedule.
prefetchSchedule_arn :: Lens.Lens' PrefetchSchedule Prelude.Text
prefetchSchedule_arn :: Lens' PrefetchSchedule Text
prefetchSchedule_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PrefetchSchedule' {Text
arn :: Text
$sel:arn:PrefetchSchedule' :: PrefetchSchedule -> Text
arn} -> Text
arn) (\s :: PrefetchSchedule
s@PrefetchSchedule' {} Text
a -> PrefetchSchedule
s {$sel:arn:PrefetchSchedule' :: Text
arn = Text
a} :: PrefetchSchedule)

-- | Consumption settings determine how, and when, MediaTailor places the
-- prefetched ads into ad breaks. Ad consumption occurs within a span of
-- time that you define, called a /consumption window/. You can designate
-- which ad breaks that MediaTailor fills with prefetch ads by setting
-- avail matching criteria.
prefetchSchedule_consumption :: Lens.Lens' PrefetchSchedule PrefetchConsumption
prefetchSchedule_consumption :: Lens' PrefetchSchedule PrefetchConsumption
prefetchSchedule_consumption = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PrefetchSchedule' {PrefetchConsumption
consumption :: PrefetchConsumption
$sel:consumption:PrefetchSchedule' :: PrefetchSchedule -> PrefetchConsumption
consumption} -> PrefetchConsumption
consumption) (\s :: PrefetchSchedule
s@PrefetchSchedule' {} PrefetchConsumption
a -> PrefetchSchedule
s {$sel:consumption:PrefetchSchedule' :: PrefetchConsumption
consumption = PrefetchConsumption
a} :: PrefetchSchedule)

-- | The name of the prefetch schedule. The name must be unique among all
-- prefetch schedules that are associated with the specified playback
-- configuration.
prefetchSchedule_name :: Lens.Lens' PrefetchSchedule Prelude.Text
prefetchSchedule_name :: Lens' PrefetchSchedule Text
prefetchSchedule_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PrefetchSchedule' {Text
name :: Text
$sel:name:PrefetchSchedule' :: PrefetchSchedule -> Text
name} -> Text
name) (\s :: PrefetchSchedule
s@PrefetchSchedule' {} Text
a -> PrefetchSchedule
s {$sel:name:PrefetchSchedule' :: Text
name = Text
a} :: PrefetchSchedule)

-- | The name of the playback configuration to create the prefetch schedule
-- for.
prefetchSchedule_playbackConfigurationName :: Lens.Lens' PrefetchSchedule Prelude.Text
prefetchSchedule_playbackConfigurationName :: Lens' PrefetchSchedule Text
prefetchSchedule_playbackConfigurationName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PrefetchSchedule' {Text
playbackConfigurationName :: Text
$sel:playbackConfigurationName:PrefetchSchedule' :: PrefetchSchedule -> Text
playbackConfigurationName} -> Text
playbackConfigurationName) (\s :: PrefetchSchedule
s@PrefetchSchedule' {} Text
a -> PrefetchSchedule
s {$sel:playbackConfigurationName:PrefetchSchedule' :: Text
playbackConfigurationName = Text
a} :: PrefetchSchedule)

-- | A complex type that contains settings for prefetch retrieval from the ad
-- decision server (ADS).
prefetchSchedule_retrieval :: Lens.Lens' PrefetchSchedule PrefetchRetrieval
prefetchSchedule_retrieval :: Lens' PrefetchSchedule PrefetchRetrieval
prefetchSchedule_retrieval = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PrefetchSchedule' {PrefetchRetrieval
retrieval :: PrefetchRetrieval
$sel:retrieval:PrefetchSchedule' :: PrefetchSchedule -> PrefetchRetrieval
retrieval} -> PrefetchRetrieval
retrieval) (\s :: PrefetchSchedule
s@PrefetchSchedule' {} PrefetchRetrieval
a -> PrefetchSchedule
s {$sel:retrieval:PrefetchSchedule' :: PrefetchRetrieval
retrieval = PrefetchRetrieval
a} :: PrefetchSchedule)

instance Data.FromJSON PrefetchSchedule where
  parseJSON :: Value -> Parser PrefetchSchedule
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"PrefetchSchedule"
      ( \Object
x ->
          Maybe Text
-> Text
-> PrefetchConsumption
-> Text
-> Text
-> PrefetchRetrieval
-> PrefetchSchedule
PrefetchSchedule'
            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
"StreamId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser 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 a
Data..: Key
"Consumption")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser 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 a
Data..: Key
"PlaybackConfigurationName")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"Retrieval")
      )

instance Prelude.Hashable PrefetchSchedule where
  hashWithSalt :: Int -> PrefetchSchedule -> Int
hashWithSalt Int
_salt PrefetchSchedule' {Maybe Text
Text
PrefetchConsumption
PrefetchRetrieval
retrieval :: PrefetchRetrieval
playbackConfigurationName :: Text
name :: Text
consumption :: PrefetchConsumption
arn :: Text
streamId :: Maybe Text
$sel:retrieval:PrefetchSchedule' :: PrefetchSchedule -> PrefetchRetrieval
$sel:playbackConfigurationName:PrefetchSchedule' :: PrefetchSchedule -> Text
$sel:name:PrefetchSchedule' :: PrefetchSchedule -> Text
$sel:consumption:PrefetchSchedule' :: PrefetchSchedule -> PrefetchConsumption
$sel:arn:PrefetchSchedule' :: PrefetchSchedule -> Text
$sel:streamId:PrefetchSchedule' :: PrefetchSchedule -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
streamId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
arn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` PrefetchConsumption
consumption
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
playbackConfigurationName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` PrefetchRetrieval
retrieval

instance Prelude.NFData PrefetchSchedule where
  rnf :: PrefetchSchedule -> ()
rnf PrefetchSchedule' {Maybe Text
Text
PrefetchConsumption
PrefetchRetrieval
retrieval :: PrefetchRetrieval
playbackConfigurationName :: Text
name :: Text
consumption :: PrefetchConsumption
arn :: Text
streamId :: Maybe Text
$sel:retrieval:PrefetchSchedule' :: PrefetchSchedule -> PrefetchRetrieval
$sel:playbackConfigurationName:PrefetchSchedule' :: PrefetchSchedule -> Text
$sel:name:PrefetchSchedule' :: PrefetchSchedule -> Text
$sel:consumption:PrefetchSchedule' :: PrefetchSchedule -> PrefetchConsumption
$sel:arn:PrefetchSchedule' :: PrefetchSchedule -> Text
$sel:streamId:PrefetchSchedule' :: PrefetchSchedule -> Maybe Text
..} =
    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 Text
arn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf PrefetchConsumption
consumption
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
playbackConfigurationName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf PrefetchRetrieval
retrieval