csound-expression-5.0.0: library to make electronic music

Safe HaskellNone
LanguageHaskell98

Csound.Air.Patch

Contents

Description

Patches.

Synopsis

Documentation

type CsdNote a = (a, a) Source #

A simple csound note (good for playing with midi-keyboard). It's a pair of amplitude (0 to 1) and freuqncy (Hz).

type Instr a b = CsdNote a -> SE b Source #

An instrument transforms a note to a signal.

type Fx a = a -> SE a Source #

An effect processes the input signal.

type Fx1 = Fx Sig Source #

Mono effect.

type Fx2 = Fx Sig2 Source #

Stereo effect.

data FxSpec a Source #

Constructors

FxSpec 

Fields

type Patch1 = Patch D Sig Source #

Mono patches.

type Patch2 = Patch D Sig2 Source #

Stereo patches.

data Patch a b Source #

A patch. It's an instrument, an effect and default dry/wet ratio.

Constructors

Patch 

Fields

Instances

SigSpace a => SigSpace (Patch b a) Source # 

Methods

mapSig :: (Sig -> Sig) -> Patch b a -> Patch b a Source #

type PatchSig1 = Patch Sig Sig Source #

Mono continuous patches.

type PatchSig2 = Patch Sig Sig2 Source #

Stereo continuous patches.

getPatchFx :: (SigSpace a, Sigs a) => Patch b a -> Fx a Source #

Transforms all the effects for the given patch into a single function.

dryPatch :: Patch a b -> Patch a b Source #

atMix :: Sig -> Patch a b -> Patch a b Source #

Sets the mix of the last effect.

atMixes :: [Sig] -> Patch a b -> Patch a b Source #

Sets the mix of the effects from last to first.

Midi

atMidi :: (SigSpace a, Sigs a) => Patch D a -> SE a Source #

Plays a patch with midi. Supplies a custom value for mixing effects (dry/wet). The 0 is a dry signal, the 1 is a wet signal.

atMono :: (SigSpace a, Sigs a) => Patch Sig a -> SE a Source #

Simplified monosynth patch

atMono' :: (SigSpace a, Sigs a) => MidiChn -> D -> D -> Patch Sig a -> SE a Source #

Monosynth patch. Plays the patch with function monoMsg

atMonoMidi midiChn portamentotime releaseTime patch

atMonoSharp :: (SigSpace a, Sigs a) => Patch Sig a -> SE a Source #

Simplified monosynth patch (sharp attack and transitions)

atHoldMidi :: (SigSpace a, Sigs a) => MidiChn -> D -> Patch Sig a -> SE a Source #

Monosynth patch. Plays the patch with function holdMsg

atMonoMidi midiChn portamentotime patch

Events

atSched :: (SigSpace a, Sigs a) => Patch D a -> Evt (Sco (CsdNote D)) -> SE a Source #

Plays a patch with event stream. Supplies a custom value for mixing effects (dry/wet). The 0 is a dry signal, the 1 is a wet signal.

atSchedUntil :: (SigSpace a, Sigs a) => Patch D a -> Evt (CsdNote D) -> Evt b -> SE a Source #

Sco

atSco :: (SigSpace a, Sigs a) => Patch D a -> Sco (CsdNote D) -> Sco (Mix a) Source #

Plays a patch with scores. Supplies a custom value for mixing effects (dry/wet). The 0 is a dry signal, the 1 is a wet signal.

Single note

atNote :: (SigSpace b, Sigs b) => Patch a b -> CsdNote a -> SE b Source #

Plays a patch at the given note.

Fx

addInstrFx :: Fx b -> Patch a b -> Patch a b Source #

Adds an effect to the patch's instrument.

addPreFx :: DryWetRatio -> Fx b -> Patch a b -> Patch a b Source #

Appends an effect before patch's effect.

addPostFx :: DryWetRatio -> Fx b -> Patch a b -> Patch a b Source #

Appends an effect after patch's effect.

Pads

