1/*
    2Copyright (c) 2018 Mauro DiNuzzo
    3
    4Permission is hereby granted, free of charge, to any person
    5obtaining a copy of this software and associated documentation
    6files (the "Software"), to deal in the Software without
    7restriction, including without limitation the rights to use,
    8copy, modify, merge, publish, distribute, sublicense, and/or sell
    9copies of the Software, and to permit persons to whom the
   10Software is furnished to do so, subject to the following
   11conditions:
   12
   13The above copyright notice and this permission notice shall be
   14included in all copies or substantial portions of the Software.
   15
   16THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND,
   17EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES
   18OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND
   19NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT
   20HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY,
   21WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING
   22FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR
   23OTHER DEALINGS IN THE SOFTWARE.
   24*/

   25
   26:- module(lambda_abstractions, [
   27        (:-)/2, (:-)/3, (:-)/4, (:-)/5, (:-)/6, (:-)/7, (:-)/8, (:-)/9, (:-)/10
   28    ]).

Lambda Expressions

This library provides a minimal set of predicates (currently about 30 lines of code) to implement anonymous predicates (i.e. lambda expressions) in Prolog (presently developed under SWI Prolog 7.x).

Please notice that this library relies on copy_term_nat/2 and term_singletons/2 predicates and is NOT fully tested.

Features

Compared to other lambda libraries, the present implementation has several advantages:

Known limitations

Examples

Example 1:

?- maplist(( (X) :- X>2 ), [3, 4, 5]).
true.

Example 2:

?- maplist(( (X, Y) :- Y is X+1 ), [1, 2, 3], List).
List = [2, 3, 4]

The following examples are adapted from http://www.complang.tuwien.ac.at/ulrich/Prolog-inedit/ISO-Hiord.html.

Example 3:

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

Example 4:

?- use_module(library(clpfd)).

