isobmff-0.14.0.0: A parser and generator for the ISO-14496-12/14 base media file format

Safe HaskellNone
LanguageHaskell2010

Data.ByteString.IsoBaseFileFormat.Util.Time

Description

Time and timing utilities.

Synopsis

Documentation

referenceTime :: UTCTime Source #

According to the standard, fields with absolute dates and times are in seconds since 19040101 at midnight (UTC). This is this reference time.

utcToMp4 :: Num t => UTCTime -> t Source #

Convert a UTCTime to a number of seconds since referenceTime.

mp4CurrentTime :: Num t => IO t Source #

Get the current time as number of seconds since referenceTime

durationFromSeconds :: Num t => TimeScale -> Integer -> t Source #

Utility function to convert seconds (Integers) to any Num using a TimeScale, Since Scalar has a Num instance this can be used to generate duration fields.

oneSecond32 :: TimeScale -> TS32 label Source #

Utility function to generate the equivalent of one second (1 s)

oneSecond64 :: TimeScale -> TS64 label Source #

Utility function to generate the equivalent of one second (1 s)

diffTimeToTicks :: Integral t => NominalDiffTime -> TimeScale -> t Source #

Convert a NominalDiffTime to the number of Ticks with respect to a given TimeScale.

ticksToDiffTime :: Integral t => t -> TimeScale -> NominalDiffTime Source #

Convert a NominalDiffTime to the number of Ticks with respect to a given TimeScale.

newtype TimeScale Source #

Default time-scale value Based on history and tradition this value is 90000. MPEG-2 TS defines a single clock for each program, running at 27MHz. The timescale of MPEG-2 TS Hint Tracks should be divisable by 90000.

Constructors

TimeScale 
Instances
Bounded TimeScale Source # 
Instance details

Defined in Data.ByteString.IsoBaseFileFormat.Util.Time

Enum TimeScale Source # 
Instance details

Defined in Data.ByteString.IsoBaseFileFormat.Util.Time

Eq TimeScale Source # 
Instance details

Defined in Data.ByteString.IsoBaseFileFormat.Util.Time

Integral TimeScale Source # 
Instance details

Defined in Data.ByteString.IsoBaseFileFormat.Util.Time

Num TimeScale Source # 
Instance details

Defined in Data.ByteString.IsoBaseFileFormat.Util.Time

Ord TimeScale Source # 
Instance details

Defined in Data.ByteString.IsoBaseFileFormat.Util.Time

Real TimeScale Source # 
Instance details

Defined in Data.ByteString.IsoBaseFileFormat.Util.Time

Show TimeScale Source # 
Instance details

Defined in Data.ByteString.IsoBaseFileFormat.Util.Time

Storable TimeScale Source # 
Instance details

Defined in Data.ByteString.IsoBaseFileFormat.Util.Time

Bits TimeScale Source # 
Instance details

Defined in Data.ByteString.IsoBaseFileFormat.Util.Time

Default TimeScale Source # 
Instance details

Defined in Data.ByteString.IsoBaseFileFormat.Util.Time

Methods

def :: TimeScale #

IsBoxContent TimeScale Source # 
Instance details

Defined in Data.ByteString.IsoBaseFileFormat.Util.Time

type Timing (version :: Nat) = Versioned TimingV0 TimingV1 version Source #

Time and timing information about a movie.

The creation/modification times are in seconds since midnight, Jan. 1, 1904, in UTC time. Time scale declares the time coordinate system, it specifies the number of time units that pass one second. The time coordinate system is used by e.g. the duration field, which by the way contains the duration of the longest track, if known, or simply the equivalent of 1s.

data TS (version :: Nat) (label :: Symbol) where Source #

Constructors

TSv0 :: !Word32 -> TS 0 label 
TSv1 :: !Word64 -> TS 1 label 
Instances
IsBoxContent (TS v n) Source # 
Instance details

Defined in Data.ByteString.IsoBaseFileFormat.Util.Time

Methods

boxSize :: TS v n -> BoxSize Source #

boxBuilder :: TS v n -> Builder Source #

newtype Ticks (timeScale :: Nat) Source #

A type that denotes a time relative to a TimeScale which is included in its type. Ticks is the number of time units passed, where each time unit has a physical duration of timescale * 1/s i.e. timescale Ticks last about 1 s. TODO use this instead of raw Word32s

Constructors

MkTicks 

Fields

Instances
Bounded (Ticks timeScale) Source # 
Instance details

Defined in Data.ByteString.IsoBaseFileFormat.Util.Time

Methods

