Skip to content

Commit 768babe

Browse files
committed
WASM: Move bind/4 from library(dom) to library(wasm)
Also added wait/3.
1 parent 609eb29 commit 768babe

File tree

3 files changed

+127
-110
lines changed

3 files changed

+127
-110
lines changed

library/dom.pl

+14-73
Original file line numberDiff line numberDiff line change
@@ -62,7 +62,6 @@
6262
sibling/2, % ?Elem1, ?Elem2
6363
style/3, % +Elem, +Attr, ?Style
6464
bind/4, % +Elem, +EventType, -Event, :Goal
65-
bind_async/4, % +Elem, +EventType, -Event, :Goal
6665
event_property/3, % +Event, +Prop, -Value
6766
prevent_default/1, % +Event
6867
unbind/2, % +Elem, +EventType
@@ -71,33 +70,18 @@
7170
toggle/1 % +Elem
7271
]).
7372
:- use_module(wasm).
74-
:- use_module(autoload(apply), [maplist/3, maplist/2]).
75-
:- use_module(library(gensym), [gensym/2]).
73+
:- use_module(autoload(apply), [maplist/3]).
7674
:- use_module(library(lists), [member/2]).
77-
:- use_module(library(terms), [foldsubterms/5]).
7875

7976
/** <module> Tau-Prolog compatible DOM manipulation
8077
8178
This module is part of the WASM distribution of SWI-Prolog. It
82-
implements the Tau-Prolog DOM library.
83-
84-
__Status__
85-
86-
Implements all "DOM Manipulation" predicates of the Tau library(dom).
87-
The implementation is barely tested though and details may be different.
88-
89-
All the "Events" predicates except for unbind/3 are implemented.
90-
91-
All the "Effects" predicates are implemented.
79+
implements the Tau-Prolog DOM library. The event handling predicate
80+
bind/4 is implemented in the low-level library(wasm).
9281
9382
@see https://tau-prolog.org/documentation#prolog
9483
*/
9584

