Skip to content

Commit b96f245

Browse files
committed
WASM: Enhanced error message when evaluating :=/2
1 parent c398254 commit b96f245

File tree

2 files changed

+59
-25
lines changed

2 files changed

+59
-25
lines changed

library/wasm.pl

+26
Original file line numberDiff line numberDiff line change
@@ -60,6 +60,7 @@
6060
[instantiation_error/1, existence_error/2, permission_error/3]).
6161
:- use_module(library(uri), [uri_is_global/1, uri_normalized/3, uri_normalized/2]).
6262
:- use_module(library(debug), [debug/3]).
63+
:- autoload(library(dcg/high_order), [sequence/5]).
6364

6465
:- set_prolog_flag(generate_debug_info, false).
6566

@@ -638,3 +639,28 @@
638639
[ 'await/2 is only allowed in Prolog.forEach() queries' ].
639640
prolog:error_message(js_error(Msg)) -->
640641
[ 'JavaScript: ~w'-[Msg] ].
642+
prolog:error_message(js_eval_error(Msg, Chain)) -->
643+
[ 'JavaScript: Could not evaluate ' ],
644+
sequence(msg_call1, [.], Chain),
645+
msg_noeval(Msg).
646+
647+
msg_call1(Dict) -->
648+
{ is_dict(Dict),
649+
_{f:Name, args:Args} :< Dict,
650+
!,
651+
compound_name_arguments(Term, Name, Args)
652+
},
653+
[ '~p'-[Term] ].
654+
msg_call1(Dict) -->
655+
{ is_dict(Dict),
656+
_{v:Value} :< Dict,
657+
!
658+
},
659+
[ '~p'-[Value] ].
660+
msg_call1(Term) -->
661+
[ '~p'-[Term] ].
662+
663+
msg_noeval('TypeError: obj is undefined') -->
664+
[ ' (undefined)' ].
665+
msg_noeval(Msg) -->
666+
[ ': ~w'-[Msg] ].

src/wasm/prolog.js

+33-25
Original file line numberDiff line numberDiff line change
@@ -2387,19 +2387,22 @@ function prolog_js_call(request, result)
23872387
}
23882388
}
23892389

2390+
if ( obj == null || obj == undefined )
2391+
throw new TypeError(`${obj} has no attribute ${fname}`);
2392+
23902393
const func = obj[fname];
23912394
if ( typeof(func) === "function" )
23922395
return func.apply(obj, args);
23932396
else
2394-
console.error(`Function ${fname} is not defined on ${obj}`);
2397+
throw new TypeError(`${obj}.${fname} is not a function`);
23952398
}
23962399

2397-
for(let i=0; i<ar.length; i++)
2398-
{ const next = ar[i];
2400+
for(let i=0; i<ar.length; i++) {
2401+
const next = ar[i];
23992402

2400-
if ( typeof(next) === "string" )
2401-
{ if ( i == 0 )
2402-
{ switch(next)
2403+
if ( typeof(next) === "string" ) {
2404+
if ( i == 0 ) {
2405+
switch(next)
24032406
{ case "prolog":
24042407
obj = prolog;
24052408
break;
@@ -2409,13 +2412,15 @@ function prolog_js_call(request, result)
24092412
default:
24102413
obj = eval(next);
24112414
}
2412-
} else
2413-
{ obj = obj[next];
2415+
} else if ( obj == null || obj == undefined ) {
2416+
throw new TypeError(`${obj} has no attribute ${next}`);
2417+
} else {
2418+
obj = obj[next];
24142419
}
2415-
} else if ( next.v !== undefined )
2416-
{ obj = next.v;
2417-
} else
2418-
{ const args = next.args.map((v) => eval_chain(v));
2420+
} else if ( next.v !== undefined ) {
2421+
obj = next.v;
2422+
} else {
2423+
const args = next.args.map((v) => eval_chain(v));
24192424

24202425
obj = eval_one(obj, next.f, args);
24212426
}
@@ -2424,28 +2429,31 @@ function prolog_js_call(request, result)
24242429
return obj;
24252430
}
24262431

2427-
try
2428-
{ return prolog.with_frame(() =>
2429-
{ const ar = prolog.toJSON(request, { string: "string" });
2432+
try {
2433+
return prolog.with_frame(() => {
2434+
const ar = prolog.toJSON(request, { string: "string" });
24302435
let obj;
24312436

2432-
if ( ar.setter )
2433-
{ const target = eval_chain(ar.target);
2437+
if ( ar.setter ) {
2438+
const target = eval_chain(ar.target);
24342439
const value = eval_chain(ar.value);
24352440
target[ar.setter] = value;
24362441
obj = true;
2437-
} else
2438-
{ obj = eval_chain(ar);
2442+
} else {
2443+
obj = eval_chain(ar);
24392444
}
24402445

24412446
return prolog.unify(result, prolog.toProlog(obj));
24422447
}, false);
2443-
} catch (e)
2444-
{ return prolog.bindings.PL_raise_exception(
2445-
prolog.toProlog(new prolog.Compound("error",
2446-
[ new prolog.Compound("js_error", [e.toString()]),
2447-
new prolog.Var()
2448-
])));
2448+
} catch (e) {
2449+
return prolog.bindings.PL_raise_exception(
2450+
prolog.toProlog(new prolog.Compound(
2451+
"error",
2452+
new prolog.Compound("js_eval_error",
2453+
e.toString(),
2454+
new prolog.Term(request)),
2455+
new prolog.Var()
2456+
)));
24492457
}
24502458
}
24512459

0 commit comments

Comments
 (0)