csound-expression-5.3.2: 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 MonoInstr a = MonoArg -> SE a Source #

Data type for monophonic instruments.

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 #

Fx specification. It;s a pair of dryWet ratio and a transformation function.

Constructors

FxSpec 

Fields

type Patch1 = Patch Sig Source #

Mono-output patch.

type Patch2 = Patch Sig2 Source #

Stereo-output patch.

data Patch a Source #

The patch can be:

  • a monophonic synt
  • polyphonic synt
  • set of common parameters (SyntSkin)
  • patch with chain of effects,
  • split on keyboard with certain frequency
  • layer of patches. That is a several patches that sound at the same time. the layer is a patch and the weight of volume for a given patch.

data MonoSyntSpec Source #

Specification for monophonic synthesizer.

  • Chn -- midi channel to listen on
  • SlideTime -- time of transition between notes

type SyntSkin = ResonFilter Source #

Common parameters for patches. We use this type to parametrize the patch with some tpyes of arguments that we'd like to be able to change after patch is already constructed. For instance the filter type can greatly change the character of the patch. So by making patches depend on filter type we can let the user to change the filter type and leave the algorithm the same. It's like changing between trademarks. Moog sound vs Korg sound.

The instruments in the patches depend on the SyntSkin through the Reader data type.

If user doesn't supply any syntSkin value the default is used (mlp -- moog low pass filter). Right now the data type is just a synonym for filter but it can become a data type with more parameters in the future releases.

type GenInstr a b = Reader SyntSkin (Instr a b) Source #

Generic polyphonic instrument. It depends on SyntSkin.

type GenMonoInstr a = Reader SyntSkin (MonoInstr a) Source #

Generic monophonic instrument. It depends on SyntSkin.

type GenFxSpec a = Reader SyntSkin (FxSpec a) Source #

Generic FX. It depends on SyntSkin.

polySynt :: Instr D a -> Patch a Source #

Constructor for polyphonic synthesizer. It expects a function from notes to signals.

monoSynt :: MonoInstr a -> Patch a Source #

Constructor for monophonic synthesizer. The instrument is defned on the raw monophonic aruments (see MonoArg).

adsrMono :: (MonoAdsr -> Instr Sig a) -> Patch a Source #

Constructor for monophonic synth with envelope generator. The envelope generator is synced with note triggering. So it restarts itself when the note is retriggered. The envelope generator is a simple ADSR gennerator see the type MonoAdsr.

adsrMonoFilter :: (ResonFilter -> MonoAdsr -> Instr Sig a) -> Patch a Source #

Constructor for monophonic synth with envelope generator and flexible choice of filter. It's just like adsrMono but the user lately can change filter provided in the first argument to some another filter.

fxSpec :: Sig -> Fx a -> GenFxSpec a Source #

Constructor for FX-specification.

fxSpec dryWetRatio fxFun

polySyntFilter :: (ResonFilter -> Instr D a) -> Patch a Source #

Constructor for polyphonic synthesizer with flexible choice of the low-pass filter. If we use the filter from the first argument user lately can change it to some another filter. It defaults to mlp.

monoSyntFilter :: (ResonFilter -> MonoInstr a) -> Patch a Source #

Constructor for monophonic synthesizer with flexible filter choice.

fxSpecFilter :: Sig -> (ResonFilter -> Fx a) -> GenFxSpec a Source #

Constructor for FX-specification with flexible filter choice.

fxSpec dryWetRatio fxFun

mapPatchInstr :: (Instr D a -> Instr D a) -> Patch a -> Patch a Source #

mapMonoPolyInstr :: (MonoInstr a -> MonoInstr a) -> (Instr D a -> Instr D a) -> Patch a -> Patch a Source #

transPatch :: D -> Patch a -> Patch a Source #

Transpose the patch by a given ratio. We can use the functions semitone, cent to calculate the ratio.

dryPatch :: Patch a -> Patch a Source #

Removes all effects from the patch.

getPatchFx :: (SigSpace a, Sigs a) => Maybe SyntSkin -> [GenFxSpec a] -> Fx a Source #

