csound-expression-5.4.3.1: library to make electronic music
Safe HaskellSafe-Inferred
LanguageHaskell2010

Csound.Air.Misc

Description

Patterns

Synopsis

Documentation

mean :: Fractional a => [a] -> a Source #

Mean value.

vibrate :: Sig -> Sig -> (Sig -> a) -> Sig -> a Source #

Adds vibrato to the sound unit. Sound units is a function that takes in a frequency.

randomPitch :: Sig -> Sig -> (Sig -> a) -> Sig -> SE a Source #

Adds a random vibrato to the sound unit. Sound units is a function that takes in a frequency.

chorusPitch :: Int -> Sig -> (Sig -> Sig) -> Sig -> Sig Source #

Chorus takes a number of copies, chorus width and wave shape.

resons :: [(Sig, Sig)] -> Sig -> Sig Source #

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 -> Sig Source #

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 -> Sig Source #

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 -> Sig Source #

Mixes dry and wet signals.

dryWet ratio effect asig
  • ratio - of dry signal to wet
  • effect - means to wet the signal
  • asig -- processed signal

once :: Tab -> Sig Source #

Reads table once during the note length.

onceBy :: D -> Tab -> Sig Source #

Reads table once during a given period of time.

several :: Tab -> Sig -> Sig Source #

Reads table several times during the note length.

fromMono :: Sig -> (Sig, Sig) Source #

Doubles the mono signal to get the stereo signal.

List functions

odds :: [a] -> [a] Source #

Selects odd elements from the list.

evens :: [a] -> [a] Source #

Selects even elements from the list.

Random functions

rndPan :: Sig -> SE Sig2 Source #

Random panning

rndPan2 :: Sig2 -> SE Sig2 Source #

Random panning

rndVol :: SigSpace a => (D, D) -> a -> SE a Source #

Random volume

gaussVol (minVolume, maxVolume)

gaussVol :: SigSpace a => D -> a -> SE a Source #

Random volume (with gauss distribution)

gaussVol radiusOfDistribution

Choose signals

selector :: (Num a, SigSpace a) => [a] -> Sig -> a Source #

It picks a signal from the list by integer index. The original value is taken from the head of the list (the first element).

Saving to file

writeHifi :: D -> String -> SE Sig2 -> IO () Source #

Hi-fi output for stereo signals. Saves the stereo signal to file. The length of the file is defined in seconds.

writeHifi fileLength fileName asig

Arpeggios

arpeggi :: SigSpace a => [Sig] -> [Sig] -> (Sig -> a) -> Sig -> a Source #

Creates running arpeggios.

arpeggiBy ampWeights pitches instrument cps

It plays an instrument with fast sequence of notes. We can specify the pitches and amplitude weights of the notes as well as frequency of repetition.

arpBy :: SigSpace a => ([Sig] -> Sig -> Sig) -> ([Sig] -> Sig -> Sig) -> [Sig] -> [Sig] -> (Sig -> a) -> Sig -> a Source #

Creates running arpeggios.

arpeggiBy ampWave pitchwave ampWeights pitches instrument cps

It plays an instrument with fast sequence of notes. We can specify amplitude envelope wave, pitch envelope wave, the pitches and amplitude weights of the notes as well as frequency of repetition.

GUI

lpJoy :: Source (Sig -> Sig) Source #

Low-pass filter pictured as joystick. Ox is for center frequency and Oy is for resonance.

Effects

delaySig :: D -> Sig -> Sig Source #

Delay a signal by certain number of seconds There is a subtle difference between the function and the function delaySnd. The delaySig is for delaying a signal on a micro level (the delay time have to be small) It's implemented with delay buffer in the csound. But delaySnd is for delaying on macro level (the delay time can be big). It's implemented with scores and invocation of hidden instruments.

delaySig numOfSamples asig

delay1k :: Sig -> Sig #

Delay a control signal by single sample.

Wave shaper

wshaper :: Tab -> Sig -> Sig -> Sig Source #

Wave shaper. The signal should be bipolar. It ranges within the interval [-1, 1].

wshaper table amount asig

wave shaper transforms the input signal with the table. The amount of transformation scales the signal from 0 to 1. the amount is ratio of scaling. It expects the values from the interval [0, 1].

genSaturator :: Double -> Sig -> Sig -> Sig Source #

Wave shaper with sigmoid.

genSaturator sigmoidRadius amount asig
  • sigmoid radius is 5 to 100.
  • amount is [0, 1]

saturator :: Sig -> Sig -> Sig Source #

Alias for

genSaturator 10

mildSaturator :: Sig -> Sig -> Sig Source #

Alias for

genSaturator 5

hardSaturator :: Sig -> Sig -> Sig Source #

Alias for

genSaturator 50

hardSaturator2 :: Sig -> Sig -> Sig Source #

Alias for

genSaturator 100

Function composition

funSeq :: [a -> a] -> a -> a Source #

Chains all functions in the list.

funPar :: Num a => [a -> a] -> a -> a Source #

Applies all functions in the list to the given input and summs them up.

Metronome

ticks :: Int -> Sig -> Sig Source #

Metronome.

ticks n bpm

nticks :: [Int] -> Sig -> Sig Source #

Metronome with a chain of accents. A typical 7/8 for example:

dac $ nticks [3, 2, 2] (135 * 2)

nticks2 :: [Int] -> Sig -> Sig Source #

nticks3 :: [Int] -> Sig -> Sig Source #

nticks4 :: [Int] -> Sig -> Sig Source #

Drone

Attack detection

attackTrig :: Sig -> Sig -> SE (Evt Unit) Source #

Detects attacks in the signal. Outputs event stream of attack events.

attackTrig threshold sigIn

threshhold cnmtrols the sensitivity of attack detection. Try out different values in [0, 0.2]

attackTrigSig :: Sig -> Sig -> SE Sig Source #

Detects attacks in the signal. Outputs trigger-signal where 1 is when attack happens and 0 otherwise.

Ambient guitar FX

ambiEnv :: Sig -> Sig -> SE Sig Source #

Make smooth attacks for the input guitar or piano-like sounds. It simulates automatic volume control pedal. It detects striken attacks and makes them sound more PAD-like.

first argument is threshold that controls sensitivity of attack detection. The values like ~ 0.01, 0.02 is good start.

To use it with guitar it's good to add a bit of distortion and compression to the signal to make it brighter and then to apply several delays to prolong the sustain and release phases. And it's good to add some reverb at the end.

Here is an example of how to make ambient guitar with this effect:

main = dac proc

-- | Let's assume we read guitar from the first input of sound card
proc :: Sig2 -> SE Sig2
proc (x, _) = mul 1 $ hall 0.25 $
         fmap ( fromMono . (adele 0.35 1 0.65 0.34) . (adele 0.35 0.25 0.75 0.34) .
                saturator 0.3  . tort 0.1 0.25 .
                magnus 2 0.25 1.1 0.6 0.4 1.8) $
          ambiEnv 0.02 x

So I've added a tape echo with magnus, then goes combo of saturator (compressor) and tort (distortion) then goes a couple of delays (adele) and the last part is sweet reverb (hall).