csound-expression-4.8.4: library to make electronic music

Safe HaskellNone
LanguageHaskell98

Csound.Control.Midi

Contents

Description

Midi.

Synopsis

Documentation

data MidiChn Source

Specifies the midi channel or programm.

Constructors

ChnAll 
Chn Int 
Pgm (Maybe Int) Int 

type MidiFun a = (Msg -> SE a) -> SE a Source

data Msg :: *

Instances

MidiInstr (Msg -> (Sig, Sig)) Source 
MidiInstr (Msg -> (Sig, Sig, Sig)) Source 
MidiInstr (Msg -> (Sig, Sig, Sig, Sig)) Source 
MidiInstr (Msg -> Sig) Source 
MidiInstr (Msg -> SE (Sig, Sig)) Source 
MidiInstr (Msg -> SE (Sig, Sig, Sig)) Source 
MidiInstr (Msg -> SE (Sig, Sig, Sig, Sig)) Source 
MidiInstr (Msg -> SE Sig) Source 
type MidiInstrOut (Msg -> (Sig, Sig)) = (Sig, Sig) Source 
type MidiInstrOut (Msg -> (Sig, Sig, Sig)) = (Sig, Sig, Sig) Source 
type MidiInstrOut (Msg -> (Sig, Sig, Sig, Sig)) = (Sig, Sig, Sig, Sig) Source 
type MidiInstrOut (Msg -> Sig) = Sig Source 
type MidiInstrOut (Msg -> SE (Sig, Sig)) = (Sig, Sig) Source 
type MidiInstrOut (Msg -> SE (Sig, Sig, Sig)) = (Sig, Sig, Sig) Source 
type MidiInstrOut (Msg -> SE (Sig, Sig, Sig, Sig)) = (Sig, Sig, Sig, Sig) Source 
type MidiInstrOut (Msg -> SE Sig) = Sig Source 

type Channel = Int

midi :: (Num a, Sigs a) => (Msg -> SE a) -> SE a