harmonPatch :: (Fractional a, SigSpace b, Sigs b) => [Sig] -> [a] -> Patch a b -> Patch a b Source #

deepPad :: (Fractional a, SigSpace b, Sigs b) => Patch a b -> Patch a b Source #

Misc

patchWhen :: Sigs b => BoolSig -> Patch a b -> Patch a b Source #

Plays the patch when confition is true otherwise it produces silence.

mixInstr :: (SigSpace b, Num b) => Sig -> Patch a b -> Patch a b -> Patch a b Source #

Rever

Sound font patches

Csound API

patchByNameMidi :: (SigSpace a, Sigs a) => String -> Patch D a -> SE a Source #

Triggers patch with Csound API. It creates a named instruement with given name (first argument).

It simulates the midi-like instrument. Notes are encoded with messages:

i "givenName" 1 pitchKey volumeKey     -- note on
i "givenName" 0 pitchKey volumeKey     -- note off

monoPatchByNameMidi :: (SigSpace a, Sigs a) => String -> Patch Sig a -> SE a Source #

Triggers patch with Csound API. It creates a named instruement with given name (first argument).

It simulates the midi-like instrument. Notes are encoded with messages:

i "givenName" 1 pitchKey volumeKey     -- note on
i "givenName" 0 pitchKey volumeKey     -- note off

It behaves just like the function patchByNameMidi but it's defined for monophonic patches. For instruments that take in continuous signals not messages/notes.

monoSharpPatchByNameMidi :: (SigSpace a, Sigs a) => String -> Patch Sig a -> SE a Source #

The monophonic patch with sharper transition from note to note.

monoPatchByNameMidi' :: (SigSpace a, Sigs a) => D -> D -> String -> Patch Sig a -> SE a Source #

Generic function fr invocation of monophonic instrument with Csound API. We can specify portamento and release times.

Custom temperament

Midi

atMidiTemp :: (SigSpace a, Sigs a) => Temp -> Patch D a -> SE a Source #

Plays a patch with midi. Supplies a custom value for mixing effects (dry/wet). The 0 is a dry signal, the 1 is a wet signal.

atMonoTemp :: (SigSpace a, Sigs a) => Temp -> Patch Sig a -> SE a Source #

Simplified monosynth patch with custom temperament.

atMonoSharpTemp :: (SigSpace a, Sigs a) => Temp -> Patch Sig a -> SE a Source #

Simplified monosynth patch (sharp attack and transitions) with custom temperament.

atMonoTemp' :: (SigSpace a, Sigs a) => Temp -> MidiChn -> D -> D -> Patch Sig a -> SE a Source #

Monosynth patch with custom temperament. Plays the patch with function monoMsgTemp

atMonoMidi midiChn portamentotime releaseTime patch

atHoldMidiTemp :: (SigSpace a, Sigs a) => Temp -> MidiChn -> D -> Patch Sig a -> SE a Source #

Monosynth patch with custom temperament. Plays the patch with function holdMsgTemp

atMonoMidi midiChn portamentotime patch

Csound API

patchByNameMidiTemp :: (SigSpace a, Sigs a) => Temp -> String -> Patch D a -> SE a Source #

Triggers patch with Csound API. It creates a named instruement with given name (second argument). It behaves like the function patchByNameMidi but we can specify custom temperament.

monoPatchByNameMidiTemp :: (SigSpace a, Sigs a) => Temp -> String -> Patch Sig a -> SE a Source #

Triggers patch with Csound API. It creates a named instruement with given name (first argument). It behaves like the function monoPatchByNameMidi but we can specify custom temperament.

monoSharpPatchByNameMidiTemp :: (SigSpace a, Sigs a) => Temp -> String -> Patch Sig a -> SE a Source #

The monophonic patch with sharper transition from note to note. We can specify a custom temperament.

monoPatchByNameMidiTemp' :: (SigSpace a, Sigs a) => Temp -> D -> D -> String -> Patch Sig a -> SE a Source #

Generic function fr invocation of monophonic instrument with Csound API. We can specify portamento and release times. Also we can specify a temperament.