mediabus-0.4.0.1: Multimedia streaming on top of Conduit

Safe HaskellNone
LanguageHaskell2010

Data.MediaBus.Media.Audio.Raw

Description

Sub-types of Audio for uncompressed audio.

Synopsis

Documentation

data Raw encoding Source #

An indicator for uncompressed audio with a given per sample encoding type.

Instances

(Typeable k t, KnownRate r, KnownChannelLayout * c) => Show (MediaDescription * (Audio r c (Raw k t))) Source # 

Methods

showsPrec :: Int -> MediaDescription * (Audio r c (Raw k t)) -> ShowS #

show :: MediaDescription * (Audio r c (Raw k t)) -> String #

showList :: [MediaDescription * (Audio r c (Raw k t))] -> ShowS #

CanBeSample (Pcm c t) => Eq (Audio r c (Raw * t)) Source # 

Methods

(==) :: Audio r c (Raw * t) -> Audio r c (Raw * t) -> Bool #

(/=) :: Audio r c (Raw * t) -> Audio r c (Raw * t) -> Bool #

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

Methods

showsPrec :: Int -> Audio r c (Raw * t) -> ShowS #

show :: Audio r c (Raw * t) -> String #

showList :: [Audio r c (Raw * t)] -> ShowS #

CanBeSample (Pcm c t) => Monoid (Audio r c (Raw * t)) Source # 

Methods

mempty :: Audio r c (Raw * t) #

mappend :: Audio r c (Raw * t) -> Audio r c (Raw * t) -> Audio r c (Raw * t) #

mconcat :: [Audio r c (Raw * t)] -> Audio r c (Raw * t) #

CanBeSample (Pcm c t) => NFData (Audio r c (Raw * t)) Source # 

Methods

rnf :: Audio r c (Raw * t) -> () #

