{-# 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.KinesisVideoArchivedMedia.Types.ClipTimestampRange
-- 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.KinesisVideoArchivedMedia.Types.ClipTimestampRange where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude

-- | The range of timestamps for which to return fragments.
--
-- /See:/ 'newClipTimestampRange' smart constructor.
data ClipTimestampRange = ClipTimestampRange'
  { -- | The starting timestamp in the range of timestamps for which to return
    -- fragments.
    --
    -- Only fragments that start exactly at or after @StartTimestamp@ are
    -- included in the session. Fragments that start before @StartTimestamp@
    -- and continue past it aren\'t included in the session. If
    -- @FragmentSelectorType@ is @SERVER_TIMESTAMP@, the @StartTimestamp@ must
    -- be later than the stream head.
    ClipTimestampRange -> POSIX
startTimestamp :: Data.POSIX,
    -- | The end of the timestamp range for the requested media.
    --
    -- This value must be within 24 hours of the specified @StartTimestamp@,
    -- and it must be later than the @StartTimestamp@ value. If
    -- @FragmentSelectorType@ for the request is @SERVER_TIMESTAMP@, this value
    -- must be in the past.
    --
    -- This value is inclusive. The @EndTimestamp@ is compared to the
    -- (starting) timestamp of the fragment. Fragments that start before the
    -- @EndTimestamp@ value and continue past it are included in the session.
    ClipTimestampRange -> POSIX
endTimestamp :: Data.POSIX
  }
  deriving (ClipTimestampRange -> ClipTimestampRange -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ClipTimestampRange -> ClipTimestampRange -> Bool
$c/= :: ClipTimestampRange -> ClipTimestampRange -> Bool
== :: ClipTimestampRange -> ClipTimestampRange -> Bool
$c== :: ClipTimestampRange -> ClipTimestampRange -> Bool
Prelude.Eq, ReadPrec [ClipTimestampRange]
ReadPrec ClipTimestampRange
Int -> ReadS ClipTimestampRange
ReadS [ClipTimestampRange]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ClipTimestampRange]
$creadListPrec :: ReadPrec [ClipTimestampRange]
readPrec :: ReadPrec ClipTimestampRange
$creadPrec :: ReadPrec ClipTimestampRange
readList :: ReadS [ClipTimestampRange]
$creadList :: ReadS [ClipTimestampRange]
readsPrec :: Int -> ReadS ClipTimestampRange
$creadsPrec :: Int -> ReadS ClipTimestampRange
Prelude.Read, Int -> ClipTimestampRange -> ShowS
[ClipTimestampRange] -> ShowS
ClipTimestampRange -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ClipTimestampRange] -> ShowS
$cshowList :: [ClipTimestampRange] -> ShowS
show :: ClipTimestampRange -> String
$cshow :: ClipTimestampRange -> String
showsPrec :: Int -> ClipTimestampRange -> ShowS
$cshowsPrec :: Int -> ClipTimestampRange -> ShowS
Prelude.Show, forall x. Rep ClipTimestampRange x -> ClipTimestampRange
forall x. ClipTimestampRange -> Rep ClipTimestampRange x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ClipTimestampRange x -> ClipTimestampRange
$cfrom :: forall x. ClipTimestampRange -> Rep ClipTimestampRange x
Prelude.Generic)

-- |
-- Create a value of 'ClipTimestampRange' 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:
--
-- 'startTimestamp', 'clipTimestampRange_startTimestamp' - The starting timestamp in the range of timestamps for which to return
-- fragments.
--
-- Only fragments that start exactly at or after @StartTimestamp@ are
-- included in the session. Fragments that start before @StartTimestamp@
-- and continue past it aren\'t included in the session. If
-- @FragmentSelectorType@ is @SERVER_TIMESTAMP@, the @StartTimestamp@ must
-- be later than the stream head.
--
-- 'endTimestamp', 'clipTimestampRange_endTimestamp' - The end of the timestamp range for the requested media.
--
-- This value must be within 24 hours of the specified @StartTimestamp@,
-- and it must be later than the @StartTimestamp@ value. If
-- @FragmentSelectorType@ for the request is @SERVER_TIMESTAMP@, this value
-- must be in the past.
--
-- This value is inclusive. The @EndTimestamp@ is compared to the
-- (starting) timestamp of the fragment. Fragments that start before the
-- @EndTimestamp@ value and continue past it are included in the session.
newClipTimestampRange ::
  -- | 'startTimestamp'
  Prelude.UTCTime ->
  -- | 'endTimestamp'
  Prelude.UTCTime ->
  ClipTimestampRange
