1:- module(nb_set_term, [nb_set_has/2, nb_set_add/2, nb_set_add1/2, nb_set_rem/2, nb_set_rem1/2]).

Utility LOGICMOO NB SET TERM

This module allows non-backtrackable manipulation of prolog data. Manipulate and edit terms without worrying about them reverting.

   10*/
   11:- set_module(class(library)).
   12/*  Logicmoo Debug Tools
   13% ===================================================================
   14% File 'logicmoo_util_varnames.pl'
   15% Purpose: An Implementation in SWI-Prolog of certain debugging tools
   16% Maintainer: Douglas Miles
   17% Contact: $Author: dmiles $@users.sourceforge.net ;
   18% Version: 'logicmoo_util_varnames.pl' 1.0.0
   19% Revision: $Revision: 1.1 $
   20% Revised At:  $Date: 2002/07/11 21:57:28 $
   21% ===================================================================
   22*/
   23
   24%nb_set_has(F, List):- arg(N, List, E), E =@= F, !.
   25nb_set_has(Set, F):- must_be(compound,Set),functor(Set,_, A),  
   26  ((arg(N, Set, E), N < A, E=@=F) -> true;
   27   (arg(A,Set,T), ((T==[];var(T)) -> (!,fail) ; nb_set_has(T, F)))).
   28
   29nb_set_unify(Set, F, E):- must_be(compound,Set),functor(Set,_, A), 
   30  ((arg(N, Set, E), N < A, E=F) -> true;
   31   (arg(A,Set,T), ((T==[];var(T)) -> (!,fail) ; nb_set_unify(T, F, E)))).
   32
   33nb_set_add(Set, List):- is_list(List), !, maplist(nb_set_add1(Set),List).
   34nb_set_add(Set, E):- nb_set_add1(Set,E), !.
   35
   36nb_set_add1(Set, F):- must_be(compound,Set),functor(Set,_, A), 
   37  ((arg(N, Set, E), N < A, E=@=F) -> true;
   38   (arg(A,Set,T), ((T==[];var(T)) -> nb_linkarg(A, Set, [F]) ; nb_set_add1(T, F)))).
   39
   40nb_set_rem(Set, List):- is_list(List), !, maplist(nb_set_rem1(Set),List).
   41nb_set_rem(Set, E):- nb_set_rem1(Set,E), !.
   42
   43nb_set_rem1(Set, F):- must_be(compound,Set), functor(Set,_, A), 
   44  ((arg(N, Set, E), N < A, E=@=F) -> throw(cant_remove(arg(N, Set, E))) ;
   45   (arg(A,Set,T), ((T==[];var(T)) -> true ; nb_set_rem1(T, F)))).
   46
   47
   48nb_remove_first(List):- List = [_|Second],compound(Second),arg(1,Second,NewFirst),arg(2,Second,NewRest),nb_setarg(1,List,NewFirst),nb_setarg(2,List,NewRest),!.
   49remove_el_via_setarg(List,Value):- [Value,_|_] = List, !, nb_remove_first(List).
   50remove_el_via_setarg([_|List],Value):- remove_el_via_setarg(List,Value).
   51
   52append_el_via_setarg(List,Value):- List = [_|T], (T==[] -> setarg(2,List,[Value]) ; append_el_via_setarg(T,Value)).
   53
   54merge_nb_values(Into,From):- Into=@=From,!.
   55merge_nb_values(Into,From):- is_list(From),!,maplist(nb_set_add1(Into),From).
   56merge_nb_values(Into,From):- is_list(Into),!,maplist(merge_nb_values(Into),From).
   57merge_nb_values(Into,From):- \+ compound(From),!, nb_set_add1(Into,From).
   58merge_nb_values(Into,From):- compound(Into),
   59  compound_name_arguments(From,FF,ArgF),
   60  compound_name_arguments(Into,FI,ArgI),
   61  FF=FI, !, 
   62  maplist(merge_nb_values_if_differnt(Into),ArgI,ArgF).
   63merge_nb_values(Into,From):- duplicate_term(From,F),nb_set_add1(Into,F).
   64
   65merge_nb_values_if_differnt(_,To,From):- To=@=From,!.
   66merge_nb_values_if_differnt(_,To,From):- is_list(To),!,merge_nb_values(To,From).
   67merge_nb_values_if_differnt(Into,_,From):-  merge_nb_values(Into,From),!.
   68
   69find_subterm(P,Seg):- find_subterm(P,Seg,_).
   70
   71find_subterm(P,Seg,S):- compound(P), sub_term(S,P),nonvar(S),Seg=S.
   72
   73
   74
   75
   76:- fixup_exports.