?- Xss = [[1, 2], [3]], maplist(maplist(( (X, Y, Z) :- X+Y#=Z )), Xss, Yss, Zss).
Xss = [[1, 2], [3]],
Yss = [[_3308, _3314], [_3326]],
Zss = [[_3350, _3356], [_3368]],
1+_3308#=_3350,
2+_3314#=_3356,
3+_3326#=_3368.

?- Xss = [[1, 2], [3]], maplist(maplist(( (X,Z) :- X+Y#=Z )), Xss, Zss).
Xss = [[1, 2], [3]],
Zss = [[_4406, _4412], [_4424]],
3+Y#=_4424,
2+Y#=_4412,
1+Y#=_4406.

The following examples are adapted from https://blog.logtalk.org/tag/lambdas/.

Example 5:

?- maplist(( (A-B, B-A) :- true ), [1-a, 2-b, 3-c], Zs).
Zs = [a-1, b-2, c-3].

Example 6:

?- use_module(library(clpfd)).

?- maplist(( (X, Y) :- Z#=X+Y ), Xs, Ys).
Xs = Ys, Ys = [] ;
Xs = [_3210],
Ys = [_3228],
_3210+_3228#=Z ;
Xs = [_3800, _3806],
Ys = [_3824, _3830],
_3806+_3830#=Z,
_3800+_3824#=Z ;
Xs = [_4390, _4396, _4402],
Ys = [_4420, _4426, _4432],
_4402+_4432#=Z,
_4396+_4426#=Z,
_4390+_4420#=Z ;
...

The following example is adapted from https://rosettacode.org/wiki/Y_combinator#Prolog.

Example 7:

% The Y combinator
y(P, Arg, R) :-
        Pred = ((Nb2, F2) :- call(P, Nb2, F2, P)),
        call(Pred, Arg, R).

?-
    Fib = ( (N, F, P) :- (N<2 -> F=N ; N1 is N-1, N2 is N-2, call(P, N1, F1, P), call(P, N2, F2, P), F is F1+F2) ),
    y(Fib, 10, FR), format('Fib(~w) = ~w~n', [10, FR]),
    Fact = ( (N, F, P) :- (N=1 -> F=N ; N1 is N-1, call(P, N1, F1, P), F is N*F1) ),
    y(Fact, 10, FF), format('Fact(~w) = ~w~n', [10, FF]).
Fib(10) = 55
Fact(10) = 3628800
true.

Other examples.

Example 8:

% side-effects

?- X = 5, ( (X, Y, Z) :- Y is X+X, Z is Y+Y, format('Double of ~w is ~w.\nDouble of ~w is ~w.\n', [X, Y, Y, Z]) ).
Double of 5 is 10.
Double of 10 is 20.
X = 5.

Example 9: == % side-effects and nesting

?- X = 5, ( (X, Y, Z) :- Y is X+X, format('Double of ~w is ~w.\n', [X, Y]), ( (Y, Z) :- Z is Y+Y, format('Double of ~w is ~w.\n', [Y, Z]) ) ). Double of 5 is 10. Double of 10 is 20. X = 5.


Example 10:
~~~{.pl}
% Forcing variables to be local using var/1
% Example provided by Ulrich Neumerkel

?- maplist(( (p(s(_))) :- true ), [A,B]).
A = B, B = p(s(_2634)).

?- maplist(( (p(s(X))) :- var(X) ), [A,B]). % no singletons anymore
A = p(s(_3104)),
B = p(s(_3176)).

?- maplist(( (X, Y) :- true ), [A, B], L).
X = A, A = B,
L = [Y, Y].

?- maplist(( (X, Y) :- var(X), var(Y) ), [A, B], L).
L = [_3116, _3210].

Example 11:

% Adapted from an example provided by Jan Burse

?- Y=6, maplist(( (X, H) :- H is sqrt(X*X+Y*Y) ), [1,2,3,4,5], L).
Y = 6,
L = [6.082762530298219, 6.324555320336759, 6.708203932499369, 7.211102550927978, 7.810249675906654].

?- maplist(( (X, H) :- H is sqrt(X*X+Y*Y) ), [1,2,3,4,5], L).
ERROR: Arguments are not sufficiently instantiated

Download and installation

To install and use the module, type:

?- pack_install(lambda_abstractions).
true
?- use_module(library(lambda_abstractions)).

from the Prolog toplevel.

Enjoy!

Planned Improvements

Planned improvements include:

Version 0.2.1

Version 0.1.1

  274:- meta_predicate
  275    :-(?, 0),
  276    :-(?, 0, ?),
  277    :-(?, 0, ?, ?),
  278    :-(?, 0, ?, ?, ?),
  279    :-(?, 0, ?, ?, ?, ?),
  280    :-(?, 0, ?, ?, ?, ?, ?),
  281    :-(?, 0, ?, ?, ?, ?, ?, ?),
  282    :-(?, 0, ?, ?, ?, ?, ?, ?, ?),
  283    :-(?, 0, ?, ?, ?, ?, ?, ?, ?, ?).
  284
  285:-(Head, Body) :- lambda(Head, Body, _).
  286:-(Head, Body, V1) :- lambda(Head, Body, (V1)).
  287:-(Head, Body, V1, V2) :- lambda(Head, Body, (V1, V2)).
  288:-(Head, Body, V1, V2, V3) :- lambda(Head, Body, (V1, V2, V3)).
  289:-(Head, Body, V1, V2, V3, V4) :- lambda(Head, Body, (V1, V2, V3, V4)).
  290:-(Head, Body, V1, V2, V3, V4, V5) :- lambda(Head, Body, (V1, V2, V3, V4, V5)).
  291:-(Head, Body, V1, V2, V3, V4, V5, V6) :- lambda(Head, Body, (V1, V2, V3, V4, V5, V6)).
  292:-(Head, Body, V1, V2, V3, V4, V5, V6, V7) :- lambda(Head, Body, (V1, V2, V3, V4, V5, V6, V7)).
  293:-(Head, Body, V1, V2, V3, V4, V5, V6, V7, V8) :- lambda(Head, Body, (V1, V2, V3, V4, V5, V6, V7, V8)).
  294
  295:- meta_predicate lambda(?, 0, ?).
  296
  297lambda(H, B, T) :-
  298    term_singletons((H, B), Globals),
  299    copy_term_nat((H, B), (Hcopy, Bcopy)),
  300    term_singletons((Hcopy, Bcopy), Globalscopy),
  301    Globals = Globalscopy,
  302    Hcopy = T,
  303    call(Bcopy).
  304
  305
  306% ?- doc_server(4000).
  307% ?- [lambda_abstractions].
  308% ?- doc_browser.