hommage-0.0.5: Haskell Offline Music Manipulation And Generation EDSLSource codeContentsIndex
Sound.Hommage.Signal
Contents
Mono and Stereo Values
Signal datatype
Description
Dieses Module stellt Datentypen und Funktionen zum Umgang mit Mono- und Stereodaten zur Verfgung. Speziell im Falle des ffnens einer WAV-Datei ist erst zur Laufzeit bekannt, ob es sich um eine Mono- oder Stereodatei handelt, hier wird der Typ Signal bentigt.
Synopsis
type Mono = Double
data Stereo = !Double :><: !Double
leftStereo :: Stereo -> Mono
rightStereo :: Stereo -> Mono
stereoToMono :: Stereo -> Mono
monoToStereo :: Mono -> Stereo
balance :: Double -> Stereo -> Stereo
data Signal
= Mono [Mono]
| Stereo [Stereo]
readWavSignal :: FilePath -> IO Signal
openWavSignal :: FilePath -> Signal
writeWavMono :: FilePath -> [Mono] -> IO ()
writeWavStereo :: FilePath -> [Stereo] -> IO ()
writeWavSignal :: FilePath -> Signal -> IO ()
writeTracks :: FilePath -> [Signal] -> IO ()
signalToMono :: Signal -> [Mono]
signalToStereo :: Signal -> [Stereo]
eitherSignal :: ([Mono] -> a) -> ([Stereo] -> a) -> Signal -> a
liftSignal :: ([Mono] -> [Mono]) -> Signal -> Signal
mergeSignal :: Signal -> Signal -> Signal
mergeSignals :: [Signal] -> Signal
multSignal :: Signal -> Signal -> Signal
infiniteSignal :: Double -> Signal -> Signal
Mono and Stereo Values
type Mono = DoubleSource
A mono value.
data Stereo Source
A stereo value with left and right part. It is an instance of class Num and Fractional.
Constructors
!Double :><: !Double
show/hide Instances
leftStereo :: Stereo -> MonoSource
Access to the left part of a Stereo value.
rightStereo :: Stereo -> MonoSource
Access to the right part of a Stereo value.
stereoToMono :: Stereo -> MonoSource
Converts a Stereo value to a Mono value (Double)
monoToStereo :: Mono -> StereoSource
Converts a Mono value (Double) to a Stereo value
balance :: Double -> Stereo -> StereoSource
The range of the Double value must be between -1 and 1. If it is below 0 the left channel is turned down, if it is greater than 0 the right channel is turned down. NOTE: This function should be replaced by a better one.
Signal datatype
data Signal Source
A Signal is either a list of Mono values or a list of Stereo values.
Constructors
Mono [Mono]
Stereo [Stereo]
show/hide Instances
readWavSignal :: FilePath -> IO SignalSource
Reads a Signal from a WAV-File.
openWavSignal :: FilePath -> SignalSource
Opens a Signal from a WAV-File.
writeWavMono :: FilePath -> [Mono] -> IO ()Source
Writes a list of mono values to a WAV-File.
writeWavStereo :: FilePath -> [Stereo] -> IO ()Source
Writes a list of stereo values to a WAV-File.
writeWavSignal :: FilePath -> Signal -> IO ()Source
Writes a Signal to a WAV-File.
writeTracks :: FilePath -> [Signal] -> IO ()Source
signalToMono :: Signal -> [Mono]Source
Transfroms a signal to a list of mono values.
signalToStereo :: Signal -> [Stereo]Source
Transfroms a signal to a list of stereo values.
eitherSignal :: ([Mono] -> a) -> ([Stereo] -> a) -> Signal -> aSource
liftSignal :: ([Mono] -> [Mono]) -> Signal -> SignalSource
Applies the function to the input signal. If it is a stereo signal, the function is applied to both channels seperately.
mergeSignal :: Signal -> Signal -> SignalSource
The sum of two signals
mergeSignals :: [Signal] -> SignalSource
The sum of a set of signals. If all signals are mono, the result will be mono. Otherwise it will be stereo.
multSignal :: Signal -> Signal -> SignalSource
Multiplies two signals.
infiniteSignal :: Double -> Signal -> SignalSource
The Double value is added to the input signal (offset). The resulting signal will be infinie in any case.
Produced by Haddock version 2.4.2