minBound :: Ticks timeScale #

maxBound :: Ticks timeScale #

Enum (Ticks timeScale) Source # 
Instance details

Defined in Data.ByteString.IsoBaseFileFormat.Util.Time

Methods

succ :: Ticks timeScale -> Ticks timeScale #

pred :: Ticks timeScale -> Ticks timeScale #

toEnum :: Int -> Ticks timeScale #

fromEnum :: Ticks timeScale -> Int #

enumFrom :: Ticks timeScale -> [Ticks timeScale] #

enumFromThen :: Ticks timeScale -> Ticks timeScale -> [Ticks timeScale] #

enumFromTo :: Ticks timeScale -> Ticks timeScale -> [Ticks timeScale] #

enumFromThenTo :: Ticks timeScale -> Ticks timeScale -> Ticks timeScale -> [Ticks timeScale] #

Eq (Ticks timeScale) Source # 
Instance details

Defined in Data.ByteString.IsoBaseFileFormat.Util.Time

Methods

(==) :: Ticks timeScale -> Ticks timeScale -> Bool #

(/=) :: Ticks timeScale -> Ticks timeScale -> Bool #

Integral (Ticks timeScale) Source # 
Instance details

Defined in Data.ByteString.IsoBaseFileFormat.Util.Time

Methods

quot :: Ticks timeScale -> Ticks timeScale -> Ticks timeScale #

rem :: Ticks timeScale -> Ticks timeScale -> Ticks timeScale #

div :: Ticks timeScale -> Ticks timeScale -> Ticks timeScale #

mod :: Ticks timeScale -> Ticks timeScale -> Ticks timeScale #

quotRem :: Ticks timeScale -> Ticks timeScale -> (Ticks timeScale, Ticks timeScale) #

divMod :: Ticks timeScale -> Ticks timeScale -> (Ticks timeScale, Ticks timeScale) #

toInteger :: Ticks timeScale -> Integer #

Num (Ticks timeScale) Source # 
Instance details

Defined in Data.ByteString.IsoBaseFileFormat.Util.Time

Methods

(+) :: Ticks timeScale -> Ticks timeScale -> Ticks timeScale #

(-) :: Ticks timeScale -> Ticks timeScale -> Ticks timeScale #

(*) :: Ticks timeScale -> Ticks timeScale -> Ticks timeScale #

negate :: Ticks timeScale -> Ticks timeScale #

abs :: Ticks timeScale -> Ticks timeScale #

signum :: Ticks timeScale -> Ticks timeScale #

fromInteger :: Integer -> Ticks timeScale #

Ord (Ticks timeScale) Source # 
Instance details

Defined in Data.ByteString.IsoBaseFileFormat.Util.Time

Methods

compare :: Ticks timeScale -> Ticks timeScale -> Ordering #

(<) :: Ticks timeScale -> Ticks timeScale -> Bool #

(<=) :: Ticks timeScale -> Ticks timeScale -> Bool #

(>) :: Ticks timeScale -> Ticks timeScale -> Bool #

(>=) :: Ticks timeScale -> Ticks timeScale -> Bool #

max :: Ticks timeScale -> Ticks timeScale -> Ticks timeScale #

min :: Ticks timeScale -> Ticks timeScale -> Ticks timeScale #

Real (Ticks timeScale) Source # 
Instance details

Defined in Data.ByteString.IsoBaseFileFormat.Util.Time

Methods

toRational :: Ticks timeScale -> Rational #

Show (Ticks timeScale) Source # 
Instance details

Defined in Data.ByteString.IsoBaseFileFormat.Util.Time

Methods

showsPrec :: Int -> Ticks timeScale -> ShowS #

show :: Ticks timeScale -> String #

showList :: [Ticks timeScale] -> ShowS #

Storable (Ticks timeScale) Source # 
Instance details

Defined in Data.ByteString.IsoBaseFileFormat.Util.Time

Methods

sizeOf :: Ticks timeScale -> Int #

alignment :: Ticks timeScale -> Int #

peekElemOff :: Ptr (Ticks timeScale) -> Int -> IO (Ticks timeScale) #

pokeElemOff :: Ptr (Ticks timeScale) -> Int -> Ticks timeScale -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Ticks timeScale) #

pokeByteOff :: Ptr b -> Int -> Ticks timeScale -> IO () #

peek :: Ptr (Ticks timeScale) -> IO (Ticks timeScale) #

poke :: Ptr (Ticks timeScale) -> Ticks timeScale -> IO () #

Bits (Ticks timeScale) Source # 
Instance details

