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