scanl and foldl.
This commit is contained in:
		
							
								
								
									
										80
									
								
								docs/yap.tex
									
									
									
									
									
								
							
							
						
						
									
										80
									
								
								docs/yap.tex
									
									
									
									
									
								
							@@ -4667,7 +4667,7 @@ backtracking) or to access the stream for a file @var{F} in mode
 | 
			
		||||
@var{M}, or to find properties for a stream @var{S}. Notice that some
 | 
			
		||||
streams might not be associated to a file: in this case YAP tries to
 | 
			
		||||
return the file number. If that is not available, YAP unifies @var{F}
 | 
			
		||||
with @var(S}.
 | 
			
		||||
with @var{S}.
 | 
			
		||||
 | 
			
		||||
@item is_stream(@var{S})
 | 
			
		||||
@findex is_stream/1
 | 
			
		||||
@@ -9557,21 +9557,21 @@ The following routines are available once included with the
 | 
			
		||||
@code{use_module(library(apply_macros))} command.
 | 
			
		||||
 | 
			
		||||
@table @code
 | 
			
		||||
@item maplist(+@var{Pred}, ?@var{ListIn}, ?@var{ListOut})
 | 
			
		||||
@item maplist(:@var{Pred}, ?@var{ListIn}, ?@var{ListOut})
 | 
			
		||||
@findex maplist/3
 | 
			
		||||
@snindex maplist/3
 | 
			
		||||
@cnindex maplist/3
 | 
			
		||||
      Creates @var{ListOut} by applying the predicate @var{Pred} to all
 | 
			
		||||
elements of @var{ListIn}.
 | 
			
		||||
 | 
			
		||||
@item maplist(+@var{Pred}, ?@var{ListIn})
 | 
			
		||||
@item maplist(:@var{Pred}, ?@var{ListIn})
 | 
			
		||||
@findex maplist/3
 | 
			
		||||
@snindex maplist/3
 | 
			
		||||
@cnindex maplist/3
 | 
			
		||||
      Creates @var{ListOut} by applying the predicate @var{Pred} to all
 | 
			
		||||
elements of @var{ListIn}.
 | 
			
		||||
 | 
			
		||||
@item maplist(+@var{Pred}, ?@var{L1}, ?@var{L2}, ?@var{L3})
 | 
			
		||||
@item maplist(:@var{Pred}, ?@var{L1}, ?@var{L2}, ?@var{L3})
 | 
			
		||||
@findex maplist/4
 | 
			
		||||
@snindex maplist/4
 | 
			
		||||
@cnindex maplist/4
 | 
			
		||||
@@ -9579,7 +9579,7 @@ elements of @var{ListIn}.
 | 
			
		||||
      @code{call(@var{Pred},@var{A1},@var{A2},@var{A3})} holds for every
 | 
			
		||||
      corresponding element in lists @var{L1},  @var{L2}, and @var{L3}.
 | 
			
		||||
 | 
			
		||||
@item maplist(+@var{Pred}, ?@var{L1}, ?@var{L2}, ?@var{L3}, ?@var{L4})
 | 
			
		||||
@item maplist(:@var{Pred}, ?@var{L1}, ?@var{L2}, ?@var{L3}, ?@var{L4})
 | 
			
		||||
@findex maplist/5
 | 
			
		||||
@snindex maplist/5
 | 
			
		||||
@cnindex maplist/5
 | 
			
		||||
@@ -9588,19 +9588,19 @@ elements of @var{ListIn}.
 | 
			
		||||
      for every corresponding element in lists @var{L1}, @var{L2}, @var{L3}, and
 | 
			
		||||
      @var{L4}.
 | 
			
		||||
 | 
			
		||||
@item checklist(+@var{Pred}, +@var{List})
 | 
			
		||||
@item checklist(:@var{Pred}, +@var{List})
 | 
			
		||||
@findex checklist/2
 | 
			
		||||
@snindex checklist/2
 | 
			
		||||
