For more information about quasi-quotations in SWI-Prolog, see
[[https://www.swi-prolog.org/pldoc/man?section=quasiquotations][library(quasi_quotations) in the SWI-Prolog manual]].
+** Hover for Help
+:PROPERTIES:
+:CUSTOM_ID: help-echo
+:DESCRIPTION: Display description of Prolog tokens by hovering with the mouse
+:ALT_TITLE: Hover for Help
+:END:
+
+In the [[#semantic-highlighting][Semantic Highlighting]] section we talked about how Sweep
+performs semantic analysis to determine the meaning of different terms
+in different contexts and highlight them accordingly. Beyond
+highlighting, Sweep can also tell you explicitly what different tokens
+in Prolog code mean by annotating them with a textual description
+that's displayed when you hover over them with the mouse.
+
+- User Option: sweeprolog-enable-help-echo :: If non-nil, annotate
+ Prolog tokens with help text via the ~help-echo~ text
+ property. Defaults to ~t~.
+- Key: C-h . (display-local-help) :: Display the ~help-echo~ text of the
+ token at point in the echo area.
+
+If the user option ~sweeprolog-enable-help-echo~ is non-nil, as it is by
+default, ~sweeprolog-mode~ annotates tokens with a short description of
+their meaning in that specific context. This is done by adding the
+~help-echo~ text property to different parts of the buffer based on
+semantic analysis. The ~help-echo~ text is automatically displayed at
+the mouse tooltip when you hover over different tokens in the buffer.
+
+Alternatively, you can display the ~help-echo~ text for the token at
+point in the echo area by typing ~C-h .~ (~C-h~ followed by dot).
+
+The ~help-echo~ description of file specification in import directives
+is especially useful as it tells you which predicates that the current
+buffer uses actually come from the imported file. For example, if we
+have a Prolog file with the following contents:
+
+#+begin_src prolog
+ :- use_module(library(lists)).
+
+ foo(Foo, Bar) :- flatten(Bar, Baz), member(Foo, Baz).
+#+end_src
+
+Then hovering over ~library(lists)~ shows:
+
+#+begin_quote
+Dependency on /usr/local/lib/swipl/library/lists.pl, resolves calls to flatten/2, member/2
+#+end_quote
+
** Maintaining Code Layout
:PROPERTIES:
:CUSTOM_ID: whitespace
of missing terms that the user can later fill in, essentially they
represent source-level unknown terms and their presence satisfies the
Prolog parser. Holes are written in the buffer as regular Prolog
-variables, but they are annotated with a special text property[fn:2]
-that allows Sweep to recognize them as holes needed to be filled.
+variables, but they are annotated with a special text property that
+allows Sweep to recognize them as holes needed to be filled.
#+KINDEX: C-c C-m
- Key: C-c RET (sweeprolog-insert-term-with-holes) :: Insert a Prolog
automatically deleted when you insert a character while the region is
active (see also [[info:emacs#Using Region][Using Region in the Emacs manual]]).
-[fn:2] see [[info:elisp#Text Properties][Text Properties in the Elisp manual]]
-
** Definitions and References
:PROPERTIES:
:CUSTOM_ID: sweeprolog-xref
sweep_format_term/2,
sweep_current_functors/2,
sweep_term_search/2,
- sweep_terms_at_point/2
+ sweep_terms_at_point/2,
+ sweep_predicate_dependencies/2
]).
:- use_module(library(pldoc)).
sweep_source_id(Path) :-
sweep_main_thread,
- user:sweep_funcall("buffer-file-name", Path),
- string(Path).
+ user:sweep_funcall("buffer-file-name", Path0),
+ string(Path0),
+ atom_string(Path, Path0).
sweep_atom_collection(Sub, Col) :-
findall(S,
sweep_file_path_in_library(Path, Spec) :-
file_name_on_path(Path, Spec0),
prolog_deps:segments(Spec0, Spec1),
- term_string(Spec1, Spec).
+ ( string(Spec1)
+ -> Spec = Spec1
+ ; term_string(Spec1, Spec)
+ ).
predicate_argument_names(M:F/A, Args) :-
doc_comment(M:F/A, _, _, C),
list_tail([_|T], T).
sweep_terms_at_point([String, Start, Point], Res) :-
- ( sweep_source_id(Path0),
- atom_string(Path, Path0),
+ ( sweep_source_id(Path),
findall(Op, xref_op(Path, Op), Ops),
( xref_module(Path, Module)
-> true
sweep_terms_at_point_(SubPos, Start, Point, Beg, End).
sweep_terms_at_point_(quasi_quotation_position(_, _, _, SubPos, _), Start, Point, Beg, End) :-
sweep_terms_at_point_(SubPos, Start, Point, Beg, End).
+
+sweep_predicate_dependencies([To0|From0], Deps) :-
+ atom_string(To, To0),
+ atom_string(From, From0),
+ setof(PI,
+ PI0^Head^By^(
+ xref_defined(To, Head, imported(From)),
+ xref_called(To, Head, By),
+ pi_head(PI0, Head),
+ term_string(PI0, PI)
+ ),
+ Deps).
:tag "Custom Function"))
:group 'sweeprolog)
+(defcustom sweeprolog-enable-help-echo t
+ "If non-nil, annotate Prolog tokens with the `help-echo' property.
+
+When enabled, `sweeprolog-mode' adds a short description to each
+token via its `help-echo' text property."
+ :package-version '((sweeprolog "0.12.0"))
+ :type 'boolean
+ :group 'sweeprolog)
;;;; Keymaps
(with-silent-modifications
(remove-list-of-text-properties beg end '(font-lock-face))))
+(defun sweeprolog-analyze-start-help-echo (beg end)
+ (with-silent-modifications
+ (remove-list-of-text-properties beg end '(help-echo))))
+
(defun sweeprolog-maybe-syntax-error-face (end)
(or (and (or (derived-mode-p 'sweeprolog-top-level-mode)
(and sweeprolog--analyze-point
- (<= (save-excursion
- (goto-char sweeprolog--analyze-point)
- (sweeprolog-beginning-of-top-term)
- (1- (point)))
- (1+ end) sweeprolog--analyze-point))
+ (<= (save-excursion
+ (goto-char sweeprolog--analyze-point)
+ (sweeprolog-beginning-of-top-term)
+ (1- (point)))
+ (1+ end) sweeprolog--analyze-point))
(< (save-excursion
(goto-char sweeprolog--analyze-point)
(sweeprolog-end-of-top-term) (point))
(goto-char hend)
(setq hole (sweeprolog--next-hole))))))))))
+(defun sweeprolog--help-echo-for-comment (kind)
+ (pcase kind
+ ("string" "XPCE method summary")
+ ("structured" "PlDoc structured comment")
+ (_ "Comment")))
+
+(defun sweeprolog--help-echo-for-dependency (file)
+ (lambda (_ buf _)
+ (let ((preds
+ (sweeprolog--query-once "sweep" "sweep_predicate_dependencies"
+ (cons (buffer-file-name buf)
+ file))))
+ (format "Dependency on %s, resolves calls to %s"
+ file
+ (mapconcat (lambda (pi)
+ (propertize pi 'face
+ (sweeprolog-predicate-indicator-face)))
+ preds ", ")))))
+
+(defun sweeprolog--help-echo-for-unused-dependency (file)
+ (format "Unused dependency on %s" file))
+
+(defun sweeprolog--help-echo-for-module (module)
+ (format "Module %s" module))
+
+(defun sweeprolog--help-echo-for-type-error (error-type)
+ (format "Type error (expected %s)" error-type))
+
+(defun sweeprolog--help-echo-for-head-functor (kind functor arity)
+ (pcase kind
+ ("unreferenced" (format "Unreferenced predicate %s/%s head term"
+ functor arity))
+ ("test" "PlUnit test")
+ ("meta" (format "Meta predicate %s/%s head term"
+ functor arity))
+ ("def_iso" (format "Built-in ISO specified predicate %s/%s head term"
+ functor arity))
+ ("def_swi" (format "Built-in SWI-Prolog predicate %s/%s head term"
+ functor arity))
+ ("iso" (format "ISO specified predicate %s/%s head term"
+ functor arity))
+ ("exported" (format "Exported predicate %s/%s head term"
+ functor arity))
+ ("hook" (format "Hook predicate %s/%s head term"
+ functor arity))
+ ("built_in" (format "Built-in predicate %s/%s head term"
+ functor arity))
+ (`("imported" . ,file) (format "Predicate %s/%s head term imported from %s"
+ functor arity file))
+ (`("extern" ,module . ,_) (format "External predicate %s/%s head term from module %s"
+ functor arity module))
+ ("public" (format "Public predicate %s/%s head term"
+ functor arity))
+ ("dynamic" (format "Public predicate %s/%s head term"
+ functor arity))
+ ("multifile" (format "Multifile predicate %s/%s head term"
+ functor arity))
+ ("local" (format "Local predicate %s/%s head term"
+ functor arity))))
+
+(defun sweeprolog--help-echo-for-goal-functor (kind functor arity)
+ (pcase kind
+ ("built_in" (format "Call to built-in predicate %s/%s"
+ functor arity))
+ (`("imported" . ,file) (format "Call to predicate %s/%s imported from %s"
+ functor arity file))
+ (`("autoload" . ,file) (format "Call to predicate %s/%s autoloaded from %s"
+ functor arity file))
+ ("global" (format "Call to global predicate %s/%s"
+ functor arity))
+ (`("global" . ,type) (format "Call to %s global predicate %s/%s"
+ type functor arity))
+ ("undefined" (format "Call to undefined predicate %s/%s"
+ functor arity))
+ ("thread_local" (format "Call to thread-local predicate %s/%s"
+ functor arity))
+ ("dynamic" (format "Call to dynamic predicate %s/%s"
+ functor arity))
+ ("multifile" (format "Call to multifile predicate %s/%s"
+ functor arity))
+ ("expanded" (format "Call to expanded predicate %s/%s"
+ functor arity))
+ (`("extern" ,module . ,_) (format "Call to external predicate %s/%s from module %s"
+ functor arity module))
+ ("recursion" (format "Recursive call to predicate %s/%s"
+ functor arity))
+ ("meta" (format "Call to meta predicate %s/%s"
+ functor arity))
+ ("foreign" (format "Call to foreign predicate %s/%s"
+ functor arity))
+ ("local" (format "Call to local predicate %s/%s"
+ functor arity))
+ ("constraint" (format "Call to constraint %s/%s"
+ functor arity))
+ ("not_callable" "Call to a non-callable term")))
+
+(defun sweeprolog-analyze-fragment-help-echo (beg end arg)
+ (when-let
+ (help-echo
+ (pcase arg
+ (`("comment" . ,kind)
+ (sweeprolog--help-echo-for-comment kind))
+ (`("head" ,kind ,functor ,arity)
+ (sweeprolog--help-echo-for-head-functor kind functor arity))
+ (`("goal" ,kind ,functor ,arity)
+ (sweeprolog--help-echo-for-goal-functor kind functor arity))
+ ("instantiation_error" "Instantiation error")
+ (`("type_error" . ,kind)
+ (sweeprolog--help-echo-for-type-error kind))
+ ("unused_import" "Unused import")
+ ("undefined_import" "Undefined import")
+ ("error" "Unknown error")
+ ("html_attribute" "HTML attribute")
+ ("html" "HTML")
+ ("dict_tag" "Dict tag")
+ ("dict_key" "Dict key")
+ ("dict_sep" "Dict separator")
+ ("meta" "Meta predicate argument specification")
+ ("flag_name" "Flag name")
+ ("no_flag_name" "Unknown flag")
+ ("ext_quant" "Existential quantification")
+ ("atom" "Atom")
+ ("float" "Float")
+ ("int" "Integer")
+ ("singleton" "Singleton variable")
+ ("option_name" "Option name")
+ ("no_option_name" "Unknown option")
+ ("control" "Control construct")
+ ("var" "Variable")
+ ("fullstop" "Fullstop")
+ ("functor" "Functor")
+ ("arity" "Arity")
+ ("predicate_indicator" "Predicate indicator")
+ ("string" "String")
+ ("codes" "Codes")
+ ("chars" "Chars")
+ (`("module" . ,module)
+ (sweeprolog--help-echo-for-module module))
+ ("neck" "Neck")
+ (`("hook" . ,_) "Hook")
+ ("hook" "Hook")
+ ("qq_type" "Quasi-quotation type specifier")
+ ("qq_sep" "Quasi-quotation separator")
+ ("qq_open" "Quasi-quotation opening delimiter")
+ ("qq_close" "Quasi-quotation closing delimiter")
+ ("identifier" "Identifier")
+ (`("file" . ,file)
+ (sweeprolog--help-echo-for-dependency file))
+ (`("file_no_depend" . ,file)
+ (sweeprolog--help-echo-for-unused-dependency file))
+ ("nofile" "Unknown file specification")
+ ("op_type" "Operator type")
+ ("keyword" "Keyword")
+ ("rational" "Rational")
+ ("dict_function" "Dict function")
+ ("dict_return_op" "Dict return operator")
+ ("func_dot" "Dict function dot")))
+ (with-silent-modifications
+ (put-text-property beg end 'help-echo help-echo))))
+
(defun sweeprolog-analyze-fragment-fullstop (beg end arg)
(pcase arg
((or "term"
(when (fboundp 'eldoc-documentation-default)
(setq-local eldoc-documentation-strategy #'eldoc-documentation-default))
(add-hook 'eldoc-documentation-functions #'sweeprolog-predicate-modes-doc nil t))
+ (when sweeprolog-enable-help-echo
+ (add-hook 'sweeprolog-analyze-region-start-hook #'sweeprolog-analyze-start-help-echo nil t)
+ (add-hook 'sweeprolog-analyze-region-fragment-hook #'sweeprolog-analyze-fragment-help-echo nil t))
(when sweeprolog-enable-flymake
(add-hook 'flymake-diagnostic-functions #'sweeprolog-diagnostic-function nil t)
(flymake-mode)
'sweeprolog--find-predicate-from-symbol))
-;;;; Dependency Managagement
+;;;; Dependency Management
(defun sweeprolog-update-dependencies ()
"Add explicit dependencies for implicitly autoaloaded predicates."