csound-catalog-0.7.1: a gallery of Csound instruments.

Safe HaskellNone
LanguageHaskell98

Csound.Catalog.Wave

Contents

Description

Timbres

Synopsis

Woodwind instruments

flute :: D -> D -> D -> D -> D -> D -> D -> Sig Source #

An emulation of the flute. Parameters

flute seed vibDepth attack sustain decay brightnessLevel cps = 
  • seed - a seed for the random signals/numbers. It's in (0, 1)
  • vibDepth - Amount of the vibrato. It's in [-1, 1]
  • attack - duration of the attack. Recommended value: 0.12 for slurred notes, 0.06 for tongued notes, 0.03 for short notes.
  • sustain - duration of the sustain
  • decay - duration of the decay. Recommended value: 0.1 (0.05 for short notes).
  • brightnessLevel - filter cutoff factor. It's in (0, 1). The 0 is 40 Hz, the 1 s 10240 Hz
  • cps - frequency of the note

bassClarinet :: D -> D -> D -> D -> D -> D -> D -> Sig Source #

An emulation of the bass clarinet. Parameters

bassClarinet seed vibDepth attack sustain decay brightnessLevel cps = 
  • seed - a seed for the random signals/numbers. It's in (0, 1)
  • vibDepth - Amount of the vibrato. It's in [-1, 1]
  • attack - duration of the attack. Recommended value: 0.06 for tongued notes, 0.03 for short notes.
  • sustain - duration of the sustain
  • decay - duration of the decay. Recommended value: 0.15 (0.04 for short notes).
  • brightnessLevel - filter cutoff factor. It's in (0, 1). The 0 is 40 Hz, the 1 s 10240 Hz
  • cps - frequency of the note

frenchHorn :: D -> D -> D -> D -> D -> D -> D -> Sig Source #

An emulation of the french horn. Parameters

frenchHorn seed vibDepth attack sustain decay brightnessLevel cps = 
  • seed - a seed for the random signals/numbers. It's in (0, 1)
  • vibDepth - Amount of the vibrato. It's in [-1, 1]
  • attack - duration of the attack. Recommended value: 0.06 for tongued notes (up to 0.12 for lower notes, up to G2), 0.03 for short notes.
  • sustain - duration of the sustain
  • decay - duration of the decay. Recommended value: 0.25 (0.04 for short notes).
  • brightnessLevel - filter cutoff factor. It's in (0, 1). The 0 is 40 Hz, the 1 s 10240 Hz
  • cps - frequency of the note

sheng :: D -> D -> D -> D -> D -> D -> D -> Sig Source #

An emulation of the sheng. Parameters

sheng seed vibDepth attack sustain decay brightnessLevel cps = 
  • seed - a seed for the random signals/numbers. It's in (0, 1)
  • vibDepth - Amount of the vibrato. It's in [-1, 1]
  • attack - duration of the attack. Recommended value: 0.1, 0.03 for short notes.
  • sustain - duration of the sustain
  • decay - duration of the decay. Recommended value: 0.2 (0.04 for short notes).
  • brightnessLevel - filter cutoff factor. It's in (0, 1). The 0 is 40 Hz, the 1 s 10240 Hz
  • cps - frequency of the note

hulusi :: D -> D -> D -> D -> D -> D -> D -> Sig Source #

An emulation of the hulusi. Parameters

hulusi seed vibDepth attack sustain decay brightnessLevel cps = 
  • seed - a seed for the random signals/numbers. It's in (0, 1)
  • vibDepth - Amount of the vibrato. It's in [-1, 1]
  • attack - duration of the attack. Recommended value: 0.03
  • sustain - duration of the sustain
  • decay - duration of the decay. Recommended value: 0.1 (0.04 for short notes).
  • brightnessLevel - filter cutoff factor. It's in (0, 1). The 0 is 40 Hz, the 1 s 10240 Hz
  • cps - frequency of the note

dizi :: D -> D -> D -> D -> D -> D -> D -> Sig Source #

An emulation of the dizi. Parameters

dizi seed vibDepth attack sustain decay brightnessLevel cps = 
  • seed - a seed for the random signals/numbers. It's in (0, 1)
  • vibDepth - Amount of the vibrato. It's in [-1, 1]
  • attack - duration of the attack. Recommended value: 0.12 for slurred notes, 0.07 for tongued notes, 0.03 for short notes.
  • sustain - duration of the sustain
  • decay - duration of the decay. Recommended value: 0.14 (0.04 for short notes).
  • brightnessLevel - filter cutoff factor. It's in (0, 1). The 0 is 40 Hz, the 1 s 10240 Hz
  • cps - frequency of the note

Michael Gogins gallery

pulseWidth :: Sig -> Sig -> Sig Source #

aout = pulseWidth amplitude cps

xanadu1 :: D -> SE Sig Source #

aout <- xanadu1 cps

xanadu2 :: D -> SE Sig Source #

aout <- xanadu2 cps

stringPad :: Sig -> Sig -> Sig Source #

stringPad amplitude cps

toneWheel :: D -> Sig Source #

Tone wheel organ by Mikelson

toneWheel cps