@cnindex checklist/2
 | 
			
		||||
      Succeeds if the predicate @var{Pred} succeeds on all elements of @var{List}.
 | 
			
		||||
 | 
			
		||||
@item selectlist(+@var{Pred}, +@var{ListIn}, ?@var{ListOut})
 | 
			
		||||
@item selectlist(:@var{Pred}, +@var{ListIn}, ?@var{ListOut})
 | 
			
		||||
@findex selectlist/3
 | 
			
		||||
@snindex selectlist/3
 | 
			
		||||
@cnindex selectlist/3
 | 
			
		||||
      Creates @var{ListOut} of all list elements of @var{ListIn} that pass a given test
 | 
			
		||||
 | 
			
		||||
@item convlist(+@var{Pred}, +@var{ListIn}, ?@var{ListOut})
 | 
			
		||||
@item convlist(:@var{Pred}, +@var{ListIn}, ?@var{ListOut})
 | 
			
		||||
@findex convlist/3
 | 
			
		||||
@snindex convlist/3
 | 
			
		||||
@cnindex convlist/3
 | 
			
		||||
@@ -9608,13 +9608,75 @@ elements of @var{ListIn}.
 | 
			
		||||
applying the predicate @var{Pred} to all list elements on which
 | 
			
		||||
@var{Pred} succeeds
 | 
			
		||||
 | 
			
		||||
@item sumlist(+@var{Pred}, +@var{List}, ?@var{AccIn}, ?@var{AccOut})
 | 
			
		||||
@item sumlist(:@var{Pred}, +@var{List}, ?@var{AccIn}, ?@var{AccOut})
 | 
			
		||||
@findex sumlist/4
 | 
			
		||||
@snindex sumlist/4
 | 
			
		||||
@cnindex sumlist/4
 | 
			
		||||
      Calls @var{Pred} on all elements of List and collects a result in
 | 
			
		||||
@var{Accumulator}. Same as @code{foldl/4}.
 | 
			
		||||
 | 
			
		||||
@item foldl(:@var{Pred}, +@var{List}, ?@var{AccIn}, ?@var{AccOut})
 | 
			
		||||
@findex foldl/4
 | 
			
		||||
@snindex foldl/4
 | 
			
		||||
@cnindex foldl/4
 | 
			
		||||
      Calls @var{Pred} on all elements of @code{List} and collects a result in
 | 
			
		||||
@var{Accumulator}.
 | 
			
		||||
 | 
			
		||||
@item foldl(:@var{Pred}, +@var{List1}, +@var{List2}, ?@var{AccIn}, ?@var{AccOut})
 | 
			
		||||
@findex foldl/5
 | 
			
		||||
@snindex foldl/5
 | 
			
		||||
@cnindex foldl/5
 | 
			
		||||
      Calls @var{Pred} on all elements of @code{List1} and
 | 
			
		||||
@code{List2} and collects a result in @var{Accumulator}. Same as
 | 
			
		||||
@code{foldr/4}.
 | 
			
		||||
 | 
			
		||||
@item foldl(:@var{Pred}, +@var{List1}, +@var{List2}, +@var{List3}, ?@var{AccIn}, ?@var{AccOut})
 | 
			
		||||
@findex foldl/6
 | 
			
		||||
@snindex foldl/6
 | 
			
		||||
@cnindex foldl/6
 | 
			
		||||
      Calls @var{Pred} on all elements of @code{List1}, @code{List2}, and
 | 
			
		||||
@code{List3} and collects a result in @var{Accumulator}.
 | 
			
		||||
 | 
			
		||||
@item foldl(:@var{Pred}, +@var{List1}, +@var{List2}, +@var{List3}, +@var{List4}, ?@var{AccIn}, ?@var{AccOut})
 | 
			
		||||
@findex foldl/7
 | 
			
		||||
@snindex foldl/7
 | 
			
		||||
