1/*
    2    Author:        Ulrich Neumerkel
    3    E-mail:        ulrich@complang.tuwien.ac.at
    4    Copyright (C): 2009 Ulrich Neumerkel. All rights reserved.
    5
    6Redistribution and use in source and binary forms, with or without
    7modification, are permitted provided that the following conditions are
    8met:
    9
   101. Redistributions of source code must retain the above copyright
   11   notice, this list of conditions and the following disclaimer.
   12
   132. Redistributions in binary form must reproduce the above copyright
   14   notice, this list of conditions and the following disclaimer in the
   15   documentation and/or other materials provided with the distribution.
   16
   17THIS SOFTWARE IS PROVIDED BY Ulrich Neumerkel ``AS IS'' AND ANY
   18EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
   19IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR
   20PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL Ulrich Neumerkel OR
   21CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL,
   22EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO,
   23PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR
   24PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF
   25LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING
   26NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS
   27SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
   28
   29The views and conclusions contained in the software and documentation
   30are those of the authors and should not be interpreted as representing
   31official policies, either expressed or implied, of Ulrich Neumerkel.
   32
   33
   34
   35*/
   36
   37:- module(lambda, [
   38		   (^)/3, (^)/4, (^)/5, (^)/6, (^)/7, (^)/8, (^)/9,
   39		   (\)/1, (\)/2, (\)/3, (\)/4, (\)/5, (\)/6, (\)/7,
   40		   (+\)/2, (+\)/3, (+\)/4, (+\)/5, (+\)/6, (+\)/7,
   41		   op(201,xfx,+\)]).

Lambda expressions

This library provides lambda expressions to simplify higher order programming based on call/N.

Lambda expressions are represented by ordinary Prolog terms. There are two kinds of lambda expressions:

Free+\X1^X2^ ..^XN^Goal

     \X1^X2^ ..^XN^Goal

The second is a shorthand for t+\X1^X2^..^XN^Goal.

Xi are the parameters.

Goal is a goal or continuation. Syntax note: Operators within Goal require parentheses due to the low precedence of the ^ operator.

Free contains variables that are valid outside the scope of the lambda expression. They are thus free variables within.

All other variables of Goal are considered local variables. They must not appear outside the lambda expression. This restriction is currently not checked. Violations may lead to unexpected bindings.

In the following example the parentheses around X>3 are necessary.

?- use_module(library(lambda)).
?- use_module(library(apply)).

?- maplist(\X^(X>3),[4,5,9]).
true.

In the following X is a variable that is shared by both instances of the lambda expression. The second query illustrates the cooperation of continuations and lambdas. The lambda expression is in this case a continuation expecting a further argument.

?- Xs = [A,B], maplist(X+\Y^dif(X,Y), Xs).
Xs = [A, B],
dif(X, A),
dif(X, B).

?- Xs = [A,B], maplist(X+\dif(X), Xs).
Xs = [A, B],
dif(X, A),
dif(X, B).

The following queries are all equivalent. To see this, use the fact f(x,y).

?- call(f,A1,A2).
?- call(\X^f(X),A1,A2).
?- call(\X^Y^f(X,Y), A1,A2).
?- call(\X^(X+\Y^f(X,Y)), A1,A2).
?- call(call(f, A1),A2).
?- call(f(A1),A2).
?- f(A1,A2).
A1 = x,
A2 = y.

Further discussions http://www.complang.tuwien.ac.at/ulrich/Prolog-inedit/ISO-Hiord

