25
26:- module(lambda_abstractions, [
27 (:-)/2, (:-)/3, (:-)/4, (:-)/5, (:-)/6, (:-)/7, (:-)/8, (:-)/9, (:-)/10
28 ]).
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
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
andterm_singletons/2
predicates and is NOT fully tested.Features
Compared to other lambda libraries, the present implementation has several advantages:
_/N
whose form is the well-known(Head :- Body)
construct. Therefore, there is no need for parameter passing (e.g., using the^
operator) and no continuations. Note thatBody
is mandatory (it can be set totrue
, see below for an example).\
and+\
operators as in Ulrich Nuemerkel's lambda libray or/
and>>
operators and{}
construct as in Paulo Moura's LogTalk lambdas). While it is relatively easy to force variables to be local (see below for examples), it is currently not possible to force non-singletons to be global (in most of such cases, global variables are instantiated; see below for an example).Known limitations
library(lamba_abstractions)
is almost as fast aslibrary(lamba)
but somewhat slower thanlibrary(yall)
. This is largely due to the use ofterm_singletons/2
.Examples
Example 1:
Example 2:
The following examples are adapted from http://www.complang.tuwien.ac.at/ulrich/Prolog-inedit/ISO-Hiord.html.
Example 3:
Example 4:
The following examples are adapted from https://blog.logtalk.org/tag/lambdas/.
Example 5:
Example 6:
The following example is adapted from https://rosettacode.org/wiki/Y_combinator#Prolog.
Example 7:
Other examples.
Example 8:
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 11:
Download and installation
To install and use the module, type:
from the Prolog toplevel.
Enjoy!
Planned Improvements
Planned improvements include:
meta_predicate
declarations (to identify arity for the cross-referencer) This issue has been raise in comp.lang.prolog
by Ulrich Neumerkel:However, the warnings could not be reproduced using SWI Prolog (threaded, 64 bits, version 7.6.4) under Windows 10.
Version 0.2.1
Version 0.1.1