csound-expression-4.6.1: library to make electronic music

Safe HaskellNone
LanguageHaskell98

Csound.Air.Wav

Contents

Description

Sound file playback

Synopsis

Stereo

readSnd :: String -> (Sig, Sig) Source

Reads stereo signal from the sound-file (wav or mp3 or aiff).

loopSnd :: String -> (Sig, Sig) Source

Reads stereo signal from the sound-file (wav or mp3 or aiff) and loops it with the file length.

loopSndBy :: D -> String -> (Sig, Sig) Source

Reads stereo signal from the sound-file (wav or mp3 or aiff) and loops it with the given period (in seconds).

readWav :: Sig -> String -> (Sig, Sig) Source

Reads the wav file with the given speed (if speed is 1 it's a norma playback). We can use negative speed to read file in reverse.

loopWav :: Sig -> String -> (Sig, Sig) Source

Reads th wav file and loops over it.

readSegWav :: D -> D -> Sig -> String -> (Sig, Sig) Source

Reads a segment from wav file.

tempoLoopWav :: Sig -> String -> (Sig, Sig) Source

Reads th wav file and loops over it. Scales the tempo with first argument.

tempoReadWav :: Sig -> String -> (Sig, Sig) Source

Reads the wav file with the given speed (if speed is 1 it's a norma playback). We can use negative speed to read file in reverse. Scales the tempo with first argument.

Mono

readSnd1 :: String -> Sig Source

The mono variant of the function readSnd.

loopSnd1 :: String -> Sig Source

The mono variant of the function loopSnd.

loopSndBy1 :: D -> String -> Sig Source

The mono variant of the function loopSndBy.

readWav1 :: Sig -> String -> Sig Source

The mono variant of the function readWav.

loopWav1 :: Sig -> String -> Sig Source

The mono variant of the function loopWav.

readSegWav1 :: D -> D -> Sig -> String -> Sig Source

Reads a segment from wav file.

tempoLoopWav1 :: Sig -> String -> Sig Source

Reads th mono wav file and loops over it. Scales the tempo with first argument.

tempoReadWav1 :: Sig -> String -> Sig Source

Reads the mono wav file with the given speed (if speed is 1 it's a norma playback). We can use negative speed to read file in reverse. Scales the tempo with first argument.

Read sound with RAM

data LoopMode Source

Constructors

Once 
Loop 
Bounce 

ramSnd :: LoopMode -> Sig -> String -> Sig2 Source

Loads the sample in the table. The sample should be short. The size of the table is limited. It's up to 3 minutes for 44100 sample rate (sr), 2.9 minutes for 48000 sr, 1.4 minutes for 96000 sr.

ramSnd1 :: LoopMode -> Sig -> String -> Sig Source

Loads the sample in the table. The sample should be short. The size of the table is limited. It's up to 6 minutes for 44100 sample rate (sr), 5.9 minutes for 48000 sr, 2.8 minutes for 96000 sr.

ramTab :: Fidelity -> Tab -> Sig -> Sig -> Sig Source

Mincer. We can playback a table and scale by tempo and pitch.

mincer fidelity table pointer pitch 

fidelity is the parameter that specifies the size of the window (for FFT transform). The size equals to formula (fidelity + 11) ^ 2. If you don't know what to choose choose 0 for pitched sounds and -2 for drums. The table contains the sample to playback. The pointer loops over the table. The pitch specifies a scaling factor for pitch. So we can raise tone an octave up by setting the pitch to 2.

mincer :: Sig -> Sig -> Sig -> Tab -> Sig -> Sig Source

mincer — Phase-locked vocoder processing.

mincer implements phase-locked vocoder processing using function tables containing sampled-sound sources, with GEN01, and mincer will accept deferred allocation tables.

This opcode allows for time and frequency-independent scaling. Time is controlled by a time index (in seconds) to the function table position and can be moved forward and backward at any chosen speed, as well as stopped at a given position ("frozen"). The quality of the effect is generally improved with phase locking switched on.

asig mincer atimpt, kamp, kpitch, ktab, klock[,ifftsize,idecim]

csound doc: http://www.csounds.com/manual/html/mincer.html

data Phsr Source

Looping phasor. It creates a looping pointer to the file. It's used in the function ram.

Ther arguments are: file name, start and end of the looping segment (in seconds), and the playback speed.

Constructors

Phsr 

lphase :: D -> Sig -> Sig -> Sig -> Sig Source

Creates a pointer signal for reading audio from the table in loops.

lphase length start end speed

Arguments are:

  • length of the table in seconds
  • start and end points of the reading interval
  • playback speed

relPhsr :: String -> Sig -> Sig -> Sig -> Phsr Source

Creates a phasor if segments are relative to the total length. It can be useful for drum loops. If we don't know the complete length but we know that loop contains four distinct parts.

sndPhsr :: String -> Sig -> Phsr Source

Creates a phasor for reading the whole audio file in loops with given speed.

phsrBounce :: Phsr -> Phsr Source

Reads the file forth and back.

phsrOnce :: Phsr -> Phsr Source

Forces phasor to play only once.

ram :: Fidelity -> Phsr -> Sig -> Sig2 Source

Reads audio files in loops. The file is loaded in RAM. The size of the file is limited. It should be not more than 6 minutes for sample rate of 44100. 5.9 minutes for 48000.

What makes this function so cool is that we can scale the sound by tempo without affecting pitch, and we can scale the sound by pitch without affecting the tempo. Let's study the arguments.

ram fidelity phasor pitch 

fidelity corresponds to the size of the FFT-window. The function performs the FFT transform and it has to know the size. It's not the value for the size it's an integer value that proportional to the size. The higher the value the higher the size the lower the value the lower the size. The default value is 0. Zero is best for most of the cases. For drums we can lower it to (-2).

The phasor is a quadruple of values

(Phsr fileName startTime endTime playbackSpeed)

we can read the file from startTime to endTime (in seconds) and we can set the speed for playback. If speed is negative file is played in reverse. The playback is looped. So to scale the tempo or play in reverse we can change the playbackSpeed.

The last argument is pitch factor. We can rise by octave with factor 2. It's good place to use the function semitone. It produces factors for a number in semitones.

Note that all parameters (except window size) are signals. It makes this function very flexible. We can change the speed of playback and start and end of the reading segment as we wish.

ram 0 (Phsr "file.wav" 0 1 1.2) 1

PS: here is the formula for window size: 2 ** (fidelity + 11)

Simple audio reading functions (Stereo)

type Fidelity = D Source

Fidelity corresponds to the size of the FFT-window that is used by functions of RAM-family. The function performs the FFT transform and it has to know the size. It's not the value for the size it's an integer value that proportional to the size. The higher the value the higher the size the lower the value the lower the size. The default value is 0. Zero is best for most of the cases. For drums we can lower it to (-2).

PS: here is the formula for window size: 2 ** (fidelity + 11). So the fidelity is actually the degree for power of two. The FFT-algorithm requires the window size to be a power of two.

The lower fidelity is the less power is consumed by the function.

type TempoSig = Sig Source

Scaling factor for tempo. The 1 is inherent tempo.

type PitchSig = Sig Source

Scaling factor for pitch. The 1 is inherent pitch.

readRam :: Fidelity -> TempoSig -> PitchSig -> String -> Sig2 Source

Reads file once and scales it by tempo and pitch.

loopRam :: Fidelity -> TempoSig -> PitchSig -> String -> Sig2 Source

Loop over file and scales it by tempo and pitch.

readSeg :: Fidelity -> (Sig, Sig) -> TempoSig -> PitchSig -> String -> Sig2 Source

Reads a segment from file once and scales it by tempo and pitch. Segment is defined in seconds.

loopSeg :: Fidelity -> (Sig, Sig) -> TempoSig -> PitchSig -> String -> Sig2 Source

Loops over a segment of file and scales it by tempo and pitch. Segment is defined in seconds.

readRel :: Fidelity -> (Sig, Sig) -> TempoSig -> PitchSig -> String -> Sig2 Source

Reads a relative segment from file once and scales it by tempo and pitch. Segment is defined in seconds. The end ponits for the segment are relative to the total length of the file.

loopRel :: Fidelity -> (Sig, Sig) -> TempoSig -> PitchSig -> String -> Sig2 Source

Loops over a relative segment of file and scales it by tempo and pitch. Segment is defined in seconds. The end ponits for the segment are relative to the total length of the file.

Simple audio reading functions (Mono)

readRam1 :: Fidelity -> TempoSig -> PitchSig -> String -> Sig Source

The mono version of readRam.

loopRam1 :: Fidelity -> TempoSig -> PitchSig -> String -> Sig Source

The mono version of loopRam.

readSeg1 :: Fidelity -> (Sig, Sig) -> TempoSig -> PitchSig -> String -> Sig Source

The mono version of readSeg.

loopSeg1 :: Fidelity -> (Sig, Sig) -> TempoSig -> PitchSig -> String -> Sig Source

The mono version of loopSeg.

readRel1 :: Fidelity -> (Sig, Sig) -> TempoSig -> PitchSig -> String -> Sig Source

The mono version of readRel.

loopRel1 :: Fidelity -> (Sig, Sig) -> TempoSig -> PitchSig -> String -> Sig Source

The mono version of loopRel.

Writing sound files

data SampleFormat Source

The sample format.

Constructors

NoHeaderFloat32

32-bit floating point samples without header

NoHeaderInt16

16-bit integers without header

HeaderInt16

16-bit integers with a header. The header type depends on the render (-o) format

UlawSamples

u-law samples with a header

Int16

16-bit integers with a header

Int32

32-bit integers with a header

Float32

32-bit floats with a header

Uint8

8-bit unsigned integers with a header

Int24

24-bit integers with a header

Float64

64-bit floats with a header

writeSigs :: FormatType -> SampleFormat -> String -> [Sig] -> SE () Source

Writes a sound signal to the file with the given format. It supports only four formats: Wav, Aiff, Raw and Ircam.

writeWav :: String -> (Sig, Sig) -> SE () Source

Writes wav files.

writeAiff :: String -> (Sig, Sig) -> SE () Source

Writes aiff files.

writeWav1 :: String -> Sig -> SE () Source

Writes mono signals to wav files.

writeAiff1 :: String -> Sig -> SE () Source

Writes mono signals to aiff files.

Utility

lengthSnd :: String -> D Source

Length in seconds of the sound file.

segments :: D -> Evt (D, Unit) Source

Produces repeating segments with the given time in seconds.

Signal manipulation

takeSnd :: Sigs a => D -> a -> a Source

Takes only given amount (in seconds) from the signal (the rest is silence).

delaySnd :: Sigs a => D -> a -> a Source

Delays signals by the given amount (in seconds).

afterSnd :: (Num b, Sigs b) => D -> b -> b -> b Source

Plays the first signal for some time (in seconds) and then switches to the next one.

afterSnd dur sig1 sig2

lineSnd :: (Num a, Sigs a) => D -> [a] -> a Source

Creates a sequence of signals. Each segment lasts for fixed amount of time given in the first argument.

loopLineSnd :: (Num a, Sigs a) => D -> [a] -> a Source

Creates a sequence of signals and loops over the sequence. Each segment lasts for fixed amount of time given in the first argument.

segmentSnd :: Sigs a => D -> D -> a -> a Source

Delays a signal by the first argument and takes only second argument amount of signal (everything is measured in seconds).

repeatSnd :: Sigs a => D -> a -> a Source

Repeats the signal with the given period.

toMono :: (Sig, Sig) -> Sig Source

Converts stereosignal to mono with function mean.