(Typeable * t, KnownRate r, KnownChannelLayout * c, CanBeSample (Pcm c t)) => IsMedia (Audio r c (Raw * t)) Source # 
(KnownRate r, CanBeSample (Pcm c t)) => HasDuration (Audio r c (Raw * t)) Source # 
(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 #

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

Methods

blankFor :: NominalDiffTime -> Audio r c (Raw * t) Source #

blankForTicks :: CanBeTicks r i => Ticks r i -> Audio r c (Raw * t) Source #

(CanBeSample (Pcm c t), CanBeSample (Pcm c' t'), EachSampleL (Audio r c (Raw * t)) (Audio r' c' (Raw * t')) (Pcm c t) (Pcm c' t'), EachChannelL (Pcm c t) (Pcm c' t') t t') => EachChannel (Audio r c (Raw * t)) (Audio r' c' (Raw * t')) Source # 

Associated Types

type ChannelsFrom (Audio r c (Raw * t)) :: * Source #

type ChannelsTo (Audio r' c' (Raw * t')) :: * Source #

Methods

eachChannel :: Traversal (Audio r c (Raw * t)) (Audio r' c' (Raw * t')) (ChannelsFrom (Audio r c (Raw * t))) (ChannelsTo (Audio r' c' (Raw * t'))) Source #

(CanBeSample (Pcm c t), CanBeSample (Pcm c' t')) => EachSample (Audio r c (Raw * t)) (Audio r' c' (Raw * t')) Source # 

Associated Types

type SamplesFrom (Audio r c (Raw * t)) :: * Source #

type SamplesTo (Audio r' c' (Raw * t')) :: * Source #

Methods

eachSample :: Traversal (Audio r c (Raw * t)) (Audio r' c' (Raw * t')) (SamplesFrom (Audio r c (Raw * t))) (SamplesTo (Audio r' c' (Raw * t'))) Source #

(CanBeSample (Pcm ca a), CanBeSample (Pcm cb b)) => HasMediaBuffer (Audio r ca (Raw * a)) (Audio r' cb (Raw * b)) Source # 

Associated Types

type MediaBufferFrom (Audio r ca (Raw * a)) :: * Source #

type MediaBufferTo (Audio r' cb (Raw * b)) :: * Source #

Methods

mediaBuffer :: Lens (Audio r ca (Raw * a)) (Audio r' cb (Raw * b)) (MediaBufferFrom (Audio r ca (Raw * a))) (MediaBufferTo (Audio r' cb (Raw * b))) Source #

data Audio r c (Raw * t) Source #

All Pcm audio is audio. An Audio instance with Pcms in a MediaBuffer.

data Audio r c (Raw * t) = MkPcm {}
type ChannelsFrom (Audio r c (Raw * t)) Source # 
type ChannelsFrom (Audio r c (Raw * t)) = ChannelsFrom (Pcm c t)
type ChannelsTo (Audio r' c' (Raw * t')) Source # 
type ChannelsTo (Audio r' c' (Raw * t')) = ChannelsTo (Pcm c' t')
type SamplesFrom (Audio r c (Raw * t)) Source # 
type SamplesFrom (Audio r c (Raw * t)) = Pcm c t
type SamplesTo (Audio r' c' (Raw * t')) Source # 
type SamplesTo (Audio r' c' (Raw * t')) = Pcm c' t'
type MediaBufferFrom (Audio r ca (Raw * a)) Source # 
type MediaBufferFrom (Audio r ca (Raw * a)) = MediaBuffer (Pcm ca a)
type MediaBufferTo (Audio r' cb (Raw * b)) Source # 
type MediaBufferTo (Audio r' cb (Raw * b)) = MediaBuffer (Pcm cb b)

data family Pcm c t Source #

A family of multi-channel audio sample value types. Values of this type are stored in MediaBuffers. The Audio instances with Raw encodings use MediaBuffers of Pcm values to store (multi-channel-) samples.

Instances

Enum s => Enum (Pcm Mono s) # 

Methods

succ :: Pcm Mono s -> Pcm Mono s #

pred :: Pcm Mono s -> Pcm Mono s #

toEnum :: Int -> Pcm Mono s #

fromEnum :: Pcm Mono s -> Int #

enumFrom :: Pcm Mono s -> [Pcm Mono s] #

enumFromThen :: Pcm Mono s -> Pcm Mono s -> [Pcm Mono s] #

enumFromTo :: Pcm Mono s -> Pcm Mono s -> [Pcm Mono s] #

enumFromThenTo :: Pcm Mono s -> Pcm Mono s -> Pcm Mono s -> [Pcm Mono s] #

Eq s => Eq (Pcm Mono s) # 

Methods

(==) :: Pcm Mono s -> Pcm Mono s -> Bool #

(/=) :: Pcm Mono s -> Pcm Mono s -> Bool #

Eq t => Eq (Pcm Stereo t) # 

Methods

(==) :: Pcm Stereo t -> Pcm Stereo t -> Bool #

(/=) :: Pcm Stereo t -> Pcm Stereo t -> Bool #

Integral s => Integral (Pcm Mono s) # 

Methods

quot :: Pcm Mono s -> Pcm Mono s -> Pcm Mono s #

rem :: Pcm Mono s -> Pcm Mono s -> Pcm Mono s #

div :: Pcm Mono s -> Pcm Mono s -> Pcm Mono s #

mod :: Pcm Mono s -> Pcm Mono s -> Pcm Mono s #

quotRem :: Pcm Mono s -> Pcm Mono s -> (Pcm Mono s, Pcm Mono s) #

divMod :: Pcm Mono s -> Pcm Mono s -> (Pcm Mono s, Pcm Mono s) #

toInteger :: Pcm Mono s -> Integer #

Num s => Num (Pcm Mono s) # 

Methods

(+) :: Pcm Mono s -> Pcm Mono s -> Pcm Mono s #

(-) :: Pcm Mono s -> Pcm Mono s -> Pcm Mono s #

(*) :: Pcm Mono s -> Pcm Mono s -> Pcm Mono s #

negate :: Pcm Mono s -> Pcm Mono s #

abs :: Pcm Mono s -> Pcm Mono s #

signum :: Pcm Mono s -> Pcm Mono s #

fromInteger :: Integer -> Pcm Mono s #

Ord s => Ord (Pcm Mono s) # 

Methods

compare :: Pcm Mono s -> Pcm Mono s -> Ordering #

(<) :: Pcm Mono s -> Pcm Mono s -> Bool #

(<=) :: Pcm Mono s -> Pcm Mono s -> Bool #

(>) :: Pcm Mono s -> Pcm Mono s -> Bool #

(>=) :: Pcm Mono s -> Pcm Mono s -> Bool #

max :: Pcm Mono s -> Pcm Mono s -> Pcm Mono s #

min :: Pcm Mono s -> Pcm Mono s -> Pcm Mono s #

Ord t => Ord (Pcm Stereo t) # 

Methods

compare :: Pcm Stereo t -> Pcm Stereo t -> Ordering #

(<) :: Pcm Stereo t -> Pcm Stereo t -> Bool #

(<=) :: Pcm Stereo t -> Pcm Stereo t -> Bool #

(>) :: Pcm Stereo t -> Pcm Stereo t -> Bool #

(>=) :: Pcm Stereo t -> Pcm Stereo t -> Bool #

max :: Pcm Stereo t -> Pcm Stereo t -> Pcm Stereo t #

min :: Pcm Stereo t -> Pcm Stereo t -> Pcm Stereo t #

Real s => Real (Pcm Mono s) # 

Methods

toRational :: Pcm Mono s -> Rational #

Show s => Show (Pcm Mono s) # 

Methods

showsPrec :: Int -> Pcm Mono s -> ShowS #

show :: Pcm Mono s -> String #

showList :: [Pcm Mono s] -> ShowS #

Show a => Show (Pcm Stereo a) # 

Methods

showsPrec :: Int -> Pcm Stereo a -> ShowS #

show :: Pcm Stereo a -> String #

showList :: [Pcm Stereo a] -> ShowS #

Generic (Pcm Stereo t) # 

Associated Types

type Rep (Pcm Stereo t) :: * -> * #

Methods

from :: Pcm Stereo t -> Rep (Pcm Stereo t) x #

to :: Rep (Pcm Stereo t) x -> Pcm Stereo t #

Arbitrary s => Arbitrary (Pcm Mono s) # 

Methods

arbitrary :: Gen (Pcm Mono s) #

shrink :: Pcm Mono s -> [Pcm Mono s] #

Arbitrary t => Arbitrary (Pcm Stereo t) # 

Methods

arbitrary :: Gen (Pcm Stereo t) #

shrink :: Pcm Stereo t -> [Pcm Stereo t] #

Storable s => Storable (Pcm Mono s) # 

Methods

sizeOf :: Pcm Mono s -> Int #

alignment :: Pcm Mono s -> Int #

peekElemOff :: Ptr (Pcm Mono s) -> Int -> IO (Pcm Mono s) #

pokeElemOff :: Ptr (Pcm Mono s) -> Int -> Pcm Mono s -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pcm Mono s) #

pokeByteOff :: Ptr b -> Int -> Pcm Mono s -> IO () #

peek :: Ptr (Pcm Mono s) -> IO (Pcm Mono s) #

poke :: Ptr (Pcm Mono s) -> Pcm Mono s -> IO () #

Storable s => Storable (Pcm Stereo s) # 

Methods

sizeOf :: Pcm Stereo s -> Int #

alignment :: Pcm Stereo s -> Int #

peekElemOff :: Ptr (Pcm Stereo s) -> Int -> IO (Pcm Stereo s) #

pokeElemOff :: Ptr (Pcm Stereo s) -> Int -> Pcm Stereo s -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Pcm Stereo s) #

pokeByteOff :: Ptr b -> Int -> Pcm Stereo s -> IO () #

peek :: Ptr (Pcm Stereo s) -> IO (Pcm Stereo s) #

poke :: Ptr (Pcm Stereo s) -> Pcm Stereo s -> IO () #

Default s => Default (Pcm Mono s) # 

Methods

def :: Pcm Mono s #

Default a => Default (Pcm Stereo a) # 

Methods

def :: Pcm Stereo a #

NFData s => NFData (Pcm Mono s) # 

Methods

rnf :: Pcm Mono s -> () #

NFData t => NFData (Pcm Stereo t) # 

Methods

rnf :: Pcm Stereo t -> () #

CanBeBlank s => CanBeBlank (Pcm Mono s) Source # 

Methods

blank :: Pcm Mono s Source #

CanBeBlank a => CanBeBlank (Pcm Stereo a) Source # 

Methods

blank :: Pcm Stereo a Source #

IsPcmValue s => IsPcmValue (Pcm Mono s) Source # 

Methods

pcmAverage :: Pcm Mono s -> Pcm Mono s -> Pcm Mono s Source #

IsPcmValue a => IsPcmValue (Pcm Stereo a) Source # 

Methods

pcmAverage :: Pcm Stereo a -> Pcm Stereo a -> Pcm Stereo a Source #

(IsPcmValue a, IsPcmValue b) => EachChannel (Pcm Mono a) (Pcm Mono b) Source # 

Associated Types

type ChannelsFrom (Pcm Mono a) :: * Source #

type ChannelsTo (Pcm Mono b) :: * Source #

EachChannel (Pcm Stereo a) (Pcm Stereo b) Source # 

Associated Types

type ChannelsFrom (Pcm Stereo a) :: * Source #

type ChannelsTo (Pcm Stereo b) :: * Source #

data Pcm Mono Source # 
data Pcm Stereo Source # 
type Rep (Pcm Stereo t) # 
type Rep (Pcm Stereo t) = D1 (MetaData "Pcm" "Data.MediaBus.Media.Audio.Raw.Stereo" "mediabus-0.4.0.1-KxOztWIrQ7SL9k5ZMcQI4H" False) (C1 (MetaCons "MkStereo" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_leftSample") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 t)) (S1 (MetaSel (Just Symbol "_rightSample") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 t))))
type ChannelsFrom (Pcm Mono a) Source # 
type ChannelsFrom (Pcm Mono a) = a
type ChannelsFrom (Pcm Stereo a) Source # 
type ChannelsFrom (Pcm Stereo a) = a
type ChannelsTo (Pcm Mono b) Source # 
type ChannelsTo (Pcm Mono b) = b
type ChannelsTo (Pcm Stereo b) Source # 
type ChannelsTo (Pcm Stereo b) = b

pcmMediaBuffer :: Iso (Audio r c (Raw t)) (Audio r' c' (Raw t')) (MediaBuffer (Pcm c t)) (MediaBuffer (Pcm c' t')) Source #

An isomorphism for Audio and MediaBuffer

class (CanBeBlank a, CanBeSample a, Arbitrary a) => IsPcmValue a where Source #

Types of per channel PCM audio sample value.

Minimal complete definition

pcmAverage

Methods

pcmAverage :: a -> a -> a Source #

Calculate the average of two pcm samples