mediabus-0.4.0.1: Multimedia streaming on top of Conduit

Safe HaskellNone
LanguageHaskell2010

Data.MediaBus.Media.Segment

Description

Media segments with a fixed duration

Synopsis

Documentation

newtype Segment duration c Source #

A segment is some content with a fixed (type level) duration.

Constructors

MkSegment c 

Instances

Functor (Segment duration) Source # 

Methods

fmap :: (a -> b) -> Segment duration a -> Segment duration b #

(<$) :: a -> Segment duration b -> Segment duration a #

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

Associated Types

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

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

Eq c => Eq (Segment duration c) Source # 

Methods

(==) :: Segment duration c -> Segment duration c -> Bool #

(/=) :: Segment duration c -> Segment duration c -> Bool #

(HasStaticDuration StaticTicks d, Show c) => Show (Segment d c) Source # 

Methods

showsPrec :: Int -> Segment d c -> ShowS #

show :: Segment d c -> String #

showList :: [Segment d c] -> ShowS #

Arbitrary c => Arbitrary (Segment duration c) Source # 

Methods

arbitrary :: Gen (Segment duration c) #

shrink :: Segment duration c -> [Segment duration c] #

Default c => Default (Segment duration c) Source # 

Methods

def :: Segment duration c #

NFData c => NFData (Segment duration c) Source # 

Methods

rnf :: Segment duration c -> () #

HasStaticDuration StaticTicks d => HasDuration (Segment d x) Source # 
HasRate c => HasRate (Segment d c) Source # 

Associated Types

type SetRate (Segment d c) (r :: Rate) :: * Source #

type GetRate (Segment d c) :: Rate Source #

(HasStaticDuration StaticTicks d, CanGenerateBlankMedia a) => CanBeBlank (Segment d a) Source # 

Methods

blank :: Segment d a Source #

HasMedia c c' => HasMedia (Segment d c) (Segment d c') Source # 

Associated Types

type MediaFrom (Segment d c) :: * Source #

type MediaTo (Segment d c') :: * Source #

Methods

media :: Lens (Segment d c) (Segment d c') (MediaFrom (Segment d c)) (MediaTo (Segment d c')) Source #

EachChannel c c' => EachChannel (Segment d c) (Segment d c') Source # 

Associated Types

type ChannelsFrom (Segment d c) :: * Source #

type ChannelsTo (Segment d c') :: * Source #

EachSample c c' => EachSample (Segment d c) (Segment d c') Source # 

Associated Types

type SamplesFrom (Segment d c) :: * Source #

type SamplesTo (Segment d c') :: * 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 # 

Methods

coerceRate :: proxy rj -> Segment d i -> SetRate (Segment d i) rj Source #

type GetStaticDuration * (Segment d x) Source # 
type GetStaticDuration * (Segment d x) = d
type SetStaticDuration * (Segment d x) pt Source # 
type SetStaticDuration * (Segment d x) pt = Segment pt x
type MediaFrom (Segment d c) Source # 
type MediaFrom (Segment d c) = MediaFrom c
type MediaTo (Segment d c') Source # 
type MediaTo (Segment d c') = MediaTo c'
type ChannelsFrom (Segment d c) Source # 
type ChannelsTo (Segment d c') Source # 
type ChannelsTo (Segment d c') = ChannelsTo c'
type GetRate (Segment d c) Source # 
type GetRate (Segment d c) = GetRate c
type SamplesFrom (Segment d c) Source # 
type SamplesTo (Segment d c') Source # 
type SamplesTo (Segment d c') = SamplesTo c'
type SetRate (Segment d c) r' Source # 
type SetRate (Segment d c) r' = Segment d (SetRate c r')

segmentContent :: Iso (Segment d c) (Segment d c') c c' Source #

An Iso for the Segment newtype.

class CanSegment a where Source #

Class of types that support splitting values into parts with a certain duration.

Minimal complete definition

splitAfterDuration

Methods

splitAfterDuration :: HasStaticDuration d => proxy d -> a -> Maybe (Segment d a, a) Source #

Try to split the packet into the a part which has the given duration and a rest. If it is not possible to split of the desired duration, e.g. because the input data is too short, return Nothing.

Instances

(CanBeSample (Pcm c t), KnownRate r) => CanSegment (Audio r c (Raw * t)) Source # 

Methods

splitAfterDuration :: HasStaticDuration StaticTicks d => proxy d -> Audio r c (Raw * t) -> Maybe (Segment d (Audio r c (Raw * t)), Audio r c (Raw * t)) Source #