ftp.nice.ch/pub/next/unix/music/cm.sd.tar.gz#/doc/midi.rtf

This is midi.rtf in view mode; [Download] [Up]

MIDI Support in Common Music

Heinrich Taube

Zentrum fuer Kunst und Medientechnologie
Ritterstr. 42
7500 Karlsruhe 1
Germany
		
				Mail:  hkt@zkm.de
				Fax: +49 721 9340 39 
				Vox: +49 721 9340 300
		

___________________________________________________________


Introduction

Common Music supports MIDI real time and MIDI file generation through the midi syntax.  MIDI real time is implemented at the lowest level by a MIDI message facility, and provides the ability to directly read and write MIDI messages to a MIDI driver.  An object oriented representation of MIDI objects is built on top of the basic messaging facility and provides the ability to use midi-notes, algorithms, generators, and item streams when working with midi data.

1.1 MIDI Real Time Messages

To support MIDI real time, a low-level representation of a MIDI event, called a "message", is implemented.  MIDI messages are really just formatted 28-bit fixnums containing up to three bytes of data.  All of the MIDI messages defined in the MIDI specification, (including system exclusive and meta event messages) are supported through a notion of MIDI message type and subtype.

1.2 MIDI Message Types

Each MIDI message type is implemented by a type name (either symbol or keyword), a constructor function, a predicate, and one or more message data field accessors, if appropriate.  For example, MIDI note on messages are supported through the note-on message type:

Type name			note-on, :note-on
Message constructor		make-note-on
Message predicate		note-on-p
Data field accessors	 	note-on-channel, note-on-key, note-on-velocity
			
The data field accessors are implemented as functions, not macros, so they are suitable for use in mapping.  For example:

