|
33 | 33 | */
|
34 | 34 |
|
35 | 35 | :- module(wasm,
|
36 |
| - [ wasm_abort/0, |
| 36 | + [ wasm_query/1, % +Query:string |
37 | 37 | wasm_call_string/3, % +String, +Input, -Output
|
38 | 38 | wasm_call_string_with_heartbeat/4,
|
39 | 39 | % +String, +Input, -Output, Rate
|
40 | 40 | is_object/1, % @Term
|
41 | 41 | is_object/2, % @Term,?Class
|
42 | 42 | (:=)/2, % -Result, +Call
|
43 |
| - await/2, % +Request, - Result |
| 43 | + await/2, % +Request, =Result |
44 | 44 | is_async/0,
|
45 |
| - sleep/1, |
| 45 | + sleep/1, % +Time |
| 46 | + bind/4, % +Elem, +EventType, -Event, :Goal |
| 47 | + bind_async/4, % +Elem, +EventType, -Event, :Goal |
| 48 | + unbind/2, % +Elem, +EventType |
| 49 | + wait/3, % +Elem, +EventType, =Event |
46 | 50 | js_script/2, % +String, +Options
|
47 | 51 | fetch/3, % +URL, +Type, -Value
|
48 | 52 |
|
49 | 53 | op(700, xfx, :=), % Result := Expression
|
50 | 54 | op(50, fx, #), % #Value
|
51 |
| - op(40, yf, []), % Expr[Expr] |
52 |
| - wasm_query/1 % +Query:string |
| 55 | + op(40, yf, []) % Expr[Expr] |
53 | 56 | ]).
|
54 | 57 | :- autoload(library(apply), [exclude/3, maplist/3]).
|
55 |
| -:- autoload(library(terms), [mapsubterms/3]). |
| 58 | +:- autoload(library(terms), [mapsubterms/3, foldsubterms/5]). |
56 | 59 | :- autoload(library(error),
|
57 | 60 | [instantiation_error/1, existence_error/2, permission_error/3]).
|
58 | 61 | :- use_module(library(uri), [uri_is_global/1, uri_normalized/3, uri_normalized/2]).
|
59 | 62 | :- use_module(library(debug), [debug/3]).
|
60 | 63 |
|
61 | 64 | :- set_prolog_flag(generate_debug_info, false).
|
62 | 65 |
|
| 66 | +:- meta_predicate |
| 67 | + bind(+,+,-,0), |
| 68 | + bind_async(+,+,-,0). |
| 69 | + |
63 | 70 | /** <module> WASM version support
|
64 | 71 |
|
65 | 72 | This library is only available in the WASM version. It provides helper
|
|
92 | 99 | '$execute_query'(M:Query, Bindings, _Truth),
|
93 | 100 | Rate).
|
94 | 101 |
|
95 |
| -% wasm_abort |
96 |
| -% |
97 |
| -% Execution aborted by user. |
98 |
| - |
99 |
| -wasm_abort :- |
100 |
| - print_message(error, unwind(abort)), |
101 |
| - abort. |
102 |
| - |
103 | 102 | with_heartbeat(Goal, Rate) :-
|
104 | 103 | current_prolog_flag(heartbeat, Old),
|
105 | 104 | setup_call_cleanup(
|
|
165 | 164 | with_heartbeat(wasm_call_string(String, Input, Dict), Rate).
|
166 | 165 |
|
167 | 166 |
|
168 |
| -%! await(+Request, -Result) is det. |
| 167 | +%! await(+Request, =Result) is det. |
169 | 168 | %
|
170 | 169 | % Call asynchronous behavior. Request is normally a JavaScript Promise
|
171 | 170 | % instance. If we want Prolog to wait for some task to complete, we
|
|
175 | 174 | % success, Result is unified to the value with which the `Promise` was
|
176 | 175 | % resolved. If the `Promise` is rejected, this predicate raises an
|
177 | 176 | % exception using the value passed to `reject()`.
|
| 177 | +% |
| 178 | +% @see sleep/1, fetch/3 and wait/3 in this library use await/2. |
| 179 | +% @error permission_error(run, goal, Goal) if the current query is |
| 180 | +% not aynchronous. |
178 | 181 |
|
179 | 182 | await(Request, Result) :-
|
| 183 | + must_be_async(await(Request, Result)), |
180 | 184 | '$await'(Request, Result0),
|
181 | 185 | ( is_dict(Result0),
|
182 | 186 | get_dict('$error', Result0, Error)
|
183 | 187 | -> ( Error == "abort"
|
184 |
| - -> wasm_abort |
| 188 | + -> abort |
185 | 189 | ; throw(Error)
|
186 | 190 | )
|
187 | 191 | ; Result = Result0
|
|
205 | 209 | must_be_async(Message) :-
|
206 | 210 | permission_error(run, goal, Message).
|
207 | 211 |
|
208 |
| -%! sleep(+Seconds) |
| 212 | + /******************************* |
| 213 | + * ALLOW . IN :=/2 * |
| 214 | + *******************************/ |
| 215 | + |
| 216 | +:- multifile |
| 217 | + system:goal_expansion/2. |
| 218 | + |
| 219 | +system:goal_expansion(In, Out) :- |
| 220 | + In = (_Left := _Right), |
| 221 | + mapsubterms(dot_list, In, Out), |
| 222 | + Out \== In. |
| 223 | + |
| 224 | +dot_list(Dot, List) :- |
| 225 | + compound(Dot), |
| 226 | + compound_name_arguments(Dot, '.', [A1, A2]), |
| 227 | + List = A1[A2]. |
| 228 | + |
| 229 | +%! sleep(+Seconds) is det. |
209 | 230 | %
|
210 | 231 | % Sleep by yielding when possible. Note that this defines sleep/1 in
|
211 | 232 | % `user`, overruling system:sleep/1.
|
212 | 233 |
|
213 | 234 | sleep(Seconds) :-
|
214 | 235 | ( is_async
|
215 |
| - -> Promise := prolog[promise_sleep(Seconds)], |
| 236 | + -> Promise := prolog.promise_sleep(Seconds), |
216 | 237 | await(Promise, _)
|
217 | 238 | ; system:sleep(Seconds)
|
218 | 239 | ).
|
219 | 240 |
|
| 241 | + /******************************* |
| 242 | + * EVENT HANDLING * |
| 243 | + *******************************/ |
| 244 | + |
| 245 | +%! bind(+Elem, +EventType, -Event, :Goal) is det. |
| 246 | +%! bind_async(+Elem, +EventType, -Event, :Goal) is det. |
| 247 | +% |
| 248 | +% Bind EventType on Elem to call Goal. If Event appears in Goal is is |
| 249 | +% bound to the current event. |
| 250 | +% |
| 251 | +% The bind_async/4 variation runs the event handler on a new Prolog |
| 252 | +% _engine_ using Prolog.forEach(). This implies that the handler runs |
| 253 | +% asynchronously and all its solutions are enumerated. |
| 254 | +% |
| 255 | +% @compat bind_async/5 is a SWI-Prolog extension to the Tau library |
| 256 | + |
| 257 | +bind(Elem, On, Ev, Goal) :- |
| 258 | + bind(Elem, On, Ev, Goal, #{}). |
| 259 | + |
| 260 | +bind_async(Elem, On, Ev, Goal) :- |
| 261 | + bind(Elem, On, Ev, Goal, #{async:true}). |
| 262 | + |
| 263 | +bind(Elem, On, Ev, Goal, Options) :- |
| 264 | + foldsubterms(map_object, Goal, Goal1, t(1,[],[]), t(_,VarNames,Map)), |
| 265 | + Map \== [], |
| 266 | + dict_pairs(Input, #, Map), |
| 267 | + term_string(Goal1, String, [variable_names(['Event__'=Ev|VarNames])]), |
| 268 | + _ := prolog.bind(Elem, #On, String, Input, Options). |
| 269 | +bind(Elem, On, Ev, Goal, Options) :- |
| 270 | + term_string(Goal, String, [variable_names(['Event__'=Ev])]), |
| 271 | + _ := prolog.bind(Elem, #On, String, Options). |
| 272 | + |
| 273 | +map_object(Obj, Var, t(N0,VN,Map), t(N,[VarName=Var|VN], [VarName-Obj|Map])) :- |
| 274 | + is_object(Obj), |
| 275 | + N is N0+1, |
| 276 | + format(atom(VarName), 'JsObject__~d__', [N0]). |
| 277 | + |
| 278 | +%! unbind(+Elem, +EventType) is det. |
| 279 | +% |
| 280 | +% Remove the event listener for EventType. |
| 281 | + |
| 282 | +unbind(Elem, EventType) :- |
| 283 | + _ := Elem.removeEventListener(#EventType). |
| 284 | + |
| 285 | +%! unbind(+Elem, +EventType, :Goal) is det. |
| 286 | +% |
| 287 | +% Remove the event listener for EventType that executes Goal. |
| 288 | +% @tbd Implement. How do we do this? We somehow need to be |
| 289 | +% able to find the function from Goal. |
| 290 | + |
| 291 | +%! wait(+Elem, +EventType, =Event) is det. |
| 292 | +% |
| 293 | +% Make the calling task wait for EventType on Elem. If the event is |
| 294 | +% triggered, Event is unified with the event object. |
| 295 | + |
| 296 | +wait(Elem, EventType, Event) :- |
| 297 | + must_be_async(wait/3), |
| 298 | + Promise := prolog.promise_event(Elem, #EventType), |
| 299 | + await(Promise, Event). |
| 300 | + |
| 301 | + /******************************* |
| 302 | + * JAVASCRIPT CALLING * |
| 303 | + *******************************/ |
| 304 | + |
220 | 305 | %! is_object(@Term) is semidet.
|
221 | 306 | %! is_object(@Term, ?Class) is semidet.
|
222 | 307 | %
|
|
309 | 394 | unwrap_hash(V0, V) =>
|
310 | 395 | V = V0.
|
311 | 396 |
|
312 |
| -:- multifile |
313 |
| - system:goal_expansion/2. |
314 |
| - |
315 |
| -system:goal_expansion(In, Out) :- |
316 |
| - In = (_Left := _Right), |
317 |
| - mapsubterms(dot_list, In, Out), |
318 |
| - Out \== In. |
319 |
| - |
320 |
| -dot_list(Dot, List) :- |
321 |
| - compound(Dot), |
322 |
| - compound_name_arguments(Dot, '.', [A1, A2]), |
323 |
| - List = A1[A2]. |
324 |
| - |
325 | 397 | %! js_script(+String, +Options) is det.
|
326 | 398 | %
|
327 | 399 | % Evaluate String as JavaScript, for example for defining a
|
|
0 commit comments