newClipTimestampRange :: UTCTime -> UTCTime -> ClipTimestampRange
newClipTimestampRange UTCTime
pStartTimestamp_ UTCTime
pEndTimestamp_ =
  ClipTimestampRange'
    { $sel:startTimestamp:ClipTimestampRange' :: POSIX
startTimestamp =
        forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pStartTimestamp_,
      $sel:endTimestamp:ClipTimestampRange' :: POSIX
endTimestamp = forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pEndTimestamp_
    }

-- | The starting timestamp in the range of timestamps for which to return
-- fragments.
--
-- Only fragments that start exactly at or after @StartTimestamp@ are
-- included in the session. Fragments that start before @StartTimestamp@
-- and continue past it aren\'t included in the session. If
-- @FragmentSelectorType@ is @SERVER_TIMESTAMP@, the @StartTimestamp@ must
-- be later than the stream head.
clipTimestampRange_startTimestamp :: Lens.Lens' ClipTimestampRange Prelude.UTCTime
clipTimestampRange_startTimestamp :: Lens' ClipTimestampRange UTCTime
clipTimestampRange_startTimestamp = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ClipTimestampRange' {POSIX
startTimestamp :: POSIX
$sel:startTimestamp:ClipTimestampRange' :: ClipTimestampRange -> POSIX
startTimestamp} -> POSIX
startTimestamp) (\s :: ClipTimestampRange
s@ClipTimestampRange' {} POSIX
a -> ClipTimestampRange
s {$sel:startTimestamp:ClipTimestampRange' :: POSIX
startTimestamp = POSIX
a} :: ClipTimestampRange) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The end of the timestamp range for the requested media.
--
-- This value must be within 24 hours of the specified @StartTimestamp@,
-- and it must be later than the @StartTimestamp@ value. If
-- @FragmentSelectorType@ for the request is @SERVER_TIMESTAMP@, this value
-- must be in the past.
--
-- This value is inclusive. The @EndTimestamp@ is compared to the
-- (starting) timestamp of the fragment. Fragments that start before the
-- @EndTimestamp@ value and continue past it are included in the session.
clipTimestampRange_endTimestamp :: Lens.Lens' ClipTimestampRange Prelude.UTCTime
clipTimestampRange_endTimestamp :: Lens' ClipTimestampRange UTCTime
clipTimestampRange_endTimestamp = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ClipTimestampRange' {POSIX
endTimestamp :: POSIX
$sel:endTimestamp:ClipTimestampRange' :: ClipTimestampRange -> POSIX
endTimestamp} -> POSIX
endTimestamp) (\s :: ClipTimestampRange
s@ClipTimestampRange' {} POSIX
a -> ClipTimestampRange
s {$sel:endTimestamp:ClipTimestampRange' :: POSIX
endTimestamp = POSIX
a} :: ClipTimestampRange) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

instance Prelude.Hashable ClipTimestampRange where
  hashWithSalt :: Int -> ClipTimestampRange -> Int
hashWithSalt Int
_salt ClipTimestampRange' {POSIX
endTimestamp :: POSIX
startTimestamp :: POSIX
$sel:endTimestamp:ClipTimestampRange' :: ClipTimestampRange -> POSIX
$sel:startTimestamp:ClipTimestampRange' :: ClipTimestampRange -> POSIX
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` POSIX
startTimestamp
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` POSIX
endTimestamp

instance Prelude.NFData ClipTimestampRange where
  rnf :: ClipTimestampRange -> ()
rnf ClipTimestampRange' {POSIX
endTimestamp :: POSIX
startTimestamp :: POSIX
$sel:endTimestamp:ClipTimestampRange' :: ClipTimestampRange -> POSIX
$sel:startTimestamp:ClipTimestampRange' :: ClipTimestampRange -> POSIX
..} =
    forall a. NFData a => a -> ()
Prelude.rnf POSIX
startTimestamp
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf POSIX
endTimestamp

instance Data.ToJSON ClipTimestampRange where
  toJSON :: ClipTimestampRange -> Value
toJSON ClipTimestampRange' {POSIX
endTimestamp :: POSIX
startTimestamp :: POSIX
$sel:endTimestamp:ClipTimestampRange' :: ClipTimestampRange -> POSIX
$sel:startTimestamp:ClipTimestampRange' :: ClipTimestampRange -> POSIX
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just
              (Key
"StartTimestamp" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= POSIX
startTimestamp),
            forall a. a -> Maybe a
Prelude.Just (Key
"EndTimestamp" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= POSIX
endTimestamp)
          ]
      )