Skip to content

Commit

Permalink
move call_residue_vars/2 from atts.pl to iso_ext.pl
Browse files Browse the repository at this point in the history
  • Loading branch information
mthom committed Jan 25, 2024
1 parent 9913113 commit bc616ca
Show file tree
Hide file tree
Showing 6 changed files with 15 additions and 17 deletions.
9 changes: 0 additions & 9 deletions src/lib/atts.pl
Original file line number Diff line number Diff line change
@@ -1,5 +1,4 @@
:- module(atts, [op(1199, fx, attribute),
call_residue_vars/2,
term_attributed_variables/2]).

:- use_module(library(dcgs)).
Expand Down Expand Up @@ -111,13 +110,5 @@
nonvar(Term),
Term = get_atts(Var, M, Attr).

:- meta_predicate call_residue_vars(0, ?).

call_residue_vars(Goal, Vars) :-
can_be(list, Vars),
'$get_attr_var_queue_delim'(B),
call(Goal),
'$get_attr_var_queue_beyond'(B, Vars).

term_attributed_variables(Term, Vars) :-
'$term_attributed_variables'(Term, Vars).
9 changes: 9 additions & 0 deletions src/lib/iso_ext.pl
Original file line number Diff line number Diff line change
Expand Up @@ -9,6 +9,7 @@
bb_put/2,
call_cleanup/2,
call_with_inference_limit/3,
call_residue_vars/2,
forall/2,
partial_string/1,
partial_string/3,
Expand Down Expand Up @@ -397,3 +398,11 @@
Gs = []
; true
).

:- meta_predicate call_residue_vars(0, ?).

call_residue_vars(Goal, Vars) :-
can_be(list, Vars),
'$get_attr_var_queue_delim'(B),
call(Goal),
'$get_attr_var_queue_beyond'(B, Vars).
4 changes: 2 additions & 2 deletions src/tests/dif.pl
Original file line number Diff line number Diff line change
@@ -1,10 +1,10 @@
/**/

:- use_module(library(format)).
:- use_module(library(dcgs)).
:- use_module(library(format)).
:- use_module(library(lists)).
:- use_module(library(debug)).
:- use_module(library(atts)).
:- use_module(library(iso_ext)).
:- use_module(library(dif)).

% Tests from https://www.complang.tuwien.ac.at/ulrich/iso-prolog/dif
Expand Down
2 changes: 1 addition & 1 deletion src/tests/when.pl
Original file line number Diff line number Diff line change
@@ -1,10 +1,10 @@
/**/

:- use_module(library(iso_ext)).
:- use_module(library(format)).
:- use_module(library(dcgs)).
:- use_module(library(lists)).
:- use_module(library(debug)).
:- use_module(library(atts)).

:- use_module(library(when)).

Expand Down
6 changes: 2 additions & 4 deletions src/toplevel.pl
Original file line number Diff line number Diff line change
@@ -1,6 +1,5 @@
:- module('$toplevel', []).

:- use_module(library(atts), [call_residue_vars/2]).
:- use_module(library(charsio)).
:- use_module(library(error)).
:- use_module(library(files)).
Expand Down Expand Up @@ -28,7 +27,7 @@
).

'$repl' :-
asserta('$toplevel':started),
asserta('$toplevel':started),
raw_argv(Args0),
( append(Args1, ["--"|_], Args0) ->
Args = Args1
Expand Down Expand Up @@ -186,7 +185,7 @@
bb_put('$report_all', false),
bb_put('$report_n_more', 0),
expand_goal(Term, user, Term0),
atts:call_residue_vars(user:Term0, AttrVars),
call_residue_vars(user:Term0, AttrVars),
write_eqs_and_read_input(B, VarList, AttrVars),
!.
submit_query_and_print_results_(_, _) :-
Expand Down Expand Up @@ -451,4 +450,3 @@
% is expected to be printed instead.
; print_exception(E)
).

2 changes: 1 addition & 1 deletion tests/scryer/cli/issues/handle_residual_goal.stdin
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
use_module(library(dif)).
use_module(library(atts)).
use_module(library(iso_ext)).
-X\=X.
-X=X.
dif(-X,X).
Expand Down

0 comments on commit bc616ca

Please sign in to comment.