Defined in Data.ByteString.IsoBaseFileFormat.Util.Time

Methods

(.&.) :: Ticks timeScale -> Ticks timeScale -> Ticks timeScale #

(.|.) :: Ticks timeScale -> Ticks timeScale -> Ticks timeScale #

xor :: Ticks timeScale -> Ticks timeScale -> Ticks timeScale #

complement :: Ticks timeScale -> Ticks timeScale #

shift :: Ticks timeScale -> Int -> Ticks timeScale #

rotate :: Ticks timeScale -> Int -> Ticks timeScale #

zeroBits :: Ticks timeScale #

bit :: Int -> Ticks timeScale #

setBit :: Ticks timeScale -> Int -> Ticks timeScale #

clearBit :: Ticks timeScale -> Int -> Ticks timeScale #

complementBit :: Ticks timeScale -> Int -> Ticks timeScale #

testBit :: Ticks timeScale -> Int -> Bool #

bitSizeMaybe :: Ticks timeScale -> Maybe Int #

bitSize :: Ticks timeScale -> Int #

isSigned :: Ticks timeScale -> Bool #

shiftL :: Ticks timeScale -> Int -> Ticks timeScale #

unsafeShiftL :: Ticks timeScale -> Int -> Ticks timeScale #

shiftR :: Ticks timeScale -> Int -> Ticks timeScale #

unsafeShiftR :: Ticks timeScale -> Int -> Ticks timeScale #

rotateL :: Ticks timeScale -> Int -> Ticks timeScale #

rotateR :: Ticks timeScale -> Int -> Ticks timeScale #

popCount :: Ticks timeScale -> Int #

IsBoxContent (Ticks n) Source # 
Instance details

Defined in Data.ByteString.IsoBaseFileFormat.Util.Time

newtype Ticks32 (timeScale :: Nat) Source #

Constructors

MkTicks32 

Fields

Instances
Bounded (Ticks32 timeScale) Source # 
Instance details

Defined in Data.ByteString.IsoBaseFileFormat.Util.Time

Methods

minBound :: Ticks32 timeScale #

maxBound :: Ticks32 timeScale #

Enum (Ticks32 timeScale) Source # 
Instance details

Defined in Data.ByteString.IsoBaseFileFormat.Util.Time

Methods

succ :: Ticks32 timeScale -> Ticks32 timeScale #

pred :: Ticks32 timeScale -> Ticks32 timeScale #

toEnum :: Int -> Ticks32 timeScale #

fromEnum :: Ticks32 timeScale -> Int #

enumFrom :: Ticks32 timeScale -> [Ticks32 timeScale] #

enumFromThen :: Ticks32 timeScale -> Ticks32 timeScale -> [Ticks32 timeScale] #

enumFromTo :: Ticks32 timeScale -> Ticks32 timeScale -> [Ticks32 timeScale] #

enumFromThenTo :: Ticks32 timeScale -> Ticks32 timeScale -> Ticks32 timeScale -> [Ticks32 timeScale] #

Eq (Ticks32 timeScale) Source # 
Instance details

Defined in Data.ByteString.IsoBaseFileFormat.Util.Time

Methods

(==) :: Ticks32 timeScale -> Ticks32 timeScale -> Bool #

(/=) :: Ticks32 timeScale -> Ticks32 timeScale -> Bool #

Integral (Ticks32 timeScale) Source # 
Instance details

Defined in Data.ByteString.IsoBaseFileFormat.Util.Time

Methods

quot :: Ticks32 timeScale -> Ticks32 timeScale -> Ticks32 timeScale #

rem :: Ticks32 timeScale -> Ticks32 timeScale -> Ticks32 timeScale #

div :: Ticks32 timeScale -> Ticks32 timeScale -> Ticks32 timeScale #

mod :: Ticks32 timeScale -> Ticks32 timeScale -> Ticks32 timeScale #

quotRem :: Ticks32 timeScale -> Ticks32 timeScale -> (Ticks32 timeScale, Ticks32 timeScale) #

divMod :: Ticks32 timeScale -> Ticks32 timeScale -> (Ticks32 timeScale, Ticks32 timeScale) #

toInteger :: Ticks32 timeScale -> Integer #

Num (Ticks32 timeScale) Source # 
Instance details

Defined in Data.ByteString.IsoBaseFileFormat.Util.Time

Methods

(+) :: Ticks32 timeScale -> Ticks32 timeScale -> Ticks32 timeScale #

(-) :: Ticks32 timeScale -> Ticks32 timeScale -> Ticks32 timeScale #

