mediabus-0.2.0.1: Multimedia streaming on top of Conduit

Safe HaskellNone
LanguageHaskell2010

Data.MediaBus.Ticks

Synopsis

Documentation

class HasDuration a where Source #

Types with a duration (e.g. audio samples).

Instances

HasDuration a => HasDuration (Maybe a) Source # 
HasDuration a => HasDuration (Discontinous a) Source # 
(HasDuration (Proxy * sampleType), Storable sampleType) => HasDuration (SampleBuffer sampleType) Source # 
HasDuration (Proxy * a) => HasDuration (Proxy * (ChannelPair a)) Source # 
KnownNat r => HasDuration (Proxy * (S16 r)) Source # 
HasDuration (Proxy * ALaw) Source # 
HasStaticDuration StaticTicks d => HasDuration (Segment d x) 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 # 

Methods

getDuration :: Stream i s t p c -> NominalDiffTime Source #

getDurationTicks :: (Integral i, KnownNat r) => Stream i s t p c -> Ticks r i Source #

class SetTimestamp t (GetTimestamp t) ~ t => HasTimestampT t Source #

Associated Types

type GetTimestamp t Source #

type SetTimestamp t s Source #

Instances

(HasTimestampT a, HasTimestampT b, (~) * (GetTimestamp a) (GetTimestamp b)) => HasTimestampT (Series a b) Source # 

Associated Types

type GetTimestamp (Series a b) :: * Source #

type SetTimestamp (Series a b) s :: * Source #

HasTimestampT (Frame s t c) Source # 

Associated Types

type GetTimestamp (Frame s t c) :: * Source #

type SetTimestamp (Frame s t c) s :: * Source #

HasTimestampT (FrameCtx i s t p) Source # 

Associated Types

type GetTimestamp (FrameCtx i s t p) :: * Source #

type SetTimestamp (FrameCtx i s t p) s :: * Source #

HasTimestampT (Stream i s t p c) Source # 

Associated Types

type GetTimestamp (Stream i s t p c) :: * Source #

type SetTimestamp (Stream i s t p c) s :: * Source #

class HasTimestampT t => HasTimestamp t where Source #

Minimal complete definition

timestamp

Instances

(HasTimestamp a, HasTimestamp b, (~) * (GetTimestamp a) (GetTimestamp b)) => HasTimestamp (Series a b) Source # 

Methods

timestamp :: Functor f => (GetTimestamp (Series a b) -> f s) -> Series a b -> f (SetTimestamp (Series a b) s) Source #

timestamp' :: Lens' (Series a b) (GetTimestamp (Series a b)) Source #

HasTimestamp (Frame s t c) Source # 

Methods

timestamp :: Functor f => (GetTimestamp (Frame s t c) -> f s) -> Frame s t c -> f (SetTimestamp (Frame s t c) s) Source #

timestamp' :: Lens' (Frame s t c) (GetTimestamp (Frame s t c)) Source #

HasTimestamp (FrameCtx i s t p) Source # 

Methods

timestamp :: Functor f => (GetTimestamp (FrameCtx i s t p) -> f s) -> FrameCtx i s t p -> f (SetTimestamp (FrameCtx i s t p) s) Source #

timestamp' :: Lens' (FrameCtx i s t p) (GetTimestamp (FrameCtx i s t p)) Source #

HasTimestamp (Stream i s t p c) Source # 

Methods

timestamp :: Functor f => (GetTimestamp (Stream i s t p c) -> f s) -> Stream i s t p c -> f (SetTimestamp (Stream i s t p c) s) Source #

timestamp' :: Lens' (Stream i s t p c) (GetTimestamp (Stream i s t p c)) Source #

newtype Ticks rate w Source #

Constructors

MkTicks w 

Instances

Enum w => Enum (Ticks rate w) Source # 

Methods

succ :: Ticks rate w -> Ticks rate w #

pred :: Ticks rate w -> Ticks rate w #

toEnum :: Int -> Ticks rate w #

fromEnum :: Ticks rate w -> Int #

enumFrom :: Ticks rate w -> [Ticks rate w] #

enumFromThen :: Ticks rate w -> Ticks rate w -> [Ticks rate w] #

enumFromTo :: Ticks rate w -> Ticks rate w -> [Ticks rate w] #

enumFromThenTo :: Ticks rate w -> Ticks rate w -> Ticks rate w -> [Ticks rate w] #

Eq w => Eq (Ticks rate w) Source # 

Methods

(==) :: Ticks rate w -> Ticks rate w -> Bool #

(/=) :: Ticks rate w -> Ticks rate w -> Bool #

(LocalOrd w, Integral w) => Integral (Ticks rate w) Source # 

Methods

quot :: Ticks rate w -> Ticks rate w -> Ticks rate w #

rem :: Ticks rate w -> Ticks rate w -> Ticks rate w #

div :: Ticks rate w -> Ticks rate w -> Ticks rate w #

mod :: Ticks rate w -> Ticks rate w -> Ticks rate w #

quotRem :: Ticks rate w -> Ticks rate w -> (Ticks rate w, Ticks rate w) #

divMod :: Ticks rate w -> Ticks rate w -> (Ticks rate w, Ticks rate w) #

toInteger :: Ticks rate w -> Integer #

Num w => Num (Ticks rate w) Source # 

Methods

(+) :: Ticks rate w -> Ticks rate w -> Ticks rate w #

(-) :: Ticks rate w -> Ticks rate w -> Ticks rate w #

(*) :: Ticks rate w -> Ticks rate w -> Ticks rate w #

negate :: Ticks rate w -> Ticks rate w #

abs :: Ticks rate w -> Ticks rate w #