@cnindex foldl/7
 | 
			
		||||
      Calls @var{Pred} on all elements of @code{List1}, @code{List2}, @code{List3}, and
 | 
			
		||||
@code{List4} and collects a result in @var{Accumulator}.
 | 
			
		||||
 | 
			
		||||
@item scanl(:@var{Pred}, +@var{List}, +@var{V0}, ?@var{Values})
 | 
			
		||||
@findex scanl/4
 | 
			
		||||
@snindex scanl/4
 | 
			
		||||
@cnindex scanl/4
 | 
			
		||||
         Left scan of  list.  The  scanl   family  of  higher  order list
 | 
			
		||||
	operations is defined by:
 | 
			
		||||
 | 
			
		||||
@example
 | 
			
		||||
	  scanl(P, [X11,...,X1n], ..., [Xm1,...,Xmn], V0, [V0,V1,...,Vn]) :-
 | 
			
		||||
		P(X11, ..., Xm1, V0, V1),
 | 
			
		||||
		...
 | 
			
		||||
	        P(X1n, ..., Xmn, Vn-1, Vn).
 | 
			
		||||
@end example
 | 
			
		||||
 | 
			
		||||
 | 
			
		||||
@item scanl(:@var{Pred}, +@var{List1}, +@var{List2}, ?@var{V0}, ?@var{Vs})
 | 
			
		||||
@findex scanl/5
 | 
			
		||||
@snindex scanl/5
 | 
			
		||||
@cnindex scanl/5
 | 
			
		||||
         Left scan of  list.  
 | 
			
		||||
 | 
			
		||||
@item scanl(:@var{Pred}, +@var{List1}, +@var{List2}, +@var{List3}, ?@var{V0}, ?@var{Vs})
 | 
			
		||||
@findex scanl/6
 | 
			
		||||
@snindex scanl/6
 | 
			
		||||
@cnindex scanl/6
 | 
			
		||||
         Left scan of  list.  
 | 
			
		||||
 | 
			
		||||
@item scanl(:@var{Pred}, +@var{List1}, +@var{List2}, +@var{List3}, +@var{List4}, ?@var{V0}, ?@var{Vs})
 | 
			
		||||
@findex scanl/7
 | 
			
		||||
@snindex scanl/7
 | 
			
		||||
@cnindex scanl/7
 | 
			
		||||
         Left scan of  list.  
 | 
			
		||||
 | 
			
		||||
@item mapargs(+@var{Pred}, ?@var{TermIn}, ?@var{TermOut})
 | 
			
		||||
@findex mapargs/3
 | 
			
		||||
@snindex mapargs/3
 | 
			
		||||
 
 | 
			
		||||
@@ -13,22 +13,31 @@
 | 
			
		||||
 | 
			
		||||
 | 
			
		||||
