1/* 2 shorthand.pl 3 4@author Francois Fages 5@email Francois.Fages@inria.fr 6@license LGPL-2 7@version 1.1.5 8 9 General purpose definitions of shorthand functional notations with run-time expansion. 10 11*/ 12 13 14:- module( 15 shorthand, 16 [ 17 expand/1, 18 expand/2, 19 expand_subterms/2, 20 evaluate/2, 21 22 apply_list/2, 23 call_list/2, 24 call_list/3, 25 call_list/4, 26 call_list/5, 27 call_list/6 28 ]).
68:- multifile user:shorthand/3. 69:- dynamic user:shorthand/3. % just for adding shorthand clauses at toplevel as in the example above
Shorthand functional notations are expanded by expand/2, expand/1 and evaluate/2.
The Goal is not recursively expansed so write expand(Goal)
in the shorthand if it is what you wish.
The shorthands and the Goal can be non-deterministic, in which case the expansion is non-deterministic.
One shorthand notation is defined here for conditional expression if(Cond, Expr1, Expr2)
by
user:shorthand(if(Condition, Expr1, Expr2), Var, expand(Condition -> Var=Expr1 ; Var=Expr2))) :- !.
The expansion of some global variables can be specified by the user adding shorthand/3 clauses as follows (taking care of properly preserving the indexing of shorthand/3 on its first argument)
user:shorthand(global_variable_name, Value, nb_getval(global_variable_name, Value)):- !.
In library(arrays)
a shorthand clause is defined for Array[Indices] functional notation
In library(comprehension)
shorthands are expanded in "in" domain and "where" conditions
and a shorthand is defined for let expressions using let/2 predicate of that library.
In principle, any n-ary predicate for which the last argument can be interpreted as a result,
can be transformed in a shorthand functional notation with n-1 arguments.
E.g. library(clp)
uses shorthands in constraints and domains
and defines shorthand functional notations for constraints where the last argument can be interpreted as a result,
e.g. sum with 2 arguments, defined using constraint sum/3, is allowed in expressions and constraints.
103usershorthand(if(Condition, Expr1, Expr2), Var, expand((Condition -> Var=Expr1 ; Var=Expr2))) :- !.
111expand(Term, Expr):-
112 (var(Term)
113 ->
114 Expr=Term
115 ;
116 (user:shorthand(Term, T, Goal)
117 ->
118 % not expanded because perhaps too early for the arguments inside
119 ;
120 T=Term),
121 expand_subterms(T, Expr)
122 ).
129expand_subterms(Term, Expanded):-
130 (compound(Term)
131 ->
132 (Term=[T | Tail]
133 ->
134 Expanded=[ET | ETail],
135 expand_subterms(T, ET),
136 expand_subterms(Tail,ETail)
137 ;
138 Term =.. [F | Subterms],
139 call_list(expand, Subterms, ExpandedSubterms),
140 Expanded =.. [F | ExpandedSubterms]
141 )
142 ;
143 Expanded=Term
144 ).
151expand(Goal) :-
152 expand(Goal, G),
153 .
160evaluate(Expr, Number):- 161 expand(Expr, E), 162 Number is E. 163 164 165 166 % CONJUNCTIVE APPLICATION OF A GOAL TO ARGUMENTS IN LISTS 167 168:- meta_predicate apply_list( , ).
175apply_list(Goal, ArgsList):- 176 list_apply(ArgsList, Goal). 177 178 179list_apply([], _). 180list_apply([Args | ArgsList], Goal):- 181 apply(Goal, Args), 182 list_apply(ArgsList, Goal). 183 184 185:- meta_predicate call_list( , ). 186:- meta_predicate call_list( , , ). 187:- meta_predicate call_list( , , , ). 188 189:- meta_predicate list_call( , ). 190:- meta_predicate list_call( , , ). 191:- meta_predicate list_call( , , , ).
198call_list(Goal, Args1):- 199 list_call(Args1, Goal). 200 201list_call([], _). 202list_call([Arg1 | Args1], Goal):- 203 call(Goal, Arg1), 204 list_call(Args1, Goal).
212call_list(Goal, Args1, Args2):- 213 list_call(Args1, Args2, Goal). 214 215list_call([], [], _). 216list_call([Arg1 | Args1], [Arg2 | Args2], Goal):- 217 call(Goal, Arg1, Arg2), 218 list_call(Args1, Args2, Goal).
226call_list(Goal, Args1, Args2, Args3):- 227 list_call(Args1, Args2, Args3, Goal). 228 229list_call([], [], [], _). 230list_call([Arg1 | Args1], [Arg2 | Args2], [Arg3 | Args3], Goal):- 231 call(Goal, Arg1, Arg2, Arg3), 232 list_call(Args1, Args2, Args3, Goal).
240call_list(Goal, Args1, Args2, Args3, Args4):- 241 list_call(Args1, Args2, Args3, Args4, Goal). 242 243list_call([], [], [], [], _). 244list_call([Arg1 | Args1], [Arg2 | Args2], [Arg3 | Args3], [Arg4 | Args4], Goal):- 245 call(Goal, Arg1, Arg2, Arg3, Arg4), 246 list_call(Args1, Args2, Args3, Args4, Goal).
254call_list(Goal, Args1, Args2, Args3, Args4, Args5):- 255 list_call(Args1, Args2, Args3, Args4, Args5, Goal). 256 257list_call([], [], [], [], [], _). 258list_call([Arg1 | Args1], [Arg2 | Args2], [Arg3 | Args3], [Arg4 | Args4], [Arg5 | Args5], Goal):- 259 call(Goal, Arg1, Arg2, Arg3, Arg4, Arg5), 260 list_call(Args1, Args2, Args3, Args4, Args5, Goal)
General purpose definitions of shorthand functional notations with run-time expansion.
This library provides general purpose multifile shorthand/3 and expand/1 expand/2 metapredicates for introducing shorthand functional notations.
if(Condition, Expr1, Expr2)
in expressions;library(comprehension)
forlet(Bindings, Expr)
expressions similarly to let/2 goal predicate defined there;library(arrays)
for Array[Indices] functional notation,library(clp)
forsum(VarDomains, Expr)
expressions with sum/3 constraint, and for all other constraints where the last argument can be seen as a result.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:
*/