Did you know ... Search Documentation:
Pack modeling -- prolog/shorthand.pl
PublicShow source
author
- Francois Fages
version
- 1.1.5

This library provides general purpose multifile shorthand/3 and expand/1 expand/2 metapredicates for introducing shorthand functional notations.

  • defined here for allowing conditional expression if(Condition, Expr1, Expr2) in expressions;
  • proposed for allowing global variables in expressions by adding clauses to shorthand/3;
  • defined in library(comprehension) for let(Bindings, Expr) expressions similarly to let/2 goal predicate defined there;
  • in library(arrays) for Array[Indices] functional notation,
  • in library(clp) for sum(VarDomains, Expr) expressions with sum/3 constraint, and for all other constraints where the last argument can be seen as a result.
?- X = -2, expand(Y is if(X>0, X, -X)).
X = -2,
Y = 2.

?- nb_setval(n, 42).
true.

?- asserta(user:shorthand(n, V, nb_getval(n, V))).
true.

?- expand(X is n^2).
X = 1764.

In addition, metapredicates apply_list/2 and call_list/2 up to call_list/6 are defined here, for calling a predicate to a list of arguments similarly to maplist/2 but without transposing the arguments:



 expand(+Term, ?Expanded)
First-level expansion of Term and its subterms according to multifile definitions of shorthand/3. The expansion is first-level and not recursive unless the goal in shorthand/3 clause calls expand/2.
 expand_subterms(+Term, ?Expanded)
recursive expansion of the strict subterms of Term according to multifile definitions of shorthand/3.
 expand(+Goal)
expands and calls Goal.
 evaluate(+Expr, ?Number)
evaluates an arithmetic expression with shorthand/3 functional notations.
 apply_list(+Goal, +ArgsList)
Conjunctive application of Goal to list of list of arguments ArgsList. Fails if the conjunction is not satisfiable. Similar to maplist on transposed lists of arguments.
 call_list(+Goal, ?Args)
More efficient conjunctive application of a unary Goal to each argument in list Args. Similar to maplist on transposed lists of arguments.
 call_list(+Goal, ?Args1, ?Args2)
Conjunctive application of a binary Goal to the arguments in lists Args1, Args2. Similar to maplist on transposed lists of arguments.
 call_list(+Goal, ?Args1, ?Args2, ?Args3)
Conjunctive application of a ternary Goal to the arguments in lists Args1, Args2, Args3. Similar to maplist on transposed lists of arguments.
 call_list(+Goal, ?Args1, ?Args2, ?Args3, ?Args4)
Conjunctive application of a 4-ary Goal. Similar to maplist on transposed lists of arguments.
 call_list(+Goal, ?Args1, ?Args2, ?Args3, ?Args4, ?Args5)
Conjunctive application of a 5-ary Goal. Similar to maplist on transposed lists of arguments.