1% MODULE div_utils  EXPORTS
    2
    3:- module(div_utils,
    4        [ remove/3,
    5          sort_by_length/3,
    6          mysetof/3,
    7          sum/2,
    8          efface/3,
    9          buildpar2/3,
   10          neg/2,
   11          contains_duplicates/1,
   12          contains_identicals/1,
   13          identical_member/2,
   14          convert_to_horn_clause/3,
   15          extract_body/2,
   16          list_to_struct/2,
   17          clist_to_prolog/2,
   18          append_all/2,
   19          maximum/2,
   20          myforall/2,
   21          identical_make_unique/2,
   22          remove_v/3,
   23          remove_variant/3,
   24          make_unique/2,
   25          variant_mem/2,
   26          different_predicates/2,
   27          nth_arg/3,
   28          split_examples/4,
   29          shares_var/2,
   30          body2list/2,
   31          insert_unique/3,
   32          insert_unique/4,
   33          effaceall/3,
   34          genterm_test/2,
   35          subset_chk/2,
   36          best/2,
   37          subterm_at_position/4,
   38          part_of_clause/2,
   39          fak/2,
   40          fak1/3,
   41          nueberk/3,
   42          log2/2,
   43          log2nueberk/3,
   44          sum_of_logs/3]).   45
   46
   47% METAPREDICATES
   48:- meta_predicate(mysetof(+,:,-)).   49
   50
   51% IMPORTS
   52
   53:- use_module_if_exists(library(basics),
   54              [member/2]).   55:- use_module_if_exists(library(subsumes),
   56                      [variant/2]).   57:- use_module_if_exists(library(occurs),
   58                      [sub_term/2,contains_var/2]).   59:- use_module_if_exists(library(lists),
   60              [rev/2]).   61:- use_module_if_exists(library(math),
   62              [log/2]).   63
   64%***********************************************************************
   65%*	
   66%* module: div_utils.pl        					
   67%*									
   68%* author: B.Jung, M.Mueller, I.Stahl, B.Tausend              date:12/92	
   69%*									
   70%* changed:								
   71%*									
   72%* description:	small auxiliary procedures
   73%*		
   74%* see also:								
   75%*									
   76%***********************************************************************
   77
   78
   79%***********************************************************************
   80%*									
   81%* predicate:	remove/3								
   82%*									
   83%* syntax: remove(+I,+L,-L)								
   84%*									
   85%* args: I .. number, L ... list of numbers
   86%*									
   87%* description:	removes I from L (I occurs at most once in L)
   88%*									
   89%* example:								
   90%*									
   91%* peculiarities:	none						
   92%*									
   93%* see also:								
   94%*									
   95%***********************************************************************
   96
   97remove(_,[],[]).
   98remove(I,[I|R],R):- !.
   99remove(I,[J|R],[J|R1]):-
  100   remove(I,R,R1).
  101
  102%***********************************************************************
  103%*									
  104%* predicate:	sort_by_length/3							
  105%*									
  106%* syntax: sort_by_length(+L,+Accu,-Accu)
  107%*									
  108%* args: L ... list of lists
  109%*       Accu ... L sorted increasingly according to the length of sublists
  110%*									
  111%* description:	sorts a list of lists increasingly according to 
  112%*              the length of sublists							
  113%*									
  114%* example:								
  115%*									
  116%* peculiarities:	none						
  117%*									
  118%* see also:								
  119%*									
  120%***********************************************************************
  121
  122sort_by_length([],L,L).
  123sort_by_length([IXS|R],L,L2):-
  124   insert_by_length(IXS,L,L1),
  125   sort_by_length(R,L1,L2).
  126
  127insert_by_length(X,[Y|R],[Y|R1]):-
  128   length(X,N),length(Y,N1),
  129   N > N1,!,
  130   insert_by_length(X,R,R1).
  131insert_by_length(X,L,[X|L]).
  132
  133
  134%***********************************************************************
  135%*									
  136%* predicate:	mysetof/3							
  137%*									
  138%* syntax: mysetof(+Template,+Generator,-Set)
  139%*									
  140%* args: 								
  141%*									
  142%* description:	as setof/3, but succeeds with Set = [], if Generator
  143%*		fails							
  144%*									
  145%* example: setof(X, append([1,2,3],X,[4,5]),Set) -> fail
  146%*          mysetof(X, append([1,2,3],X,[4,5]),Set) -> Set = []
  147%*									
  148%* peculiarities:	none						
  149%*									
  150%* see also:								
  151%*									
  152%***********************************************************************
  153
  154mysetof(A,B,C):- setof(A,B,C),!.
  155mysetof(_,_,[]).
  156
  157
  158%***********************************************************************
  159%*									
  160%* predicate:	sum/2							
  161%*									
  162%* syntax: sum(+LN,-S)								
  163%*									
  164%* args: LN .. list of numbers, S number
  165%*									
  166%* description:	if LN = [I1,..,In], then S = I1 + ... + In
  167%*									
  168%* example:								
  169%*									
  170%* peculiarities:	none				
  171%*									
  172%* see also:								
  173%*									
  174%***********************************************************************
  175
  176sum([I],I).
  177sum([I|More],C):- sum(More,J), C is I + J.
  178
  179
  180%***********************************************************************
  181%*									
  182%* predicate:	efface/3 (by Clocksin/Mellish)						
  183%*									
  184%* syntax: efface(+E,+L,-L)								
  185%*									
  186%* args: E .. element of list L								
  187%*									
  188%* description:	removes the first element of L that is unifiable with E
  189%*              from L.							
  190%*
  191%* example:								
  192%*									
  193%* peculiarities:	none				
  194%*									
  195%* see also:								
  196%*									
  197%***********************************************************************
  198
  199efface(A, [A|L], L) :- !.
  200efface(A, [B|L], [B|M]) :- efface(A, L, M).
  201
  202
  203%***********************************************************************
  204%*									
  205%* predicate: effaceall/3	
  206%*									
  207%* syntax: effacell(+E,+L,-L)								
  208%*									
  209%* args: E .. element of list L								
  210%*									
  211%* description:	as efface, but allows backtracking
  212%*									
  213%* example:								
  214%*									
  215%* peculiarities:	none						
  216%*									
  217%* see also:								
  218%*									
  219%***********************************************************************
  220
  221effaceall(A, [A|L], L).
  222effaceall(A, [B|L], [B|M]) :- effaceall(A, L, M).
  223
  224
  225%***********************************************************************
  226%*									
  227%* predicate:	best/2							
  228%*									
  229%* syntax: best(+List,-Elem)								
  230%*									
  231%* args:								
  232%*									
  233%* description:	returns the first element of List, on backtracking
  234%*              the second etc.
  235%*									
  236%* example:								
  237%*									
  238%* peculiarities:	none						
  239%*									
  240%* see also:								
  241%*									
  242%***********************************************************************
  243
  244best([X|_],X).
  245best([_|R],X):- best(R,X).
  246
  247
  248%***********************************************************************
  249%*									
  250%* predicate:	buildpar2/3							
  251%*									
  252%* syntax: buildpar2(+Lit:M,+CL,-CL1)
  253%*									
  254%* args: Lit .. literal, M in {p,n,r}, CL and CL1 clauses in list representation
  255%*									
  256%* description:	if M = p then CL1 = [Lit:p|CL] 
  257%*		else CL1 results from CL by adding Lit:M at the end
  258%*									
  259%* example:								
  260%*									
  261%* peculiarities:	none				
  262%*									
  263%* see also:	
  264%*
  265%***********************************************************************
  266
  267buildpar2(Elem1:p,List2,[Elem1:p|List2]).
  268buildpar2(ResLit,List2,Parent2) :- append(List2,[ResLit],Parent2).
  269
  270
  271%************************************************************************
  272%*
  273%* predicate: neg/2
  274%*
  275%* syntax: neg(+Lit:M,-Lit:M1)
  276%*
  277%* args: Lit .... literal, M in {p,n,r}
  278%*
  279%* description: switches the mark of the literal, i.e. if M = p then
  280%*              M1 = n and vice versa
  281%*
  282%* example:
  283%*
  284%* peculiarities:
  285%*
  286%* see also:
  287%*
  288%************************************************************************
  289
  290neg(F:p, F:n).
  291neg(F:n, F:p).
  292
  293
  294%***********************************************************************
  295%*									
  296%* predicate:	contains_duplicates/1							
  297%*									
  298%* syntax: contains_duplicates(+L)
  299%*									
  300%* args: L ... list								
  301%*									
  302%* description:	succeeds if L contains two unifiable elements
  303%*									
  304%* example:								
  305%*									
  306%* peculiarities:	none				
  307%*									
  308%* see also:								
  309%*									
  310%***********************************************************************
  311
  312contains_duplicates([H|T]):- member(H,T).
  313contains_duplicates([_|T]):- contains_duplicates(T).
  314
  315
  316
  317%***********************************************************************
  318%*									
  319%* predicate:	contains_identicals/1							
  320%*									
  321%* syntax: contains_identicals(+L)
  322%*									
  323%* args: L ... list								
  324%*									
  325%* description:	succeeds if L contains two identical (==) elements
  326%*									
  327%* example:								
  328%*									
  329%***********************************************************************
  330
  331contains_identicals([H|T]):- contains_var(H,T).
  332contains_identicals([_|T]):- contains_identicals(T).
  333
  334
  335
  336%***********************************************************************
  337%*									
  338%* predicate: identical_member/2							
  339%*									
  340%* syntax: identical_member(+Elem,+List)   
  341%*									
  342%* args:  								
  343%*									
  344%* description: succeeds if Elem is identically (==) contained  in List	
  345%*									
  346%* example:								
  347%*									
  348%* peculiarities:	none				
  349%*									
  350%* see also:								
  351%*									
  352%***********************************************************************
  353
  354identical_member(A,[A1|_]):- A == A1.    
  355identical_member(A,[_|R]):- identical_member(A,R). 
  356
  357
  358%***********************************************************************
  359%*									
  360%* predicate:	convert_to_horn_clause/3
  361%*									
  362%* syntax: convert_to_horn_clause(+PHead,+CL,-HCL)
  363%*									
  364%* args: PHead ... preferred head
  365%*       CL ... general clause in list representation
  366%*       HCL ... horn clause in list representation
  367%*									
  368%* description:	if CL = [H1:p,..,Hn:p,L1:M1,..,Lm:Mm] where Mi in {p,r}
  369%*              then HCL = [Hj:p,L1:M1,...,Lm:Mm], where Hj is the first
  370%*                   head in CL unifiable with PHead (if one exists), else
  371%*                   the first head in CL
  372%*									
  373%* example:								
  374%*									
  375%* peculiarities:	none				
  376%*									
  377%* see also:								
  378%*									
  379%***********************************************************************
  380
  381convert_to_horn_clause(PrefHead,GenClause,HornClause):-
  382      extract_body(GenClause,Body),      
  383      !,
  384      ( member( PrefHead:p, GenClause) -> Head = PrefHead   % if preferred head is among 
  385      ;                                                     % candidates, select it.
  386        member( Head:p, GenClause)                          % Else select first candidate.
  387      ),
  388      HornClause = [ Head:p | Body ].
  389
  390
  391
  392%***********************************************************************
  393%*									
  394%* predicate:	extract_body/2							
  395%*									
  396%* syntax: extract_body(+CL,-CL1)
  397%*									
  398%* args: CL .. clause in list representation
  399%*       CL1 = [...,L:M,...] where M in {p,n} and L in CL
  400%*									
  401%* description:	
  402%*									
  403%* example:								
  404%*									
  405%* peculiarities:			
  406%*									
  407%* see also:								
  408%*									
  409%***********************************************************************
  410
  411
  412extract_body([],[]).
  413extract_body([L:n| Rest], [L:n|Rest1]):- extract_body(Rest,Rest1).
  414extract_body([L:r| Rest], [L:r|Rest1]):- extract_body(Rest,Rest1).
  415extract_body([_:p| Rest], Rest1):- extract_body(Rest,Rest1).
  416
  417
  418
  419%***********************************************************************
  420%*									
  421%* predicate: 	list_to_struct/2							
  422%*									
  423%* syntax: list_to_struct(+L,-C)
  424%*									
  425%* args: L ... list, C ... conjunction of elements of L
  426%*									
  427%* description:	if L = [E1,...,En] then C = (E1,..,En)
  428%*									
  429%* example:								
  430%*									
  431%* peculiarities:	none				
  432%*									
  433%* see also:								
  434%*									
  435%***********************************************************************
  436
  437list_to_struct([A,B|Rest],(A,Rest1) ):- list_to_struct([B|Rest],Rest1).
  438list_to_struct([A],A).
  439list_to_struct([],true).
  440
  441
  442%***********************************************************************
  443%*									
  444%* predicate: clist_to_prolog/2								
  445%*									
  446%* syntax: clist_to_prolog(+CL,-C)
  447%*									
  448%* args: CL .. Horn clause in list representation
  449%*       C ... Horn clause in prolog format
  450%*									
  451%* description:	convert list format to clause format and vice versa
  452%*              (should use body2list!!)
  453%*									
  454%* example:								
  455%*									
  456%* peculiarities:	none				
  457%*									
  458%* see also:								
  459%*									
  460%***********************************************************************
  461
  462clist_to_prolog([A:p,B|Rest],(A:-Rest1) ):- !,clist_to_prolog([B|Rest],Rest1).
  463clist_to_prolog([A:p],(A:-true)):-!.
  464clist_to_prolog([A:n,B|Rest],(A,Rest1) ):- !, clist_to_prolog([B|Rest],Rest1).
  465clist_to_prolog([A:n],A):-!.
  466clist_to_prolog([A:r,B|Rest],(A,Rest1) ):- clist_to_prolog([B|Rest],Rest1).
  467clist_to_prolog([A:r],A).
  468
  469
  470%***********************************************************************
  471%*									
  472%* predicate:	append_all/2							
  473%*									
  474%* syntax: append_all(+LL,-L)								
  475%*									
  476%* args: LL .. list of lists, L .. list
  477%*									
  478%* description:	appends all lists in LL -> L
  479%*									
  480%* example:								
  481%*									
  482%* peculiarities:	none				
  483%*									
  484%* see also:								
  485%*									
  486%***********************************************************************
  487
  488append_all([],[]).
  489append_all([P|R],R2):-
  490    append_all(R,R1),
  491    append(P,R1,R2).
  492
  493
  494
  495%***********************************************************************
  496%*									
  497%* predicate:	maximum/2							
  498%*									
  499%* syntax: maximum(+L,-M)								
  500%*									
  501%* args: L .. list of numbers, M number
  502%*									
  503%* description:	M is the maximum element of L
  504%*									
  505%* example:								
  506%*									
  507%* peculiarities:	none				
  508%*									
  509%* see also:								
  510%*									
  511%***********************************************************************
  512
  513maximum([I],I).
  514
  515maximum([I|Rest], I):-
  516        maximum(Rest,J),
  517        I >= J,!.
  518
  519maximum([_|Rest],J):-
  520        maximum(Rest,J),!. 
  521
  522									
  523%***********************************************************************
  524%*									
  525%* predicate:	myforall/2							
  526%*									
  527%* syntax: myforall(+E,+Pred)								
  528%*									
  529%* args: E ... argument terms, Pred .. type predicate
  530%*									
  531%* description:	calls Pred(e) for each e in E, and succeeds only if 
  532%*              every call succeeds
  533%*									
  534%* example:								
  535%*									
  536%* peculiarities:	none						
  537%*									
  538%* see also:								
  539%*									
  540%***********************************************************************
  541
  542myforall([],_).
  543myforall([E|R],Pred):-
  544   C =.. [Pred,E],
  545   call(C),
  546   myforall(R,Pred).
  547
  548
  549%***********************************************************************
  550%*									
  551%* predicate:	identical_make_unique/2	
  552%*									
  553%* syntax: identical_make_unique(+L,-L1)
  554%*									
  555%* args: L,L1 ... lists								
  556%*									
  557%* description: removes all identical duplicates (==) from L
  558%*
  559%* example:								
  560%*									
  561%* peculiarities:	none						
  562%*									
  563%* see also:								
  564%*									
  565%***********************************************************************
  566
  567identical_make_unique([],[]).
  568identical_make_unique([X|R],R1):-
  569   contains_var(X,R),!,
  570   identical_make_unique(R,R1).   
  571identical_make_unique([X|R],[X|R1]):-
  572   identical_make_unique(R,R1). 
  573
  574
  575%***********************************************************************
  576%*									
  577%* predicate: remove_v/3								
  578%*									
  579%* syntax: remove_v(+L0,+L,-L1)
  580%*									
  581%* args: L0,L,L1 lists								
  582%*									
  583%* description:	removes each E in L0  from L if E is identically (==) 
  584%*              contained  in  L							
  585%*									
  586%* example:								
  587%*									
  588%* peculiarities:	none						
  589%*									
  590%* see also:								
  591%*									
  592%***********************************************************************
  593
  594remove_v(_,[],[]).
  595remove_v(T,[T1|R],R1):- identical_member(T1,T),!,remove_v(T,R,R1).
  596remove_v(T,[T1|R],[T1|R1]):- remove_v(T,R,R1).
  597
  598
  599
  600%***********************************************************************
  601%*									
  602%* predicate: remove_variant/3								
  603%*									
  604%* syntax: remove_variant(+L0,+L,-L1)
  605%*									
  606%* args: L0,L,L1 lists								
  607%*									
  608%* description:	removes each E in L0  from L if E is 
  609%*              contained as variant in  L
  610%*									
  611%* example:								
  612%*									
  613%* peculiarities:	none						
  614%*									
  615%* see also:								
  616%*									
  617%***********************************************************************
  618
  619remove_variant(_,[],[]).
  620remove_variant(T,[T1|R],R1):- variant_mem(T1,T),!,remove_variant(T,R,R1).
  621remove_variant(T,[T1|R],[T1|R1]):- remove_variant(T,R,R1).
  622
  623
  624%***********************************************************************
  625%*									
  626%* predicate: make_unique/2								
  627%*									
  628%* syntax: make_unique(+L,-L1)								
  629%*									
  630%* args: L,L1 .. lists								
  631%*									
  632%* description:	removes all duplicates (variant) from L
  633%*									
  634%* example:								
  635%*									
  636%* peculiarities:	none						
  637%*									
  638%* see also:								
  639%*									
  640%***********************************************************************
  641
  642make_unique([],[]).
  643make_unique([X|R],R1):-
  644   variant_mem(X,R),!,
  645   make_unique(R,R1).
  646make_unique([X|R],[X|R1]):-
  647   make_unique(R,R1).
  648
  649
  650%***********************************************************************
  651%*									
  652%* predicate: variant_mem/2
  653%*									
  654%* syntax: variant_mem(+Elem,+List)
  655%*									
  656%* args:								
  657%*									
  658%* description:	succeeds if an alphabetical variant of Elem is
  659%*              contained in List							
  660%*									
  661%* example:								
  662%*									
  663%* peculiarities:	none						
  664%*									
  665%* see also:								
  666%*									
  667%***********************************************************************
  668
  669variant_mem(T,[T1|_]):- variant(T,T1),!.
  670variant_mem(T,[_|R]):- variant_mem(T,R).
  671
  672
  673%***********************************************************************
  674%*									
  675%* predicate: different_predicates/2
  676%*									
  677%* syntax: different_predicates(+L,-LL)
  678%*									
  679%* args: L .. list of terms, LL list of lists of terms
  680%*									
  681%* description:	for each functor f/n occuring in L, LL contains a list Lf 
  682%*      consisting of all terms in L with principal functor f/n	
  683%*									
  684%* example: L = [f(a,b),f(c,d),h(g)] LL = [[f(a,b),f(c,d)],[h(g)]]
  685%*									
  686%* peculiarities:	none						
  687%*									
  688%* see also:								
  689%*									
  690%***********************************************************************
  691
  692different_predicates([],[]).
  693different_predicates([E|R],[[E|Es]|R2]):-
  694   functor(E,F,N),
  695   diff_predicates(R,R1,Es,F,N),
  696   different_predicates(R1,R2).
  697
  698diff_predicates([],[],[],_,_).
  699diff_predicates([E|R],R2,Es2,_,0):- !,
  700   diff_predicates(R,R1,Es1,_,0),
  701   (   functor(E,_,0) ->
  702       R2 = R1, Es2 = [E|Es1]
  703   ;   R2 = [E|R1], Es2 = Es1
  704   ).
  705diff_predicates([E|R],R2,Es2,F,N):-
  706   diff_predicates(R,R1,Es1,F,N),
  707   (   functor(E,F,N) ->
  708       R2 = R1, Es2 = [E|Es1]
  709   ;   R2 = [E|R1], Es2 = Es1
  710   ).
  711
  712
  713%***********************************************************************
  714%*									
  715%* predicate: nth_arg/3								
  716%*									
  717%* syntax: nth_arg(+E,+N,-Args)								
  718%*									
  719%* args: E ... list of terms with principal functor p/n
  720%*       N =< n	argument position
  721%*       Args ... list of argument terms
  722%*									
  723%* description:	Args = {A | arg(N,P,A) and P in E}
  724%*									
  725%* example:								
  726%*									
  727%* peculiarities:	none						
  728%*									
  729%* see also:								
  730%*									
  731%***********************************************************************
  732
  733nth_arg([],_,[]).
  734nth_arg([F|R],N,[Argn|R1]):-
  735   arg(N,F,Argn),
  736   nth_arg(R,N,R1).
  737
  738
  739%***********************************************************************
  740%*									
  741%* predicate: split_examples/4								
  742%*									
  743%* syntax: split_examples(+E,+Term,-P,-N)
  744%*									
  745%* args: E,P,N ... list of terms
  746%*									
  747%* description: P = {e in E | Term, e unifiable}
  748%*              N = E - P								
  749%*									
  750%* example:								
  751%*									
  752%* peculiarities:	none						
  753%*									
  754%* see also:								
  755%*									
  756%***********************************************************************
  757
  758split_examples([E1|R],Lgg,P,[E1|M1]):-
  759   \+(E1 = Lgg),
  760   split_examples(R,Lgg,P,M1),!.
  761
  762split_examples([E1|R],Lgg,[E1|P],M1):-
  763  split_examples(R,Lgg,P,M1),!.
  764
  765split_examples([],_,[],[]):- !.
  766
  767
  768%***********************************************************************
  769%*									
  770%* predicate:	shares_var/2							
  771%*									
  772%* syntax:	shares_var(+T,+Ts)						
  773%*									
  774%* args:	T: a term or a clause,Ts: a list of terms or clauses
  775%*									
  776%* description:	tests if T shares at least one variable
  777%*		with the terms in t						
  778%*									
  779%* example:								
  780%*									
  781%* peculiarities:	none						
  782%*									
  783%* see also:								
  784%*									
  785%***********************************************************************
  786
  787shares_var(T,Ts):-
  788   sub_term(V,T), var(V), contains_var(V,Ts).
  789
  790
  791
  792%***********************************************************************
  793%*									
  794%* predicate:	body2list/2							
  795%*									
  796%* syntax:	body2list(?B,?BList)
  797%*									
  798%* args:	B: Body of a clause (L1,...,Ln)	
  799%*		BList: [L1:x,...,Ln:x] where x is in {r,n}
  800%*									
  801%* description:	transforms a clause body to a list of its literals
  802%*		where each literal is augmented by :n (i.e. negative clause literal)
  803%*		or :r (i.e. recursive goal in the clause body).
  804%*              works in both directions
  805%*									
  806%* example:	(p(x,y),q(z,w)),[(p(x,y):r,q(z,w):r]
  807%*									
  808%* peculiarities:	none						
  809%*									
  810%* see also:								
  811%*									
  812%***********************************************************************
  813
  814body2list(B, [L1:n|RestL]) :-
  815        functor(B,',',2),
  816        arg(1,B,L1),arg(2,B,RestB),
  817        body2list(RestB, RestL).
  818body2list(B, [B:n]) :- !.
  819body2list(B, [L1:r|RestL]) :-
  820        functor(B,',',2),
  821        arg(1,B,L1),arg(2,B,RestB),
  822        body2list(RestB, RestL).
  823body2list(B, [B:r]) :- !.
  824
  825
  826
  827%***********************************************************************
  828%*									
  829%* predicate:	insert_unique/3						
  830%*									
  831%* syntax: insert_unique(+N,+L,-L1)
  832%*									
  833%* args: N .. number, L,L1 sorted lists of numbers
  834%*									
  835%* description:	inserts N uniquely in the ascendingly sorted list L
  836%*									
  837%* example:								
  838%*									
  839%* peculiarities:	none						
  840%*									
  841%* see also:								
  842%*									
  843%***********************************************************************
  844
  845insert_unique(I,[I|R],[I|R]):- !.
  846insert_unique(I,[J|R],[J|R1]):-
  847   I > J,!,
  848   insert_unique(I,R,R1).
  849insert_unique(I,L,[I|L]).
  850
  851
  852
  853%***********************************************************************
  854%*									
  855%* predicate:	insert_unique/4							
  856%*									
  857%* syntax: insert_unique(+ID,+A,+L,-L1)
  858%*									
  859%* args: ID,A .. numbers, L,L1 = [...,ID:List,...]
  860%*									
  861%* description:	inserts A in the sublist identified by ID in L
  862%*									
  863%* example: insert_unique(2,5,[1:[5,6],2:[4],3:[9,8]],
  864%*                            [1:[5,6],2:[5,4],3:[9,8]])
  865%*									
  866%* peculiarities:	none						
  867%*									
  868%* see also:								
  869%*									
  870%***********************************************************************
  871
  872insert_unique(I,A,[],[I:[A]]):- !.
  873insert_unique(I,A,[I:A1|R],[I:[A|A1]|R]):- !.
  874insert_unique(I,A,[J|R],[J|R1]):-
  875   insert_unique(I,A,R,R1).
  876
  877
  878%***********************************************************************
  879%*									
  880%* predicate: genterm_test/3	
  881%*									
  882%* syntax: genterm_test(+X/T,+Subst)
  883%*									
  884%* args: X/T element of a substitution, Subst substitution
  885%*									
  886%* description: succeeds if Subst contains a tuple Y/T1 such that
  887%*      T1 == T. In that case, X and Y are unified.
  888%*									
  889%* example:								
  890%*									
  891%* peculiarities:	none						
  892%*									
  893%* see also:								
  894%*									
  895%***********************************************************************
  896
  897genterm_test(X/T1, [X/T2|_]) :-
  898        T1 == T2, !.
  899genterm_test(S, [_|Rest]) :-
  900        genterm_test(S, Rest).
  901
  902
  903
  904%***********************************************************************
  905%*									
  906%* predicate: subset_chk/2
  907%*									
  908%* syntax: subset_chk(+L,+L1)	
  909%*									
  910%* args: L, L1 .. lists 								
  911%*									
  912%* description:	succeeds, if L is a subset of L1 (without unification)
  913%*									
  914%* example:								
  915%*									
  916%* peculiarities:	none						
  917%*									
  918%* see also:								
  919%*									
  920%***********************************************************************
  921
  922
  923% subset check uses library 'basics'
  924subset_chk([],_) :- !.
  925subset_chk([Elem1|Rest1], List2) :-
  926        identical_member(Elem1, List2),!,
  927        subset_chk(Rest1, List2).
  928
  929
  930%***********************************************************************
  931%*									
  932%* predicate:	subterm_at_position/4							
  933%*									
  934%* syntax: subterm_at_position(+Term,-Sub,+Pos,-Pos)
  935%*									
  936%* args: Term, Sub: Prolog terms
  937%*       Pos: position of Sub within Term (a list of numbers)
  938%*									
  939%* description:	returns a subterm of Term and its position, on backtracking
  940%*              further subterms
  941%*									
  942%* example: ?- subterm_at_position(p(a,[a]),S,[],P).
  943%*          S = p(a,[a]), P = [];
  944%*          S = a         P = [1];
  945%*          S = [a]       P = [2];
  946%*          S = a         P = [2,1];
  947%*          S = []        P = [2,2]							
  948%*									
  949%* peculiarities:	none						
  950%*									
  951%* see also:								
  952%*									
  953%***********************************************************************
  954   
  955subterm_at_position(T,T,P,P1):- rev(P,P1).
  956subterm_at_position(T,S,P,P1):-
  957   nonvar(T),
  958   functor(T,_,N),N > 0,
  959   subterm_at_position(N,T,S,P,P1).
  960
  961subterm_at_position(N,T,S,P,P1):-
  962   N > 0,
  963   arg(N,T,Tn),
  964   subterm_at_position(Tn,S,[N|P],P1).
  965subterm_at_position(N,T,S,P,P1):-
  966   N > 0,N1 is N - 1,
  967   subterm_at_position(N1,T,S,P,P1).
  968
  969
  970%***********************************************************************
  971%*									
  972%* predicate: part_of_clause/2	
  973%*									
  974%* syntax: part_of_clause(+Term,+Clause)						
  975%*									
  976%* args: Term: a prolog term, Clause: a prolog clause
  977%*									
  978%* description:	succeeds if Term is a literal within clause, a part
  979%*              of the clause body or the clause itself
  980%*									
  981%* example:								
  982%*									
  983%* peculiarities:	none						
  984%*									
  985%* see also:								
  986%*									
  987%***********************************************************************
  988
  989part_of_clause(S,B):- 
  990   S == B.
  991part_of_clause(S,(H:-B)):- !,
  992   (   (S == H;S == B) ->
  993       true
  994   ;   part_of_clause(S,B)
  995   ).
  996part_of_clause(S,(H,B)):- !,
  997   (   (S == H;S == B) ->
  998       true
  999   ;   part_of_clause(S,B)
 1000   ).
 1001
 1002
 1003
 1004%***********************************************************************
 1005%*									
 1006%* predicate: several arithmetic predicates	
 1007%*									
 1008%* syntax: 
 1009%*									
 1010%* args: 
 1011%*									
 1012%* description:	arithmetic predicates used in heuristic measures
 1013%*									
 1014%* example:								
 1015%*									
 1016%* peculiarities:	none						
 1017%*									
 1018%* see also:								
 1019%*									
 1020%***********************************************************************
 1021
 1022
 1023fak(X,1):- X =:= 0,!.
 1024fak(N,NF):-
 1025   N1 is N - 1,
 1026   fak(N1,N1F),
 1027   NF is N1F * N.
 1028
 1029fak1(N,N,1):- !.
 1030fak1(A,B,C):-
 1031   A1 is A + 1,
 1032   fak1(A1,B,C1),
 1033   C is C1 * A1.
 1034
 1035nueberk(N,K,NUK):-
 1036   NK is N - K,
 1037   fak1(NK,N,NKF),
 1038   fak(K,KF),
 1039   NUK is NKF / KF.
 1040
 1041log2(X,LX):-
 1042   log(X,LNX),
 1043   log(2,LN2),
 1044   LX is LNX / LN2.
 1045
 1046log2nueberk(_,0.0,0.0):- !.
 1047log2nueberk(N,1.0,LN):- log2(N,LN),!.
 1048log2nueberk(N,N,0.0):- !.
 1049log2nueberk(N,K,L):-
 1050   N1 is (N - K) + 1,
 1051   sum_of_logs(N1,N,L1),
 1052   sum_of_logs(1.0,K,L2),
 1053   L is L1 - L2.
 1054
 1055sum_of_logs(O,O,LO):- log2(O,LO),!.
 1056sum_of_logs(U,O,L):-
 1057   U < O,!,
 1058   U1 is U + 1,
 1059   sum_of_logs(U1,O,L1),
 1060   log2(U,LU),
 1061   L is L1 + LU.
 1062sum_of_logs(U,O,_):-
 1063   U > O,!,fail