signum :: Ticks rate w -> Ticks rate w #

fromInteger :: Integer -> Ticks rate w #

(Eq w, LocalOrd w) => Ord (Ticks rate w) Source # 

Methods

compare :: Ticks rate w -> Ticks rate w -> Ordering #

(<) :: Ticks rate w -> Ticks rate w -> Bool #

(<=) :: Ticks rate w -> Ticks rate w -> Bool #

(>) :: Ticks rate w -> Ticks rate w -> Bool #

(>=) :: Ticks rate w -> Ticks rate w -> Bool #

max :: Ticks rate w -> Ticks rate w -> Ticks rate w #

min :: Ticks rate w -> Ticks rate w -> Ticks rate w #

(LocalOrd w, Real w) => Real (Ticks rate w) Source # 

Methods

toRational :: Ticks rate w -> Rational #

(KnownNat r, Integral w, Show w) => Show (Ticks r w) Source # 

Methods

showsPrec :: Int -> Ticks r w -> ShowS #

show :: Ticks r w -> String #

showList :: [Ticks r w] -> ShowS #

Generic (Ticks rate w) Source # 

Associated Types

type Rep (Ticks rate w) :: * -> * #

Methods

from :: Ticks rate w -> Rep (Ticks rate w) x #

to :: Rep (Ticks rate w) x -> Ticks rate w #

Arbitrary w => Arbitrary (Ticks rate w) Source # 

Methods

arbitrary :: Gen (Ticks rate w) #

shrink :: Ticks rate w -> [Ticks rate w] #

Default w => Default (Ticks rate w) Source # 

Methods

def :: Ticks rate w #

NFData w => NFData (Ticks rate w) Source # 

Methods

rnf :: Ticks rate w -> () #

Random w => Random (Ticks rate w) Source # 

Methods

randomR :: RandomGen g => (Ticks rate w, Ticks rate w) -> g -> (Ticks rate w, g) #

random :: RandomGen g => g -> (Ticks rate w, g) #

randomRs :: RandomGen g => (Ticks rate w, Ticks rate w) -> g -> [Ticks rate w] #

randoms :: RandomGen g => g -> [Ticks rate w] #

randomRIO :: (Ticks rate w, Ticks rate w) -> IO (Ticks rate w) #

randomIO :: IO (Ticks rate w) #

LocalOrd w => LocalOrd (Ticks rate w) Source # 

Methods

succeeds :: Ticks rate w -> Ticks rate w -> Bool Source #

type Rep (Ticks rate w) Source # 
type Rep (Ticks rate w) = D1 (MetaData "Ticks" "Data.MediaBus.Ticks" "mediabus-0.2.0.1-GufOXSQMJOgBSiYlFFnZ4L" True) (C1 (MetaCons "MkTicks" PrefixI True) (S1 (MetaSel (Just Symbol "_ticks") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 w)))

mkTicks :: forall proxy rate baseType. proxy '(rate, baseType) -> baseType -> Ticks rate baseType Source #

convertTicks :: (Integral w, Integral w', KnownNat r, KnownNat r') => Ticks r w -> Ticks r' w' Source #

data StaticTicks where Source #

Constructors

MkStaticTicks :: Nat -> Rate -> StaticTicks 

Instances

class KnownStaticTicks s where Source #

Minimal complete definition

staticTicksVal

Methods

staticTicksVal :: KnownNat r => proxy s -> Ticks r Integer Source #

data Rate Source #

Constructors

MkRate Nat 

type (:@) ticks rate = MkStaticTicks ticks (MkRate rate) Source #

type family StaticTicksRate (s :: StaticTicks) :: Nat where ... Source #

Equations

StaticTicksRate (t :@ r) = r 

type family StaticTicksTicks (s :: StaticTicks) :: Nat where ... Source #

Equations

StaticTicksTicks (t :@ r) = t 

class (KnownStaticTicks (GetStaticDuration s), SetStaticDuration s (GetStaticDuration s) ~ s) => HasStaticDuration s Source #

Associated Types

type SetStaticDuration s (pt :: StaticTicks) :: k' Source #

type GetStaticDuration s :: StaticTicks Source #

Instances

(KnownNat r, KnownNat t) => HasStaticDuration StaticTicks ((:@) t r) Source # 

Associated Types

type SetStaticDuration k' ((:@) t r) (s :: (:@) t r) (pt :: StaticTicks) :: k' Source #

type GetStaticDuration ((:@) t r) (s :: (:@) t r) :: StaticTicks Source #

KnownStaticTicks d => HasStaticDuration * (Segment d x) Source # 

Associated Types

type SetStaticDuration k' (Segment d x) (s :: Segment d x) (pt :: StaticTicks) :: k' Source #

type GetStaticDuration (Segment d x) (s :: Segment d x) :: StaticTicks Source #

getStaticDuration :: forall proxy s. HasStaticDuration s => proxy s -> NominalDiffTime Source #

getStaticTicks :: forall proxy s r t i. (KnownNat r, KnownNat t, HasStaticDuration s, GetStaticDuration s ~ (t :@ r), Integral i) => proxy s -> Ticks r i Source #

getStaticRate :: forall proxy s r t. (KnownNat r, KnownNat t, HasStaticDuration s, GetStaticDuration s ~ (t :@ r)) => proxy s -> Integer Source #

ticksFromStaticDuration :: forall proxy rate ticks i. (KnownNat rate, KnownNat ticks, Integral i) => proxy (ticks :@ rate) -> Ticks rate i Source #

rateFromStaticDuration :: forall proxy rate ticks. (KnownNat rate, KnownNat ticks) => proxy (ticks :@ rate) -> Integer Source #