mediabus-0.4.0.0: Multimedia streaming on top of Conduit

Safe HaskellNone
LanguageHaskell2010

Data.MediaBus.Media.Channels

Description

Channel representation types.

Synopsis

Documentation

class Typeable c => KnownChannelLayout c where Source #

Like KnownNat but for promoted ChannelLayouts.

Minimal complete definition

numberOfChannels

Methods

numberOfChannels :: proxy c -> Int Source #

Return the ChannelLayout for type c

data ChannelLayoutProxy c where Source #

A Proxy specifically to prevent orphan instances of e.g. Proxy channelLayoyt.

Instances

KnownChannelLayout k c => Show (ChannelLayoutProxy k c) Source #

Create a textual representation of the channel layout.

class SetChannelLayout s (ChannelLayout s) ~ s => HasChannelLayout s Source #

Types that have some KnownChannelLayout

Associated Types

type ChannelLayout s Source #

The channel layout contained in s

type SetChannelLayout s b Source #

The type resulting from changing the channel layout type in s to b

Instances

KnownChannelLayout * c => HasChannelLayout (Audio r c t) Source # 

Associated Types

type ChannelLayout (Audio r c t) :: * Source #

type SetChannelLayout (Audio r c t) b :: * Source #

class EachChannel s t where Source #

Types, e.g samples, that have one or more channels

Minimal complete definition

eachChannel

Associated Types

type ChannelsFrom s Source #

The channel layout contained in s

type ChannelsTo t Source #

The channel layout contained in t

Instances

EachChannel a b => EachChannel (Discontinous a) (Discontinous b) 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 #

(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 #

(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 #

EachChannel c c' => EachChannel (Frame s t c) (Frame s t c') Source # 

Associated Types

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

type ChannelsTo (Frame s t c') :: * Source #

Methods

eachChannel :: Traversal (Frame s t c) (Frame s t c') (ChannelsFrom (Frame s t c)) (ChannelsTo (Frame s t c')) Source #

EachChannel (Frame s t c) (Frame s t c') => EachChannel (Stream i s t p c) (Stream i s t p c') Source # 

Associated Types

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

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

Methods

eachChannel :: Traversal (Stream i s t p c) (Stream i s t p c') (ChannelsFrom (Stream i s t p c)) (ChannelsTo (Stream i s t p c')) Source #

type EachChannelL s t a b = (EachChannel s t, ChannelsFrom s ~ a, ChannelsTo t ~ b) Source #

A constraint type alias for EachChannel similar to the parameters of type class Each from the lens package.

type EachChannelL' s a = (EachChannel s s, ChannelsFrom s ~ a, ChannelsTo s ~ a) Source #

A constraint type alias for EachChannel with a simple traversal

type EachChannel' s = (ChannelsFrom s ~ ChannelsTo s, EachChannel s s) Source #

A simple Traversal for the channels in samples

eachChannel' :: EachChannel' i => Traversal' i (ChannelsFrom i) Source #

A simple Traversal for the channels in samples