1:- module(macros, 2 [ macro_position/1, % -Position 3 % private 4 expand_macros/5, % +M, +In, -Out, +P0, -P 5 include_macros/3, % +M,+Macro,-Expanded 6 op(10, fx, #) 7 ]). 8:- use_module(library(terms)). 9:- use_module(library(error)). 10:- use_module(library(lists)).
107define_macro((#define(From, To)), Clauses) => 108 valid_macro(From), 109 Clause0 = ('$macro'(From, Expansion) => Expansion = To), 110 prepare_module(Clause0, Clauses). 111define_macro((#define(From, To) :- Cond), Clauses) => 112 valid_macro(From), 113 Clause0 = ('$macro'(From, Expansion), Cond => Expansion = To), 114 prepare_module(Clause0, Clauses). 115define_macro((#import(File)), Clauses) => 116 use_module(File, []), 117 source_file_property(File, module(M)), 118 Clause0 = ('$macro'(Macro, Expansion), include_macros(M, Macro, Expansion) 119 => true), 120 prepare_module(Clause0, Clauses). 121 122define_macro(_, _) => 123 fail. 124 125valid_macro(Macro), reserved_macro(Macro) => 126 domain_error(macro, Macro). 127valid_macro(Macro), callable(Macro) => 128 true. 129valid_macro(_Macro) => 130 fail. 131 132reserved_macro(define(_,_)) => true. 133reserved_macro(import(_)) => true. 134reserved_macro(_) => fail. 135 136:- multifile 137 error:has_type/2. 138 139errorhas_type(macro, Term) :- 140 callable(Term), 141 \+ reserved_macro(Term). 142 143prepare_module(Clause0, Clauses) :- 144 prolog_load_context(module, M), 145 ( is_prepared_module(M) 146 -> Clauses = Clause0 147 ; Clauses = [ (:- multifile(('$macro'/2,term_expansion/4))), 148 (term_expansion(In, PIn, Out, Pout) :- 149 expand_macros(M, In, Out, PIn, Pout)), 150 expand_macros, 151 Clause0 152 ] 153 ). 154 155is_prepared_module(M) :- 156 current_predicate(M:expand_macros/0), 157 \+ predicate_property(M:expand_macros, imported_from(_)).
import(File)
`. It calls '$macro'/2 in M, but fails silently in
case Macro is not defined in M as it may be defined in another
imported macro file or further down in the current file.
166include_macros(M, Macro, Expanded) :-
167 catch(M:'$macro'(Macro, Expanded),
168 error(existence_error(matching_rule,
169 M:'$macro'(Macro,_)),_),
170 fail).
This predicate is not intended for direct usage.
180expand_macros(M, T0, T, P0, P) :- 181 prolog_load_context(module, M), 182 \+ is_define(T0), 183 expand_macros(M, T0, T, P0, P, _State0, _State), 184 T \== T0. 185 186is_define(#Macro), reserved_macro(Macro) => true. 187is_define((#Macro :- _)), reserved_macro(Macro) => true. 188is_define(_) => fail. 189 190:- meta_predicate 191 foldsubterms_pos( , , , , , , ). 192 193expand_macros(M, T0, T, P0, P, State0, State) :- 194 foldsubterms_pos(expand_macro(M), T0, T, P0, P, State0, State). 195 196expand_macro(M, #Macro, T, P0, P, State0, State) => 197 valid_macro(Macro), 198 arg_pos(1, P0, P1), 199 call_macro(M, Macro, Expanded, P1, P2), 200 expand_macros(M, Expanded, T, P2, P, State0, State). 201expand_macro(_, \#(T0), T, P0, P, State0, State) => 202 arg_pos(1, P0, P), 203 T = T0, State = State0. 204expand_macro(_, _, _, _, _, _, _) => 205 fail. 206 207call_macro(M, Macro, Expanded, P0, P) :- 208 b_setval('$macro_position', P0), 209 catch(M:'$macro'(Macro, Expanded), 210 error(existence_error(matching_rule, _), _), 211 macro_failed(Macro, P0)), 212 fix_pos_shape(Macro, Expanded, P0, P), 213 b_setval('$macro_position', 0). 214 215macro_failed(Macro, TermPos) :- 216 macro_error_position(TermPos, Pos), 217 throw(error(existence_error(macro, Macro), Pos)). 218 219macro_error_position(TermPos, Position) :- 220 macro_position(TermPos, AtMacro), 221 !, 222 prolog_load_context(stream, Input), 223 stream_position_to_position_term(Input, AtMacro, Position). 224macro_error_position(_, _). 225 226stream_position_to_position_term(Stream, StreamPos, 227 stream(Stream, Line, LinePos, CharNo)) :- 228 stream_position_data(line_count, StreamPos, Line), 229 stream_position_data(line_position, StreamPos, LinePos), 230 stream_position_data(char_count, StreamPos, CharNo).
File:Line:LinePos
. If File is unknown it is unified with -
. If
Line and/or LinePos are unknown they are unified with 0. This
predicate can be used in the body of a macro definition to provide
the source location. The example below defines `#pp(Var)
` to print a
variable together with the variable name and source location.
#define(pp(Var), print_message(debug, dump_var(Pos, Name, Var))) :- ( var_property(Var, name(Name)) -> true ; Name = 'Var' ), macro_position(Pos). :- multifile prolog:message//1. prolog:message(dump_var(Pos,Name,Var)) --> [ url(Pos), ': ', ansi([fg(magenta),bold], '~w', [Name]), ' = ', ansi(code, '~p', [Var]) ].
257macro_position(File:Line:LinePos) :- 258 prolog_load_context(file, File), 259 !, 260 ( b_getval('$macro_position', TermPos), 261 macro_position(TermPos, StreamPos) 262 -> stream_position_data(line_count, StreamPos, Line), 263 stream_position_data(line_position, StreamPos, LinePos) 264 ; Line = 0, 265 LinePos = 0 266 ). 267macro_position((-):0:0). 268 269macro_position(TermPos, AtMacro) :- 270 compound(TermPos), 271 arg(1, TermPos, MacroStartCharCount), 272 integer(MacroStartCharCount), 273 prolog_load_context(stream, Input), 274 stream_property(Input, reposition(true)), 275 stream_property(Input, position(Here)), 276 prolog_load_context(term_position, ClauseStart), 277 stream_position_data(char_count, ClauseStart, ClauseStartCharCount), 278 MacroStartCharCount >= ClauseStartCharCount, 279 $, 280 set_stream_position(Input, ClauseStart), 281 Skip is MacroStartCharCount - ClauseStartCharCount, 282 forall(between(1, Skip, _), get_char(Input, _)), 283 stream_property(Input, position(AtMacro)), 284 set_stream_position(Input, Here).
292fix_pos_shape(_, _, P0, _), var(P0) => 293 true. 294fix_pos_shape(_, V, P0, P), 295 atomic(V), 296 compound(P0), compound_name_arity(P0, _, Arity), Arity >= 2 => 297 P = F-T, 298 arg(1, P0, F), 299 arg(2, P0, T). 300fix_pos_shape(_, _, P0, P) => 301 P = P0.
310foldsubterms_pos(Goal, Term1, Term2, P1, P2, State0, State) :- 311 call(Goal, Term1, Term2, P1, P2, State0, State), 312 !. 313foldsubterms_pos(Goal, Term1, Term2, P1, P2, State0, State) :- 314 is_dict(Term1), 315 !, 316 pos_parts(dict, P1, P2, VPos1, VPos2), 317 dict_pairs(Term1, Tag, Pairs1), 318 fold_dict_pairs(Pairs1, Pairs2, VPos1, VPos2, Goal, State0, State), 319 dict_pairs(Term2, Tag, Pairs2). 320foldsubterms_pos(Goal, Term1, Term2, P1, P2, State0, State) :- 321 nonvar(Term1), Term1 = [_|_], % [] is not a list 322 !, 323 pos_parts(list, P1, P2, list(Elms1,Tail1), list(Elms2,Tail2)), 324 fold_list(Term1, Term2, Elms1, Elms2, Tail1, Tail2, Goal, State0, State). 325foldsubterms_pos(Goal, Term1, Term2, P1, P2, State0, State) :- 326 compound(Term1), 327 !, 328 pos_parts(compound, P1, P2, ArgPos1, ArgPos2), 329 same_functor(Term1, Term2, Arity), 330 foldsubterms_(1, Arity, Goal, Term1, Term2, ArgPos1, ArgPos2, State0, State). 331foldsubterms_pos(_, Term, Term, P, P, State, State). 332 333:- det(fold_dict_pairs/7). 334fold_dict_pairs([], [], KVPos, KVPos, _, State, State). 335fold_dict_pairs([K0-V0|T0], [K-V|T1], KVPos0, KVPos, Goal, State0, State) :- 336 ( nonvar(KVPos0), 337 selectchk(key_value_position(F,T,SF,ST,K0,KP0,VP0), KVPos0, 338 key_value_position(F,T,SF,ST,K, KP, VP), KVPos1) 339 -> true 340 ; true 341 ), 342 foldsubterms_pos(Goal, K0, K, KP0, KP, State0, State1), 343 foldsubterms_pos(Goal, V0, V, VP0, VP, State1, State2), 344 fold_dict_pairs(T0, T1, KVPos1, KVPos, Goal, State2, State). 345 346:- det(fold_list/9). 347fold_list(Var0, Var, EP, EP, TP0, TP, Goal, State0, State) :- 348 var(Var0), 349 !, 350 foldsubterms_pos(Goal, Var0, Var, TP0, TP, State0, State). 351fold_list([], [], [], [], TP, TP, _, State, State) :- 352 !. 353fold_list([H0|T0], [H|T], [EP0|EPT0], [EP1|EPT1], TP1, TP2, Goal, State0, State) :- 354 !, 355 foldsubterms_pos(Goal, H0, H, EP0, EP1, State0, State1), 356 fold_list(T0, T, EPT0, EPT1, TP1, TP2, Goal, State1, State). 357fold_list(T0, T, EP, EP, TP0, TP, Goal, State0, State) :- 358 foldsubterms_pos(Goal, T0, T, TP0, TP, State0, State). 359 360:- det(foldsubterms_/9). 361foldsubterms_(I, Arity, Goal, Term1, Term2, PosIn, PosOut, State0, State) :- 362 I =< Arity, 363 !, 364 ( PosIn = [AP1|APT1] 365 -> PosOut = [AP2|APT2] 366 ; true 367 ), 368 arg(I, Term1, A1), 369 arg(I, Term2, A2), 370 foldsubterms_pos(Goal, A1, A2, AP1, AP2, State0, State1), 371 I2 is I+1, 372 foldsubterms_(I2, Arity, Goal, Term1, Term2, APT1, APT2, State1, State). 373foldsubterms_(_, _, _, _, _, _, [], State, State). 374 375:- det(pos_parts/5). 376pos_parts(_, Var, _, _, _), var(Var) => true. 377pos_parts(Type, parentheses_term_position(F,T,In), PosOut, SubIn, SubOut) => 378 PosOut = parentheses_term_position(F,T,Out), 379 pos_parts(Type, In, Out, SubIn, SubOut). 380pos_parts(compound, term_position(From, To, FFrom, FTo, SubPos), 381 PosOut, SubIn, SubOut) => 382 PosOut = term_position(From, To, FFrom, FTo, SubOut), 383 SubIn = SubPos. 384pos_parts(compound, brace_term_position(From, To, ArgPos0), 385 PosOut, SubIn, SubOut) => 386 PosOut = brace_term_position(From, To, ArgPos), 387 SubIn = [ArgPos0], 388 SubOut = [ArgPos]. 389pos_parts(list, list_position(From, To, Elms, Tail), 390 PosOut, SubIn, SubOut) => 391 PosOut = list_position(From, To, Elms1, Tail1), 392 SubIn = list(Elms, Tail), 393 SubOut = list(Elms1, Tail1). 394pos_parts(dict, dict_position(From, To, TagFrom, TagTo, KVPosIn), 395 PosOut, SubIn, SubOut) => 396 PosOut = dict_position(From, To, TagFrom, TagTo, SubOut), 397 SubIn = KVPosIn. 398pos_parts(_, _, _, _, _) => 399 true. % mismatch term and pos 400 401arg_pos(_, TermPos, _), var(TermPos) => true. 402arg_pos(I, parentheses_term_position(_,_,TP), AP) => 403 arg_pos(I, TP, AP). 404arg_pos(I, term_position(_,_,_,_,APL), AP) => 405 ignore(nth1(I, APL, AP)). 406arg_pos(1, brace_term_position(_,_,TPA), AP) => 407 AP = TPA. 408arg_pos(_,_,_) => 409 true. 410 411 /******************************* 412 * REGISTER * 413 *******************************/ 414 415% Hook to deal with #define and #import if this library was loaded into 416% this context. 417 418systemterm_expansion(In, Out) :- 419 is_define(In), 420 prolog_load_context(module, M), 421 predicate_property(M:expand_macros(_,_,_,_,_), imported_from(macros)), 422 $, 423 define_macro(In, Out). 424 425 426 /******************************* 427 * MESSAGES * 428 *******************************/ 429 430:- multifile prolog:error_message//1. 431 432prologerror_message(domain_error(macro, Macro)) --> 433 [ 'Invalid macro: ~p'-[Macro] ]. 434prologerror_message(existence_error(macro, Macro)) --> 435 [ 'Failed to expand macro: ~p'-[Macro] ]. 436 437 438 /******************************* 439 * IDE SUPPORT * 440 *******************************/ 441 442:- multifile prolog_colour:term_colours/2. 443 444prolog_colourterm_colours(#define(_Macro, _Replacement), 445 expanded - [ expanded - [ classify, classify ]]). 446prolog_colourterm_colours((#define(_Macro, _Replacement) :- _Body), 447 neck(:-) - [ expanded - [ expanded - [ classify, classify ]], 448 body 449 ]). 450prolog_colourterm_colours(#import(_File), 451 expanded - [ expanded - [ file ]])
Macro expansion
This library defines a macro expansion mechanism that operates on arbitrary terms. Unlike term_expansion/2 and goal_expansion/2, a term is explicitly designed for expansion using the term
#(Macro)
. Macros are first of all intended to deal with compile time constants. They can also be used to construct terms at compile time.Defining and using macros
Macros are defined for the current module using one of the three constructs below.
Macro is a callable term, not being
define(_,_)
, orimport(_)
. Replacement is an arbitrary Prolog term. Code is a Prolog body term that must succeed and can be used to dynamically generate (parts of) Replacement.The `#
import(ModuleFile)
` definition makes all macros from the given module available for expansion in the module it appears. Normally this shall be appear after local macro definitions.A macro is called using the term
#(Macro)
.#
is defined as a low-priority (10) prefix operator to allow for `#Macro`. Macros can appear at the following places:Macros can not appear as name of a compound or tag of a dict. A term `#Macro` appearing in one of the allowed places must have a matching macro defined, i.e., `#Macro` is always expanded. An error is emitted if the expansion fails. Macro expansion is applied recursively and thus, macros may be passed to macro arguments and macro expansion may use other macros.
Macros are matched to terms using Single Sided Unification (SSU), implemented using
Head => Body
rules. This implies that the matching never instantiates variables in the term that is being expanded.Below are some examples. The first line defines the macro and the indented line after show example usage of the macro.
Macro expansion expands terms
#(Callable)
. If the argument to the #-term is not acallable
, the #-term is not modified. This notably allows for#(Var)
as used by library(clpfd) to indicate that a variable is constraint to be an (clp(fd)
) integer.Implementation details
A macro `#
define(Macro, Expanded)
:- Body.` is, after some basic sanity checks, translated into a ruleThe `#
import(File)
` is translated into:- use_module(File, [])
and a link clause that links the macro expansion from the module defined in File to the current module.Macro expansion is realised by creating a clause for term_expansion/2 in the current module. This clause results from expanding the first `#define
or
#importdefinition. Thus, if macros are defined before any other local definition for term_expansion/2 it is executed as the first step. The macro expansion fails if no macros were encounted in the term, allowing other term_expansion rules local to the module to take effect. In other words, a term holding macros is not subject to any other term expansion local to the module. It is subject to term expansion defined in module
userand
system` that is performed after the local expansion is completed.Predicates
*/