% This LaTeX document was generated using the LaTeX backend of PlDoc, % The SWI-Prolog documentation system \section{library(yall): Lambda expressions} \label{sec:yall} \begin{tags} \tag{author} Paulo Moura and Jan Wielemaker \tag{To be done} Extend optimization support \end{tags} Prolog realizes \textit{high-order} programming with meta-calling. The core predicate of this is \predref{call}{1}, which simply calls its argument. This can be used to define higher-order predicates such as \predref{ignore}{1} or \predref{forall}{2}. The call/N construct calls a \textit{closure} with N-1 \textit{additional arguments}. This is used to define higher-order predicates such as the \predref{maplist}{2}-5 family or \predref{foldl}{4}-7. The \textit{closure} concept used here is somewhat different from the closure concept from functional programming. The latter is a function that is always evaluated in the context that existed at function creation time. Here, a closure is a term of arity \textit{0 \Sle{} L \Sle{} K}. The term's functor is the name of a predicate of arity \textit{K} and the term's \textit{L} arguments (where \textit{L} could be 0) correspond to \textit{L} leftmost arguments of said predicate, bound to parameter values. For example, a closure involving \predref{atom_concat}{3} might be the term \verb$atom_concat(prefix)$. In order of increasing \textit{L}, one would have increasingly more complete closures that could be passed to \predref{call}{3}, all giving the same result: \begin{code} call(atom_concat,prefix,suffix,R). call(atom_concat(prefix),suffix,R). call(atom_concat(prefix,suffix),R). call(atom_concat(prefix,suffix,R)). \end{code} 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 \verb$atom_concat(In,Postfix,Out)$, but \verb$maplist(atom_concat(Postfix),ListIn,ListOut)$ calls \verb$atom_concat(Postfix,In,Out)$. This is where \file{library(yall)} comes in, where the module name, \textit{yall}, stands for \textit{Yet Another Lambda Library}. The library allows us to write a lambda expression that \textit{wraps around} the (possibly complex) goal to call: \begin{code} ?- maplist([In,Out]>>atom_concat(In,'_p',Out), [a,b], ListOut). ListOut = [a_p, b_p]. \end{code} A bracy list \verb${...}$ specifies which variables are \textit{shared} between the wrapped goal and the surrounding context. This allows us to write the code below. Without the \verb${Postfix}$ a fresh variable would be passed to \predref{atom_concat}{3}. \begin{code} add_postfix(Postfix, ListIn, ListOut) :- maplist({Postfix}/[In,Out]>>atom_concat(In,Postfix,Out), ListIn, ListOut). \end{code} This introduces the second application area of lambda expressions: the ability to confine variables to the called goal's context. This features shines when combined with \predref{bagof}{3} or \predref{setof}{3} where one normally has to list those variables whose bindings one is \textit{not} interested in using the \verb$Var^Goal$ construct (marking \arg{Var} as existentially quantified and confining it to the called goal's context). Lambda expressions allow you to do the converse: specify the variables which one \textit{is} interested in. These variables are common to the context of the called goal and the surrounding context. Lambda expressions use the syntax below \begin{code} {...}/[...]>>Goal. \end{code} The \verb${...}$ optional part is used for lambda-free variables (the ones shared between contexts). The order of variables doesn't matter, hence the \verb${...}$ set notation. The \verb$[...]$ optional part lists lambda parameters. Here, order of variables matters, hence the list notation. As \verb$/$ and \verb$>>$ 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 \verb${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 \file{library(apply_macros)}, \file{library(yall)} allows writing one-liners for many list operations that have the same performance as hand-written code. This module implements \href{https://logtalk.org/manuals/refman/grammar.html\#lambda-expressions}{Logtalk's lambda expressions syntax}. The development of this module was sponsored by Kyndi, Inc.\vspace{0.7cm} \begin{description} \infixop{\Srshift}{+Parameters}{+Lambda} \nodescription \predicate{\Srshift}{3}{+Parameters, +Lambda, ?A1} \nodescription \predicate{\Srshift}{4}{+Parameters, +Lambda, ?A1, ?A2} \nodescription \predicate{\Srshift}{5}{+Parameters, +Lambda, ?A1, ?A2, ?A3} \nodescription \predicate{\Srshift}{6}{+Parameters, +Lambda, ?A1, ?A2, ?A3, ?A4} \nodescription \predicate{\Srshift}{7}{+Parameters, +Lambda, ?A1, ?A2, ?A3, ?A4, ?A5} \nodescription \predicate{\Srshift}{8}{+Parameters, +Lambda, ?A1, ?A2, ?A3, ?A4, ?A5, ?A6} \nodescription \predicate{\Srshift}{9}{+Parameters, +Lambda, ?A1, ?A2, ?A3, ?A4, ?A5, ?A6, ?A7} Calls a copy of \arg{Lambda}. This is similar to \verb$call(Lambda,A1,...)$, but arguments are reordered according to the list \arg{Parameters}: \begin{itemize} \item The first \verb$length(Parameters)$ arguments from \arg{A1}, ... are unified with (a copy of) \arg{Parameters}, which \textit{may} share them with variables in \arg{Lambda}. \item Possible excess arguments are passed by position. \end{itemize} \begin{arguments} \arg{Parameters} & is either a plain list of parameters or a term \verb${Free}/List$. \arg{Free} represents variables that are shared between the context and the \arg{Lambda} term. This is needed for compiling \arg{Lambda} expressions. \\ \end{arguments} \infixop{\Sdiv}{+Free}{:Lambda} \nodescription \predicate{\Sdiv}{3}{+Free, :Lambda, ?A1} \nodescription \predicate{\Sdiv}{4}{+Free, :Lambda, ?A1, ?A2} \nodescription \predicate{\Sdiv}{5}{+Free, :Lambda, ?A1, ?A2, ?A3} \nodescription \predicate{\Sdiv}{6}{+Free, :Lambda, ?A1, ?A2, ?A3, ?A4} \nodescription \predicate{\Sdiv}{7}{+Free, :Lambda, ?A1, ?A2, ?A3, ?A4, ?A5} \nodescription \predicate{\Sdiv}{8}{+Free, :Lambda, ?A1, ?A2, ?A3, ?A4, ?A5, ?A6} \nodescription \predicate{\Sdiv}{9}{+Free, :Lambda, ?A1, ?A2, ?A3, ?A4, ?A5, ?A6, ?A7} Shorthand for \verb$Free/[]>>Lambda$. This is the same as applying call/N on \arg{Lambda}, except that only variables appearing in \arg{Free} are bound by the call. For example \begin{code} p(1,a). p(2,b). ?- {X}/p(X,Y). X = 1; X = 2. \end{code} This can in particularly be combined with \predref{bagof}{3} and \predref{setof}{3} to \textit{select} particular variables to be concerned rather than using existential quantification (\predref{\Shat}{2}) to \textit{exclude} variables. For example, the two calls below are equivalent. \begin{code} setof(X, Y^p(X,Y), Xs) setof(X, {X}/p(X,_), Xs) \end{code} \predicate[semidet]{is_lambda}{1}{@Term} True if \arg{Term} is a valid Lambda expression. \predicate[det]{lambda_calls}{2}{+LambdaExpression, -Goal} \nodescription \predicate[det]{lambda_calls}{3}{+LambdaExpression, +ExtraArgs, -Goal} \arg{Goal} is the goal called if call/N is applied to \arg{LambdaExpression}, where \arg{ExtraArgs} are the additional arguments to call/N. \arg{ExtraArgs} can be an integer or a list of concrete arguments. This predicate is used for cross-referencing and code highlighting. \end{description}