Renders the effect chain to a single function.

setFxMix :: Sig -> Patch a -> Patch a Source #

Sets the dryWet ratio of the effects wwithin the patch.

setFxMixes :: [Sig] -> Patch a -> Patch a Source #

Sets the dryWet ratios for the chain of the effects wwithin the patch.

setMidiChn :: MidiChn -> Patch a -> Patch a Source #

Sets the midi channel for all instruments in the patch.

Midi

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

Plays a patch with midi.

Events

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

Plays a patch with event stream.

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

Plays a patch with event stream with stop-note event stream.

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

Plays notes indefinetely (it's more useful for monophonic synthesizers).

Sco

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

Plays a patch with scores.

Single note

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

Plays a patch with a single infinite note.

Fx

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

Adds an effect to the patch's instrument.

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

Appends an effect before patch's effect.

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

Appends an effect after patch's effect.

Specific fx

fxSig :: SigSpace a => (Sig -> Sig) -> GenFxSpec a Source #

Make an effect out of a pure function.

fxSigMix :: SigSpace a => Sig -> (Sig -> Sig) -> GenFxSpec a Source #

Make an effect out of a pure function and specify dry/wet ratio.

fxSig2 :: (Sig2 -> Sig2) -> GenFxSpec Sig2 Source #

Make an effect out of a stereo pure function.

fxSigMix2 :: Sig -> (Sig2 -> Sig2) -> GenFxSpec Sig2 Source #

Make an effect out of a stereo pure function and specify dry/wet ratio.

mapFx :: SigSpace a => (Sig -> Sig) -> Patch a -> Patch a Source #

Adds post fx with pure signal function.

mapFx' :: SigSpace a => Sig -> (Sig -> Sig) -> Patch a -> Patch a Source #

Adds post fx with pure signal function and specifies dry/wet ratio.

bindFx :: BindSig a => (Sig -> SE Sig) -> Patch a -> Patch a Source #

Adds post fx with effectful signal function.

bindFx' :: BindSig a => Sig -> (Sig -> SE Sig) -> Patch a -> Patch a Source #

Adds post fx with effectful signal function and specifies dry/wet ratio.

mapPreFx :: SigSpace a => (Sig -> Sig) -> Patch a -> Patch a Source #

Adds pre fx with pure signal function.

mapPreFx' :: SigSpace a => Sig -> (Sig -> Sig) -> Patch a -> Patch a Source #

Adds pre fx with pure signal function and specifies dry/wet ratio.

bindPreFx :: BindSig a => (Sig -> SE Sig) -> Patch a -> Patch a Source #

Adds pre fx with effectful signal function.

bindPreFx' :: BindSig a => Sig -> (Sig -> SE Sig) -> Patch a -> Patch a Source #

Adds pre fx with effectful signal function and specifies dry/wet ratio.

Pads

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

Harmnoic series of patches.

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

Adds an octave below note for a given patch to make the sound deeper.

Misc

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

Plays a patch when the condition signal is satisfied. Can be useful for switches.

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

Mix two patches together.

Rever

Sound font patches

sfPatch :: Sf -> Patch2 Source #

Sound font patch.

sfPatchHall :: Sf -> Patch2 Source #

Sound font patch with a bit of reverb.

Monosynt params

onMonoSyntSpec :: (MonoSyntSpec -> MonoSyntSpec) -> Patch a -> Patch a Source #

Transform the spec for monophonic patch.

setMonoSlide :: D -> Patch a -> Patch a Source #

Sets the slide time for pitch and amplitude of monophomic synthesizers.

setMonoSharp :: Patch a -> Patch a Source #

Sets the monophonic to sharp transition and quick release.

Csound API

patchByNameMidi :: (SigSpace a, Sigs a) => String -> Patch 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

Custom temperament

Midi

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

Plays a patch with midi with given temperament (see Csound.Tuning).

Csound API

patchByNameMidiTemp :: (SigSpace a, Sigs a) => Temp -> String -> Patch 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.