rhine-0.6.0: Functional Reactive Programming with type-level clocks

Safe HaskellNone
LanguageHaskell2010

FRP.Rhine.Clock.Realtime.Audio

Description

Provides several clocks to use for audio processing, for realtime as well as for batch/file processing.

Synopsis

Documentation

data AudioClock (rate :: AudioRate) (bufferSize :: Nat) Source #

A clock for audio analysis and synthesis. It internally processes samples in buffers of size bufferSize, (the programmer does not have to worry about this), at a sample rate of rate (of type AudioRate). Both these parameters are in the type signature, so it is not possible to compose signals with different buffer sizes or sample rates.

After processing a buffer, the clock will wait the remaining time until the next buffer must be processed, using system UTC time. The tag of the clock specifies whether the attempt to finish the last buffer in real time was successful. A value of Nothing represents success, a value of Just double represents a lag of double seconds.

Constructors

AudioClock 
Instances
(MonadIO m, KnownNat bufferSize, AudioClockRate rate) => Clock m (AudioClock rate bufferSize) Source # 
Instance details

Defined in FRP.Rhine.Clock.Realtime.Audio

Associated Types

type Time (AudioClock rate bufferSize) :: Type Source #

type Tag (AudioClock rate bufferSize) :: Type Source #

Methods

initClock :: AudioClock rate bufferSize -> RunningClockInit m (Time (AudioClock rate bufferSize)) (Tag (AudioClock rate bufferSize)) Source #

type Time (AudioClock rate bufferSize) Source # 
Instance details

Defined in FRP.Rhine.Clock.Realtime.Audio

type Time (AudioClock rate bufferSize) = UTCTime
type Tag (AudioClock rate bufferSize) Source # 
Instance details

Defined in FRP.Rhine.Clock.Realtime.Audio

type Tag (AudioClock rate bufferSize) = Maybe Double

data AudioRate Source #

Rates at which audio signals are typically sampled.

Constructors

Hz44100 
Hz48000 
Hz96000 

data PureAudioClock (rate :: AudioRate) Source #

A side-effect free clock for audio synthesis and analysis. The sample rate is given by rate (of type AudioRate). Since this clock does not wait for the completion of buffers, the producer or the consumer of the signal has the obligation to synchronise the signal with the system clock, if realtime is desired. Otherwise, the clock is also suitable e.g. for batch processing of audio files.

Constructors

PureAudioClock 
Instances
(Monad m, PureAudioClockRate rate) => Clock m (PureAudioClock rate) Source # 
Instance details

Defined in FRP.Rhine.Clock.Realtime.Audio

Associated Types

type Time (PureAudioClock rate) :: Type Source #

type Tag (PureAudioClock rate) :: Type Source #

type Time (PureAudioClock rate) Source # 
Instance details

Defined in FRP.Rhine.Clock.Realtime.Audio

type Time (PureAudioClock rate) = Double
type Tag (PureAudioClock rate) Source # 
Instance details

Defined in FRP.Rhine.Clock.Realtime.Audio

type Tag (PureAudioClock rate) = ()

pureAudioClockF :: PureAudioClockF rate Source #

A rescaled version of PureAudioClock with TimeDomain Float, using double2Float to rescale.