(*) :: Ticks32 timeScale -> Ticks32 timeScale -> Ticks32 timeScale #

negate :: Ticks32 timeScale -> Ticks32 timeScale #

abs :: Ticks32 timeScale -> Ticks32 timeScale #

signum :: Ticks32 timeScale -> Ticks32 timeScale #

fromInteger :: Integer -> Ticks32 timeScale #

Ord (Ticks32 timeScale) Source # 
Instance details

Defined in Data.ByteString.IsoBaseFileFormat.Util.Time

Methods

compare :: Ticks32 timeScale -> Ticks32 timeScale -> Ordering #

(<) :: Ticks32 timeScale -> Ticks32 timeScale -> Bool #

(<=) :: Ticks32 timeScale -> Ticks32 timeScale -> Bool #

(>) :: Ticks32 timeScale -> Ticks32 timeScale -> Bool #

(>=) :: Ticks32 timeScale -> Ticks32 timeScale -> Bool #

max :: Ticks32 timeScale -> Ticks32 timeScale -> Ticks32 timeScale #

min :: Ticks32 timeScale -> Ticks32 timeScale -> Ticks32 timeScale #

Real (Ticks32 timeScale) Source # 
Instance details

Defined in Data.ByteString.IsoBaseFileFormat.Util.Time

Methods

toRational :: Ticks32 timeScale -> Rational #

Show (Ticks32 timeScale) Source # 
Instance details

Defined in Data.ByteString.IsoBaseFileFormat.Util.Time

Methods

showsPrec :: Int -> Ticks32 timeScale -> ShowS #

show :: Ticks32 timeScale -> String #

showList :: [Ticks32 timeScale] -> ShowS #

Storable (Ticks32 timeScale) Source # 
Instance details

Defined in Data.ByteString.IsoBaseFileFormat.Util.Time

Methods

sizeOf :: Ticks32 timeScale -> Int #

alignment :: Ticks32 timeScale -> Int #

peekElemOff :: Ptr (Ticks32 timeScale) -> Int -> IO (Ticks32 timeScale) #

pokeElemOff :: Ptr (Ticks32 timeScale) -> Int -> Ticks32 timeScale -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Ticks32 timeScale) #

pokeByteOff :: Ptr b -> Int -> Ticks32 timeScale -> IO () #

peek :: Ptr (Ticks32 timeScale) -> IO (Ticks32 timeScale) #

poke :: Ptr (Ticks32 timeScale) -> Ticks32 timeScale -> IO () #

Bits (Ticks32 timeScale) Source # 
Instance details

Defined in Data.ByteString.IsoBaseFileFormat.Util.Time

Methods

(.&.) :: Ticks32 timeScale -> Ticks32 timeScale -> Ticks32 timeScale #

(.|.) :: Ticks32 timeScale -> Ticks32 timeScale -> Ticks32 timeScale #

xor :: Ticks32 timeScale -> Ticks32 timeScale -> Ticks32 timeScale #

complement :: Ticks32 timeScale -> Ticks32 timeScale #

shift :: Ticks32 timeScale -> Int -> Ticks32 timeScale #

rotate :: Ticks32 timeScale -> Int -> Ticks32 timeScale #

zeroBits :: Ticks32 timeScale #

bit :: Int -> Ticks32 timeScale #

setBit :: Ticks32 timeScale -> Int -> Ticks32 timeScale #

clearBit :: Ticks32 timeScale -> Int -> Ticks32 timeScale #

complementBit :: Ticks32 timeScale -> Int -> Ticks32 timeScale #

testBit :: Ticks32 timeScale -> Int -> Bool #

bitSizeMaybe :: Ticks32 timeScale -> Maybe Int #

bitSize :: Ticks32 timeScale -> Int #

isSigned :: Ticks32 timeScale -> Bool #

shiftL :: Ticks32 timeScale -> Int -> Ticks32 timeScale #

unsafeShiftL :: Ticks32 timeScale -> Int -> Ticks32 timeScale #

shiftR :: Ticks32 timeScale -> Int -> Ticks32 timeScale #

unsafeShiftR :: Ticks32 timeScale -> Int -> Ticks32 timeScale #

rotateL :: Ticks32 timeScale -> Int -> Ticks32 timeScale #

rotateR :: Ticks32 timeScale -> Int -> Ticks32 timeScale #

popCount :: Ticks32 timeScale -> Int #

IsBoxContent (Ticks32 n) Source # 
Instance details

Defined in Data.ByteString.IsoBaseFileFormat.Util.Time