guitar :: D -> Sig Source #

Guitar, Michael Gogins

guitar cps

xing :: D -> Sig -> Sig Source #

Xing by Andrew Horner

xing cycleDuration cps

fmMod :: D -> Sig -> Sig Source #

FM modulated left and right detuned chorusing, Thomas Kung

fmMod cycleDuration cps

filteredChorus :: D -> Sig -> Sig Source #

Filtered chorus, Michael Bergeman

filteredChorus cycleDuration cps

plainString :: D -> Sig Source #

Plain plucked string, Michael Gogins

plainString cps

fmTubularBell :: Sig -> Sig Source #

Tubular bell model, Perry Cook

fmTubularBell cps

delayedString :: D -> Sig Source #

Delayed plucked string, Michael Gogins

delayedString cps

melody :: D -> Sig -> SE Sig Source #

Melody (Chebyshev FM additive), Jon Nelson

melody cycleDuration cps

rhodes :: Sig -> Sig Source #

Rhodes electric piano model, Perry Cook

rhodes cps

Amsterdam catalog instruments

tibetan :: Int -> Sig -> Sig -> Sig Source #

Tibetan chant. It's a chorus of many sinusoids.

tibetan n off cps
  • n - the number of sinusoids (the best is 9)
  • off - frequency step of the harmonics ~ (0.01, 0.03)
  • cps - the frequency of the note

Bay at night

Instruments from the piece "Bay at night" by JL Diaz.

nightPad :: D -> Sig -> Sig Source #

nightPad fadeInTime cps

Vestige of time

Instruments from the piece "Vestige of time" by Matthew Mariano.

filteredSaw :: Sig -> Sig -> Sig Source #

The saw is filtered with band pass filter. Centere frequency of the filter can vary.

filteredSaw centerFrequency sawCps

filteredSawRising :: D -> Sig -> Sig Source #

Filtered saw with rising envelope. Centere frequency starts at 500 Hz and then rises to 5000 by riseDur seconds.

filteredSawRising riseDur cps

filteredSawFalling :: D -> Sig -> Sig Source #

Filtered saw with falling envelope. Centere frequency starts at 5000 Hz and then falls down to 500 by riseDur seconds.

filteredSawFalling riseDur cps

filteredNoise :: Sig -> Sig -> SE Sig Source #

The white noise is filtered with band pass filter. Centere frequency of the filter can vary.

filteredNoise centerFrequency sawCps

resonInstr :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig Source #

Signal is passed through three band-pass filters. We can alter the relative center frequencies of the filters.

resonInstr filt1 filt2 filt3 amp cps = aout

simpleResonInstr :: D -> Sig -> Sig Source #

simpleResonInstr cycleLength cps

resonVibrato :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig Source #

Vibrato and resonant filter with varying center frequency.

resonVibrato vibDepth vibRate filtCps amp cps = aout

delaySaw :: Sig -> Sig Source #

Delayed saw wave.

femaleVowel :: Reson -> Sig -> Sig Source #

Singing a reson's vowels (see Csound.Catalog.Reson).

amBell :: D -> Sig -> Sig Source #

Detuned bell.

amBell amp cps

Desrted

Instruments from the piece "Desrted" by Jen Scaturro.

simpleMarimba :: D -> Sig -> Sig Source #

Simple marimba (by John Fitch) with percussive envelope.

simpleMarimba noteDur cps

marimbaWave :: D -> Sig -> Sig -> Sig Source #

Simple marimba (by John Fitch) without fixed envelope.

marimba noteDur amp cps

phasingSynth :: Sig -> Sig -> Sig Source #

phasingSynth amp cps

noiz :: Sig -> SE Sig Source #

noiz cps

wind :: D -> (D, D) -> (D, D) -> D -> SE Sig Source #

Sound of the wind.

wind noteDur (bandRise, bandDecay) (freqRise, freqDecay) attackDecayRatio
  • * bandRise, banDecay, freqRise, freqDecay -- (50, 1000)
  • attackDecayRatio -- (0, 1)

The Heartbeat

Instruments from the piece "The Heartbeat" by Julie Friedman.

heartbeat :: Sig Source #

Deep kick sound.

monoPluck :: D -> D -> Sig Source #

monoPluck xdur cps

chorusel :: D -> D -> D -> Sig -> (Sig, Sig) Source #

chorusel dur rise dec cps
  • dur - note duration
  • rise - rise time
  • dec - decay time
  • cps - frequency of the note

Trapped in convert

Instruments from the piece "Trapped in convert" by Richard Boulanger

ivory :: D -> D -> Sig -> D -> Sig -> Sig Source #

ivory xdur glisDur vibRate cpsCoeff cps

blue :: D -> D -> D -> Sig -> Sig -> SE Sig Source #

blue noteDuration numberOfHarmonics sweepRate lfoCps cps
  • numberOfHarmonics ~ (6, 10)
  • sweepRate ~ (0, 1)
  • lfoCps ~ 20

black :: D -> D -> D -> Sig -> Sig -> SE Sig Source #

Noise filtered with sweep filter.

