We present a very simple implementation of lambda expressions in
ISO Prolog that fits into the existing conventions for higher order
predicates based on call/N
. No syntax or compiler
extension is needed.
?- use_module(library(clpfd)). ?- use_module(library(apply)).How to say that
Y
is different from all elements in a
list? So Y #\= X
for all X
in
list Xs
.
?- Xs = [1,2], maplist(#\=(Y), Xs). Xs = [1, 2], Y in inf..0\/3..sup.And in a list of lists?
?- Xss= [[1,2],[3]], maplist(maplist(#\=(Y)), Xss). Xss = [[1, 2], [3]], Y in inf..0\/4..sup.And that they are all greater
Y
?
into the equivalentX #> Y
for all elementsX
Now,Y #< X
for all elementsX
X
is the last
argument. We can therefore use the goal without the last
argument: #<(Y)
. Such goals with missing arguments
are called continuations. Unfortunately, we are not always
that lucky.
?- Xss= [[1,2],[3]], maplist(maplist(#<(Y)), Xss). Xss = [[1, 2], [3]], Y in inf..0.And that
Xss
+ Yss
= Zss
with pointwise
addition?
This time we went too far. We have to use an auxiliary definition
like zplus/3
. Welcome to the world of superfluous
use-once predicate names!
zplus(X,Y,Z) :- X + Y #= Z. ?- Xss= [[1,2],[3]], maplist(maplist(zplus), Xss, Yss, Zss). Xss = [[1, 2], [3]], Yss = [[_G2492, _G2495], [_G2501]], Zss = [[_G2513, _G2516], [_G2522]], 1+_G2492#=_G2513, 2+_G2495#=_G2516, 3+_G2501#=_G2522.
Can't we do this without the extra definition? After all, predicate
definitions are global which means we have to remember that name. And
finding a good name in Prolog isn't easy. For
instance, z_z_sum/3
would have been a more relational
name. Or 'x + y = z'/3
, but that would have been
ambiguous: Are we talking about elements in N, Z
or R? I can ponder such questions for days. What we would like
to have, is some device for describing all this within the argument
of maplist/4
.
That's what lambda expressions are for. There have been many attempts to include them in Prolog, but they do not fit into ISO Prolog. They require syntax and compiler extensions. Fortunately, it is possible to respect ISO Prolog's syntax and get nice lambdas that collaborate with the existing higher order programming conventions. A simple library is all we need. Here is how:
?- use_module(lambda). ?- Xss= [[1,2],[3]], maplist(maplist(\X^Y^Z^(X+Y#=Z)), Xss, Yss, Zss). Xss = [[1, 2], [3]], Yss = [[_G3804, _G3807], [_G3813]], Zss = [[_G3825, _G3828], [_G3834]], 1+_G3804#=_G3825, 2+_G3807#=_G3828, 3+_G3813#=_G3834.The underlined part is the lambda expression. It starts with a backslash and adds a caret after each argument. The scope of variables within lambdas is local. To get a global variable, i.e. a variable that is free within the expression, consider
Xss
+ Y
= Zss
:
?- Xss= [[1,2],[3]], maplist(maplist(Y+\X^Z^(X+Y#=Z)), Xss, Zss). Xss = [[1, 2], [3]], Zss = [[_G2965, _G2968], [_G2974]], 3+Y#=_G2974, 2+Y#=_G2968, 1+Y#=_G2965.Instead of a simple backslash, we use now
+\
. The
variables in the term before the +\
have a global scope.
For more details see the manual.
\
together
with a ^
for each argument. The \
is responsible for
appropriate renaming, whereas the ^
is responsible for parameter
passing. The (^)/2
is frequently used for lambda-like
parameter passing. See Pereira and Shieber's (undervalued) 1987 book
which justifies the choice
of the symbol (1st ed. p.96, digital ed.p.75, PDF p.85):
Thus the lambda expression λ x. x + 1 would be encoded in Prolog asIn Pereira and Shieber's book theX^(X+1)
. Similarly, the lambda expression λ x. λ y.wrote(y, x) would be encoded as the Prolog termX^Y^wrote(Y,X)
, assuming right associativity of "^".3
3 There is precedent for the use of the caret to form lambda expressions. The notation that Montague himself used for the lambda expression λ x.φ was (ignoring details of intensionality operators) x^φ, which we have merely linearized.
Remark: the x^ should look like a circumflex, e.g. â
^
-notation is only used
for passing parameters. No copying takes place. It therefore resembles
very closely our use of ^
.
A remark to the remark about Montague using x^ for lambda expressions: This notation is already used in Quine's Mathematical Logic.
apply/2,3...
is defined much in the same way as the still
uninvented
call/2,3...
The examples below are given in their
original syntax. Note, that have_property/2
does not
facilitate nesting, due to the argument order.
have_property([], P). have_property([X|L], P) :- apply(P,X), have_property(L, P).
R
and Y
must be declared explicitly.
common(R,L,Y) :- have_property(L, lambda(X).R(X,Y)).
common(R,L,Y) :- maplist([R,Y]+\X^call(R,X,Y),L).
common(R, L, Y) :- have_property(L, foo(R,Y)). apply(foo(R,Y),X) :- apply(R,X,Y). apply(pastime,X,Y) :- pastime(X,Y).Note, that
foo/2
corresponds closely to the
continuation call/2
.
apply
is for explicitly constructing
partial expressions.
apply(twice,F,twice(F)). apply(twice(F),X,Z) :- apply(F,X,Y), apply(F,Y,Z). apply(succ,X,Y) :- Y is X + 1. ?- apply(twice, twice, F1), apply(F1,twice,F2), apply(F2,succ,F3), apply(F3,0,Ans). F1 = twice(twice), F2 = twice(twice(twice)), F3 = twice(twice(twice(twice(succ)))), Ans = 16.How can we obtain such terms without the ad hoc facts in
apply/3
above? We would have to
use (=..)/2
, a.k.a. boum(2)
to
transform twice/0
to twice/1
. But there is a
simpler way. Remark that a continuation twice(QQ)
can
also be represented as call(twice,QQ)
! This is much in
the same way, as a goal p(X)
could be written
as call(p,X)
. For a more detailed discussion,
see Richard O'Keefe's elaboration.
twice(Cont,S0,S) :- call(Cont,S0,S1), call(Cont,S1,S). ?- call(call(twice,call(twice,call(twice,call(twice,call(succ))))),0,N). N = 16.
without compiler assistance, lambda-expressions either don't work or require more, and more error-prone, annotation than I think the average programmer would be happy with. I do not want to recommend anything which requires compiler support or even that there be a compiler.We completely agree with his distrust in compiler based approaches. Compilers in this context should reduce resource consumption and should detect certain errors statically, but they should not be required to implement variable scoping.
?- all((\(X, Y) :- Body), Xs, Ys).
?- maplist(\X^Y^Body, Xs, Ys).
common_prefix(Front, Xs, Ys) :- all((\(X, Y) :- append(Front)), Xs, Ys).
common_prefix(Front, Xs, Ys) :- maplist(Front+\append(Front), Xs, Ys).Above code is a shorthand for:
common_prefix(Front, Xs, Ys) :- maplist(Front+\X^Y^append(Front,X,Y), Xs, Ys).
''/N
. This corresponds to
our \
-notation. The major difference is that
Hiord-lambdas do not permit partial application. The other notation
using positional parameters has no direct counterpart. It is a slight
generalization of the traditional higher order approach. Both depend
on argument ordering. The extensions of Hiord are incompatible with ISO
Prolog and require extensions in various parts of a Prolog system. We
compare our approach with Hiord following the ASIAN
2004 paper, since no implementation is
available. The programs are colored as follows:
list([], _). list([X|Xs], P) :- P(X), list(Xs, P).
:- meta_predicate maplist(1,?). maplist(_, []). maplist(P, [X|Xs]) :- call(P, X), maplist(P, Xs).
all_less(L1, L2) :- map(L1, {''(X,Y) :- X < Y}, L2).
all_less(L1, L2) :- maplist(\X^Y^(X < Y), L1, L2).
same_mother(L) :- list(L, {M-> ''(S) :- child_of(S,M,_)}).
same_mother(L) :- maplist(M+\S^child_of(S,M,_), L).
same_parents(L) :- list(L, {M,F -> ''(S) :- child_of(S,M,F)}, L).
same_parents(L) :- maplist( [M,F] +\S^child_of(S,M,F), L).
same_parents(L) :- list(L, {child_of(#,_M,_F)}).
parents_of(M, F, C) :- child_of(C, M, F). same_parents(L) :- maplist(parents_of(_M,_F), L).
all_less(L1, L2) :- map(L1, {# < #}, L2).
all_less(L1, L2) :- maplist(<, L1, L2).
closure(R,X,Y) :- R(X,Y). closure(R,X,Y) :- R(X,Z), closure(R,Z,Y).
:- meta_predicate closure(2, ?,?). closure(R,S0,S) :- call(R,S0,S). closure(R,S0,S) :- call(R,S0,S1), closure(R,S1,S).
same_father(L) :- list(L, {F -> ''(S) :- child_of(S,_,F)}).
same_father(L) :- maplist(F +\ S ^ child_of(S,_,F), L).
father(F, S) :- child_of(S,_,F).
same_father(L) :- list(L, {father(_,#)}).
same_father(L) :- maplist(father(_), L).
descendent_Y(X,Y) :- closure({father(#,#)},X,Y).
descendent_Y(X,Y) :- closure(father, X,Y).
descendent_Y(X,Y) :- closure({''(F,S) :- child_of(S,_,F)},X,Y).
descendent_Y(X,Y) :- closure(\F^S^child_of(S,_,F), X,Y).
:-
set_prolog_flag(occurs_check,error).
was very helpful to locate those errors. I can only hope that also
other systems will adopt this feature, which nicely fits into ISO
Prolog's approach to unification (see 13211-1:7.3).
lists_mod(Member, List /*, Reverse*/) :- Me = { ''(X, L, R) :- L = [X|_] ; L = [_|Xs], R(X, Xs, R) }, Member = { Me -> ''(X,L) :- Me(X, L, Me) }, Li = { ''(L, P, R) :- L = [] ; L = [X|Xs], P(X), R(Xs,P,R) }, List = { Li -> ''(L,P) :- Li(L, P, Li) }.
lists_mod(Member, List) :- Me = \X^L^R^ ( L = [X|_] ; L = [_|Xs], call(R, X, Xs, R) ), Member = Me +\Xr1^Lr1^ call(Me, Xr1, Lr1, Me), Li = \Lr1^P^Rr1^ ( Lr1 = [] ; Lr1 = [X|Xs], call(P,X), call(Rr1,Xs,P,Rr1) ), List = Li +\Lr2^Pr1^call(Li,Lr2,Pr1,Li).
main(X) :- lists_mod(Member,_), Member(X,[1,3,4]).
main(X) :- lists_mod(Member,_), call(Member,X,[1,3,4]).
r1
x). Compiler support (actually term
expansion would suffice) could produce appropriate error messages to
avoid accidental clashes.
main_member(X,Xs) :- lists_mod(Member,_), call(Member, X, Xs). main_list(Xss) :- lists_mod(Member,List), call(List,Xss,\Xs^call(Member,1,Xs)). main_list2(Xss) :- lists_mod(Member,List), call(List,Xss,\[1]^true).
The lambda is realized in two steps corresponding to different predicates. The first step creates a new instance with variables renamed appropriately. The second step is responsible for argument passing.
(+\)/2,..
Instantiation with free variables.
(\)/1,...
Instantiation without free variables.
(^)/3,..
Argument passing
^(V1, G_0, V1) :- call(G_0). ^(V1, G_1, V1, V2) :- call(G_1, V2). ^(V1, G_2, V1, V2, V3) :- call(G_2, V2, V3). ^(V1, G_3, V1, V2, V3, V4) :- call(G_3, V2, V3, V4). ^(V1, G_4, V1, V2, V3, V4, V5) :- call(G_4, V2, V3, V4, V5). ^(V1, G_5, V1, V2, V3, V4, V5, V6) :- call(G_5, V2, V3, V4, V5, V6). ^(V1, G_6, V1, V2, V3, V4, V5, V6, V7) :- call(G_6, V2, V3, V4, V5, V6, V7). ^(V1, G_7, V1, V2, V3, V4, V5, V6, V7, V8) :- call(G_7, V2, V3, V4, V5, V6, V7, V8). :- op(201,xfx,+\). +\(GV, FC_0) :- copy_term(GV+FC_0,GV+C_0), call(C_0). +\(GV, FC_1, V1) :- copy_term(GV+FC_1,GV+C_1), call(C_1, V1). +\(GV, FC_2, V1, V2) :- copy_term(GV+FC_2,GV+C_2), call(C_2, V1, V2). +\(GV, FC_3, V1, V2, V3) :- copy_term(GV+FC_3,GV+C_3), call(C_3, V1, V2, V3). +\(GV, FC_4, V1, V2, V3, V4) :- copy_term(GV+FC_4,GV+C_4), call(C_4, V1, V2, V3, V4). +\(GV, FC_5, V1, V2, V3, V4, V5) :- copy_term(GV+FC_5,GV+C_5), call(C_5, V1, V2, V3, V4, V5). +\(GV, FC_6, V1, V2, V3, V4, V5, V6) :- copy_term(GV+FC_6,GV+C_6), call(C_6, V1, V2, V3, V4, V5, V6). +\(GV, FC_7, V1, V2, V3, V4, V5, V6, V7) :- copy_term(GV+FC_7,GV+C_7), call(C_7, V1, V2, V3, V4, V5, V6, V7). \(FC_0) :- copy_term(FC_0,C_0), call(C_0). \(FC_1, V1) :- copy_term(FC_1,C_1), call(C_1, V1). \(FC_2, V1, V2) :- copy_term(FC_2,C_2), call(C_2, V1, V2). \(FC_3, V1, V2, V3) :- copy_term(FC_3,C_3), call(C_3, V1, V2, V3). \(FC_4, V1, V2, V3, V4) :- copy_term(FC_4,C_4), call(C_4, V1, V2, V3, V4). \(FC_5, V1, V2, V3, V4, V5) :- copy_term(FC_5,C_5), call(C_5, V1, V2, V3, V4, V5). \(FC_6, V1, V2, V3, V4, V5, V6) :- copy_term(FC_6,C_6), call(C_6, V1, V2, V3, V4, V5, V6). \(FC_7, V1, V2, V3, V4, V5, V6, V7) :- copy_term(FC_7,C_7), call(C_7, V1, V2, V3, V4, V5, V6, V7).Above code should run immediately for systems without constraints. With constraints make sure that
copy_term/2
does not copy
constraints. Since current Prolog systems differ here quite
significantly, consider one of the following implementations:
copy_term_nat/2
.
call_residue/2
use:copy_term_nat(T, TC) :- call_residue(copy_term(T, TC),_).
copy_term/3
:copy_term_nat(T, C) :- copy_term(T, C, _).
E.g. lambdas occurring in maplist/2
can be expanded
similarly to library(apply_macros)
, if all variables are
correctly scoped statically. A clause
p(...) :- ... X ..., maplist(\Y^p(X,Y), L), ...must not compile the lambda, due to the variable
X
.
Ideally an error is produced in this case.
Systems that perform semantics altering translations when
converting a term to a clause (13211-1:7.6) do not preserve the
equivalence between a goal and the same goal wrapped
with call/1
. They should better refuse incorrectly scoped
lambda expressions altogether. Note that otherwise the only semantics
altering effect of 13211-1:7.6 w.r.t. wrapping a goal
with call/1
is the scope of cuts.
expand_term
.
(^)/2
would lead to skipping the
remaining arguments. Note that the ISO standard does not define a
predicate (^)/2
. It is rather an artefact in most current
implementations.
?- maplist(\X^Y^Z^(Z #= X+Y), [1], [3]). ERROR: user://3:324: Cannot represent due to `lambda_parameters'
setof/3
for
a predicate of larger arity? With something
like country/10
? You must have noticed the big
problem with existential variables. In Chat-80 a country's
currency is in the last argument of country/10
. What are
the currencies on this planet? We could try
?- country(_,_,_,_,_,_,_,_,_,Currency). Currency = afghani ; Currency = lek ; Currency = dinarBut we want them in an ascending list without duplicates like the popular
dinar
. So...
?- setof(Currency,country(_,_,_,_,_,_,_,_,_,Currency),Currencies). Currencies = [afghani] ; Currencies = [lek] ; Currencies = [dinar]Not exactly what we wanted. See it? Now, correct that compactly! I wish you luck. You would have to give all those anonymous variables a name! With lambdas things remain compact:
?- setof(Currency,Currency+\country(_,_,_,_,_,_,_,_,_,Currency),Currencies). Currencies = [?, afghani, ariary, australian_dollar, bahamian_dollar, baht, balboa, bolivar, ... ].
call/N
and this library are
sufficient. The real challenge is an effective error detection and an
efficient compilation scheme. But all this can be done within 13211-1
and 13211-2.
Originally: International Machine Intelligence Workshop, Cleveland, April 1981, DAI Research Paper 154.