<cl> (mapcar #'note-on-key message-list)

would return a list of all the key numbers in a list of note-on messages.

All data field accessors are setf-able, that is, they may be used to both set and retrieve the contents of message data fields:

<cl> (setf x (make-note-on 0 60 64))
59784256

<cl> (note-on-key x)
60

<cl> (incf (note-on-key x) 10)
70

<cl> (midi-print-message x)
#<NoteOn: 0, 70, 64>

Some message types, such as MIDI file "meta events" are implemented as composite messages.  Constructors for composite message types return multiple values: the message created and a (possibly empty) list of message data.  Each element of the message data list is itself a message of type midi-data.  A midi-data message contains from one to three bytes of raw MIDI data.

The following is a list of supported MIDI message types along with their constructors, predicates and data accessors:
	
channel-message							[basic message type]
	make-channel-message status channel data1 &optional data2
	channel-message-p message
	channel-message-status message
	channel-message-channel message
	channel-message-data1 message
	channel-message-data2 message

note-on									[channel message]
	make-note-on channel key velocity
	note-on-p message
	note-on-channel message
	note-on-key message
	note-on-velocity message

note-off									[channel message]
	make-note-off channel key velocity
	note-off-p message		
	note-off-channel message
	note-off-key message
	note-off-velocity message

key-pressure								[channel message]
	make-key-pressure channel key velocity
	key-pressure-p message
	key-pressure-channel message
	key-pressure-key message
	key-pressure-pressure message

control-change								[channel message]
	make-control-change channel controller value
	control-change-p message
	control-change-channel message
	control-change-control message
	control-change-change message

program-change							[channel message]
	make-program-change channel program
	program-change-p message
	program-change-channel message
	program-change-program message

channel-pressure							[channel message]
	make-channel-pressure channel pressure
	channel-pressure-p message
	channel-pressure-channel message
	channel-pressure-pressure message

pitch-bend								[channel message]
	make-pitch-bend channel lsb msb
	pitch-bend-p message
	pitch-bend-channel message
	pitch-bend-lsb message
	pitch-bend-msb message

channel-mode								[channel message]
	make-channel-mode channel control change
	channel-mode-p message
	channel-mode-channel message
	channel-mode-control message
	channel-mode-change message

system-message							[basic message type]
	make-system-message status &optional data1 data2
	system-message-p message
	system-message-status message
	system-message-data1 message
	system-message-data2 message

song-position								[system message]
	make-song-position lsb msb
	song-position-p message
	song-position-lsb message
	song-position-msb message

song-select								[system message]
	make-song-select song
	song-select-p message
	song-select-song message

tune-request								[system message]
	make-tune-request ()
	tune-request-p message

sysex-message								[system message]

The :sysex-message type is implemented across multiple messages.  The constructor function make-sysex-message returns multiple values:  a message (of type :sysex-message) and a (possibly empty) list of message data. Each element in the data list is itself a message of type midi-data.  Each data element in a sysex messages holds one byte of MIDI data.

	make-sysex-message &rest data
	sysex-message-p message

meta-message								[basic message type]

The :meta-message type and all its subtypes are implemented across multiple messages.   Every meta-message constructor function returns multiple values:  a meta message and a (possibly empty) list of  meta message data. Each element in the data list is itself a message of type 	midi-data.  Each data element of a meta message holds one byte of MIDI data.
	make-meta-message type
	meta-message-p message
	meta-message-type message

time-signature									[meta message]
	make-time-signature n d &optional (clock 24) (32nds 8)
	time-signature-p message

tempo-change									[meta message]
	make-tempo-change usecs
	tempo-change-p message

eot										[meta message]
	make-eot ()
	eot-p message


midi-data									[basic message type]
	make-midi-data data1 &optional data2 data3
	midi-data-p message
	midi-data-size message
	midi-data-data1 message
	midi-data-data2 message
	midi-data-data3 message


1.3 MIDI Message Utilities

A number of general purpose functions are provided for working with MIDI messages and MIDI files:

make-midi-message  type &rest args 					[function]

This function provides the most general means for creating MIDI messages.  type must be one of the defined MIDI message types,  specified as either a keyword or a symbol. args is zero or more data arguments appropriate for the type of message.

Example:

;; The following two calls are equivalent:

<cl> (make-note-on 0 60 64)
126893120 

<cl> (make-midi-message 'note-on 0 60 64)
126893120 


midi-print-message message &optional time 				[function]
	                            &key stream time-format  message-data

Prints message on stream, which defaults to the standard output.  If time is specified, it is printed first according to the format string time-format.  midi-print-message returns message as its value.

Examples:

<cl> (midi-print-message (make-note-on 0 60 127))
#<NoteOn: 0, 60, 127>
126893183	

<cl> (multiple-value-bind (msg data) (make-time-signature 4 4)
	     (midi-print-message msg nil :message-data data))
#<TimeSig: 4/4 clocks=24 32nds=8>
251615232 


1.4 Using MIDI Real Time 

To use MIDI messages in real time, a MIDI driver must be opened on some port.  MIDI messages are then directly read from and written to the MIDI driver.   Here is
a very brief MIDI session:

<cl> (midi-open :port :A)
:A

<cl> (midi-write-message (make-note-on 0 60 127))
T

<cl> (midi-write-message (make-note-off 0 60 127))
T

<cl> (midi-close)
T

1.4.1 Opening and Closing the MIDI port

Before any MIDI messages are sent or received, MIDI must first be opened on some port.  This port should then be closed after it is no longer needed.  Opening and closing MIDI ports are implemented by the following functions:

midi-open &key port								[function]

Open MIDI driver on the specified port. The port may designated by number: 1 or 2, or by symbol: a or b.  (The keyword forms of the symbols may also be used.) midi-open returns the port name  if it was able to open the port, otherwise nil.

Example:

<cl> (midi-open :port :b)
:B

midi-close ()									[function]

Close the current MIDI port, if one is open.  midi-close returns t if it was able to close the port, otherwise nil.

midi-open-p ()									[function]

Returns the port name if MIDI port is open, otherwise nil.

with-midi-open ((&key port) &body body)					[macro]

Forms in the body of with-midi-open are evaluated with MIDI open on the port specified by port.  If port is not specified its value defaults to the global variable *midi-port*.  After the forms inside the body have been evaluated,  the MIDI port is closed if it was not previously open, otherwise it is  left open.

Example:

(defun listen ()
  (with-midi-open (:port :b) 
	 (loop doing (midi-read-messages #'midi-write-message))))

*midi-port*									[variable]

The value of *midi-port* provides a default port value for MIDI input and output.   Names for the first serial port are:  A, :A, 1 and for the second:  B,:B, 2.

1.4.2  Writing and reading MIDI messages

Once a port is opened, a MIDI message may be sent to the driver:

midi-write-message message &optional (time 0) message-data		[function]

Sends MIDI message at optionally specified quanta time time.  If time is not specifed the messsage is sent immediately (time 0).

Examples:

<cl> (midi-write-message (make-note-on 0 60 127))
<cl> (midi-write-message (make-note-off 0 60 127) 1000)
	  
;;; here is a slightly more adventurous example (for my
;;; spiffy Yamaha TG33...) that plays 100 notes and chooses
;;; some sort of drum sound every so often.

(let ((on (make-note-on 0 0 127))
	    (off (make-note-off 0 0 127))
	    (cng (make-program-change 0 62))      
	    (time (midi-get-time)))
	(loop for i below 100 
	      do
	  (when (= 1 (random 10)) 
	    (setf (program-change-program cng) (+ 59 (random 6)))
	    (midi-write-message cng))
	  (setf (note-on-key on) (+ 60 (random 12)))
	  (setf (note-off-key off) (note-on-key on))
	  (incf time (+ 50 (random 450)))
	  (midi-write-message on time)
	  (midi-write-message off (+ time 600)))) 

All current MIDI messages (messages that have been received by the driver from some MIDI device, such as an external keyboard) may be read by the function midi-read-messages:

midi-read-messages &optional function					[function]
	
Reads all MIDI messages currently available (received).  If function is supplied it is invoked on each message read. The function must accept two arguments, the current message and its quanta time.

Examples:

;; read and print all currently pending messages.
(midi-read-messages #'midi-print-message)

;; return a sequence of all pending messages
(let (l '())
	(midi-read-messages #'(lambda (m q) (push m l)))
	(nreverse l))

;; define a harmonizing function and use it in a loop 
(defun harmonize (msg time)
	(midi-write-message msg time)
	(incf (note-on-key msg) 3)
	(midi-write-message msg time)
	(incf (note-on-key msg) 4)			
	(midi-write-message msg time))

(loop doing (midi-read-messages #'harmonize))

Alternately, the global variable *midi-read-hook* may be set to a function that should be invoked on a message whenever it is read by midi-read-messages.

1.4.3  MIDI Message Time

MIDI message time is expressed in terms of integer "quanta".  The default quantum size is 1000 microseconds.  The MIDI driver's current time may be accessed and set with the following functions:

midi-get-time ()									 [function]

Returns multiple values, the current quanta time and the current quantum size.

midi-set-time quanta								[function]

Sets MIDI time to new quanta time.

midi-set-quanta-size size							 [function]

Sets the number of micro seconds per quantum.

Two functions are supplied for converting between quanta (integer) and real (floating point) time:

quanta-time rtime								 [function]

Convert real time (floating point) to quanta time.

real-time qtime									 [function]

Convert quanta time (integer) to real time.

In addition to getting and setting the time, the timer itself may be stopped and started with the following two of functions: 

midi-start-timer ()								 [function]

Starts the MIDI driver's timer, if currently stopped.

midi-stop-timer ()								 [function]

Stops the midi driver's timer.

1.4.5 Real Time Scheduling
	
It is easy to write a real time scheduling loops in lisp,  so that MIDI messages
(or whatever)  are processed in real time.  As an example, here is a function
that invokes a user supplied function on each element of an event list at its proper time.   Each item in the event list is itself a list whose first element is a MIDI message and whose second element is a delta millisecond time:

(defun real-time (event-list event-fn)
  (declare (optimize (speed 3)(safety 0)))
  (excl:without-interrupts
    (let (base-time next-time next-event)
      (declare (fixnum base-time next-time))
      (setf base-time (get-internal-real-time))
      (loop while event-list
        do 
	(setf next-event (pop event-list))
	(setf next-time (+ (the fixnum (cadr next-event)) 				   base-time))
  	(loop while (< (get-internal-real-time) next-time)
	      do nil)
	(funcall event-fn next-event)
	(setf base-time next-time)))))

After compiling this function, it could be invoked with an event function that just outputs the event's message:

(real-time my-list #'(lambda (e)(midi-write-message (car e))))

The file cm/midi/examples/real-time.lisp implements a simple scheduler for scheduling MIDI messages in real time, and the file cm/midi/examples/real-time-example.lisp contains an example of using this code.  Both files should be compiled before loading.

1.5 MIDI file utilities

*default-midi-pathname* 	              				 [variable]

The value of *default-midi-pathname* is the default pathname for midi file operations.  All midi file utilities merge the user supplied pathname with the value of *default-midi-pathname* to form the fully specified pathname.  *default-midi-pathname* is initially set to "test.midi" in the user's home directory (whatever (user-homedir-pathname) returns as a value.)

midifile-print pathname &key (tracks t)  (stream *standard-output*)	[function]
	 		
Prints the contents of the MIDI file specified by pathname on stream. stream defaults to the standard output.  tracks should either be t, (in which case all MIDI tracks in the file are printed) or a list of track numbers.
	

midifile-map pathname &key (tracks t)					[function] 
				header-fn channel-message-fn
				track-fn system-message-fn meta-message-fn

Maps optionally supplied functions over the contents of the MIDI file specified by pathname.   tracks is the same as in midifile-print.  If header-fn is supplied, it is passed the header information in the MIDI file, and must accept 3 arguments:  file-format number-of-tracks divisions.  If track-fn is supplied, it is passed information about each track in the MIDI file, and must accept 2 arguments: track-number length.  If channel-message-fn is supplied it is invoked on all channel messages in each track mapped. The function must accept 2 arguments: message time.  If meta-message-fn is supplied it is invoked on all meta event messages in each track mapped. The function must accept 4 arguments: message time data-length message-data.  If system-message-fn is supplied it is invoked on all system messages in each track mapped. The function must accept 4 arguments: message time data-length message-data

Example:

;; return all the channel messages and times in a list.

(let ((list '()))
	(midifile-map "~/test.midi"
	               :channel-message-fn 
	               #'(lambda (msg time)
	                   (push (list msg time) list)))
	(nreverse list))


midifile-parse pathname fn &key (channels t) merge			[function] 

Parses midi messages into parameter note information and maps a user specified function across the data.  The user supplied function must accept 6 arguments:
(channel begin rhythm duration frequency amplitude)
where channel is the midi channel of the note, begin is the starting time (seconds) of the note, rhythm is the real time until the next note (if any), duration is the total length of the note (seconds), frequency is the midi key number of the note and amplitude is the midi velocity value of the original note on.  Note that the parsing process ignores note off velocity and sets the rhythic value of the last note to nil.  The keyword channels controls how the midifile is to be "time lined".  If channels is t (the default), each channel is parsed in its own time line, ie start times, rhythms and durations are calculated using only notes from the same channel.  If channels is nil, then all the channels are "collapsed" into one parsing time line, which is indentical to the time line represented by the midifile itself.  Otherwise, channels should be lists of lists; each sublist represents channels that are to be grouped in a single time line.  Merge controls whether or not data in seperate time lines is sorted prior to function mapping.  The default value nil means that the seperate time lines are not merged, and the function is mapped over the notes in one time line before the next time line is considered.  If merge is t then the function is mapped over notes sorted by start time.


midifile-play &optional pathname &key (start 0) end (timescale 1.0)	[function]
                                                                   (headstart 1000) port

Plays the contents of the MIDI file specified by pathname.  If pathname is not specified, it defaults to the value of *last-scorefile-written*.   Start is the start time in the file to begin listening.  End is the last time in the file to listen to, and defaults to end-of-file. Timescale is a tempo factor to appy to messages and defaults to 1.0.  Headstart is the number of milliseconds to delay the onset of sound by, and defaults to 1000 (1.0 seconds).  Port is the midi port to open if midi is not currently open.

2.1 MIDI Output Streams

The MIDI syntax implements both MIDI listening and midifiles.  MIDI output files have the following slots:

format

The MIDI format of the file.  Currently only level 0 is supported.

tracks

The number of tracks to write. Currently only 1 track is supported.

time-signature

If supplied, a time signature is written at the beginning of track 0.  The time signature is supplied as a list of the form:
(n d &optional (clocks-per-click 24) (32nd-per-quarter 8))
where n and d are the numerator and denominator of the time signature, and clocks-per-click and 32nd-per-quarter are optionally specified values. The default time signature is '(4 4).

key-signature

If supplied, a key signature is written at the start of track 0.  Currently not implemented.

divisions-per-quarter

The divisions per MIDI quarter note. The default value is 96.

tempo

The tempo written to the MIDI file.  Defaults to metronome 120.


2.2 MIDI Objects

Common Music provides two classes of MIDI parts. Both of these part classes contain the basic set of slots available to all classes of parts, such as time, rhythm, status, and count.  And, like all types of score parts, time and rhythm for MIDI parts is expressed in seconds.  The system automatically translates floating point time into the variable length delta times written to the MIDI file. 

2.2.1 The midi-message Class

Midi-message is capable of producing any type of MIDI message.  It declares two additional slots:

message

The current message.  message must be one of the defined message types.

data

The current message data of the part, if any.
	
Example:

(algorithm examp1 midi-message (message (make-note-on 0 0 64) 
                                length 10)
	(setf (note-on-key message)
	  (item (notes c4 e ef f g af bf c5 in heap))))
	

2.2.2 The midi-note Class

Midi-note implements a convenient interface for generating paired note-on and note-off messages.  Output is expressed in terms of note, amplitude and duration; the system automatically coerces these values to MIDI message data for the separate note on and note off pairs actually written to the score file.  midi-note declares six additional slots:

channel

The MIDI channel of the part.   The default channel  is 0.
	
note
The current frequency of the part. This value may be expressed as either note name, frequency or degree and the value will automatically be converted to a MIDI key number.
	
duration
The duration of the current note.  Like rhythm, duration is expressed in real seconds. The system automatically writes a note off event at time+duration time.
		
amplitude

The amplitude of the current note expressed as a real value between 0.0 and 1.0 and the system will automatically coerce this value to an integer MIDI note on velocity value. 	
	
release

The release speed of the paired note of expressed as a real value between 0.0 and 1.0 and the system will automatically coerce this value to an integer MIDI note off velocity value.  The default value for release is the maximum velocity.

Examples:

(in-package :stella)
(in-syntax :midi)
	
(algorithm examp2 midi-note (rhythm .1 duration .25)
  (setf note (item (notes c4 d ef f g af bf c5 in heap)
                   :kill 8))
  (setf amplitude 
    (item (amplitudes .1 .2 .3 .4 .5 .6 .7 .8))))

;;;
;;; this example writes 64 program changes with 2 test notes	;;; per change. the midi part's message program is initialized ;;; to -1 because we want to start with program 0 yet
;;; increment the value before each output event.
;;;

(in-package :stella)
(in-syntax :midi)

(merge foobar ()

  (algorithm foo midi-message (length 64 rhythm 1.0 
                               message (make-program-change
                                           0 -1))
  (incf (program-change-program message) 1))      
  
  ;; use midi-notes to write some test tones.
  (algorithm bar midi-note (start .25 rhythm .5 duration .24
                            amplitude .5)
    (setf note (item (notes c4 c5) :kill 64))))
    

These are the contents of the former NiCE NeXT User Group NeXTSTEP/OpenStep software archive, currently hosted by Netfuture.ch.