mediabus-0.4.0.1: Multimedia streaming on top of Conduit

Safe HaskellNone
LanguageHaskell2010

Data.MediaBus.Basics.SourceId

Description

This module contains the SourceId wrapper type, that indicate that something is identifies a single source of media. This could be an RTP SSRC or the IP/Port pair of a network source. The defining characteristic of a SourceId is that every thing that has a certain source id stems from **the same media source**, e.g. the same microphone, audio file, synthesizer,...

Synopsis

Documentation

newtype SourceId i Source #

Things that can be uniquely identified by a looking at a (much simpler) representation, the identity.

Constructors

MkSourceId i 

Instances

Eq i => Eq (SourceId i) Source # 

Methods

(==) :: SourceId i -> SourceId i -> Bool #

(/=) :: SourceId i -> SourceId i -> Bool #

Ord i => Ord (SourceId i) Source # 

Methods

compare :: SourceId i -> SourceId i -> Ordering #

(<) :: SourceId i -> SourceId i -> Bool #

(<=) :: SourceId i -> SourceId i -> Bool #

(>) :: SourceId i -> SourceId i -> Bool #

(>=) :: SourceId i -> SourceId i -> Bool #

max :: SourceId i -> SourceId i -> SourceId i #

min :: SourceId i -> SourceId i -> SourceId i #

Show i => Show (SourceId i) Source # 

Methods

showsPrec :: Int -> SourceId i -> ShowS #

show :: SourceId i -> String #

showList :: [SourceId i] -> ShowS #

Generic (SourceId i) Source # 

Associated Types

type Rep (SourceId i) :: * -> * #

Methods

from :: SourceId i -> Rep (SourceId i) x #

to :: Rep (SourceId i) x -> SourceId i #

Arbitrary i => Arbitrary (SourceId i) Source # 

Methods

arbitrary :: Gen (SourceId i) #

shrink :: SourceId i -> [SourceId i] #

Default i => Default (SourceId i) Source # 

Methods

def :: SourceId i #

NFData i => NFData (SourceId i) Source # 

Methods

rnf :: SourceId i -> () #

type Rep (SourceId i) Source # 
type Rep (SourceId i) = D1 (MetaData "SourceId" "Data.MediaBus.Basics.SourceId" "mediabus-0.4.0.1-KxOztWIrQ7SL9k5ZMcQI4H" True) (C1 (MetaCons "MkSourceId" PrefixI True) (S1 (MetaSel (Just Symbol "_sourceIdValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 i)))

sourceIdValue :: Iso (SourceId a) (SourceId b) a b Source #

An Iso for the value of a SourceId

type SrcId32 = SourceId Word32 Source #

A short alias for SourceId with a Word32 value

type SrcId64 = SourceId Word64 Source #

A short alias for SourceId with a Word64 value

class HasSourceId s t where Source #

Type class for a lens over the contained source id

Minimal complete definition

sourceId

Associated Types

type SourceIdFrom s Source #

type SourceIdTo t Source #

Methods

sourceId :: Lens s t (SourceIdFrom s) (SourceIdTo t) Source #

A lens for the SourceId

class EachSourceId s t where Source #

Type class with a Traversal for types that may or may not contain anctual source id.

Minimal complete definition

eachSourceId

Associated Types

type SourceIdsFrom s Source #

type SourceIdsTo t Source #