csound-expression-4.2.1: library to make electronic music

Safe HaskellNone
LanguageHaskell98

Csound.Control.Midi

Contents

Description

Midi.

Synopsis

Documentation

data Msg :: *

Instances

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

type Channel = Int

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

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

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

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

pgmidi :: Sigs a => Maybe Int -> Channel -> (Msg -> SE a) -> 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 :: 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 portamentoTime releaseTime

holdMsg :: 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

monoMsgn :: Channel -> D -> D -> SE (Sig, Sig) Source

Produces midi amplitude and frequency as a signal. The signal fades out when nothing is pressed. We can specify a channel. 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.

monoMsgn chnNumber portamentoTime releaseTime

holdMsgn :: Channel -> D -> SE (Sig, Sig) Source

Produces midi amplitude and frequency as a signal and holds the last value till the next one is present. We can specify a channel. 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.

holdMsgn chnNumber portamentoTime

pgmonoMsg :: Maybe Int -> Channel -> D -> D -> SE (Sig, Sig) Source

Produces midi amplitude and frequency as a signal. The signal fades out when nothing is pressed. We can specify a programm number and channel. 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.

pgmonoMsg chnNumber portamentoTime releaseTime

pgholdMsg :: Maybe Int -> Channel -> D -> SE (Sig, Sig) Source

Produces midi amplitude and frequency as a signal and holds the last value till the next one is present. We can specify a programm number and channel. 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.

pgholdMsg portamentoTime

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

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)) 
MidiInstr ((Sig, Sig) -> (Sig, Sig, Sig)) 
MidiInstr ((Sig, Sig) -> (Sig, Sig, Sig, Sig)) 
MidiInstr ((Sig, Sig) -> Sig) 
MidiInstr ((Sig, Sig) -> SE (Sig, Sig)) 
MidiInstr ((Sig, Sig) -> SE (Sig, Sig, Sig)) 
MidiInstr ((Sig, Sig) -> SE (Sig, Sig, Sig, Sig)) 
MidiInstr ((Sig, Sig) -> SE Sig) 
MidiInstr ((Sig, D) -> (Sig, Sig)) 
MidiInstr ((Sig, D) -> (Sig, Sig, Sig)) 
MidiInstr ((Sig, D) -> (Sig, Sig, Sig, Sig)) 
MidiInstr ((Sig, D) -> Sig) 
MidiInstr ((Sig, D) -> SE (Sig, Sig)) 
MidiInstr ((Sig, D) -> SE (Sig, Sig, Sig)) 
MidiInstr ((Sig, D) -> SE (Sig, Sig, Sig, Sig)) 
MidiInstr ((Sig, D) -> SE Sig) 
MidiInstr ((D, Sig) -> (Sig, Sig)) 
MidiInstr ((D, Sig) -> (Sig, Sig, Sig)) 
MidiInstr ((D, Sig) -> (Sig, Sig, Sig, Sig)) 
MidiInstr ((D, Sig) -> Sig) 
MidiInstr ((D, Sig) -> SE (Sig, Sig)) 
MidiInstr ((D, Sig) -> SE (Sig, Sig, Sig)) 
MidiInstr ((D, Sig) -> SE (Sig, Sig, Sig, Sig)) 
MidiInstr ((D, Sig) -> SE Sig) 
MidiInstr ((D, D) -> (Sig, Sig)) 
MidiInstr ((D, D) -> (Sig, Sig, Sig)) 
MidiInstr ((D, D) -> (Sig, Sig, Sig, Sig)) 
MidiInstr ((D, D) -> Sig) 
MidiInstr ((D, D) -> SE (Sig, Sig)) 
MidiInstr ((D, D) -> SE (Sig, Sig, Sig)) 
MidiInstr ((D, D) -> SE (Sig, Sig, Sig, Sig)) 
MidiInstr ((D, D) -> SE Sig) 
MidiInstr (Sig -> (Sig, Sig)) 
MidiInstr (Sig -> (Sig, Sig, Sig)) 
MidiInstr (Sig -> (Sig, Sig, Sig, Sig)) 
MidiInstr (Sig -> Sig) 
MidiInstr (Sig -> SE (Sig, Sig)) 
MidiInstr (Sig -> SE (Sig, Sig, Sig)) 
MidiInstr (Sig -> SE (Sig, Sig, Sig, Sig)) 
MidiInstr (Sig -> SE Sig) 
MidiInstr (D -> (Sig, Sig)) 
MidiInstr (D -> (Sig, Sig, Sig)) 
MidiInstr (D -> (Sig, Sig, Sig, Sig)) 
MidiInstr (D -> Sig) 
MidiInstr (D -> SE (Sig, Sig)) 
MidiInstr (D -> SE (Sig, Sig, Sig)) 
MidiInstr (D -> SE (Sig, Sig, Sig, Sig)) 
MidiInstr (D -> SE Sig) 
MidiInstr (Msg -> (Sig, Sig)) 
MidiInstr (Msg -> (Sig, Sig, Sig)) 
MidiInstr (Msg -> (Sig, Sig, Sig, Sig)) 
MidiInstr (Msg -> Sig) 
MidiInstr (Msg -> SE (Sig, Sig)) 
MidiInstr (Msg -> SE (Sig, Sig, Sig)) 
MidiInstr (Msg -> SE (Sig, Sig, Sig, Sig)) 
MidiInstr (Msg -> SE Sig)