Skip to content

Commit

Permalink
Merge pull request #2301 from aarroyoc/docs-copy-term-3
Browse files Browse the repository at this point in the history
Move copy_term/3 to library(iso_ext)
  • Loading branch information
mthom authored Jan 19, 2024
2 parents 6421fe1 + 99c8545 commit 58cd0d1
Show file tree
Hide file tree
Showing 3 changed files with 18 additions and 11 deletions.
17 changes: 16 additions & 1 deletion src/lib/iso_ext.pl
Original file line number Diff line number Diff line change
Expand Up @@ -17,7 +17,8 @@
succ/2,
call_nth/2,
countall/2,
copy_term_nat/2]).
copy_term_nat/2,
copy_term/3]).

:- use_module(library(error), [can_be/2,
domain_error/3,
Expand All @@ -26,6 +27,8 @@

:- use_module(library(lists), [maplist/3]).

:- use_module(library('$project_atts')).

:- meta_predicate(forall(0, 0)).

%% forall(Generate, Test).
Expand Down Expand Up @@ -382,3 +385,15 @@
copy_term_nat(Source, Dest) :-
'$copy_term_without_attr_vars'(Source, Dest).

%% copy_term(+Term, -Copy, -Gs).
%
% Produce a deep copy of Term and unify it to Copy, without attributes.
% Unify Gs with a list of goals that represent the attributes of Term.
% Similar to `copy_term/2` but splitting the attributes.
copy_term(Term, Copy, Gs) :-
can_be(list, Gs),
findall(Term-Rs, '$project_atts':term_residual_goals(Term,Rs), [Copy-Gs]),
( var(Gs) ->
Gs = []
; true
).
10 changes: 1 addition & 9 deletions src/machine/project_attributes.pl
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
:- module('$project_atts', [copy_term/3]).
:- module('$project_atts', []).

:- use_module(library(dcgs)).
:- use_module(library(error), [can_be/2]).
Expand Down Expand Up @@ -100,14 +100,6 @@

delete_all_attributes_from_var(V) :- '$delete_all_attributes_from_var'(V).

copy_term(Term, Copy, Gs) :-
can_be(list, Gs),
findall(Term-Rs, term_residual_goals(Term,Rs), [Copy-Gs]),
( var(Gs) ->
Gs = []
; true
).

term_residual_goals(Term,Rs) :-
'$term_attributed_variables'(Term, Vs),
phrase(gather_residual_goals(Vs), Rs),
Expand Down
2 changes: 1 addition & 1 deletion src/toplevel.pl
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
:- module('$toplevel', [copy_term/3]).
:- module('$toplevel', []).

:- use_module(library(atts), [call_residue_vars/2]).
:- use_module(library(charsio)).
Expand Down

0 comments on commit 58cd0d1

Please sign in to comment.