:- module(maplist, [selectlist/3,
 | 
			
		||||
			 checklist/2,
 | 
			
		||||
			 maplist/2,			% :Goal, +List
 | 
			
		||||
			 maplist/3,			% :Goal, ?List1, ?List2
 | 
			
		||||
			 maplist/4,			% :Goal, ?List1, ?List2, ?List
 | 
			
		||||
			 maplist/5,			% :Goal, ?List1, ?List2, ?List3, List4
 | 
			
		||||
			 convlist/3,
 | 
			
		||||
			 mapargs/3,
 | 
			
		||||
			 sumargs/4,
 | 
			
		||||
			 mapnodes/3,
 | 
			
		||||
			 checknodes/2,
 | 
			
		||||
			 sumlist/4,
 | 
			
		||||
			 sumnodes/4,
 | 
			
		||||
			 include/3,
 | 
			
		||||
			 exclude/3,
 | 
			
		||||
			 partition/4,
 | 
			
		||||
			 partition/5			
 | 
			
		||||
		    checklist/2,
 | 
			
		||||
		    maplist/2,			% :Goal, +List
 | 
			
		||||
		    maplist/3,			% :Goal, ?List1, ?List2
 | 
			
		||||
		    maplist/4,			% :Goal, ?List1, ?List2, ?List
 | 
			
		||||
		    maplist/5,			% :Goal, ?List1, ?List2, ?List3, List4
 | 
			
		||||
		    convlist/3,
 | 
			
		||||
		    mapargs/3,
 | 
			
		||||
		    sumargs/4,
 | 
			
		||||
		    mapnodes/3,
 | 
			
		||||
		    checknodes/2,
 | 
			
		||||
		    sumlist/4,
 | 
			
		||||
		    sumnodes/4,
 | 
			
		||||
		    include/3,
 | 
			
		||||
		    exclude/3,
 | 
			
		||||
		    partition/4,
 | 
			
		||||
		    partition/5,			
 | 
			
		||||
		    foldl/4,			% :Pred, +List, ?V0, ?V
 | 
			
		||||
		    foldl/5,			% :Pred, +List1, +List2, ?V0, ?V
 | 
			
		||||
		    foldl/6,			% :Pred, +List1, +List2, +List3, ?V0, ?V
 | 
			
		||||
		    foldl/7,			% :Pred, +List1, +List2, +List3, +List4,
 | 
			
		||||
				% ?V0, ?V
 | 
			
		||||
		    scanl/4,			% :Pred, +List, ?V0, ?Vs
 | 
			
		||||
		    scanl/5,			% :Pred, +List1, +List2, ?V0, ?Vs
 | 
			
		||||
		    scanl/6,			% :Pred, +List1, +List2, +List3, ?V0, ?Vs
 | 
			
		||||
		    scanl/7			% :Pred, +List1, +List2, +List3, +List4,
 | 
			
		||||
			]).
 | 
			
		||||
 | 
			
		||||
 | 
			
		||||
@@ -54,7 +63,15 @@
 | 
			
		||||
	include(1,+,-),
 | 
			
		||||
	exclude(1,+,-),
 | 
			
		||||
	partition(2,+,-,-),
 | 
			
		||||
	partition(2,+,-,-,-).
 | 
			
		||||
	partition(2,+,-,-,-),
 | 
			
		||||
	foldl(3, +, +, -),
 | 
			
		||||
	foldl(4, +, +, +, -),
 | 
			
		||||
	foldl(5, +, +, +, +, -),
 | 
			
		||||
	foldl(6, +, +, +, +, +, -),
 | 
			
		||||
	scanl(3, +, +, -),
 | 
			
		||||
	scanl(4, +, +, +, -),
 | 
			
		||||
	scanl(5, +, +, +, +, -),
 | 
			
		||||
	scanl(6, +, +, +, +, +, -).
 | 
			
		||||
	
 | 
			
		||||
	
 | 
			
		||||
:- use_module(library(lists), [append/3]).
 | 
			
		||||
@@ -256,6 +273,116 @@ sumnodes_body(Pred, Term, A1, A3, N0, Ar) :-
 | 
			
		||||
	A1 = A3.
 | 
			
		||||
 | 
			
		||||
 | 
			
		||||
		 /*******************************
 | 
			
		||||
		 *	      FOLDL		*
 | 
			
		||||
		 *******************************/
 | 
			
		||||
 | 
			
		||||
%%	foldl(:Goal, +List, +V0, -V).
 | 
			
		||||
%%	foldl(:Goal, +List1, +List2, +V0, -V).
 | 
			
		||||
%%	foldl(:Goal, +List1, +List2, +List3, +V0, -V).
 | 
			
		||||
%%	foldl(:Goal, +List1, +List2, +List3, +List4, +V0, -V).
 | 
			
		||||
%
 | 
			
		||||
%	Fold a list, using arguments of the   list as left argument. The
 | 
			
		||||
%	foldl family of predicates is defined by:
 | 
			
		||||
%
 | 
			
		||||
%	  ==
 | 
			
		||||
%	  foldl(P, [X11,...,X1n], ..., [Xm1,...,Xmn], V0, Vn) :-
 | 
			
		||||
