1/*
    2 * Prolog part of random generator library
    3 * Samer Abdallah (2009)
    4*/
    5	  
    6:- module(plmidi, [
    7		midi_mk_outlet/2		% +N:natural, -Ref
    8	,	midi_mk_inlet/3		% +N:natural, -Ref, +Handler
    9	,	midi_is_conn/1			% +Ref
   10	,	midi/3     				% +Ref, +Time:float, +Event
   11	,	midi/2     				% +Time:float, +Event
   12	,	midi_endpoints/1	
   13	,	midi_endpoint/1	
   14	,	midi_calibrate/0
   15
   16	,	midi_connect/1
   17   ,  midi_connect_named/1
   18	,	midinote/4
   19	,	midinote_at/5
   20	,	midi_outlet/2
   21	]).   22	
   23:- meta_predicate midi_mk_inlet(+,-,2).   24:- dynamic midi_outlet/2.

MIDI event output

This module provides the ability to send MIDI events. It uses the Mac OS X CoreMIDI framework. Events can be sent for immediate dispatch or scheduled for future dispatch at a given time. Times are specified in seconds since 1st Jan 1970, ie as returned by get_time/1.

author
- Samer Abdallah
version
- 0.3 */
   39:-	use_foreign_library(foreign(plmidi)).   40:- use_module(library(mididcg)).
 midi_endpoints(-L:list(endpoint)) is det
Unify L with a list of all the available MIDI outlets and inlets available on the system. Each endpoint is one of

The Id can be used with midi_mk_outlet/2 or midi_mk_inlet/3.

 midi_endpoint(-E:endpoint) is nondet
True if E is an endpoint on the system. Unifies E with all available endpoints on backtracking. Each endpoint is one of

The Id can be used with midi_mk_outlet/2 or midi_mk_inlet/3.

   57midi_endpoint(E) :- midi_endpoints(L), member(E,L).
 midi_mk_outlet(+N:natural, -Ref) is semidet
Opens a connection to the Nth CoreMIDI destination. Fails if there are fewer than N destinations available. Available destinations can be obtained using midi_endpoints/1 or midi_endpoint/1. Resources associated with the connection will be released when the Ref atom is reclaimed by the garbage collector.
Arguments:
N- is the index of the destination to open, 1 is the first.
Ref- is a BLOB atom representing the connection.
 midi_mk_inlet(+N:natural, -Ref, +Handler:pred(float,midimsg)) is semidet
Opens a connection to the Nth CoreMIDI source. Fails if there are fewer than N sources available. Available sources can be obtained using midi_endpoints/1 or midi_endpoint/1. Resources associated with the connection will be released when the Ref atom is reclaimed by the garbage collector.
Arguments:
N- is the index of the destination to open, 1 is the first.
Ref- is a BLOB atom representing the connection.
Handler- is a callable goal to handle received messages, of type pred( +Time:float, +Message:term). Message can be midi(M), midi(M,A), or midi(M,A,B), depending on how much data is associated with the message.
 midi_is_conn(+Ref) is semidet
Determines whether or not Ref is a MIDI connection BLOB as returned by midi_mk_outlet/2 or midi_mk_inlet/3.
 midi(+Ref, +Time:float, +Event) is semidet
Schedule a MIDI event, possibly consisting of multiple messages, determined by the Event term, which must be a callable predicate in library(mididcg).
Arguments:
Ref- is an atom as returned by midi_mk_outlet/2.
Time- is a Unix time as returnd by get_time/1.
Event- is a term describing an event, and is one of:
  104midi(T,E) :- midi_outlet(_,O), midi(O,T,E).
  105midi(O,T,Ev) :- 
  106   once(call(mididcg:Ev, T-Msgs, _-[])),
  107   maplist(midi_send(O),Msgs).
  108
  109% disable immediate messages!
  110% midi_send(O,imsg(M,A1))      :- M1 is M, B1 is A1, midi_send_now(O,M1,B1,255).
  111% midi_send(O,imsg(M,A1,A2))   :- M1 is M, B1 is A1, B2 is A2, midi_send_now(O,M1,B1,B2).
  112midi_send(O,msg(T,M,A1))    :- T1 is float(T), M1 is M, B1 is A1, midi_send_at(O,M1,B1,255,T1).
  113midi_send(O,msg(T,M,A1,A2)) :- T1 is float(T), M1 is M, B1 is A1, B2 is A2, midi_send_at(O,M1,B1,B2,T1).
 midi_calibrate is det
Establish a calibrated relationship between Unix time (seconds since 1st Jan 1970) and the timebase used by the CoreMIDI framework, which is mach system time and is counted in bus cycles since system boot. The relationship is not trivial since mach system time does not advance while the system is asleep (eg a laptop is closed). When the module is loaded, the calibration is done, and an IOKit wake/sleep event handler is installed. This should recalibrate the timer whenever the system is awoken from sleep, but midi_calibrate/0 can be called at any time just in case.
 midi_connect(+N:natural) is semidet
Connect to MIDI device identified by index N (starting from 1). This device is used for all subsequence MIDI output. Previous connections are dropped.
  133midi_connect(Id) :-
  134	midi_mk_outlet(Id,Outlet),
  135	retractall(midi_outlet(_,_)),
  136	assert(midi_outlet(Id,Outlet)).
 midi_connect_named(+String:atom) is det
Connect to a MIDI output which contains String as part of its name. Can throw named_midi_outlet_not_found(_) or named_midi_outlet_not_unique(_,_).
  141midi_connect_named(String) :-
  142   findall(ID-Name, (midi_endpoint(outlet(ID,Name,_,_)), sub_atom(Name,_,_,_,String)), Matches),
  143   ( Matches = [] -> throw(named_midi_outlet_not_found(String))
  144   ; Matches = [ID-Name] -> format('% Connecting to MIDI outlet ~w.\n',[Name]), midi_connect(ID)
  145   ; throw(named_midi_outlet_not_unique(String,Matches))
  146   ).
 midinote(+Ch:integer, +NN:integer, +Vel:integer, +Dur:nonneg) is det
Play a MIDI note now.
  151midinote(Ch,NN,Vel,Dur) :-
  152	get_time(T), midinote_at(T,Ch,NN,Vel,Dur).
 midinote_at(+T:time, +Ch:integer, +NN:integer, +Vel:integer, +Dur:nonneg) is det
Schedule MIDI note at given time.
  157midinote_at(T,Ch,NN,Vel,Dur) :-
  158	midi_outlet(_,M), 
  159	midi(M,T,note(Ch,NN,Vel,Dur))