emacs-elpa-diffs
[Top][All Lists]
Advanced

[Date Prev][Date Next][Thread Prev][Thread Next][Date Index][Thread Index]

[nongnu] elpa/sweeprolog d2078a324f 1/4: ADDED: new command for updating


From: ELPA Syncer
Subject: [nongnu] elpa/sweeprolog d2078a324f 1/4: ADDED: new command for updating use_module/autoload directives
Date: Sat, 26 Nov 2022 09:59:24 -0500 (EST)

branch: elpa/sweeprolog
commit d2078a324f3a7342583320a0d2a363e63f4d28fc
Author: Eshel Yaron <me@eshelyaron.com>
Commit: Eshel Yaron <me@eshelyaron.com>

    ADDED: new command for updating use_module/autoload directives
    
    * sweep.pl (sweep_file_path_in_library/2): new predicate.
    (sweep_color_normalized/3): normalize autoload source paths.
    * sweeprolog.el (sweeprolog-analyze-buffer-with): new helper function.
    (sweeprolog-update-dependencies): new command.
---
 sweep.pl            | 18 ++++++++--
 sweeprolog-tests.el | 94 ++++++++++++++++++++++++++++++++++++++++++++++++--
 sweeprolog.el       | 98 +++++++++++++++++++++++++++++++++++++++++++++++++++--
 3 files changed, 204 insertions(+), 6 deletions(-)

diff --git a/sweep.pl b/sweep.pl
index ca352010f6..2eeb37d162 100644
--- a/sweep.pl
+++ b/sweep.pl
@@ -68,7 +68,8 @@
             sweep_predicate_completion_candidates/2,
             sweep_exportable_predicates/2,
             sweep_interrupt/0,
-            sweep_string_to_atom/2
+            sweep_string_to_atom/2,
+            sweep_file_path_in_library/2
           ]).
 
 :- use_module(library(pldoc)).
@@ -84,6 +85,7 @@
 :- use_module(library(lynx/html_text)).
 :- use_module(library(http/html_write)).
 :- use_module(library(prolog_pack)).
+:- use_module(library(prolog_deps)).
 
 :- if(exists_source(library(help))).
 :- use_module(library(help)).
@@ -466,7 +468,7 @@ sweep_color_normalized_(_, Goal0, [Kind0,Head|_], 
[Goal,Kind,F,N]) :-
     sweep_color_goal(Goal0),
     !,
     atom_string(Goal0, Goal),
