1/* Part of SWI-Prolog 2 3 Author: Paulo Moura 4 E-mail: J.Wielemaker@vu.nl 5 WWW: http://www.swi-prolog.org 6 Copyright (c) 2015, Paulo Moura, Kyndi Inc., VU University Amsterdam 7 All rights reserved. 8 9 Redistribution and use in source and binary forms, with or without 10 modification, are permitted provided that the following conditions 11 are met: 12 13 1. Redistributions of source code must retain the above copyright 14 notice, this list of conditions and the following disclaimer. 15 16 2. Redistributions in binary form must reproduce the above copyright 17 notice, this list of conditions and the following disclaimer in 18 the documentation and/or other materials provided with the 19 distribution. 20 21 THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS 22 "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT 23 LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS 24 FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE 25 COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, 26 INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, 27 BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; 28 LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER 29 CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT 30 LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN 31 ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE 32 POSSIBILITY OF SUCH DAMAGE. 33*/ 34 35:- module(yall, 36 [ (>>)/2, (>>)/3, (>>)/4, (>>)/5, (>>)/6, (>>)/7, (>>)/8, (>>)/9, 37 (/)/2, (/)/3, (/)/4, (/)/5, (/)/6, (/)/7, (/)/8, (/)/9, 38 39 lambda_calls/2, % +LambdaExt, -Goal 40 lambda_calls/3, % +Lambda, +Args, -Goal 41 is_lambda/1 % @Term 42 ]). 43:- use_module(library(error)). 44:- use_module(library(lists)). 45 46:- meta_predicate 47 '>>'( , ), 48 '>>'( , , ), 49 '>>'( , , , ), 50 '>>'( , , , , ), 51 '>>'( , , , , , ), 52 '>>'( , , , , , , ), 53 '>>'( , , , , , , , ), 54 '>>'( , , , , , , , , ). 55 56:- meta_predicate 57 '/'( , ), 58 '/'( , , ), 59 '/'( , , , ), 60 '/'( , , , , ), 61 '/'( , , , , , ), 62 '/'( , , , , , , ), 63 '/'( , , , , , , , ), 64 '/'( , , , , , , , , ).
call(Lambda,A1,...)
,
but arguments are reordered according to the list Parameters:
length(Parameters)
arguments from A1, ... are
unified with (a copy of) Parameters, which may share
them with variables in Lambda.161'>>'(Parms, Lambda) :- 162 unify_lambda_parameters(Parms, [], 163 ExtraArgs, Lambda, LambdaCopy), 164 Goal =.. [call, LambdaCopy| ExtraArgs], 165 call(). 166 167'>>'(Parms, Lambda, A1) :- 168 unify_lambda_parameters(Parms, [A1], 169 ExtraArgs, Lambda, LambdaCopy), 170 Goal =.. [call, LambdaCopy| ExtraArgs], 171 call(). 172 173'>>'(Parms, Lambda, A1, A2) :- 174 unify_lambda_parameters(Parms, [A1,A2], 175 ExtraArgs, Lambda, LambdaCopy), 176 Goal =.. [call, LambdaCopy| ExtraArgs], 177 call(). 178 179'>>'(Parms, Lambda, A1, A2, A3) :- 180 unify_lambda_parameters(Parms, [A1,A2,A3], 181 ExtraArgs, Lambda, LambdaCopy), 182 Goal =.. [call, LambdaCopy| ExtraArgs], 183 call(). 184 185'>>'(Parms, Lambda, A1, A2, A3, A4) :- 186 unify_lambda_parameters(Parms, [A1,A2,A3,A4], 187 ExtraArgs, Lambda, LambdaCopy), 188 Goal =.. [call, LambdaCopy| ExtraArgs], 189 call(). 190 191'>>'(Parms, Lambda, A1, A2, A3, A4, A5) :- 192 unify_lambda_parameters(Parms, [A1,A2,A3,A4,A5], 193 ExtraArgs, Lambda, LambdaCopy), 194 Goal =.. [call, LambdaCopy| ExtraArgs], 195 call(). 196 197'>>'(Parms, Lambda, A1, A2, A3, A4, A5, A6) :- 198 unify_lambda_parameters(Parms, [A1,A2,A3,A4,A5,A6], 199 ExtraArgs, Lambda, LambdaCopy), 200 Goal =.. [call, LambdaCopy| ExtraArgs], 201 call(). 202 203'>>'(Parms, Lambda, A1, A2, A3, A4, A5, A6, A7) :- 204 unify_lambda_parameters(Parms, [A1,A2,A3,A4,A5,A6,A7], 205 ExtraArgs, Lambda, LambdaCopy), 206 Goal =.. [call, LambdaCopy| ExtraArgs], 207 call().
Free/[]>>Lambda
. This is the same as applying
call/N on Lambda, except that only variables appearing in Free
are bound by the call. For example
p(1,a). p(2,b). ?- {X}/p(X,Y). X = 1; X = 2.
This can in particularly be combined with bagof/3 and setof/3 to select particular variables to be concerned rather than using existential quantification (^/2) to exclude variables. For example, the two calls below are equivalent.
setof(X, Y^p(X,Y), Xs) setof(X, {X}/p(X,_), Xs)
242'/'(Free, Lambda) :- 243 lambda_free(Free), 244 copy_term_nat(Free+Lambda, Free+LambdaCopy), 245 call(). 246 247'/'(Free, Lambda, A1) :- 248 lambda_free(Free), 249 copy_term_nat(Free+Lambda, Free+LambdaCopy), 250 call(LambdaCopy, A1). 251 252'/'(Free, Lambda, A1, A2) :- 253 lambda_free(Free), 254 copy_term_nat(Free+Lambda, Free+LambdaCopy), 255 call(LambdaCopy, A1, A2). 256 257'/'(Free, Lambda, A1, A2, A3) :- 258 lambda_free(Free), 259 copy_term_nat(Free+Lambda, Free+LambdaCopy), 260 call(LambdaCopy, A1, A2, A3). 261 262'/'(Free, Lambda, A1, A2, A3, A4) :- 263 lambda_free(Free), 264 copy_term_nat(Free+Lambda, Free+LambdaCopy), 265 call(LambdaCopy, A1, A2, A3, A4). 266 267'/'(Free, Lambda, A1, A2, A3, A4, A5) :- 268 lambda_free(Free), 269 copy_term_nat(Free+Lambda, Free+LambdaCopy), 270 call(LambdaCopy, A1, A2, A3, A4, A5). 271 272'/'(Free, Lambda, A1, A2, A3, A4, A5, A6) :- 273 lambda_free(Free), 274 copy_term_nat(Free+Lambda, Free+LambdaCopy), 275 call(LambdaCopy, A1, A2, A3, A4, A5, A6). 276 277'/'(Free, Lambda, A1, A2, A3, A4, A5, A6, A7) :- 278 lambda_free(Free), 279 copy_term_nat(Free+Lambda, Free+LambdaCopy), 280 call(LambdaCopy, A1, A2, A3, A4, A5, A6, A7).
292unify_lambda_parameters(Parms, _Args, _ExtraArgs, _Lambda, _LambdaCopy) :- 293 var(Parms), 294 !, 295 instantiation_error(Parms). 296unify_lambda_parameters(Free/Parms, Args, ExtraArgs, Lambda, LambdaCopy) :- 297 !, 298 lambda_free(Free), 299 must_be(list, Parms), 300 copy_term_nat(Free/Parms>>Lambda, Free/ParmsCopy>>LambdaCopy), 301 unify_lambda_parameters_(ParmsCopy, Args, ExtraArgs, 302 Free/Parms>>Lambda). 303unify_lambda_parameters(Parms, Args, ExtraArgs, Lambda, LambdaCopy) :- 304 must_be(list, Parms), 305 copy_term_nat(Parms>>Lambda, ParmsCopy>>LambdaCopy), 306 unify_lambda_parameters_(ParmsCopy, Args, ExtraArgs, 307 Parms>>Lambda). 308 309unify_lambda_parameters_([], ExtraArgs, ExtraArgs, _) :- !. 310unify_lambda_parameters_([Parm|Parms], [Arg|Args], ExtraArgs, Culprit) :- 311 !, 312 Parm = Arg, 313 unify_lambda_parameters_(Parms, Args, ExtraArgs, Culprit). 314unify_lambda_parameters_(_,_,_,Culprit) :- 315 domain_error(lambda_parameters, Culprit). 316 317lambda_free(Free) :- 318 var(Free), 319 !, 320 instantiation_error(Free). 321lambda_free({_}) :- !. 322lambda_free({}) :- !. 323lambda_free(Free) :- 324 type_error(lambda_free, Free).
333expand_lambda(Goal, Head) :- 334 Goal =.. ['>>', Parms, Lambda| ExtraArgs], 335 is_callable(Lambda), 336 nonvar(Parms), 337 lambda_functor(Parms>>Lambda, Functor), 338 ( Parms = Free/ExtraArgs 339 -> is_lambda_free(Free), 340 free_to_list(Free, FreeList) 341 ; Parms = ExtraArgs, 342 FreeList = [] 343 ), 344 append(FreeList, ExtraArgs, Args), 345 Head =.. [Functor|Args], 346 compile_aux_clause_if_new(Head, Lambda). 347expand_lambda(Goal, Head) :- 348 Goal =.. ['/', Free, Closure|ExtraArgs], 349 is_lambda_free(Free), 350 is_callable(Closure), 351 free_to_list(Free, FreeList), 352 lambda_functor(Free/Closure, Functor), 353 append(FreeList, ExtraArgs, Args), 354 Head =.. [Functor|Args], 355 Closure =.. [ClosureFunctor|ClosureArgs], 356 append(ClosureArgs, ExtraArgs, LambdaArgs), 357 Lambda =.. [ClosureFunctor|LambdaArgs], 358 compile_aux_clause_if_new(Head, Lambda). 359 360lambda_functor(Term, Functor) :- 361 copy_term_nat(Term, Copy), 362 variant_sha1(Copy, Functor0), 363 atom_concat('__aux_yall_', Functor0, Functor). 364 365free_to_list({}, []). 366free_to_list({VarsConj}, Vars) :- 367 conjunction_to_list(VarsConj, Vars). 368 369conjunction_to_list(Term, [Term]) :- 370 var(Term), 371 !. 372conjunction_to_list((Term, Conjunction), [Term|Terms]) :- 373 !, 374 conjunction_to_list(Conjunction, Terms). 375conjunction_to_list(Term, [Term]). 376 377compile_aux_clause_if_new(Head, Lambda) :- 378 prolog_load_context(module, Context), 379 ( predicate_property(Context:Head, defined) 380 -> true 381 ; compile_aux_clauses([(Head :- Lambda)]) 382 ). 383 384lambda_like(Goal) :- 385 compound(Goal), 386 compound_name_arity(Goal, Name, Arity), 387 lambda_functor(Name), 388 Arity >= 2. 389 390lambda_functor(>>). 391lambda_functor(/). 392 393:- dynamic system:goal_expansion/2. 394:- multifile system:goal_expansion/2. 395 396systemgoal_expansion(Goal, Head) :- 397 lambda_like(Goal), 398 prolog_load_context(source, _), 399 \+ current_prolog_flag(xref, true), 400 expand_lambda(Goal, Head).
406is_lambda(Term) :- 407 compound(Term), 408 compound_name_arguments(Term, Name, Args), 409 is_lambda(Name, Args). 410 411is_lambda(>>, [Params,Lambda|_]) :- 412 is_lamdba_params(Params), 413 is_callable(Lambda). 414is_lambda(/, [Free,Lambda|_]) :- 415 is_lambda_free(Free), 416 is_callable(Lambda). 417 418is_lamdba_params(Var) :- 419 var(Var), !, fail. 420is_lamdba_params(Free/Params) :- 421 !, 422 is_lambda_free(Free), 423 is_list(Params). 424 425is_lambda_free(Free) :- 426 nonvar(Free), !, (Free = {_} -> true ; Free == {}). 427 428is_callable(Term) :- 429 strip_module(Term, _, Goal), 430 callable(Goal).
442lambda_calls(LambdaExtended, Goal) :- 443 compound(LambdaExtended), 444 compound_name_arguments(LambdaExtended, Name, [A1,A2|Extra]), 445 lambda_functor(Name), 446 compound_name_arguments(Lambda, Name, [A1,A2]), 447 lambda_calls(Lambda, Extra, Goal). 448 449lambda_calls(Lambda, Extra, Goal) :- 450 integer(Extra), 451 !, 452 length(ExtraVars, Extra), 453 lambda_calls_(Lambda, ExtraVars, Goal). 454lambda_calls(Lambda, Extra, Goal) :- 455 must_be(list, Extra), 456 lambda_calls_(Lambda, Extra, Goal). 457 458lambda_calls_(Params>>Lambda, Args, Goal) :- 459 unify_lambda_parameters(Params, Args, ExtraArgs, Lambda, LambdaCopy), 460 extend(LambdaCopy, ExtraArgs, Goal). 461lambda_calls_(Free/Lambda, ExtraArgs, Goal) :- 462 copy_term_nat(Free+Lambda, Free+LambdaCopy), 463 extend(LambdaCopy, ExtraArgs, Goal). 464 465extend(Var, _, _) :- 466 var(Var), 467 !, 468 instantiation_error(Var). 469extend(Cyclic, _, _) :- 470 cyclic_term(Cyclic), 471 !, 472 type_error(acyclic_term, Cyclic). 473extend(M:Goal0, Extra, M:Goal) :- 474 !, 475 extend(Goal0, Extra, Goal). 476extend(Goal0, Extra, Goal) :- 477 atom(Goal0), 478 !, 479 Goal =.. [Goal0|Extra]. 480extend(Goal0, Extra, Goal) :- 481 compound(Goal0), 482 !, 483 compound_name_arguments(Goal0, Name, Args0), 484 append(Args0, Extra, Args), 485 compound_name_arguments(Goal, Name, Args). 486 487 488 /******************************* 489 * SYNTAX HIGHLIGHTING * 490 *******************************/ 491 492:- multifile prolog_colour:goal_colours/2. 493 494yall_colours(Lambda, built_in-[classify,body(Goal)|ArgSpecs]) :- 495 catch(lambda_calls(Lambda, Goal), _, fail), 496 Lambda =.. [>>,_,_|Args], 497 classify_extra(Args, ArgSpecs). 498 499classify_extra([], []). 500classify_extra([_|T0], [classify|T]) :- 501 classify_extra(T0, T). 502 503prolog_colourgoal_colours(Goal, Spec) :- 504 lambda_like(Goal), 505 yall_colours(Goal, Spec). 506 507 508 /******************************* 509 * XREF SUPPORT * 510 *******************************/ 511 512:- multifile prolog:called_by/4. 513 514prologcalled_by(Lambda, yall, _, [Goal]) :- 515 lambda_like(Lambda), 516 catch(lambda_calls(Lambda, Goal), _, fail). 517 518 519 /******************************* 520 * SANDBOX SUPPORT * 521 *******************************/ 522 523:- multifile 524 sandbox:safe_meta_predicate/1, 525 sandbox:safe_meta/2. 526 527sandbox:safe_meta_predicate(yall:(/)/2). 528sandbox:safe_meta_predicate(yall:(/)/3). 529sandbox:safe_meta_predicate(yall:(/)/4). 530sandbox:safe_meta_predicate(yall:(/)/5). 531sandbox:safe_meta_predicate(yall:(/)/6). 532sandbox:safe_meta_predicate(yall:(/)/7). 533 534sandbox:safe_meta(yall:Lambda, [Goal]) :- 535 compound(Lambda), 536 compound_name_arity(Lambda, >>, Arity), 537 Arity >= 2, 538 lambda_calls(Lambda, Goal)
Lambda expressions
Prolog realizes high-order programming with meta-calling. The core predicate of this is call/1, which simply calls its argument. This can be used to define higher-order predicates such as ignore/1 or forall/2. The call/N construct calls a closure with N-1 additional arguments. This is used to define higher-order predicates such as the maplist/N family or foldl/N.
The problem with higher order predicates based on call/N is that the additional arguments are always added to the end of the closure's argument list. This often requires defining trivial helper predicates to get the argument order right. For example, if you want to add a common postfix to a list of atoms you need to apply
atom_concat(In,Postfix,Out)
, butmaplist(x(PostFix),ListIn,ListOut)
callsx(PostFix,In,Out)
. This is where this library comes in, which allows us to writeThe
{...}
specifies which variables are shared between the lambda and the context. This allows us to write the code below. Without the{PostFix}
a free variable would be passed to atom_concat/3.This introduces the second application area of lambda expressions: the ability to stop binding variables in the context. This features shines when combined with bagof/3 or setof/3 where you normally have to specify the the variables in whose binding you are not interested using the
Var^Goal
construct (marking Var as existential quantified). Lambdas allow doing the reverse: specify the variables in which you are interested.Lambda expressions use the syntax below
The
{...}
optional part is used for lambda-free variables. The order of variables doesn't matter hence the{...}
set notation.The
[...]
optional part lists lambda parameters. Here order of variables matters hence the list notation.As
/
and>>
are standard infix operators, no new operators are added by this library. An advantage of this syntax is that we can simply unify a lambda expression with Free/Parameters>>Lambda to access each of its components. Spaces in the lambda expression are not a problem although the goal may need to be written between ()'s. Goals that are qualified by a module prefix also need to be wrapped inside parentheses.Combined with
library(apply_macros)
,library(yall)
allows writing one-liners for many list operations that have the same performance as hand written code.The module name, yall, stands for Yet Another Lambda Library.
This module implements Logtalk's lambda expressions syntax. The development of this module was sponsored by Kyndi, Inc.