96-
:- meta_predicate
97-
bind(+,+,-,0),
98-
bind_async(+,+,-,0).
99-
100-
10185
/*******************************
10286
* DOM MANIPULATION *
10387
*******************************/
@@ -152,15 +136,15 @@
152136
create(TagName, Elem) :-
153137
Elem := document.createElement(#TagName).
154138

155-
%! document(-Document) is det.
139+
%! document(=Document) is det.
156140
%
157141
% True when Document is the HTML element representing the document.
158142

159143
document(Document) :-
160144
Document := document.
161145

162-
%! get_attr(+Elem, +Name, -Value) is semidet.
163-
%! get_attribute(+Elem, +Name, -Value) is semidet.
146+
%! get_attr(+Elem, +Name, =Value) is semidet.
147+
%! get_attribute(+Elem, +Name, =Value) is semidet.
164148
%
165149
% Get an attribute (property) from a JavaScript object. Fails if the
166150
% attribute is `undefined`.
@@ -207,7 +191,7 @@
207191
Set := document.getElementsByName(#Name).toList(),
208192
member(Elem, Set).
209193

210-
%! get_by_tag(+TagName, -Elem) is nondet.
194+
%! get_by_tag(+TagName, =Elem) is nondet.
211195
%
212196
% True when Elem is an HTML element with tag Tag.
213197

@@ -222,7 +206,7 @@
222206
get_html(Elem, HTML) :-
223207
HTML := Elem.innerHTML.
224208

225-
%! get_style(+Elem, +Attr, =Value) is det.
209+
%! get_style(+Elem, +Attr, =Value) is semidet.
226210
%
227211
% True when Value is the computed value for the given style attribute.
228212
% If the computed style is undefined, Value is unified to the element
@@ -233,7 +217,8 @@
233217
Value0 \== undefined,
234218
Value0 \== ""
235219
-> Value = Value0
236-
; Value := Elem.style.Attr
220+
; Value := Elem.style.Attr,
221+
Value \== undefined
237222
).
238223

239224
%! has_class(+Elem, +Class) is semidet.
@@ -243,7 +228,7 @@
243228
has_class(Elem, Class) :-
244229
true := Elem.classList.contains(#Class).
245230

246-
%! head(-Elem) is det.
231+
%! head(=Elem) is det.
247232
%
248233
% True when Elem is the HTML Element that holds the head.
249234

@@ -356,57 +341,13 @@
356341
* EVENTS *
357342
*******************************/
358343

359-
%! bind(+Elem, +EventType, -Event, :Goal) is det.
360-
%! bind_async(+Elem, +EventType, -Event, :Goal) is det.
361-
%
362-
% Bind EventType on Elem to call Goal. If Event appears in Goal is is
363-
% bound to the current event.
364-
%
365-
% The bind_async/4 variation runs the event handler on a new Prolog
366-
% _engine_ using Prolog.forEach(). This implies that the handler runs
367-
% asynchronously and all its solutions are enumerated.
368-
%
369-
% @compat bind_async/5 is a SWI-Prolog extension to the Tau library
370-
371-
bind(Elem, On, Ev, Goal) :-
372-
bind(Elem, On, Ev, Goal, #{}).
373-
374-
bind_async(Elem, On, Ev, Goal) :-
375-
bind(Elem, On, Ev, Goal, #{async:true}).
376-
377-
bind(Elem, On, Ev, Goal, Options) :-
378-
foldsubterms(map_object, Goal, Goal1, t(1,[],[]), t(_,VarNames,Map)),
379-
Map \== [],
380-
dict_pairs(Input, #, Map),
381-
term_string(Goal1, String, [variable_names(['Event__'=Ev|VarNames])]),
382-
_ := prolog.bind(Elem, #On, String, Input, Options).
383-
bind(Elem, On, Ev, Goal, Options) :-
384-
term_string(Goal, String, [variable_names(['Event__'=Ev])]),
385-
_ := prolog.bind(Elem, #On, String, Options).
386-
387-
map_object(Obj, Var, t(N0,VN,Map), t(N,[VarName=Var|VN], [VarName-Obj|Map])) :-
388-
is_object(Obj),
389-
N is N0+1,
390-
format(atom(VarName), 'JsObject__~d__', [N0]).
391-
392-
%! unbind(+Elem, +EventType) is det.
393-
%
394-
% Remove the event listener for EventType.
395-
396-
unbind(Elem, EventType) :-
397-
Elem.removeEventListener(#EventType).
398-
399-
%! unbind(+Elem, +EventType, :Goal) is det.
400-
%
401-
% Remove the event listener for EventType that executes Goal.
402-
% @tbd Implement. How do we do this?
403-
404-
%! event_property(+Event, +Prop, -Value)
344+
%! event_property(+Event, +Prop, =Value) is semidet.
405345
%
406346
% Extract a property from the event.
407347

408348
event_property(Event, Prop, Value) :-
409-
Value := Event.Prop.
349+
Value := Event.Prop,
350+
Value \== undefined.
410351

411352
%! prevent_default(+Event) is det.
412353
%

library/wasm.pl

+103-31
Original file line numberDiff line numberDiff line change
@@ -33,33 +33,40 @@
3333
*/
3434

3535
:- module(wasm,
36-
[ wasm_abort/0,
36+
[ wasm_query/1, % +Query:string
3737
wasm_call_string/3, % +String, +Input, -Output
3838
wasm_call_string_with_heartbeat/4,
3939
% +String, +Input, -Output, Rate
4040
is_object/1, % @Term
4141
is_object/2, % @Term,?Class
4242
(:=)/2, % -Result, +Call
43-
await/2, % +Request, - Result
43+
await/2, % +Request, =Result
4444
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
4650
js_script/2, % +String, +Options
4751
fetch/3, % +URL, +Type, -Value
4852

4953
op(700, xfx, :=), % Result := Expression
5054
op(50, fx, #), % #Value
51-
op(40, yf, []), % Expr[Expr]
52-
wasm_query/1 % +Query:string
55+
op(40, yf, []) % Expr[Expr]
5356
]).
5457
:- autoload(library(apply), [exclude/3, maplist/3]).
55-
:- autoload(library(terms), [mapsubterms/3]).
58+
:- autoload(library(terms), [mapsubterms/3, foldsubterms/5]).
5659
:- autoload(library(error),
5760
[instantiation_error/1, existence_error/2, permission_error/3]).
5861
:- use_module(library(uri), [uri_is_global/1, uri_normalized/3, uri_normalized/2]).
5962
:- use_module(library(debug), [debug/3]).
6063

6164
:- set_prolog_flag(generate_debug_info, false).
6265

66+
:- meta_predicate
67+
bind(+,+,-,0),
68+
bind_async(+,+,-,0).
69+
6370
/** <module> WASM version support
6471
6572
This library is only available in the WASM version. It provides helper
@@ -92,14 +99,6 @@
9299
'$execute_query'(M:Query, Bindings, _Truth),
93100
Rate).
94101

95-
% wasm_abort
96-
%
97-
% Execution aborted by user.
98-
99-
wasm_abort :-
100-
print_message(error, unwind(abort)),
101-
abort.
102-
103102
with_heartbeat(Goal, Rate) :-
104103
current_prolog_flag(heartbeat, Old),
105104
setup_call_cleanup(
@@ -165,7 +164,7 @@
165164
with_heartbeat(wasm_call_string(String, Input, Dict), Rate).
166165

167166

168-
%! await(+Request, -Result) is det.
167+
%! await(+Request, =Result) is det.
169168
%
170169
% Call asynchronous behavior. Request is normally a JavaScript Promise
171170
% instance. If we want Prolog to wait for some task to complete, we
@@ -175,13 +174,18 @@
175174
% success, Result is unified to the value with which the `Promise` was
176175
% resolved. If the `Promise` is rejected, this predicate raises an
177176
% 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.
178181

179182
await(Request, Result) :-
183+
must_be_async(await(Request, Result)),
180184
'$await'(Request, Result0),
181185
( is_dict(Result0),
182186
get_dict('$error', Result0, Error)
183187
-> ( Error == "abort"
184-
-> wasm_abort
188+
-> abort
185189
; throw(Error)
186190
)
187191
; Result = Result0
@@ -205,18 +209,99 @@
205209
must_be_async(Message) :-
206210
permission_error(run, goal, Message).
207211

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.
209230
%
210231
% Sleep by yielding when possible. Note that this defines sleep/1 in
211232
% `user`, overruling system:sleep/1.
212233

213234
sleep(Seconds) :-
214235
( is_async
215-
-> Promise := prolog[promise_sleep(Seconds)],
236+
-> Promise := prolog.promise_sleep(Seconds),
216237
await(Promise, _)
217238
; system:sleep(Seconds)
218239
).
219240

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+
220305
%! is_object(@Term) is semidet.
221306
%! is_object(@Term, ?Class) is semidet.
222307
%
@@ -309,19 +394,6 @@
309394
unwrap_hash(V0, V) =>
310395
V = V0.
311396

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-
325397
%! js_script(+String, +Options) is det.
326398
%
327399
% Evaluate String as JavaScript, for example for defining a

0 commit comments

Comments
 (0)