author
- Ulrich Neumerkel */
To be done
- Static expansion similar to apply_macros.
  117:- meta_predicate no_hat_call(0).  118
  119:- meta_predicate
  120	^(?,0,?),
  121	^(?,1,?,?),
  122	^(?,2,?,?,?),
  123	^(?,3,?,?,?,?),
  124	^(?,4,?,?,?,?,?),
  125	^(?,5,?,?,?,?,?,?),
  126	^(?,6,?,?,?,?,?,?,?).  127
  128
  129
  130^(V1,Goal,V1) :-
  131   no_hat_call(Goal).
  132^(V1,Goal,V1,V2) :-
  133   call(Goal,V2).
  134^(V1,Goal,V1,V2,V3) :-
  135   call(Goal,V2,V3).
  136^(V1,Goal,V1,V2,V3,V4) :-
  137   call(Goal,V2,V3,V4).
  138^(V1,Goal,V1,V2,V3,V4,V5) :-
  139   call(Goal,V2,V3,V4,V5).
  140^(V1,Goal,V1,V2,V3,V4,V5,V6) :-
  141   call(Goal,V2,V3,V4,V5,V6).
  142^(V1,Goal,V1,V2,V3,V4,V5,V6,V7) :-
  143   call(Goal,V2,V3,V4,V5,V6,V7).
  144
  145:- meta_predicate
  146	\(0),
  147	\(1,?),
  148	\(2,?,?),
  149	\(3,?,?,?),
  150	\(4,?,?,?,?),
  151	\(5,?,?,?,?,?),
  152	\(6,?,?,?,?,?,?).  153
  154\(FC) :-
  155   copy_term_nat(FC,C),no_hat_call(C).
  156\(FC,V1) :-
  157   copy_term_nat(FC,C),call(C,V1).
  158\(FC,V1,V2) :-
  159   copy_term_nat(FC,C),call(C,V1,V2).
  160\(FC,V1,V2,V3) :-
  161   copy_term_nat(FC,C),call(C,V1,V2,V3).
  162\(FC,V1,V2,V3,V4) :-
  163   copy_term_nat(FC,C),call(C,V1,V2,V3,V4).
  164\(FC,V1,V2,V3,V4,V5) :-
  165   copy_term_nat(FC,C),call(C,V1,V2,V3,V4,V5).
  166\(FC,V1,V2,V3,V4,V5,V6) :-
  167   copy_term_nat(FC,C),call(C,V1,V2,V3,V4,V5,V6).
  168
  169:- meta_predicate
  170	+\(?,0),
  171	+\(?,1,?),
  172	+\(?,2,?,?),
  173	+\(?,3,?,?,?),
  174	+\(?,4,?,?,?,?),
  175	+\(?,5,?,?,?,?,?),
  176	+\(?,6,?,?,?,?,?,?).  177
  178+\(GV,FC) :-
  179   copy_term_nat(GV+FC,GV+C),no_hat_call(C).
  180+\(GV,FC,V1) :-
  181   copy_term_nat(GV+FC,GV+C),call(C,V1).
  182+\(GV,FC,V1,V2) :-
  183   copy_term_nat(GV+FC,GV+C),call(C,V1,V2).
  184+\(GV,FC,V1,V2,V3) :-
  185   copy_term_nat(GV+FC,GV+C),call(C,V1,V2,V3).
  186+\(GV,FC,V1,V2,V3,V4) :-
  187   copy_term_nat(GV+FC,GV+C),call(C,V1,V2,V3,V4).
  188+\(GV,FC,V1,V2,V3,V4,V5) :-
  189   copy_term_nat(GV+FC,GV+C),call(C,V1,V2,V3,V4,V5).
  190+\(GV,FC,V1,V2,V3,V4,V5,V6) :-
  191   copy_term_nat(GV+FC,GV+C),call(C,V1,V2,V3,V4,V5,V6).
 no_hat_call(:Goal)
Like call, but issues an error for a goal (^)/2. Such goals are likely the result of an insufficient number of arguments.
  199no_hat_call(MGoal) :-
  200   strip_module(MGoal, _, Goal),
  201   (  nonvar(Goal),
  202      Goal = (_^_)
  203   -> throw(error(existence_error(lambda_parameters,Goal),_))
  204   ;  call(MGoal)
  205   ).
  206
  207% I would like to replace this by:
  208% V1^Goal :- throw(error(existence_error(lambda_parameters,V1^Goal),_)).