black noteDuration filterSweepStart filterSweepEnd bandWidth cps
  • filterSweepStart, filterSweepEnd - hearing range
  • bandWidth - (10, 50)

blackMarimba :: Sig -> SE Sig Source #

Black with fixed parameters.

blackMarimba cps

Modes

Percussive instruments defined with modal synthesis -- (see the functions modes and modesInstr). All instruments take in a frequency and produce the output signal with percussive envelope.

Vowel

An emulation of the singing of the vowels with granular synthesis (fof-opcode in the Csound) It's best to use these functions with vibrato.

vibrato 0.12 5 $ oneVowel maleA 330

vowels :: D -> [(Vowel, D)] -> Vowel -> Sig -> Sig Source #

Sings a sequence of vowels with the given frequency.

vowels maxDur [(vowel1, dur1), (vowel2, dur2), (vowel3, dur3), ...] lastVowel cps
  • maxDur - total duration of the note
  • vowel1, vowel2, ... lastVowel -- vowels
  • dur1, dur2, ... - durations
  • cps - frequency of the note.

loopVowels :: D -> Sig -> [(Vowel, D)] -> Sig -> Sig Source #

Sings a loop of vowels with the given frequency.

loopVowels maxDur xdur [(vowel1, dur1), (vowel2, dur2), (vowel3, dur3), ...] cps
  • maxDur - total duration of the note
  • xdur - the duration of the loop of vowels.
  • vowel1, vowel2, ... -- vowels
  • dur1, dur2, ... - durations
  • cps - frequency of the note.

oneVowel :: D -> Vowel -> Sig -> Sig Source #

Sings a single vowel with the given frequency.

oneVowel maxDur vowel cps
  • maxDur - total duration of the note.

data Vowel Source #

Abstract type that represents a vowel.

Vowels

Sean Costello

rissetBell :: RissetBellSpec -> (D, D) -> D -> Sig -> Sig -> SE Sig Source #

timpani :: (D, D) -> D -> Sig -> Sig -> SE Sig Source #

noiseBell :: (D, D) -> D -> Sig -> Sig -> SE Sig Source #

dac $ noiseBell (31, 125) 2.3 0.2 2900

snowCrackle :: Sig -> Sig Source #

speed ~ 10 - 20

snowCrackle speed

fmDrone :: Sig -> (D, D) -> Sig -> (Sig, Sig) Source #

dac $ fmDrone 3 (20, 5) 110

fmDrones :: Sig -> [Sig] -> [Sig] -> (D, D) -> Sig -> SE (Sig, Sig) Source #

tenorOsc :: (Sig -> Sig) -> Sig -> Sig -> SE Sig Source #

sopranoOsc :: (Sig -> Sig) -> Sig -> Sig -> SE Sig Source #

Flavio

amFlavio :: t -> Sig -> Sig Source #

fmFlavio :: D -> Sig -> Sig -> Sig Source #

simpleSust :: D -> (D, D) -> SE (Sig, Sig) Source #

simpleFading :: D -> (D, D) -> SE (Sig, Sig) Source #

Thor

hammondOrgan :: Sig -> Sig -> SE Sig Source #

hammondOrgan detune

detune = [0, 30] (in cents)

thorWind :: Sig -> Sig -> (Sig, Sig) -> SE Sig Source #

razorPad :: (Fractional (SE b), Fractional t, SigSpace b) => (Sig -> t -> Sig -> b) -> Sig -> Sig -> Sig -> SE b Source #

razorLead :: Sig -> Sig -> Sig -> Sig -> SE Sig Source #

FM

Bitwig

Pads

SHARC instruments

SHARC ported to Csound. SHARC is a database of musical timbre information by Gregory Sandell. It's a collection of sustain notes for real orchestra instruments.

Oscillators

sharcOsc :: SharcInstr -> D -> Sig Source #

Sharc oscillator

sigSharcOsc :: SharcInstr -> D -> Sig -> Sig Source #

Sharc oscillator with continuous pitch. The second argument picks upth table by frequency and the third supplies the frequency.

rndSharcOsc :: SharcInstr -> D -> SE Sig Source #

Sharc oscillator with randomized phase.

rndSigSharcOsc :: SharcInstr -> D -> Sig -> SE Sig Source #

Sharc oscillator with continuous pitch and randomized phase.

soloSharcOsc :: SharcInstr -> D -> SE Sig Source #

Plays a solo instrument

orcSharcOsc :: SharcInstr -> D -> SE Sig Source #

Plays a orchestrated instrument (with pitch chorus)

purePadSharcOsc :: SharcInstr -> D -> SE Sig Source #

Plays a solo instrument with pad-like envelope

padSharcOsc :: SharcInstr -> D -> SE Sig Source #

Plays orchestrated instrument with pad-like envelope

Padsynth

Instriments

newtype SharcInstr Source #

Constructors

SharcInstr 

Fields

Low-level getters

getInstrTab :: SharcInstr -> Int -> Tab Source #

Get instrument wave table by midi pitch number.

Other instruments

okComputer :: Sig -> SE Sig Source #

Tech sound. Random sinusoids palyed at the very fast rate.

okComputer rate
  • rate -- rate of new notes ~ (5, 20)