Triggers a midi-instrument (aka Csound's massign) for all channels. It's useful to test a single instrument.

midin :: (Num a, Sigs a) => Channel -> (Msg -> SE a) -> SE a

Triggers a midi-instrument (aka Csound's massign) on the specified channel.

pgmidi :: (Num a, Sigs a) => Maybe Int -> Channel -> (Msg -> SE a) -> SE a

Triggers a midi-instrument (aka Csound's pgmassign) on the specified programm bank.

ampCps :: Msg -> (D, D) Source

midi_ :: (Msg -> SE ()) -> SE ()

Triggers a midi-procedure (aka Csound's massign) for all channels.

midin_ :: Channel -> (Msg -> SE ()) -> SE ()

Triggers a midi-procedure (aka Csound's pgmassign) on the given channel.

pgmidi_ :: Maybe Int -> Channel -> (Msg -> SE ()) -> SE ()

Triggers a midi-procedure (aka Csound's pgmassign) on the given programm bank.

Mono-midi synth

monoMsg :: MidiChn -> D -> D -> SE (Sig, Sig) Source

Produces midi amplitude and frequency as a signal. The signal fades out when nothing is pressed. It can be used in mono-synths. Arguments are portamento time and release time. A portamento time is time it takes for transition from one note to another.

monoMsg channel portamentoTime releaseTime

holdMsg :: MidiChn -> D -> SE (Sig, Sig) Source

Produces midi amplitude and frequency as a signal and holds the last value till the next one is present. It can be used in mono-synths. Arguments are portamento time and release time. A portamento time is time it takes for transition from one note to another.

holdMsg portamentoTime

Midi event streams

midiKeyOn :: MidiChn -> D -> SE (Evt D) Source

Listens to midi on event on the given key as event stream. The event stream carries the level of volume (ranges from 0 to 1).

midiKeyOff :: MidiChn -> D -> SE Tick Source

Listens to midi on event off the given key as event stream.

Reading midi note parameters

cpsmidi :: Msg -> D

Get the note number of the current MIDI event, expressed in cycles-per-second.

icps  cpsmidi  

csound doc: http://www.csounds.com/manual/html/cpsmidi.html

ampmidi :: Msg -> D -> D

Get the velocity of the current MIDI event.

iamp  ampmidi  iscal [, ifn]

csound doc: http://www.csounds.com/manual/html/ampmidi.html

initc7 :: D -> D -> D -> SE () Source

Initialization of the midi control-messages.

ctrl7 :: D -> D -> D -> D -> Sig

Allows a floating-point 7-bit MIDI signal scaled with a minimum and a maximum range.

idest  ctrl7  ichan, ictlno, imin, imax [, ifn]
kdest  ctrl7  ichan, ictlno, kmin, kmax [, ifn]
adest  ctrl7  ichan, ictlno, kmin, kmax [, ifn] [, icutoff]

csound doc: http://www.csounds.com/manual/html/ctrl7.html

midiCtrl7 :: D -> D -> D -> D -> D -> SE Sig Source

Initializes midi control and get the value in the specified range.

midiCtrl :: D -> D -> D -> SE Sig Source

Initializes midi control and get the value in the range (-1) to 1.

umidiCtrl :: D -> D -> D -> SE Sig Source

Unipolar midiCtrl. Initializes midi control and get the value in the range 0 to 1.

Overload

tryMidi :: (MidiInstr a, Sigs (MidiInstrOut a)) => a -> SE (MidiInstrOut a) Source

Invokes ooverloaded instruments with midi. Example:

dac $ tryMidi (mul (fades 0.01 0.1) . tri)

class MidiInstr a where Source

Converts a value to the midi-instrument. It's used with the functions midi, midin.

Associated Types

type MidiInstrOut a :: * Source

Methods

onMsg :: a -> Msg -> SE (MidiInstrOut a) Source

Instances

MidiInstr ((Sig, Sig) -> (Sig, Sig)) Source 
MidiInstr ((Sig, Sig) -> (Sig, Sig, Sig)) Source 
MidiInstr ((Sig, Sig) -> (Sig, Sig, Sig, Sig)) Source 
MidiInstr ((Sig, Sig) -> Sig) Source 
MidiInstr ((Sig, Sig) -> SE (Sig, Sig)) Source 
MidiInstr ((Sig, Sig) -> SE (Sig, Sig, Sig)) Source 
MidiInstr ((Sig, Sig) -> SE (Sig, Sig, Sig, Sig)) Source 
MidiInstr ((Sig, Sig) -> SE Sig) Source 
MidiInstr ((Sig, D) -> (Sig, Sig)) Source 
MidiInstr ((Sig, D) -> (Sig, Sig, Sig)) Source 
MidiInstr ((Sig, D) -> (Sig, Sig, Sig, Sig)) Source 
MidiInstr ((Sig, D) -> Sig) Source 
MidiInstr ((Sig, D) -> SE (Sig, Sig)) Source 
MidiInstr ((Sig, D) -> SE (Sig, Sig, Sig)) Source 
MidiInstr ((Sig, D) -> SE (Sig, Sig, Sig, Sig)) Source 
MidiInstr ((Sig, D) -> SE Sig) Source 
MidiInstr ((D, Sig) -> (Sig, Sig)) Source 
MidiInstr ((D, Sig) -> (Sig, Sig, Sig)) Source 
MidiInstr ((D, Sig) -> (Sig, Sig, Sig, Sig)) Source 
MidiInstr ((D, Sig) -> Sig) Source 
MidiInstr ((D, Sig) -> SE (Sig, Sig)) Source 
MidiInstr ((D, Sig) -> SE (Sig, Sig, Sig)) Source 
MidiInstr ((D, Sig) -> SE (Sig, Sig, Sig, Sig)) Source 
MidiInstr ((D, Sig) -> SE Sig) Source 
MidiInstr ((D, D) -> (Sig, Sig)) Source 
MidiInstr ((D, D) -> (Sig, Sig, Sig)) Source 
MidiInstr ((D, D) -> (Sig, Sig, Sig, Sig)) Source 
MidiInstr ((D, D) -> Sig) Source 
MidiInstr ((D, D) -> SE (Sig, Sig)) Source 
MidiInstr ((D, D) -> SE (Sig, Sig, Sig)) Source 
MidiInstr ((D, D) -> SE (Sig, Sig, Sig, Sig)) Source 
MidiInstr ((D, D) -> SE Sig) Source 
MidiInstr (Sig -> (Sig, Sig)) Source 
MidiInstr (Sig -> (Sig, Sig, Sig)) Source 
MidiInstr (Sig -> (Sig, Sig, Sig, Sig)) Source 
MidiInstr (Sig -> Sig) Source 
MidiInstr (Sig -> SE (Sig, Sig)) Source 
MidiInstr (Sig -> SE (Sig, Sig, Sig)) Source 
MidiInstr (Sig -> SE (Sig, Sig, Sig, Sig)) Source 
MidiInstr (Sig -> SE Sig) Source 
MidiInstr (D -> (Sig, Sig)) Source 
MidiInstr (D -> (Sig, Sig, Sig)) Source 
MidiInstr (D -> (Sig, Sig, Sig, Sig)) Source 
MidiInstr (D -> Sig) Source 
MidiInstr (D -> SE (Sig, Sig)) Source 
MidiInstr (D -> SE (Sig, Sig, Sig)) Source 
MidiInstr (D -> SE (Sig, Sig, Sig, Sig)) Source 
MidiInstr (D -> SE Sig) Source 
MidiInstr (Msg -> (Sig, Sig)) Source 
MidiInstr (Msg -> (Sig, Sig, Sig)) Source 
MidiInstr (Msg -> (Sig, Sig, Sig, Sig)) Source 
MidiInstr (Msg -> Sig) Source 
MidiInstr (Msg -> SE (Sig, Sig)) Source 
MidiInstr (Msg -> SE (Sig, Sig, Sig)) Source 
MidiInstr (Msg -> SE (Sig, Sig, Sig, Sig)) Source 
MidiInstr (Msg -> SE Sig) Source