samer@0
|
1 /*
|
samer@0
|
2 * Prolog library for sending and receiving OSC messages
|
samer@0
|
3 * Samer Abdallah (2009)
|
samer@0
|
4 */
|
samer@0
|
5
|
samer@0
|
6 :- module(plosc, [
|
samer@0
|
7 osc_now/2 % -Seconds:int, -Fraction:int
|
samer@0
|
8 , osc_now/1 % -TS:osc_timestamp
|
samer@0
|
9 , osc_mk_address/3 % +Host:atom, +Port:nonneg, -Ref:osc_addr
|
samer@2
|
10 , osc_split_address/3 % +Ref:osc_addr, -Host:atom, -Port:nonneg
|
samer@0
|
11 , osc_is_address/1 % +Ref
|
samer@0
|
12 , osc_send/3 % +Ref, +Path:atom, +Args:list(osc_arg)
|
samer@0
|
13 , osc_send/4 % +Ref, +Path:atom, +Args:list(osc_arg), +Time:float
|
samer@0
|
14 , osc_send_from/5 % +Ref, +Ref, +Path:atom, +Args:list(osc_arg), +Time:float
|
samer@0
|
15 , osc_mk_server/2 % +Port:nonneg, -Ref
|
samer@0
|
16 , osc_start_server/1 % +Ref
|
samer@0
|
17 , osc_stop_server/1 % +Ref
|
samer@0
|
18 , osc_run_server/1 % +Ref
|
samer@0
|
19 , osc_del_handler/3 % +Ref, +Path:atom, +Types:list(osc_arg)
|
samer@0
|
20 , osc_add_handler/4 % +Ref, +Path:atom, +Types:list(osc_arg), +Goal:callable
|
samer@0
|
21 , osc_add_handler_x/4 % +Ref, +Path:atom, +Types:list(osc_arg), +Goal:callable
|
samer@0
|
22
|
samer@0
|
23 , osc_time_ts/2
|
samer@0
|
24 ]).
|
samer@0
|
25
|
samer@0
|
26 :- meta_predicate osc_add_handler(+,+,+,2).
|
samer@0
|
27 :- meta_predicate osc_add_handler_x(+,+,+,4).
|
samer@0
|
28
|
samer@0
|
29 /** <module> OSC server and client
|
samer@0
|
30
|
samer@0
|
31 ==
|
samer@0
|
32 time == float.
|
samer@0
|
33 osc_timestamp ---> osc_ts(int,int).
|
samer@0
|
34 ==
|
samer@0
|
35 */
|
samer@5
|
36 :- use_foreign_library(foreign(plosc)).
|
samer@0
|
37
|
samer@0
|
38 %% osc_mk_address(+Host:atom, +Port:nonneg, -Ref:osc_addr) is det.
|
samer@0
|
39 %
|
samer@0
|
40 % Construct a BLOB atom representing an OSC destination.
|
samer@0
|
41 %
|
samer@0
|
42 % @param Host is the hostname or IP address of the OSC receiver
|
samer@0
|
43 % @param Port is the port number of the OSC receiver
|
samer@0
|
44 % @param Ref is an atom representing the address
|
samer@0
|
45
|
samer@2
|
46 %% osc_split_address(+Ref:osc_addr,-Host:atom, -Port:nonneg) is det.
|
samer@2
|
47 %
|
samer@2
|
48 % Deconstruct a BLOB atom representing an OSC destination.
|
samer@2
|
49 %
|
samer@2
|
50 % @param Ref is an atom representing the OSC address
|
samer@2
|
51 % @param Host is the IP address of the OSC receiver
|
samer@2
|
52 % @param Port is the port number of the OSC receiver
|
samer@2
|
53
|
samer@0
|
54 %% osc_is_address(+Ref) is semidet.
|
samer@0
|
55 %
|
samer@0
|
56 % Succeeds if Ref is an OSC address created by osc_mk_address/3
|
samer@0
|
57
|
samer@0
|
58 %% osc_send(+Ref:osc_addr, +Path:atom, +Args:list(osc_arg)) is det.
|
samer@0
|
59 %% osc_send(+Ref:osc_addr, +Path:atom, +Args:list(osc_arg), +Time:time) is det.
|
samer@0
|
60 %
|
samer@0
|
61 % Sends an OSC message scheduled for immediate execution (osc_send/3) or
|
samer@0
|
62 % at a given time (osc_send/4).
|
samer@0
|
63 %
|
samer@0
|
64 % @param Ref is an OSC address BLOB as returned by osc_mk_address/3.
|
samer@0
|
65 % @param Path is an atom representing the OSC message path, eg '/foo/bar'
|
samer@0
|
66 % @param Args is a list of OSC message arguments, which can be any of:
|
samer@0
|
67 % * string(+X:text)
|
samer@0
|
68 % String as atom or Prolog string
|
samer@0
|
69 % * symbol(+X:atom)
|
samer@0
|
70 % * double(+X:float)
|
samer@0
|
71 % Double precision floating point
|
samer@0
|
72 % * float(+X:float)
|
samer@0
|
73 % Single precision floating point
|
samer@0
|
74 % * int(+X:integer)
|
samer@0
|
75 % * true
|
samer@0
|
76 % * false
|
samer@0
|
77 % * nil
|
samer@0
|
78 % * inf
|
samer@0
|
79 %
|
samer@0
|
80 osc_send(A,B,C) :- osc_send_now(A,B,C).
|
samer@0
|
81 osc_send(A,B,C,T) :- T1 is T, osc_send_at(A,B,C,T1).
|
samer@0
|
82
|
samer@0
|
83 %% osc_send_from(+Server:osc_server, +Address:osc_addr, +Path:atom, +Args:list(osc_arg), +T:time) is det.
|
samer@0
|
84 %
|
samer@0
|
85 % Like osc_send/4 but sets the return address to that of the given server.
|
samer@0
|
86 osc_send_from(Srv,Targ,Path,Args,Time) :- T1 is Time, osc_send_from_at(Srv,Targ,Path,Args,T1).
|
samer@0
|
87
|
samer@0
|
88 %% osc_now(-Secs:integer,-Frac:integer) is det.
|
samer@0
|
89 %
|
samer@0
|
90 % Gets the current OSC time in seconds and 1/2^64 ths of second.
|
samer@0
|
91
|
samer@0
|
92 %% osc_now(-TS:osc_timestamp) is det.
|
samer@0
|
93 %
|
samer@0
|
94 % Gets the current OSC time in seconds and 1/2^64 ths of second.
|
samer@0
|
95 osc_now(osc_ts(Secs,Fracs)) :- osc_now(Secs,Fracs).
|
samer@0
|
96
|
samer@6
|
97 %% osc_time_ts(+Time:float,-TS:osc_timestamp) is det.
|
samer@6
|
98 %% osc_time_ts(-Time:float,+TS:osc_timestamp) is det.
|
samer@6
|
99 %
|
samer@6
|
100 % Convert between floating point time as returned by get_time/1 and OSC
|
samer@6
|
101 % timestamp structure as returned by osc_now/1.
|
samer@0
|
102 osc_time_ts(Time,osc_ts(Secs,Fracs)) :-
|
samer@0
|
103 ( var(Time) -> time_from_ts(Time,Secs,Fracs)
|
samer@0
|
104 ; time_to_ts(Time,Secs,Fracs)).
|
samer@0
|
105
|
samer@0
|
106 %% osc_mk_server(+Port:nonneg, -Ref:osc_server) is det.
|
samer@0
|
107 %
|
samer@0
|
108 % Create an OSC server and return a BLOB atom representing it.
|
samer@0
|
109 %
|
samer@0
|
110 % @param Port is the port number of the OSC server
|
samer@0
|
111 % @param Ref is an atom representing the server
|
samer@0
|
112
|
samer@0
|
113 %% osc_start_server(+Ref:osc_server) is det.
|
samer@0
|
114 %
|
samer@0
|
115 % Run the OSC server referred to by Ref in a new thread. The new thread
|
samer@0
|
116 % dispatches OSC messages received to the appropriate handlers as registered
|
samer@0
|
117 % using osc_add_handler/4.
|
samer@0
|
118
|
samer@0
|
119 %% osc_stop_server(+Ref:osc_server) is det.
|
samer@0
|
120 %
|
samer@0
|
121 % If Ref refers to a running server thread, stop the thread.
|
samer@0
|
122
|
samer@0
|
123 %% osc_run_server(+Ref:osc_server) is det.
|
samer@0
|
124 %
|
samer@0
|
125 % The OSC server is run in the current thread, and does not return until
|
samer@0
|
126 % the message loop terminates. This can be triggered by sending the
|
samer@0
|
127 % message /plosc/stop to the server. Using this synchronous server
|
samer@0
|
128 % avoids creating a new thread and a new Prolog engine.
|
samer@0
|
129
|
samer@0
|
130 %% osc_add_handler( +Ref:osc_server, +Path:atom, +Types:list(osc_arg), +Goal:handler) is det.
|
samer@0
|
131 %
|
samer@0
|
132 % This registers a callable goal to handle the specified message Path for the
|
samer@0
|
133 % OSC server referred to by Ref.
|
samer@0
|
134 % The handler type is =|handler == pred(+atom,+list(osc_arg)).|=
|
samer@0
|
135 %
|
samer@0
|
136 % @param Types is a list of terms specifying the argument types that this handler
|
samer@0
|
137 % will match. The terms are just like those descibed in osc_send/3
|
samer@0
|
138 % and osc_send/4, except that the actual values are not used and
|
samer@0
|
139 % can be left as anonymous variables, eg [int(_),string(_)].
|
samer@0
|
140 % Alternatively, Types can be the atom 'any', which will match any
|
samer@0
|
141 % arguments.
|
samer@0
|
142 %
|
samer@0
|
143 % @param Goal is any term which can be called with call/3 with two further
|
samer@0
|
144 % arguments, which will be the message Path and the argument list, eg
|
samer@0
|
145 % call( Goal, '/foo', [int(45),string(bar)]).
|
samer@0
|
146
|
samer@0
|
147 osc_add_handler(Ref,Path,Types,Goal) :- osc_add_method(Ref,Path,Types,Goal).
|
samer@0
|
148
|
samer@0
|
149 %% osc_add_handler_x( +Ref:osc_server, +Path:atom, +Types:list(osc_arg), +Goal:handler_x) is det.
|
samer@0
|
150 %
|
samer@0
|
151 % This registers a callable goal to handle the specified message Path for the
|
samer@0
|
152 % OSC server referred to by Ref.
|
samer@0
|
153 % The extended handler type is =|handler_x == pred(+osc_addr,+time,+atom,+list(osc_arg)).|=
|
samer@0
|
154 %
|
samer@0
|
155 % @param Types is a list of terms specifying the argument types that this handler
|
samer@0
|
156 % will match. The terms are just like those descibed in osc_send/3
|
samer@0
|
157 % and osc_send/4, except that the actual values are not used and
|
samer@0
|
158 % can be left as anonymous variables, eg [int(_),string(_)].
|
samer@0
|
159 % Alternatively, Types can be the atom 'any', which will match any
|
samer@0
|
160 % arguments.
|
samer@0
|
161 %
|
samer@1
|
162 % @param Goal is any term which can be called with call/3 with four further
|
samer@1
|
163 % arguments, which will be the address of the sender, the timestamp of the
|
samer@1
|
164 % message, message path and the argument list, eg
|
samer@1
|
165 % call( Goal, SomeOSCAddress, Time, '/foo', [int(45),string(bar)]).
|
samer@0
|
166
|
samer@0
|
167 osc_add_handler_x(Ref,Path,Types,Goal) :- osc_add_method_x(Ref,Path,Types,Goal).
|
samer@0
|
168
|
samer@0
|
169 %% osc_del_handler( +Ref:osc_server, +Path:atom, +Types:list(osc_arg)) is det.
|
samer@0
|
170 %
|
samer@0
|
171 % Deregister a message handler previously registered with osc_add_handler/4.
|
samer@0
|
172
|
samer@0
|
173 osc_del_handler(Ref,Path,Types) :- osc_del_method(Ref,Path,Types).
|
samer@0
|
174
|
samer@0
|
175
|
samer@0
|
176 prolog:message(error(osc_error(Num,Msg,Path)), ['LIBLO error ~w: ~w [~w]'-[Num,Msg,Path] |Z],Z).
|