#+KINDEX: s (help-mode)
The command ~M-x sweeprolog-describe-module~ prompts for the name of a
Prolog module and displays its documentation in the =*Help*= buffer. To
-jump to the source code from its documentation, press ~s~
+jump to the source code from the documentation, press ~s~
(~help-view-source~).
+#+FINDEX: sweeprolog-describe-predicate
+Similarly, ~M-x sweeprolog-describe-predicate~ can be used to display
+the documentation of a Prolog predicate. This commands prompts for a
+predicate with completion. When the cursor is over a predicate
+definition or invocation in a ~sweeprolog-mode~, that predicate is set
+as the default selection and can be described by simply typing ~RET~ in
+response to the prompt.
+
* The Prolog top-level
:PROPERTIES:
:CUSTOM_ID: prolog-top-level
some Debug Adapter Protocol integration similar to what was done in
~dap-swi-prolog~ (see [[https://github.com/eshelyaron/debug_adapter/blob/main/README.md][Debug Adapter Protocol for SWI-Prolog]]).
-- Provide predicate documentation in a ~help-mode~ buffer :: ~sweep~
- should include a command ~sweeprolog-describe-predicate~ that works
- similarly to the built-in ~describe-function~ by opening a ~help-mode~
- buffer and populating it with the full cross-referenced
- documentation of a given Prolog predicate. We currently have
- ~sweeprolog-describe-module~ as a proof of concept which should be
- extended to cover predicate documentation as well.
-
- Integrate with =project.el= adding support for SWI-Prolog packs :: It
would be nice if ~sweep~ would "teach" =project.el= to detect
directories containing SWI-Prolog =pack.pl= package definitions as
sweep_accept_top_level_client/2,
sweep_local_predicate_export_comment/2,
write_sweep_module_location/0,
- sweep_module_html_documentation/2
+ sweep_module_html_documentation/2,
+ sweep_predicate_html_documentation/2
]).
:- use_module(library(pldoc)).
sweep_module_path_(Module, Path) :-
'$autoload':library_index(_, Module, Path0), !, string_concat(Path0, ".pl", Path).
+sweep_predicate_html_documentation(P0, D) :-
+ term_string(P1, P0),
+ ( P1 = M:F/N
+ -> true
+ ; P1 = F/N, M = system
+ ),
+ ( ( current_module(M)
+ ; xref_module(_, M)
+ )
+ -> true
+ ; '$autoload':library_index(_, M, Path),
+ xref_source(Path, [comments(store)])
+ ),
+ ( M == system
+ -> pldoc_man:load_man_object(F/N, _, _, DOM)
+ ; doc_comment(M:F/N, Pos, _, Comment),
+ pldoc_html:pred_dom(M:F/N, [], Pos-Comment, DOM)
+ ),
+ phrase(pldoc_html:html(DOM), HTML),
+ with_output_to(string(D), html_write:print_html(HTML)).
+
sweep_module_html_documentation(M0, D) :-
atom_string(M, M0),
- ( sweep_module_path_(M, _)
+ ( ( current_module(M)
+ ; xref_module(_, M)
+ )
-> true
; '$autoload':library_index(_, M, Path),
xref_source(Path, [comments(store)])
sub_string(String, _, _, _, Sub).
sweep_predicate_non_hidden([String|_]) :-
- \+ sub_string(String, _, _, _, ":'$").
+ \+ sub_string(String, _, _, _, "$").
sweep_predicate_description(M:F/N, [S|T]) :-
sweep_predicate_description_(M, F, N, T),
;; Maintainer: Eshel Yaron <~eshel/dev@lists.sr.ht>
;; Keywords: prolog languages extensions
;; URL: https://git.sr.ht/~eshel/sweep
-;; Package-Version: 0.6.3
+;; Package-Version: 0.7.0
;; Package-Requires: ((emacs "28"))
;; This file is NOT part of GNU Emacs.
(when (sweeprolog-true-p sol)
(cdr sol))))
+(defvar sweeprolog-read-predicate-history nil)
+
(defun sweeprolog-read-predicate ()
"Read a Prolog predicate (M:F/N) from the minibuffer, with completion."
(let* ((col (sweeprolog-predicates-collection))
(if val
(concat (make-string (- 64 (length key)) ? ) (car val))
nil))))))
- (completing-read sweeprolog-read-predicate-prompt col)))
+ (completing-read sweeprolog-read-predicate-prompt col nil nil nil
+ 'sweeprolog-read-predicate-history
+ (sweeprolog-identifier-at-point))))
(defun sweeprolog-predicate-prefix-boundaries (&optional point)
(let ((case-fold-search nil))
(`("head" ,(rx "public(") . ,_)
(list (list beg end (sweeprolog-head-public-face))))
(`("head",(rx "dynamic ") ,f ,a)
- (add-to-list sweeprolog--exportable-predicates (concat f "/" (number-to-string a)))
+ (add-to-list 'sweeprolog--exportable-predicates (concat f "/" (number-to-string a)))
(list (list beg end (sweeprolog-head-dynamic-face))))
(`("head",(rx "multifile ") . ,_)
(list (list beg end (sweeprolog-head-multifile-face))))
(defvar sweeprolog-help-prefix-map
(let ((map (make-sparse-keymap)))
(define-key map "m" #'sweeprolog-describe-module)
+ (define-key map "p" #'sweeprolog-describe-predicate)
map)
"Keymap for `sweeprolog' help commands.")
(buffer-list)) ]
[ "Open Top-level Menu" sweeprolog-list-top-levels t ]
"--"
+ [ "Describe Predicate" sweeprolog-describe-predicate t ]
[ "Describe Prolog module" sweeprolog-describe-module t ]
"--"
[ "Reset sweep" sweeprolog-restart t ]
(tabulated-list-print))
(pop-to-buffer-same-window buf)))
+(defun sweeprolog-render-html-a (dom)
+ (let* ((url (dom-attr dom 'href))
+ (parsed (url-generic-parse-url url))
+ (target (url-target parsed))
+ (start (point)))
+ (shr-generic dom)
+ (cond
+ ((url-host parsed))
+ (target
+ (when (string-match (rx (one-or-more anychar)
+ "/"
+ (one-or-more digit) eos)
+ target)
+ (buttonize-region start
+ (point)
+ #'sweeprolog-describe-predicate
+ target)))
+ (t (let* ((path-and-query (url-path-and-query parsed))
+ (path (car path-and-query))
+ (query (cdr path-and-query)))
+ (cond
+ ((string= path "/pldoc/man")
+ (pcase (url-parse-query-string query)
+ (`(("predicate" ,pred))
+ (buttonize-region start
+ (point)
+ #'sweeprolog-describe-predicate
+ pred))))))))))
+
+(defun sweeprolog-render-html (html)
+ (with-temp-buffer
+ (insert html)
+ (let ((shr-external-rendering-functions
+ '((a . sweeprolog-render-html-a)
+ (var . shr-tag-i))))
+ (shr-render-region (point-min) (point-max)))
+ (buffer-string)))
+
(defun sweeprolog--describe-module (mod)
(let ((page
(progn
(let ((sol (sweeprolog-next-solution)))
(sweeprolog-close-query)
(when (sweeprolog-true-p sol)
- (with-temp-buffer
- (insert (cdr sol))
- (let ((shr-external-rendering-functions
- '((a . shr-generic))))
- (shr-render-region (point-min) (point-max)))
- (buffer-string)))))))
+ (sweeprolog-render-html (cdr sol)))))))
(help-setup-xref (list #'sweeprolog--describe-module mod)
(called-interactively-p 'interactive))
(with-help-window (help-buffer)
(interactive (list (sweeprolog-read-module-name)))
(sweeprolog--describe-module mod))
+(defun sweeprolog--describe-predicate (pred)
+ (let ((page
+ (progn
+ (sweeprolog-open-query "user"
+ "sweep"
+ "sweep_predicate_html_documentation"
+ pred)
+ (let ((sol (sweeprolog-next-solution)))
+ (sweeprolog-close-query)
+ (when (sweeprolog-true-p sol)
+ (sweeprolog-render-html (cdr sol))))))
+ (path (car (sweeprolog-predicate-location pred))))
+ (help-setup-xref (list #'sweeprolog--describe-predicate pred)
+ (called-interactively-p 'interactive))
+ (with-help-window (help-buffer)
+ (with-current-buffer (help-buffer)
+ (if path
+ (progn (setq help-mode--current-data
+ (list :symbol (intern pred)
+ :type 'swi-prolog-predicate
+ :file path))
+ (insert (buttonize pred #'sweeprolog-find-predicate pred)
+ (if page
+ (concat " is a SWI-Prolog predicate.\n\n"
+ page)
+ " is an undocumented SWI-Prolog predicate.")))
+ (if page
+ (insert pred " is a built-in SWI-Prolog predicate.\n\n"
+ page)
+ (insert pred " is not documented as a SWI-Prolog predicate.")))))))
+
+;;;###autoload
+(defun sweeprolog-describe-predicate (pred)
+ "Display the full documentation for PRED (a Prolog predicate)."
+ (interactive (list (sweeprolog-read-predicate)))
+ (sweeprolog--describe-predicate pred))
+
(defvar sweeprolog-module-documentation-regexp (rx bol (zero-or-more whitespace)
":-" (zero-or-more whitespace)
"module("))
+(defun sweeprolog--find-predicate-from-symbol (sym)
+ (sweeprolog-find-predicate (symbol-name sym)))
+
(add-to-list 'find-function-regexp-alist
(cons 'swi-prolog-module
'sweeprolog-module-documentation-regexp))
+(add-to-list 'find-function-regexp-alist
+ (cons 'swi-prolog-predicate
+ 'sweeprolog--find-predicate-from-symbol))
+
(provide 'sweeprolog)
;;; sweeprolog.el ends here