%		P(X11, ..., Xm1, V0, V1),
 | 
			
		||||
%		...
 | 
			
		||||
%		P(X1n, ..., Xmn, V', Vn).
 | 
			
		||||
%	  ==
 | 
			
		||||
 | 
			
		||||
foldl(Goal, List, V0, V) :-
 | 
			
		||||
	foldl_(List, Goal, V0, V).
 | 
			
		||||
 | 
			
		||||
foldl_([], _, V, V).
 | 
			
		||||
foldl_([H|T], Goal, V0, V) :-
 | 
			
		||||
	call(Goal, H, V0, V1),
 | 
			
		||||
	foldl_(T, Goal, V1, V).
 | 
			
		||||
 | 
			
		||||
 | 
			
		||||
foldl(Goal, List1, List2, V0, V) :-
 | 
			
		||||
	foldl_(List1, List2, Goal, V0, V).
 | 
			
		||||
 | 
			
		||||
foldl_([], [], _, V, V).
 | 
			
		||||
foldl_([H1|T1], [H2|T2], Goal, V0, V) :-
 | 
			
		||||
	call(Goal, H1, H2, V0, V1),
 | 
			
		||||
	foldl_(T1, T2, Goal, V1, V).
 | 
			
		||||
 | 
			
		||||
 | 
			
		||||
foldl(Goal, List1, List2, List3, V0, V) :-
 | 
			
		||||
	foldl_(List1, List2, List3, Goal, V0, V).
 | 
			
		||||
 | 
			
		||||
foldl_([], [], [], _, V, V).
 | 
			
		||||
foldl_([H1|T1], [H2|T2], [H3|T3], Goal, V0, V) :-
 | 
			
		||||
	call(Goal, H1, H2, H3, V0, V1),
 | 
			
		||||
	foldl_(T1, T2, T3, Goal, V1, V).
 | 
			
		||||
 | 
			
		||||
 | 
			
		||||
foldl(Goal, List1, List2, List3, List4, V0, V) :-
 | 
			
		||||
	foldl_(List1, List2, List3, List4, Goal, V0, V).
 | 
			
		||||
 | 
			
		||||
foldl_([], [], [], [], _, V, V).
 | 
			
		||||
foldl_([H1|T1], [H2|T2], [H3|T3], [H4|T4], Goal, V0, V) :-
 | 
			
		||||
	call(Goal, H1, H2, H3, H4, V0, V1),
 | 
			
		||||
	foldl_(T1, T2, T3, T4, Goal, V1, V).
 | 
			
		||||
 | 
			
		||||
 | 
			
		||||
		 /*******************************
 | 
			
		||||
		 *	       SCANL		*
 | 
			
		||||
		 *******************************/
 | 
			
		||||
 | 
			
		||||
%%	scanl(:Goal, +List, +V0, -Values).
 | 
			
		||||
%%	scanl(:Goal, +List1, +List2, +V0, -Values).
 | 
			
		||||
%%	scanl(:Goal, +List1, +List2, +List3, +V0, -Values).
 | 
			
		||||
%%	scanl(:Goal, +List1, +List2, +List3, +List4, +V0, -Values).
 | 
			
		||||
%
 | 
			
		||||
%	Left scan of  list.  The  scanl   family  of  higher  order list
 | 
			
		||||
%	operations is defined by:
 | 
			
		||||
%
 | 
			
		||||
%	  ==
 | 
			
		||||
%	  scanl(P, [X11,...,X1n], ..., [Xm1,...,Xmn], V0, [V0,V1,...,Vn]) :-
 | 
			
		||||
%		P(X11, ..., Xmn, V0, V1),
 | 
			
		||||
%		...
 | 
			
		||||
%	        P(X1n, ..., Xmn, V', Vn).
 | 
			
		||||
%	  ==
 | 
			
		||||
 | 
			
		||||
scanl(Goal, List, V0, [V0|Values]) :-
 | 
			
		||||
	scanl_(List, Goal, V0, Values).
 | 
			
		||||
 | 
			
		||||
scanl_([], _, _, []).
 | 
			
		||||
scanl_([H|T], Goal, V, [VH|VT]) :-
 | 
			
		||||
	call(Goal, H, V, VH),
 | 
			
		||||
	scanl_(T, Goal, VH, VT).
 | 
			
		||||
 | 
			
		||||
 | 
			
		||||
scanl(Goal, List1, List2, V0, [V0|Values]) :-
 | 
			
		||||
	scanl_(List1, List2, Goal, V0, Values).
 | 
			
		||||
 | 
			
		||||
scanl_([], [], _, _, []).
 | 
			
		||||
scanl_([H1|T1], [H2|T2], Goal, V, [VH|VT]) :-
 | 
			
		||||
	call(Goal, H1, H2, V, VH),
 | 
			
		||||
	scanl_(T1, T2, Goal, VH, VT).
 | 
			
		||||
 | 
			
		||||
 | 
			
		||||
scanl(Goal, List1, List2, List3, V0, [V0|Values]) :-
 | 
			
		||||
	scanl_(List1, List2, List3, Goal, V0, Values).
 | 
			
		||||
 | 
			
		||||
scanl_([], [], [], _, _, []).
 | 
			
		||||
scanl_([H1|T1], [H2|T2], [H3|T3], Goal, V, [VH|VT]) :-
 | 
			
		||||
	call(Goal, H1, H2, H3, V, VH),
 | 
			
		||||
	scanl_(T1, T2, T3, Goal, VH, VT).
 | 
			
		||||
 | 
			
		||||
 | 
			
		||||
scanl(Goal, List1, List2, List3, List4, V0, [V0|Values]) :-
 | 
			
		||||
	scanl_(List1, List2, List3, List4, Goal, V0, Values).
 | 
			
		||||
 | 
			
		||||
scanl_([], [], [], [], _, _, []).
 | 
			
		||||
scanl_([H1|T1], [H2|T2], [H3|T3], [H4|T4], Goal, V, [VH|VT]) :-
 | 
			
		||||
	call(Goal, H1, H2, H3, H4, V, VH),
 | 
			
		||||
	scanl_(T1, T2, T3, T4, Goal, VH, VT).
 | 
			
		||||
 | 
			
		||||
 | 
			
		||||
:- dynamic number_of_expansions/1.
 | 
			
		||||
 | 
			
		||||
number_of_expansions(0).
 | 
			
		||||
@@ -542,6 +669,69 @@ goal_expansion(sumlist(Meta, List, AccIn, AccOut), Mod:Goal) :-
 | 
			
		||||
		     (RecursionHead :- Apply, RecursiveCall)
 | 
			
		||||
		    ], Mod).
 | 
			
		||||
 | 
			
		||||
