5
6:- module(plosc, [
7 osc_now/2 8 , osc_now/1 9 , osc_mk_address/3 10 , osc_split_address/3 11 , osc_is_address/1 12 , osc_send/3 13 , osc_send/4 14 , osc_send_from/5 15 , osc_mk_server/2 16 , osc_start_server/1 17 , osc_stop_server/1 18 , osc_run_server/1 19 , osc_del_handler/3 20 , osc_add_handler/4 21 , osc_add_handler_x/4 22
23 , osc_time_ts/2
24 ]). 25
26:- meta_predicate osc_add_handler(+,+,+,2). 27:- meta_predicate osc_add_handler_x(+,+,+,4).
36:- use_foreign_library(foreign(plosc)).
80osc_send(A,B,C) :- osc_send_now(A,B,C).
81osc_send(A,B,C,T) :- T1 is T, osc_send_at(A,B,C,T1).
86osc_send_from(Srv,Targ,Path,Args,Time) :- T1 is Time, osc_send_from_at(Srv,Targ,Path,Args,T1).
95osc_now(osc_ts(Secs,Fracs)) :- osc_now(Secs,Fracs).
102osc_time_ts(Time,osc_ts(Secs,Fracs)) :-
103 ( var(Time) -> time_from_ts(Time,Secs,Fracs)
104 ; time_to_ts(Time,Secs,Fracs)).
147osc_add_handler(Ref,Path,Types,Goal) :- osc_add_method(Ref,Path,Types,Goal).
167osc_add_handler_x(Ref,Path,Types,Goal) :- osc_add_method_x(Ref,Path,Types,Goal).
173osc_del_handler(Ref,Path,Types) :- osc_del_method(Ref,Path,Types).
174
175
176prolog:message(error(osc_error(Num,Msg,Path)), ['LIBLO error ~w: ~w [~w]'-[Num,Msg,Path] |Z],Z)
OSC server and client
*/