-    term_string(Kind0, Kind),
+    sweeprolog_goal_kind_normalized(Kind0, Kind),
     (   (   var(Head)
         ->  true
         ;   Head == []
@@ -504,6 +506,13 @@ sweep_color_normalized_(_, file_no_depend, [File0|_], 
["file_no_depend"|File]) :
 sweep_color_normalized_(_, Nom0, _, Nom) :-
     atom_string(Nom0, Nom).
 
+sweeprolog_goal_kind_normalized(autoload(Path0), ["autoload"|Path]) :-
+    !,
+    absolute_file_name(Path0, Path1, [extensions([pl])]),
+    atom_string(Path1, Path).
+sweeprolog_goal_kind_normalized(Kind0, Kind) :-
+    term_string(Kind0, Kind).
+
 sweep_color_goal(goal).
 sweep_color_goal(goal_term).
 sweep_color_goal(head).
@@ -868,3 +877,8 @@ sweep_string_to_atom(String, AtomString) :-
     format(string(AtomString),
            "~W",
            [Atom, [quoted(true), character_escapes(true)]]).
+
+sweep_file_path_in_library(Path, Spec) :-
+    file_name_on_path(Path, Spec0),
+    prolog_deps:segments(Spec0, Spec1),
+    term_string(Spec1, Spec).
diff --git a/sweeprolog-tests.el b/sweeprolog-tests.el
index fb32a9a0d2..183068134c 100644
--- a/sweeprolog-tests.el
+++ b/sweeprolog-tests.el
@@ -659,8 +659,98 @@ foo :- bar.
 foo :- Body.
 "))))
 
-(ert-deftest dwim-define-nested-phrase- ()
-  "Tests complex undefined predicate scenario"
+(ert-deftest append-dependencies ()
+  "Tests making implicit autoloads explicit with existing directive."
+  (let ((temp (make-temp-file "sweeprolog-test"
+                              nil
+                              "pl"
+                              "
+:- module(foo, [bar/1]).
+
+/** <module> Foo
+
+*/
+
+:- use_module(library(lists), [ member/2
+                              ]).
+
+bar(X) :- member(X, [1,2,3]).
+bar(X) :- permutation(X, [1,2,3]).
+"
+                              )))
+    (find-file-literally temp)
+    (sweeprolog-mode)
+    (call-interactively #'sweeprolog-update-dependencies)
+    (should (string= (buffer-string)
+                     "
+:- module(foo, [bar/1]).
+
+/** <module> Foo
+
+*/
+
+:- use_module(library(lists), [ member/2,
+                                permutation/2
+                              ]).
+
+bar(X) :- member(X, [1,2,3]).
+bar(X) :- permutation(X, [1,2,3]).
+"
+                     ))))
+
+(ert-deftest update-dependencies ()
+  "Tests making implicit autoloads explicit."
+  (let ((temp (make-temp-file "sweeprolog-test"
+                              nil
+                              "pl"
+                              "
+:- module(foo, [bar/1]).
+
+/** <module> Foo
+
+*/
+
+bar(X) :- member(X, [1,2,3]).
+"
+                              )))
+    (find-file-literally temp)
+    (sweeprolog-mode)
+    (call-interactively #'sweeprolog-update-dependencies)
+    (should (string= (buffer-string)
+                     "
+:- module(foo, [bar/1]).
+
+/** <module> Foo
+
+*/
+
+:- autoload(library(lists), [ member/2
+                            ]).
+
+bar(X) :- member(X, [1,2,3]).
+"
+
+                     ))
+    (goto-char (point-max))
+    (insert "bar(X) :- permutation(X, [1,2,3]).")
+    (call-interactively #'sweeprolog-update-dependencies)
+    (should (string= (buffer-string)
+                     "
+:- module(foo, [bar/1]).
+
+/** <module> Foo
+
+*/
+
+:- autoload(library(lists), [ member/2,
+                              permutation/2
+                            ]).
+
+bar(X) :- member(X, [1,2,3]).
+bar(X) :- permutation(X, [1,2,3])."))))
+
+(ert-deftest dwim-define-nested-phrase ()
+  "Tests complex undefined predicate scenario."
   (let ((temp (make-temp-file "sweeprolog-test"
                               nil
                               "pl"
diff --git a/sweeprolog.el b/sweeprolog.el
index f0eccbf827..4476f0feab 100644
--- a/sweeprolog.el
+++ b/sweeprolog.el
@@ -356,6 +356,7 @@ non-terminals)."
     (define-key map (kbd "C-c C-d") #'sweeprolog-document-predicate-at-point)
     (define-key map (kbd "C-c C-e") #'sweeprolog-export-predicate)
     (define-key map (kbd "C-c C-i") #'sweeprolog-forward-hole)
+    (define-key map (kbd "C-c C-u") #'sweeprolog-update-dependencies)
     (define-key map (kbd "C-c C-`")
                 (if (fboundp 'flymake-show-buffer-diagnostics)  ;; Flymake 
1.2.1+
                     #'sweeprolog-show-diagnostics
@@ -439,6 +440,7 @@ non-terminals)."
       sweeprolog-document-predicate-at-point
       (and (eq major-mode 'sweeprolog-mode)
            (sweeprolog-definition-at-point)) ]
+    [ "Update autoload directives" sweeprolog-update-dependencies t ]
     "--"
     [ "Open top-level"         sweeprolog-top-level       t ]
     [ "Signal top-level"
@@ -1834,6 +1836,8 @@ resulting list even when found in the current clause."
      (list (list beg end (sweeprolog-head-hook-face))))
     (`("head" "built_in" . ,_)
      (list (list beg end (sweeprolog-head-built-in-face))))
+    (`("goal" ("autoload" . ,_) . ,_)
+     (list (list beg end (sweeprolog-autoload-face))))
     (`("head" ,(rx "imported(") . ,_)
      (list (list beg end (sweeprolog-head-imported-face))))
     (`("head" ,(rx "extern(") . ,_)
@@ -1867,8 +1871,6 @@ resulting list even when found in the current clause."
      (list (list beg end (sweeprolog-thread-local-face))))
     (`("goal" ,(rx "extern(") . ,_)
      (list (list beg end (sweeprolog-extern-face))))
-    (`("goal" ,(rx "autoload(") . ,_)
-     (list (list beg end (sweeprolog-autoload-face))))
     (`("goal" ,(rx "imported(") . ,_)
      (list (list beg end (sweeprolog-imported-face))))
     (`("goal" ,(rx "global(") . ,_)
@@ -2756,6 +2758,11 @@ of them signal success by returning non-nil."
        (not (nth 8 (syntax-ppss)))
        (not (looking-at-p (rx bol (or "%" "/*"))))))
 
+(defun sweeprolog-analyze-buffer-with (cb)
+  (add-hook 'sweeprolog-analyze-region-fragment-hook cb nil t)
+  (sweeprolog-analyze-buffer t)
+  (remove-hook 'sweeprolog-analyze-region-fragment-hook cb t))
+
 (defun sweeprolog-analyze-term-at-point (cb)
   (let ((sweeprolog--analyze-point (point)))
     (add-hook 'sweeprolog-analyze-region-fragment-hook cb nil t)
@@ -4028,6 +4035,93 @@ valid Prolog atom."
                    'sweeprolog--find-predicate-from-symbol))
 
 
+;;;; Dependency Managagement
+
+(defun sweeprolog-update-dependencies ()
+  "Add explicit dependencies for implicitly autoaloaded predicates."
+  (interactive "" sweeprolog-mode)
+  (let ((existing nil)
+        (missing nil)
+        (current-directive-beg nil)
+        (current-directive-end nil)
+        (current-directive-file nil))
+    (sweeprolog-analyze-buffer-with
+     (lambda (beg end arg)
+       (pcase arg
+         (`("goal_term" "built_in" "autoload" 2)
+          (setq current-directive-beg beg
+                current-directive-end end))
+         (`("goal_term" "built_in" "use_module" 2)
+          (setq current-directive-beg beg
+                current-directive-end end))
+         ((or `("file"           . ,file)
+              `("file_no_depend" . ,file))
+          (when (and current-directive-beg
+                     (<= current-directive-beg
+                         beg end
+                         current-directive-end))
+            (setq current-directive-file file)))
+         ((or "list" "empty_list")
+          (when (and current-directive-beg
+                     (<= current-directive-beg
+                         beg end
+                         current-directive-end))
+            (push
+             (cons current-directive-file (copy-marker (1- end) t))
+             existing)))
+         (`("goal" ("autoload" . ,file) ,functor ,arity)
+          (let ((autoloaded (list file functor arity)))
+            (unless (member autoloaded missing)
+              (push autoloaded missing)))))))
+    (if missing
+        (progn
+          (dolist (autoloaded missing)
+            (let* ((file    (nth 0 autoloaded))
+                   (functor (nth 1 autoloaded))
+                   (arity   (nth 2 autoloaded))
+                   (pred    (concat (sweeprolog-format-string-as-atom functor)
+                                    "/" (number-to-string arity))))
+              (message "Adding explicit dependency on %s from %s."
+                       pred file)
+              (if-let ((marker (cdr (assoc-string file existing))))
+                  (save-mark-and-excursion
+                    (goto-char marker)
+                    (pcase (sweeprolog-last-token-boundaries)
+                      (`(open ,_ ,oend)
+                       (goto-char oend)
+                       (insert " " pred "\n"))
+                      (`(symbol ,_ ,oend)
+                       (let ((point (point)))
+                         (goto-char oend)
+                         (insert ",")
+                         (goto-char (1+ point))
+                         (insert pred "\n")))
+                      (tok
+                       (user-error "Unexpected token %s while looking for 
import list"
+                                   tok)))
+                    (indent-region-line-by-line  (save-excursion
+                                                   
(sweeprolog-beginning-of-top-term)
+                                                   (point))
+                                                 (save-excursion
+                                                   (sweeprolog-end-of-top-term)
+                                                   (point))))
+                (save-mark-and-excursion
+                  (goto-char (point-min))
+                  (sweeprolog-end-of-top-term)
+                  (while (forward-comment 1))
+                  (insert ":- autoload("
+                          (sweeprolog--query-once "sweep"
+                                                  "sweep_file_path_in_library"
+                                                  file)
+                          ", [ " pred "\n]).\n\n")
+                  (indent-region-line-by-line (save-excursion
+                                                
(sweeprolog-beginning-of-top-term)
+                                                (point))
+                                              (point))
+                  (push (cons file (copy-marker (- (point) 5) t)) existing)))))
+          (sweeprolog-analyze-buffer t))
+      (message "No implicit autoloads found."))))
+
 ;;;; Footer
 
 (provide 'sweeprolog)



reply via email to

[Prev in Thread] Current Thread [Next in Thread]