goal_expansion(foldl(Meta, List, AccIn, AccOut), Mod:Goal) :-
 | 
			
		||||
	goal_expansion_allowed,
 | 
			
		||||
	callable(Meta),
 | 
			
		||||
	prolog_load_context(module, Mod),
 | 
			
		||||
	aux_preds(Meta, MetaVars, Pred, PredVars, Proto),
 | 
			
		||||
	!,
 | 
			
		||||
	% the new goal
 | 
			
		||||
	pred_name(foldl, 4, Proto, GoalName),
 | 
			
		||||
	append(MetaVars, [List, AccIn, AccOut], GoalArgs),
 | 
			
		||||
	Goal =.. [GoalName|GoalArgs],
 | 
			
		||||
	% the new predicate declaration
 | 
			
		||||
	HeadPrefix =.. [GoalName|PredVars],	
 | 
			
		||||
	append_args(HeadPrefix, [[], Acc, Acc], Base),
 | 
			
		||||
	append_args(HeadPrefix, [[In|Ins], Acc1, Acc2], RecursionHead),
 | 
			
		||||
	append_args(Pred, [In, Acc1, Acc3], Apply),
 | 
			
		||||
	append_args(HeadPrefix, [Ins, Acc3, Acc2], RecursiveCall),
 | 
			
		||||
	compile_aux([
 | 
			
		||||
		     Base,
 | 
			
		||||
		     (RecursionHead :- Apply, RecursiveCall)
 | 
			
		||||
		    ], Mod).
 | 
			
		||||
 | 
			
		||||
