1%   File   : Higher_Order.PL
    2%   Author : Neil Smith
    3%   Updated: 25 January 2000
    4%   Purpose: Various "function" application routines based on lpa_apply/2.
    5%   Based on the 'applic.pl' library file from the Edinburgh Prolog libraries
    6
    7:- module(higher_order, 
    8      [	% call/2,
    9       /* call/3,
   10	call/4,
   11	call/5,
   12	call/6,*/
   13	lpa_apply/1,
   14	lpa_apply/2,
   15
   16	identity/2,
   17	complement/1,
   18	complement/2,
   19	every/2,
   20	some/2,
   21	somechk/2,
   22	map/3,
   23	filter/3,
   24	mapfilter/3,
   25	partition/4,
   26	foldl/4,
   27	foldl1/3,
   28	foldr/4,
   29	foldr1/3	]).   30
   31
   32% call(X, A):- 
   33%	X =.. XL,
   34%	append(XL, [A], XLA),
   35%	XA =.. XLA,
   36%	XA.
   37:- if( \+ current_predicate(call/3) ).   38
   39call(X, A, B):- 
   40	X =.. XL,
   41	append(XL, [A, B], XLA),
   42	XA =.. XLA,
   43	XA.
   44call(X, A, B, C):- 
   45	X =.. XL,
   46	append(XL, [A, B, C], XLA),
   47	XA =.. XLA,
   48	XA.
   49call(X, A, B, C, D):- 
   50	X =.. XL,
   51	append(XL, [A, B, C, D], XLA),
   52	XA =.. XLA,
   53	XA.
   54call(X, A, B, C, D, E):- 
   55	X =.. XL,
   56	append(XL, [A, B, C, D, E], XLA),
   57	XA =.. XLA,
   58	XA.
   59:- endif.   60
   61%   lpa_apply(Pred, Args)
   62%   is the key to this whole module.  It is basically a variant of call/1
   63%   (see the Dec-10 Prolog V3.43 manual) where some of the arguments may
   64%   be already in the Pred, and the rest are passed in the list of Args.
   65%   Thus lpa_apply(foo, [X,Y]) is the same as call(foo(X,Y)),
   66%   and lpa_apply(foo(X), [Y]) is also the same as call(foo(X,Y)).
   67%   BEWARE: any goal given to lpa_apply is handed off to call/1, which is the
   68%   Prolog *interpreter*, so if you want to lpa_apply compiled predicates you
   69%   MUST have :- public declarations for them.  The ability to pass goals
   70%   around with some of their (initial) arguments already filled in is
   71%   what makes lpa_apply/2 so useful.  Don't bother compiling anything that
   72%   uses lpa_apply heavily, the compiler won't be able to help much.  LISP
   73%   has the same problem.  Later Prolog systems may have a simpler link
   74%   between compiled and interpreted code, or may fuse compilation and
   75%   interpretation, so lpa_apply/2 may come back into its own.  At the moment,
   76%   lpa_apply and the routines based on it are not well thought of.
   77
   78:- if(\+ current_predicate(lpa_apply/1)).   79lpa_apply(Pred):-
   80	lpa_apply(Pred, []).
   81
   82lpa_apply(Pred, Args) :-
   83	(	atom(Pred)
   84	->	Goal =.. [Pred|Args]
   85        ;	Pred = complement(Term)
   86	->	Goal = complement(Term, Args)
   87	;	Pred = FormalArgs ^ Term
   88	->	copy_term(FormalArgs ^ Term, Args ^ Goal)
   89	;	Pred =.. OldList,
   90		append(OldList, Args, NewList),
   91		Goal =.. NewList	),
   92	!,
   93	call(call,Goal).
   94
   95:- endif.   96
   97
   98%   identity(Item, Item)
   99%   For those cases where predictes are needed, but values supplied
  100
  101identity(Item, Item).
  102
  103
  104%   complement(Pred)
  105%   succeeds if Pred fails, otherwise it fails
  106
  107complement(Pred):-
  108	complement(Pred, []).
  109
  110complement(Pred, Args):-
  111	(	lpa_apply(Pred, Args)
  112	->	fail
  113	;	true	).
  114
  115
  116%   every(List, Pred)
  117%   suceeds when Pred(Elem) succeeds for each Elem in the List.
  118
  119every([], _Pred):-!.
  120every([Head|Tail], Pred) :-
  121	lpa_apply(Pred, [Head]),
  122	every(Tail, Pred).
  123
  124
  125%   some(List, Pred)
  126%   succeeds when Pred(Elem) succeeds for some Elem in List.  It will
  127%   try all ways of proving Pred for each Elem, and will try each Elem
  128%   in the List.  somechk/2 is to some/2 as memberchk/2 is to member/2;
  129%   you are more likely to want somechk with its single solution.
  130
  131some([Head|_], Pred) :-
  132	lpa_apply(Pred, [Head]).
  133some([_|Tail], Pred) :-
  134	some(Tail, Pred).
  135
  136
  137somechk([Head|_], Pred) :-
  138	lpa_apply(Pred, [Head]),
  139	!.
  140somechk([_|Tail], Pred) :-
  141	somechk(Tail, Pred).
  142
  143
  144
  145
  146%   map(OldList, Pred, NewList)
  147%   succeeds when Pred(Old,New) succeeds for each corresponding
  148%   Old in OldList, New in NewList.  
  149
  150map([],     _,    []).
  151map([X|Xs], Pred, [Y|Ys]):-
  152	lpa_apply(Pred, [X, Y]),
  153	map(Xs, Pred, Ys).
  154
  155
  156%   filter(List, Pred, SubList)
  157%   succeeds when SubList is the sub-sequence of the List containing all
  158%   the Elems of List for which Pred(Elem) succeeds.
  159
  160filter([],         _Pred, []).
  161filter([Head|List], Pred, SubList) :-
  162	(	lpa_apply(Pred, [Head])
  163	->	SubList = [Head|Rest]
  164	;	SubList = Rest	),
  165	filter(List, Pred, Rest).
  166
  167
  168%   mapfilter(OldList, Rewrite, NewList)
  169%   is a sort of hybrid of map/3 and filter/3.
  170%   Each element of NewList is the image under Rewrite of some
  171%   element of OldList, and order is preserved, but elements of
  172%   OldList on which Rewrite is undefined (fails) are not represented.
  173%   Thus if foo(X,Y) :- integer(X), Y is X+1.
  174%   then 
  175%            mapfilter([1,a,0,joe(99),101], foo, [2,1,102]).
  176%
  177%   (could be rewritten as
  178%            mapfilter([1,a,0,joe(99),101], [X,Y]^(integer(X), Y is X + 1), [2,1,102]).
  179%   )
  180
  181mapfilter([],        _Pred, []).
  182mapfilter([Old|Olds], Pred, NewList) :-
  183	(	lpa_apply(Pred, [Old,New])
  184	->	NewList = [New|News]
  185	;	NewList = News	),
  186	mapfilter(Olds, Pred, News).
  187
  188
  189%   partition(Elements, Predicate, Trues, Falses)
  190%   Partitions a list according to Predicate.  Each element of Elements 
  191%   for which Predicate succeeds is in Trues, and in Falses otherwise.
  192partition([], _Pred, [], []).
  193partition([Head|List], Pred, Trues, Falses):-
  194	(	lpa_apply(Pred, [Head])
  195	->	Trues = [Head|RestTrues],
  196		Falses = RestFalses
  197	;	Trues = RestTrues,
  198		Falses = [Head|RestFalses]	),
  199	partition(List, Pred, RestTrues, RestFalses).
  200
  201
  202
  203% foldl (Elements, Pred(Folded0, Element, Folded), Base, Result)
  204% Folds a list of items, by combining the leftmost items first
  205% Predicate is true if the Element folds into Folded0 to give Folded.
  206% The first item in the list is folded into the base item
  207foldl([], _, Term0, Term0).
  208foldl([X|Xs], Pred, Term0, Term):-
  209	lpa_apply(Pred, [Term0, X, Term1]),
  210	foldl(Xs, Pred, Term1, Term).
  211
  212
  213% foldl1 (Elements, Pred(Folded0, Element, Folded), Result)
  214% Folds a non-empty list of items, by combining the leftmost items first
  215% Predicate is true if the Element folds into Folded0 to give Folded.
  216% The first item in the list forms the base item
  217foldl1([X|Xs], Pred, Term):-
  218	foldl(Xs, Pred, X, Term).
  219
  220
  221% foldr (Elements, Pred(Element, Folded0, Folded), Base, Result)
  222% Folds a list of items, by combining the rightmost items first
  223% Predicate is true if the Element folds into Folded0 to give Folded.
  224% The empty list folds into the base item.
  225foldr([], _, Term0, Term0).
  226foldr([X|Xs], Pred, Term0, Term):-
  227	foldr(Xs, Pred, Term0, Term1),
  228	lpa_apply(Pred, [X, Term1, Term]).
  229
  230% foldr (Elements, Pred(Element, Folded0, Folded), Result)
  231% Folds a non-empty list of items, by combining the rightmost items first
  232% Predicate is true if the Element folds into Folded0 to give Folded.
  233% The last element of the list forms the base item.
  234
  235foldr1([X|Xs], Pred, Term):-
  236	(	Xs = []
  237	->	Term = X
  238	;	foldr1(Xs, Pred, Term0),
  239		lpa_apply(Pred, [X, Term0, Term])	)