Safe Haskell | None |
---|
- osc :: Sig -> Sig
- oscBy :: Tab -> Sig -> Sig
- saw :: Sig -> Sig
- isaw :: Sig -> Sig
- pulse :: Sig -> Sig
- sqr :: Sig -> Sig
- tri :: Sig -> Sig
- blosc :: Tab -> Sig -> Sig
- unipolar :: Sig -> Sig
- bipolar :: Sig -> Sig
- on :: Sig -> Sig -> Sig -> Sig
- uon :: Sig -> Sig -> Sig -> Sig
- uosc :: Sig -> Sig
- uoscBy :: Tab -> Sig -> Sig
- usaw :: Sig -> Sig
- uisaw :: Sig -> Sig
- upulse :: Sig -> Sig
- usqr :: Sig -> Sig
- utri :: Sig -> Sig
- ublosc :: Tab -> Sig -> Sig
- rndh :: Sig -> SE Sig
- urndh :: Sig -> SE Sig
- rndi :: Sig -> SE Sig
- urndi :: Sig -> SE Sig
- white :: SE Sig
- pink :: SE Sig
- leg :: D -> D -> D -> D -> Sig
- xeg :: D -> D -> D -> D -> Sig
- onIdur :: [D] -> [D]
- lindur :: [D] -> Sig
- expdur :: [D] -> Sig
- linendur :: Sig -> D -> D -> Sig
- onDur :: D -> [D] -> [D]
- lindurBy :: D -> [D] -> Sig
- expdurBy :: D -> [D] -> Sig
- linendurBy :: D -> Sig -> D -> D -> Sig
- once :: Tab -> Sig
- onceBy :: D -> Tab -> Sig
- several :: Tab -> Sig -> Sig
- oscLins :: [D] -> Sig -> Sig
- oscElins :: [D] -> Sig -> Sig
- oscExps :: [D] -> Sig -> Sig
- oscEexps :: [D] -> Sig -> Sig
- oscLine :: D -> D -> Sig -> Sig
- fadeIn :: D -> Sig
- fadeOut :: D -> Sig
- fades :: D -> D -> Sig
- expFadeIn :: D -> Sig
- expFadeOut :: D -> Sig
- expFades :: D -> D -> Sig
- type Lfo = Sig
- lfo :: (Sig -> Sig) -> Sig -> Sig -> Sig
- lp :: Sig -> Sig -> Sig -> Sig
- hp :: Sig -> Sig -> Sig -> Sig
- bp :: Sig -> Sig -> Sig -> Sig
- br :: Sig -> Sig -> Sig -> Sig
- alp :: Sig -> Sig -> Sig -> Sig
- blp :: Sig -> Sig -> Sig
- bhp :: Sig -> Sig -> Sig
- bbp :: Sig -> Sig -> Sig -> Sig
- bbr :: Sig -> Sig -> Sig -> Sig
- mlp :: Sig -> Sig -> Sig -> Sig
- readSnd :: String -> (Sig, Sig)
- loopSnd :: String -> (Sig, Sig)
- loopSndBy :: D -> String -> (Sig, Sig)
- readWav :: Sig -> String -> (Sig, Sig)
- loopWav :: Sig -> String -> (Sig, Sig)
- readSnd1 :: String -> Sig
- loopSnd1 :: String -> Sig
- loopSndBy1 :: D -> String -> Sig
- readWav1 :: Sig -> String -> Sig
- loopWav1 :: Sig -> String -> Sig
- lengthSnd :: String -> D
- segments :: D -> Evt (D, Unit)
- takeSnd :: Sigs a => D -> a -> a
- delaySnd :: Sigs a => D -> a -> a
- segmentSnd :: Sigs a => D -> D -> a -> a
- repeatSnd :: Sigs a => D -> a -> a
- toMono :: (Sig, Sig) -> Sig
- toSpec :: Sig -> Spec
- fromSpec :: Spec -> Sig
- mapSpec :: (Spec -> Spec) -> Sig -> Sig
- scaleSpec :: Sig -> Sig -> Sig
- addSpec :: Sig -> Sig -> Sig
- scalePitch :: Sig -> Sig -> Sig
- mean :: Fractional a => [a] -> a
- vibrate :: Sig -> Sig -> (Sig -> a) -> Sig -> a
- randomPitch :: Sig -> Sig -> (Sig -> a) -> Sig -> SE a
- chorusPitch :: Int -> Sig -> (Sig -> Sig) -> Sig -> Sig
- resons :: [(Sig, Sig)] -> Sig -> Sig
- resonsBy :: (cps -> bw -> Sig -> Sig) -> [(cps, bw)] -> Sig -> Sig
- modes :: [(Sig, Sig)] -> Sig -> Sig -> Sig
- dryWet :: Sig -> (Sig -> Sig) -> Sig -> Sig
- odds :: [a] -> [a]
- evens :: [a] -> [a]
- data AdsrBound = AdsrBound {}
- data AdsrInit = AdsrInit {}
- linAdsr :: String -> AdsrBound -> AdsrInit -> Source Sig
- expAdsr :: String -> AdsrBound -> AdsrInit -> Source Sig
- classicWaves :: String -> Int -> Source (Sig -> Sig)
- masterVolume :: Source Sig
- masterVolumeKnob :: Source Sig
- reverbsc1 :: Sig -> Sig -> Sig -> Sig
- rever1 :: Sig -> Sig -> (Sig, Sig)
- rever2 :: Sig -> Sig -> Sig -> (Sig, Sig)
- reverTime :: Sig -> Sig -> Sig
- smallRoom :: Sig -> (Sig, Sig)
- smallHall :: Sig -> (Sig, Sig)
- largeHall :: Sig -> (Sig, Sig)
- magicCave :: Sig -> (Sig, Sig)
- smallRoom2 :: Sig -> Sig -> (Sig, Sig)
- smallHall2 :: Sig -> Sig -> (Sig, Sig)
- largeHall2 :: Sig -> Sig -> (Sig, Sig)
- magicCave2 :: Sig -> Sig -> (Sig, Sig)
- echo :: D -> Sig -> Sig -> SE Sig
- fdelay :: D -> Sig -> Sig -> Sig -> SE Sig
- fvdelay :: D -> Sig -> Sig -> Sig -> Sig -> SE Sig
- fvdelays :: D -> [(Sig, Sig)] -> Sig -> Sig -> SE Sig
- funDelays :: D -> [(Sig, Sig -> Sig)] -> Sig -> Sig -> SE Sig
- distortion :: Sig -> Sig -> Sig
- chorus :: Sig -> Sig -> Sig -> Sig -> SE Sig
- flange :: Lfo -> Sig -> Sig -> Sig -> Sig
- phase1 :: Sig -> Lfo -> Sig -> Sig -> Sig -> Sig
- harmPhase :: Sig -> Lfo -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig
- powerPhase :: Sig -> Lfo -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig
Basic waveforms
Basic waveforms that are used most often. A waveform function take in a time varied frequency (in Hz).
Bipolar
A band-limited oscillator with user defined waveform (it's stored in the table).
Unipolar
Turns a bipolar sound (ranges from -1 to 1) to unipolar (ranges from 0 to 1)
Turns an unipolar sound (ranges from 0 to 1) to bipolar (ranges from -1 to 1)
uon :: Sig -> Sig -> Sig -> SigSource
Rescaling of the unipolar signal (0, 1) -> (a, b)
on a b uniSig
Noise
Constant random signal. It updates random numbers with given frequency.
constRnd freq
Linear random signal. It updates random numbers with given frequency.
rndi freq
Envelopes
leg :: D -> D -> D -> D -> SigSource
Linear adsr envelope generator with release
leg attack decay sustain release
xeg :: D -> D -> D -> D -> SigSource
Exponential adsr envelope generator with release
xeg attack decay sustain release
Relative duration
Makes time intervals relative to the note's duration. So that:
onIdur [a, t1, b, t2, c]
becomes:
[a, t1 * idur, b, t2 * idur, c]
The opcode linseg
with time intervals
relative to the total duration of the note.
The opcode expseg
with time intervals
relative to the total duration of the note.
linendur :: Sig -> D -> D -> SigSource
The opcode linen
with time intervals relative to the total duration of the note. Total time is set to the value of idur.
linendur asig rise decay
onDur :: D -> [D] -> [D]Source
Makes time intervals relative to the note's duration. So that:
onDur dt [a, t1, b, t2, c]
becomes:
[a, t1 * dt, b, t2 * dt, c]
lindurBy :: D -> [D] -> SigSource
The opcode linseg
with time intervals
relative to the total duration of the note given by the user.
expdurBy :: D -> [D] -> SigSource
The opcode expseg
with time intervals
relative to the total duration of the note given by the user.
linendurBy :: D -> Sig -> D -> D -> SigSource
The opcode linen
with time intervals relative to the total duration of the note. Total time is set to the value of
the first argument.
linendurBy dt asig rise decay
Looping envelopes
oscLins :: [D] -> Sig -> SigSource
Loops over line segments with the given rate.
oscLins [a, durA, b, durB, c, durC ..] cps
where
-
a
,b
,c
... -- values - durA, durB, durC -- durations of the segments relative to the current frequency.
oscElins :: [D] -> Sig -> SigSource
Loops over equally spaced line segments with the given rate.
oscElins [a, b, c] === oscLins [a, 1, b, 1, c]
oscExps :: [D] -> Sig -> SigSource
Loops over exponential segments with the given rate.
oscLins [a, durA, typeA, b, durB, typeB, c, durC, typeC ..] cps
where
-
a
,b
,c
... -- values - durA, durB, durC -- durations of the segments relative to the current frequency.
- typeA, typeB, typeC, ... -- shape of the envelope. If the value is 0 then the shap eis linear; otherwise it is an concave exponential (positive type) or a convex exponential (negative type).
oscEexps :: [D] -> Sig -> SigSource
Loops over equally spaced exponential segments with the given rate.
oscLins [a, typeA, b, typeB, c, typeC ..] === oscLins [a, 1, typeA, b, 1, typeB, c, 1, typeC ..]
oscLine :: D -> D -> Sig -> SigSource
oscLine a b cps
Goes from a
to b
and back by line segments. One period is equal to 2/cps
so that one period is passed by 1/cps
seconds.
Faders
A combination of fade in and fade out.
fades attackDuration decayDuration
expFadeOut :: D -> SigSource
Fades out by exponent with the given attack time.
expFades :: D -> D -> SigSource
A combination of exponential fade in and fade out.
expFades attackDuration decayDuration
Low frequency oscillators
Filters
Arguemnts are inversed to get most out of curruing. First come parameters and the last one is the signal.
Simple filters
Butterworth filters
Specific filters
Sound files playback
Stereo
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.
Mono
loopSndBy1 :: D -> String -> SigSource
The mono variant of the function loopSndBy
.
Utility
Signal manipulation
takeSnd :: Sigs a => D -> a -> aSource
Takes only given amount (in seconds) from the signal (the rest is silence).
segmentSnd :: Sigs a => D -> D -> a -> aSource
Delays a signal by the first argument and takes only second argument amount of signal (everything is measured in seconds).
Spectral functions
mapSpec :: (Spec -> Spec) -> Sig -> SigSource
Applies a transformation to the spectrum of the signal.
scaleSpec :: Sig -> Sig -> SigSource
Scales all frequencies. Usefull for transposition. For example, we can transpose a signal by the given amount of semitones:
scaleSpec (semitone 1) asig
scalePitch :: Sig -> Sig -> SigSource
Scales frequency in semitones.
Patterns
mean :: Fractional a => [a] -> aSource
Mean value.
vibrate :: Sig -> Sig -> (Sig -> a) -> Sig -> aSource
Adds vibrato to the sound unit. Sound units is a function that takes in a frequency.
randomPitch :: Sig -> Sig -> (Sig -> a) -> Sig -> SE aSource
Adds a random vibrato to the sound unit. Sound units is a function that takes in a frequency.
chorusPitch :: Int -> Sig -> (Sig -> Sig) -> Sig -> SigSource
Chorus takes a number of copies, chorus width and wave shape.
resons :: [(Sig, Sig)] -> Sig -> SigSource
Applies a resonator to the signals. A resonator is a list of band pass filters. A list contains the parameters for the filters:
[(centerFrequency, bandWidth)]
resonsBy :: (cps -> bw -> Sig -> Sig) -> [(cps, bw)] -> Sig -> SigSource
A resonator with user defined band pass filter. Warning: a filter takes in a center frequency, band width and the signal. The signal comes last (this order is not standard in the Csound but it's more convinient to use with Haskell).
modes :: [(Sig, Sig)] -> Sig -> Sig -> SigSource
Chain of mass-spring-damping filters.
modes params baseCps exciter
- params - a list of pairs
(resonantFrequencyRatio, filterQuality)
-
baseCps
- base frequency of the resonator - exciter - an impulse that starts a resonator.
dryWet :: Sig -> (Sig -> Sig) -> Sig -> SigSource
Mixes dry and wet signals.
dryWet ratio effect asig
-
ratio
- of dry signal to wet -
effect
- means to wet the signal -
asig
-- processed signal
List functions
Widgets
classicWaves :: String -> Int -> Source (Sig -> Sig)Source
A widget with four standard waveforms: pure tone, triangle, square and sawtooth. The last parameter is a default waveform (it's set at init time).
masterVolume :: Source SigSource
Slider for master volume
masterVolumeKnob :: Source SigSource
Knob for master volume
Reverbs
reverbsc1 :: Sig -> Sig -> Sig -> SigSource
Mono version of the cool reverberation opcode reverbsc.
reverbsc1 asig feedbackLevel cutOffFreq
rever2 :: Sig -> Sig -> Sig -> (Sig, Sig)Source
Mono reverb (based on reverbsc)
rever2 feedback asigLeft asigRight
Delays
echo :: D -> Sig -> Sig -> SE SigSource
The simplest delay with feedback. Arguments are: delay length and decay ratio.
echo delayLength ratio
fdelay :: D -> Sig -> Sig -> Sig -> SE SigSource
Delay with feedback.
fdelay maxDelayLength delayLength decayRatio
fvdelay :: D -> Sig -> Sig -> Sig -> Sig -> SE SigSource
Delay with feedback.
fdelay maxDelayLength delayLength feedbackLevel decayRatio
fvdelays :: D -> [(Sig, Sig)] -> Sig -> Sig -> SE SigSource
Multitap delay. Arguments are: max delay length, list of pairs (delayLength, decayRatio)
,
balance of mixed signal with processed signal.
fdelay maxDelayLength delays balance asig
funDelays :: D -> [(Sig, Sig -> Sig)] -> Sig -> Sig -> SE SigSource
Generic multitap delay. It's just like fvdelays
but instead of constant feedbackLevel
it expects a function for processing a delayed signal on the tap.
fdelay maxDelayLength delays balance asig
Distortion
distortion :: Sig -> Sig -> SigSource
Distortion.
distort distLevel asig
Chorus
Flanger
flange :: Lfo -> Sig -> Sig -> Sig -> SigSource
Flanger. Lfo depth ranges in 0 to 1.
flanger lfo feedback balance asig