goal_expansion(foldl(Meta, List1, List2, AccIn, AccOut), Mod:Goal) :-
 | 
			
		||||
	goal_expansion_allowed,
 | 
			
		||||
	callable(Meta),
 | 
			
		||||
	prolog_load_context(module, Mod),
 | 
			
		||||
	aux_preds(Meta, MetaVars, Pred, PredVars, Proto),
 | 
			
		||||
	!,
 | 
			
		||||
	% the new goal
 | 
			
		||||
	pred_name(foldl, 4, Proto, GoalName),
 | 
			
		||||
	append(MetaVars, [List1, List2, AccIn, AccOut], GoalArgs),
 | 
			
		||||
	Goal =.. [GoalName|GoalArgs],
 | 
			
		||||
	% the new predicate declaration
 | 
			
		||||
	HeadPrefix =.. [GoalName|PredVars],	
 | 
			
		||||
	append_args(HeadPrefix, [[], Acc, Acc], Base),
 | 
			
		||||
	append_args(HeadPrefix, [[In|Ins], Acc1, Acc2], RecursionHead),
 | 
			
		||||
	append_args(Pred, [In, Acc1, Acc3], Apply),
 | 
			
		||||
	append_args(HeadPrefix, [Ins, Acc3, Acc2], RecursiveCall),
 | 
			
		||||
	compile_aux([
 | 
			
		||||
		     Base,
 | 
			
		||||
		     (RecursionHead :- Apply, RecursiveCall)
 | 
			
		||||
		    ], Mod).
 | 
			
		||||
 | 
			
		||||
goal_expansion(foldl(Meta, List1, List2, List3, AccIn, AccOut), Mod:Goal) :-
 | 
			
		||||
	goal_expansion_allowed,
 | 
			
		||||
	callable(Meta),
 | 
			
		||||
	prolog_load_context(module, Mod),
 | 
			
		||||
	aux_preds(Meta, MetaVars, Pred, PredVars, Proto),
 | 
			
		||||
	!,
 | 
			
		||||
	% the new goal
 | 
			
		||||
	pred_name(foldl, 4, Proto, GoalName),
 | 
			
		||||
	append(MetaVars, [List1, List2, List3, AccIn, AccOut], GoalArgs),
 | 
			
		||||
	Goal =.. [GoalName|GoalArgs],
 | 
			
		||||
	% the new predicate declaration
 | 
			
		||||
	HeadPrefix =.. [GoalName|PredVars],	
 | 
			
		||||
	append_args(HeadPrefix, [[], Acc, Acc], Base),
 | 
			
		||||
	append_args(HeadPrefix, [[In|Ins], Acc1, Acc2], RecursionHead),
 | 
			
		||||
	append_args(Pred, [In, Acc1, Acc3], Apply),
 | 
			
		||||
	append_args(HeadPrefix, [Ins, Acc3, Acc2], RecursiveCall),
 | 
			
		||||
	compile_aux([
 | 
			
		||||
		     Base,
 | 
			
		||||
		     (RecursionHead :- Apply, RecursiveCall)
 | 
			
		||||
		    ], Mod).
 | 
			
		||||
 | 
			
		||||
goal_expansion(mapargs(Meta, In, Out), Mod:NewGoal) :-
 | 
			
		||||
	goal_expansion_allowed,
 | 
			
		||||
	prolog_load_context(module, Mod),
 | 
			
		||||
 
 | 
			
		||||
		Reference in New Issue
	
	Block a user