| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Data.MediaBus.Basics.Ticks
Description
This module contains the Ticks time unit as well as the corresponding
known-at-compile-time StaticTicks time unit. The time stamps are given as
quotient of a Rate that indicates the number of Ticks per second.
- newtype Rate = Hertz Nat
- type Hz r = Hertz r
- type OnePerPicoSecond = Hz 1000000000000
- class KnownRate s where
- class (KnownRate (GetRate i), SetRate i (GetRate i) ~ i) => HasRate i where
- class (HasRate i, GetRate i ~ ri, SetRate i rj ~ j, KnownRate rj) => CoerceRate i j ri rj where
- getRate :: forall i proxy. HasRate i => proxy i -> Integer
- getRateProxy :: HasRate i => proxy i -> RateProxy (GetRate i)
- data RateProxy :: Rate -> Type where
- MkRateProxy :: RateProxy rate
- ConvertRateProxy :: proxy rate -> RateProxy rate
- type PeriodDuration i = 1 :/ GetRate i
- getPeriodDuration :: forall i proxy. HasRate i => proxy i -> NominalDiffTime
- coerceRateTo8kHz :: CoerceRate x y rx (Hz 8000) => x -> y
- coerceRateTo16kHz :: CoerceRate x y rx (Hz 16000) => x -> y
- coerceRateTo48kHz :: CoerceRate x y rx (Hz 48000) => x -> y
- coerceToDoubleRate :: forall r s x y. (CoerceRate x y r (Hz (s + s)), KnownRate r, RateVal r ~ s, KnownNat (s + s)) => x -> y
- newtype Ticks rate w = MkTicks w
- type CanBeTicks r w = (KnownRate r, Integral w)
- type PicoSeconds = Ticks OnePerPicoSecond Integer
- type Ticks32 r = Ticks r Word32
- mkTicks32 :: KnownRate r => proxy r -> Word32 -> Ticks32 r
- type Ticks64 r = Ticks r Word64
- mkTicks64 :: KnownRate r => proxy r -> Word64 -> Ticks64 r
- type Ticks32At8000 = Ticks32 (Hz 8000)
- mkTicks32At8000 :: Word32 -> Ticks32At8000
- type Ticks32At16000 = Ticks32 (Hz 16000)
- mkTicks32At16000 :: Word32 -> Ticks32At16000
- type Ticks32At48000 = Ticks32 (Hz 48000)
- mkTicks32At48000 :: Word32 -> Ticks32At48000
- type Ticks64At8000 = Ticks64 (Hz 8000)
- mkTicks64At8000 :: Word64 -> Ticks64At8000
- type Ticks64At16000 = Ticks64 (Hz 16000)
- mkTicks64At16000 :: Word64 -> Ticks64At16000
- type Ticks64At48000 = Ticks64 (Hz 48000)
- mkTicks64At48000 :: Word64 -> Ticks64At48000
- nominalDiffTime :: forall r w. CanBeTicks r w => Iso' (Ticks r w) NominalDiffTime
- convertTicks :: (CanBeTicks r w, CanBeTicks r' w') => Ticks r w -> Ticks r' w'
- data StaticTicks where
- (:/:) :: Nat -> Rate -> StaticTicks
- class KnownStaticTicks s where
- type family StaticTicksRate (s :: StaticTicks) :: Rate where ...
- type family StaticTicksTicks (s :: StaticTicks) :: Nat where ...
- class HasDuration a where
- class SetTimestamp t (GetTimestamp t) ~ t => HasTimestamp t where
- type GetTimestamp t
- type SetTimestamp t s
- setTimestampFromDurations :: forall r t a. (CanBeTicks r t, HasDuration a, HasTimestamp a, GetTimestamp a ~ ()) => a -> Ticks r t -> (SetTimestamp a (Ticks r t), Ticks r t)
- removeTimestamp :: HasTimestamp a => a -> SetTimestamp a ()
- class (KnownStaticTicks (GetStaticDuration s), SetStaticDuration s (GetStaticDuration s) ~ s) => HasStaticDuration s where
- type SetStaticDuration s (pt :: StaticTicks) :: k
- type GetStaticDuration s :: StaticTicks
- getStaticDurationTicks :: forall proxy s r t i. (CanBeTicks r i, KnownNat t, HasStaticDuration s, GetStaticDuration s ~ (t :/ r)) => proxy s -> Ticks r i
- getStaticDuration :: forall proxy s. HasStaticDuration s => proxy s -> NominalDiffTime
- toStaticDurationProxy :: HasStaticDuration s => proxy s -> Proxy (GetStaticDuration s)
- ticksFromStaticDuration :: forall proxy rate ticks i. (CanBeTicks rate i, KnownNat ticks) => proxy (ticks :/ rate) -> Ticks rate i
- type (:/) ticks rate = ticks :/: rate
Documentation
type OnePerPicoSecond = Hz 1000000000000 Source #
The maximum representable frequency is 10e12 1/s which corresponds to
the resolution of NominalDiffTime, i.e. 1 pico second.
class KnownRate s where Source #
Analogous to KnownNat this (kind-)class is for StaticTicks with a runtime
Ticks value.
Minimal complete definition
class (KnownRate (GetRate i), SetRate i (GetRate i) ~ i) => HasRate i Source #
Types with a known Rate, e.g. audio media has a sample rate.
class (HasRate i, GetRate i ~ ri, SetRate i rj ~ j, KnownRate rj) => CoerceRate i j ri rj where Source #
Types which contain a rate, but are agnostic of it. The counter example would be if the rate was a type index of a data family.
Minimal complete definition
Methods
coerceRate :: proxy rj -> i -> SetRate i rj Source #
Change the static sample rate, without e.g. resampling
Instances
| (HasRate i, (~) Rate (GetRate i) ri, (~) * (SetRate i rj) j, KnownRate rj, CoerceRate i j ri rj) => CoerceRate (Discontinous i) (Discontinous j) ri rj Source # | |
| (HasRate i, (~) Rate (GetRate i) ri, (~) * (SetRate i rj) j, KnownRate rj, CoerceRate i j ri rj) => CoerceRate (Segment d i) (Segment d j) ri rj Source # | |
data RateProxy :: Rate -> Type where Source #
A proxy type for Rates useful to prevent orphan instances, is seen in
the Show instance for RateProxy. If the instance were defined as
instance KnownRate r => Show (proxy r) where ... it would be an orphan
instance.
Constructors
| MkRateProxy :: RateProxy rate | |
| ConvertRateProxy :: proxy rate -> RateProxy rate |
type PeriodDuration i = 1 :/ GetRate i Source #
Return the StaticTicks representing the shortest representable duration
of something sampled at a Rate
getPeriodDuration :: forall i proxy. HasRate i => proxy i -> NominalDiffTime Source #
Return the reciprocal of the sample rate, i.e. the duration that one sample spans
coerceRateTo8kHz :: CoerceRate x y rx (Hz 8000) => x -> y Source #
Utility around coerceRate to set the sample rate to 8000 Hz.
coerceRateTo16kHz :: CoerceRate x y rx (Hz 16000) => x -> y Source #
Utility around coerceRate to set the sample rate to 16000 Hz.
coerceRateTo48kHz :: CoerceRate x y rx (Hz 48000) => x -> y Source #
Utility around coerceRate to set the sample rate to 48000 Hz.
coerceToDoubleRate :: forall r s x y. (CoerceRate x y r (Hz (s + s)), KnownRate r, RateVal r ~ s, KnownNat (s + s)) => x -> y Source #
Utility around coerceRate to double the sample rate.
An integral time unit such that (time_in_seconds = _ticks * 1/rate)
Constructors
| MkTicks w |
Instances
| Enum w => Enum (Ticks rate w) Source # | |
| Eq w => Eq (Ticks rate w) Source # | |
| (LocalOrd w, Integral w) => Integral (Ticks rate w) Source # | |
| Num w => Num (Ticks rate w) Source # | |
| (Eq w, LocalOrd w) => Ord (Ticks rate w) Source # | |
| (LocalOrd w, Real w) => Real (Ticks rate w) Source # | |
| (CanBeTicks r w, Show w) => Show (Ticks r w) Source # | |
| Generic (Ticks rate w) Source # | |
| Arbitrary w => Arbitrary (Ticks rate w) Source # | |
| Default w => Default (Ticks rate w) Source # | |
| NFData w => NFData (Ticks rate w) Source # | |
| Random w => Random (Ticks rate w) Source # | |
| LocalOrd w => LocalOrd (Ticks rate w) Source # | |
| type Rep (Ticks rate w) Source # | |
type CanBeTicks r w = (KnownRate r, Integral w) Source #
The constraint on the type parameters of 'Ticks
type PicoSeconds = Ticks OnePerPicoSecond Integer Source #
The highest resolution Ticks possible, such that it can still be
converted to NominalDiffTime
type Ticks32At8000 = Ticks32 (Hz 8000) Source #
mkTicks32At8000 :: Word32 -> Ticks32At8000 Source #
Create a Ticks32At8000 from a tick count.
type Ticks32At16000 = Ticks32 (Hz 16000) Source #
mkTicks32At16000 :: Word32 -> Ticks32At16000 Source #
Create a 'Ticks32At16000 from a tick count.
type Ticks32At48000 = Ticks32 (Hz 48000) Source #
mkTicks32At48000 :: Word32 -> Ticks32At48000 Source #
Create a 'Ticks32At48000 from a tick count.
type Ticks64At8000 = Ticks64 (Hz 8000) Source #
mkTicks64At8000 :: Word64 -> Ticks64At8000 Source #
Create a 'Ticks64At8000 from a tick count.
type Ticks64At16000 = Ticks64 (Hz 16000) Source #
mkTicks64At16000 :: Word64 -> Ticks64At16000 Source #
Create a 'Ticks64At16000 from a tick count.
type Ticks64At48000 = Ticks64 (Hz 48000) Source #
mkTicks64At48000 :: Word64 -> Ticks64At48000 Source #
Create a 'Ticks64At48000 from a tick count.
nominalDiffTime :: forall r w. CanBeTicks r w => Iso' (Ticks r w) NominalDiffTime Source #
A function (an Iso) that converts back-and-forth between Ticks and
NominalDiffTimes
convertTicks :: (CanBeTicks r w, CanBeTicks r' w') => Ticks r w -> Ticks r' w' Source #
Transform a Tick value to another Tick value.
data StaticTicks where Source #
Time unit for durations known at compile time.
Constructors
| (:/:) :: Nat -> Rate -> StaticTicks |
Instances
| (KnownRate r, KnownNat t) => HasStaticDuration StaticTicks ((:/) t r) Source # | |
| type GetStaticDuration StaticTicks ((:/) t r) Source # | |
| type SetStaticDuration StaticTicks ((:/) t r) ((:/) t' r') Source # | |
class KnownStaticTicks s where Source #
Analog to KnownNat this (kind-)class is for StaticTicks with a runtime
Ticks value.
Minimal complete definition
type family StaticTicksRate (s :: StaticTicks) :: Rate where ... Source #
Return the Rate value of a promoted StaticTicks.
Equations
| StaticTicksRate (t :/ r) = r |
type family StaticTicksTicks (s :: StaticTicks) :: Nat where ... Source #
Return the ticks value of a promoted StaticTicks.
Equations
| StaticTicksTicks (t :/ r) = t |
class HasDuration a where Source #
Types with a duration (e.g. audio samples).
Methods
getDuration :: a -> NominalDiffTime Source #
getDurationTicks :: CanBeTicks r i => a -> Ticks r i Source #
Instances
| HasDuration a => HasDuration (Maybe a) Source # | |
| HasDuration a => HasDuration (Discontinous a) Source # | |
| HasStaticDuration StaticTicks d => HasDuration (Segment d x) Source # | |
| (KnownRate r, CanBeSample (Pcm c t)) => HasDuration (Audio r c (Raw * t)) Source # | |
| HasDuration c => HasDuration (Frame s t c) Source # | |
| HasDuration (FrameCtx i s t p) Source # | |
| HasDuration c => HasDuration (Stream i s t p c) Source # | |
class SetTimestamp t (GetTimestamp t) ~ t => HasTimestamp t where Source #
Types that contain a Timestamp
Minimal complete definition
Methods
timestamp :: Lens t (SetTimestamp t s) (GetTimestamp t) s Source #
timestamp' :: Lens' t (GetTimestamp t) Source #
Instances
| (HasTimestamp a, HasTimestamp b, (~) * (GetTimestamp a) (GetTimestamp b)) => HasTimestamp (Series a b) Source # | |
| HasTimestamp (Frame s t c) Source # | |
| HasTimestamp (FrameCtx i s t p) Source # | |
| HasTimestamp (Stream i s t p c) Source # | |
setTimestampFromDurations :: forall r t a. (CanBeTicks r t, HasDuration a, HasTimestamp a, GetTimestamp a ~ ()) => a -> Ticks r t -> (SetTimestamp a (Ticks r t), Ticks r t) Source #
Calculate and set a timestamp.
The timestamp of each element is calculated from the sum of the durations of
the previous elements stored and the start time stamp t0.
The input elements must be instances of HasTimestamp but with the important
condition, that the input timestamp is always unit i.e. ().
This prevents meaningful timestamps from being overwritten.
Use removeTimestamp to explicitly remove a timestamp.
removeTimestamp :: HasTimestamp a => a -> SetTimestamp a () Source #
Explicitly remove a timestamp, by setting the timestamp to ().
class (KnownStaticTicks (GetStaticDuration s), SetStaticDuration s (GetStaticDuration s) ~ s) => HasStaticDuration s Source #
Types that have a duration known at compoile time.
Associated Types
type SetStaticDuration s (pt :: StaticTicks) :: k Source #
type GetStaticDuration s :: StaticTicks Source #
Instances
| (KnownRate r, KnownNat t) => HasStaticDuration StaticTicks ((:/) t r) Source # | |
| KnownStaticTicks d => HasStaticDuration * (Segment d x) Source # | |
getStaticDurationTicks :: forall proxy s r t i. (CanBeTicks r i, KnownNat t, HasStaticDuration s, GetStaticDuration s ~ (t :/ r)) => proxy s -> Ticks r i Source #
Convert the StaticDuration that some type has to any Ticks.
getStaticDuration :: forall proxy s. HasStaticDuration s => proxy s -> NominalDiffTime Source #
Convert the StaticDuration that some type has to the number of seconds.
toStaticDurationProxy :: HasStaticDuration s => proxy s -> Proxy (GetStaticDuration s) Source #
Create a Proxy for the StaticTicks type associated with s, this is
basically the analogon to the getDuration method - just for types with a
duration known at compile time.
ticksFromStaticDuration :: forall proxy rate ticks i. (CanBeTicks rate i, KnownNat ticks) => proxy (ticks :/ rate) -> Ticks rate i Source #
type (:/) ticks rate = ticks :/: rate Source #
Convenient wrapper around MkStaticTicks and
MkRate to create a promoted StaticTicks.