* sweep.pl (sweep_expand_macro/2): New predicate.
* sweeprolog.el (sweeprolog-expand-macro-at-pos): New function.
(sweeprolog-expand-macro-at-point): New command.
(sweeprolog-context-menu-functions): Add...
(sweeprolog-context-menu-for-macro): New function.
* README.org (Macro Expansion): New section.
decrement or increment the same set of numbered variables by repeating
with ~-~ and ~+~.
+** Macro Expansion
+:PROPERTIES:
+:CUSTOM_ID: macro-expansion
+:DESCRIPTION: Commands for expanding SWI-Prolog macros
+:ALT_TITLE: Macro Expansion
+:END:
+
+Recent versions of SWI-Prolog include a pre-processing mechanism called
+/Prolog macros/, implemented in ~library(macros)~. It provides a convenient
+way for computing terms at compile time and using them in code.
+
+Macros are defined using special rules with ~#define(Macro, Replacement)~
+head terms. Then, when SWI-Prolog reads a term of the form ~#(Macro)~
+during compilation, it invokes the macro replacement rule and uses the
+expanded term instead.
+
+Sweep can replace macro invocations with their expansions. To expand a
+macro in your source code, use the following command:
+
+#+FINDEX: sweeprolog-expand-macro-at-point
+- Command: sweeprolog-expand-macro-at-point :: Replace the Prolog macro
+ invocation starting at point with its expansion.
+
+You can call this command with point on the ~#~ macro indicator to expand
+the macro inline. To undo the expansion, use ~C-/~ (~undo~).
+
+With Context Menu mode enabled, you can also expand macros by right-clicking
+on the ~#~ and selecting =Expand Macro= from the context menu. See also
+[[#context-menu][Context Menu]].
+
+
* Prolog Help
:PROPERTIES:
:CUSTOM_ID: prolog-help
sweep_current_breakpoints/2,
sweep_current_breakpoints_in_region/2,
sweep_breakpoint_range/2,
- sweep_breakpoint_file/2
+ sweep_breakpoint_file/2,
+ sweep_expand_macro/2
]).
:- use_module(library(pldoc)).
:- use_module(library(prolog_pack)).
:- use_module(library(prolog_deps)).
:- use_module(library(dcg/high_order)).
+:- use_module(library(macros)).
:- if(exists_source(library(help))).
:- use_module(library(help)).
sweep_breakpoint_file(Id, File) :-
breakpoint_property(Id, file(File0)),
atom_string(File0, File).
+
+sweep_expand_macro(String0, String) :-
+ sweep_current_module(M),
+ term_string(Term0, String0, [variable_names(Vs),
+ subterm_positions(Pos0),
+ module(M)]),
+ functor(Term0, '#', 1),
+ macros:expand_macros(M, Term0, Term, Pos0, _, _, _),
+ term_string(Term, String, [variable_names(Vs), module(M)]).
(interactive)
(sweeprolog-describe-predicate sweeprolog-context-menu-predicate-at-click))
+(defun sweeprolog-context-menu-expand-macro ()
+ "Expand Prolog macro at mouse click."
+ (interactive)
+ (sweeprolog-expand-macro-at-pos sweeprolog-context-menu-point-at-click))
+
(defun sweeprolog-context-menu-rename-variable ()
"Rename Prolog variable at mouse click."
(interactive)
(define-key-after menu [sweeprolog-breakpoint]
`(menu-item "Breakpoint" ,submenu))))))
+(defun sweeprolog-context-menu-for-macro (menu tok beg _end _point)
+ "Extend MENU with macro-related commands if TOK at BEG is one."
+ (pcase tok
+ (`("macro" . ,expansion)
+ (setq sweeprolog-context-menu-point-at-click beg)
+ (define-key menu [sweeprolog-expand-macro]
+ `(menu-item "Expand Macro"
+ sweeprolog-context-menu-expand-macro
+ :help ,(format "Expand macro to %s" expansion)
+ :keys "\\[sweeprolog-expand-macro-at-point]")))))
+
(defvar sweeprolog-context-menu-functions
'(sweeprolog-context-menu-for-clause
sweeprolog-context-menu-for-file
sweeprolog-context-menu-for-module
sweeprolog-context-menu-for-predicate
- sweeprolog-context-menu-for-variable)
+ sweeprolog-context-menu-for-variable
+ sweeprolog-context-menu-for-macro)
"Functions that create context menu entries for Prolog tokens.
Each function receives as its arguments the menu, the Prolog
token's description, its start position, its end position, and
(tabulated-list-print))
(pop-to-buffer buf)))
+(defun sweeprolog-expand-macro-at-pos (pos)
+ "Expand Prolog macro starting at POS.
+
+Return nil if POS is not the beginning of a macro invocation."
+ (let* ((end (save-excursion
+ (goto-char pos)
+ (sweeprolog--forward-sexp)
+ (point)))
+ (expansion
+ (sweeprolog--query-once "sweep" "sweep_expand_macro"
+ (buffer-substring-no-properties
+ pos end))))
+ (when expansion
+ (combine-after-change-calls
+ (delete-region pos end)
+ (save-excursion
+ (goto-char pos)
+ (insert expansion)))
+ t)))
+
+(defun sweeprolog-expand-macro-at-point (point)
+ "Expand Prolog macro starting at POINT."
+ (interactive "d" sweeprolog-mode)
+ (unless (sweeprolog-expand-macro-at-pos point)
+ (user-error "No macro invocation at point")))
;;;; Footer