branch: elpa/sweeprolog
commit 9352db02765ca6e26eb53998bc3d4640aed9f611
Author: Eshel Yaron <m...@eshelyaron.com>
Commit: Eshel Yaron <m...@eshelyaron.com>

    ADDED: in-buffer completions for arithmetic functions
    
    * sweep.pl (sweep_function_functors_collection/2)
    (sweep_functions_collection/2): New predicates.
    (sweep_context_callable_arg/4): Recognize arithmetic functions.
    
    * sweeprolog.el (sweeprolog-arith-functor-completion-candidates)
    (sweeprolog-arith-completion-candidates): New functions, used in...
    (sweeprolog--atom-or-functor-completion-at-point): ...here.
    
    * sweep.texi (Code Completion): Document arithmetic function completion.
    * sweeprolog-tests.el: Test it.
---
 sweep.pl            | 40 ++++++++++++++++++++++++++++++++++++-
 sweep.texi          |  3 +++
 sweeprolog-tests.el | 36 +++++++++++++++++++++++++++++++++
 sweeprolog.el       | 57 +++++++++++++++++++++++++++++++++++++++++++++++++++++
 4 files changed, 135 insertions(+), 1 deletion(-)

diff --git a/sweep.pl b/sweep.pl
index 05f36cfb51..954b3b501a 100644
--- a/sweep.pl
+++ b/sweep.pl
@@ -104,7 +104,9 @@
             sweep_alias_source_file_name_collection/2,
             sweep_option_functors_collection/2,
             sweep_options_collection/2,
-            sweep_option_arguments_collection/2
+            sweep_option_arguments_collection/2,
+            sweep_functions_collection/2,
+            sweep_function_functors_collection/2
           ]).
 
 :- use_module(library(pldoc)).
@@ -963,6 +965,24 @@ sweep_compound_functors_collection([Arity,Bef,Aft], Fs) :-
     setof(F, sweep_matching_functor(Bef, Aft, F/Arity), Fs0),
     maplist(term_string, Fs0, Fs).
 
+sweep_function_functors_collection([Bef,Aft], Fs) :-
+    findall(F, (   current_arithmetic_function(Head),
+                   Head =.. [F0|_],
+                   term_string(F0, F),
+                   sweep_matching_atom(Bef, Aft, F)
+               ),
+            Fs).
+
+sweep_functions_collection([Bef,Aft], Fs) :-
+    findall(F, (   current_arithmetic_function(Head),
+                   Head =.. [F0|Args],
+                   length(Args, Arity),
+                   term_string(F0, F1),
+                   sweep_matching_atom(Bef, Aft, F1),
+                   sweep_format_term([F1,Arity,999], F)
+               ),
+            Fs).
+
 sweep_option_functors_collection([Bef,Aft,Pred0,Ari,Arg], Fs) :-
     atom_string(Pred, Pred0),
     current_predicate_options(Pred/Ari, Arg, Options),
@@ -1119,6 +1139,10 @@ sweep_context_callable_arg(^, _, _, 0) :- !.
 sweep_context_callable_arg(Neck, _, _, 0) :-
     op_is_neck(Neck),
     !.
+sweep_context_callable_arg(_, _, "arith", "arith") :- !.
+sweep_context_callable_arg(F, N, 0, "arith") :-
+    arith_arg(F, N),
+    !.
 sweep_context_callable_arg(F0, N, 0, ["options", F, N]) :-
     current_option_arg(F0/N, N),
     !,
@@ -1148,6 +1172,20 @@ sweep_context_callable_arg(F, N, _, R) :-
     arg(N, Spec, A),
     callable_arg(A, R).
 
+arith_arg((is), 2).
+arith_arg((<), 1).
+arith_arg((<), 2).
+arith_arg((>), 1).
+arith_arg((>), 2).
+arith_arg((=<), 1).
+arith_arg((=<), 2).
+arith_arg((>=), 1).
+arith_arg((>=), 2).
+arith_arg((=\=), 1).
+arith_arg((=\=), 2).
+arith_arg((=:=), 1).
+arith_arg((=:=), 2).
+
 source_arg(load_files, 1).
 source_arg(use_module, 1).
 source_arg(consult, 1).
diff --git a/sweep.texi b/sweep.texi
index cdd2c78d86..9036afa28e 100644
--- a/sweep.texi
+++ b/sweep.texi
@@ -2124,6 +2124,9 @@ If point is at a position where a source file 
specification should
 appear (such as the argument of @code{use_module/1}),
 @code{completion-at-point} suggests matching source file
 specifications.
+@item Source file completion
+If point is inside an arithmetic expression,
+@code{completion-at-point} suggests matching arithmetic functions.
 @item Atom completion
 If point is at a non-callable position, @code{completion-at-point}
 suggests matching atoms and functors as completion candidates.
diff --git a/sweeprolog-tests.el b/sweeprolog-tests.el
index 83782b74f5..7c0ec5bd4c 100644
--- a/sweeprolog-tests.el
+++ b/sweeprolog-tests.el
@@ -496,6 +496,42 @@ foo(T) :-
     (should (= 46 (nth 1 cap)))
     (should (equal '("fail") (nth 2 cap)))))
 
+(sweeprolog-deftest cap-arith-functor ()
+  "Completion at point for arithmetic function functors."
+  "
+foo(T) :-
+    T is cop-!-n(
+"
+  (let ((cap (sweeprolog-completion-at-point)))
+    (should (= 21 (nth 0 cap)))
+    (should (= 25 (nth 1 cap)))
+    (should (equal '("copysign")
+                   (all-completions "" (nth 2 cap))))))
+
+(sweeprolog-deftest cap-arith ()
+                    "Completion at point for arithmetic functions."
+                    "
+foo(T) :-
+    T is cop-!-
+"
+                    (let ((cap (sweeprolog-completion-at-point)))
+                      (should (= 21 (nth 0 cap)))
+                      (should (= 24 (nth 1 cap)))
+                      (should (equal '("copysign(_, _)")
+                                     (all-completions "" (nth 2 cap))))))
+
+(sweeprolog-deftest cap-arith-nested ()
+  "Completion at point for arithmetic functions."
+  "
+foo(T) :-
+    T is copysign(cop-!-
+"
+  (let ((cap (sweeprolog-completion-at-point)))
+    (should (= 30 (nth 0 cap)))
+    (should (= 33 (nth 1 cap)))
+    (should (equal '("copysign(_, _)")
+                   (all-completions "" (nth 2 cap))))))
+
 (sweeprolog-deftest cap-source ()
   "Completion at point for source files."
   ":- use_module(li-!-"
diff --git a/sweeprolog.el b/sweeprolog.el
index f600fef44d..f2c7a50b63 100644
--- a/sweeprolog.el
+++ b/sweeprolog.el
@@ -1567,6 +1567,10 @@ Used for `completion-at-point' candidates in cases such 
as:
          (sweeprolog-option-completion-candidates beg end pred ari)))
       (`("option" ,pred ,ari ,option)
        (sweeprolog-option-arg-completion-candidates beg end pred ari option))
+      ("arith"
+       (if fnc
+           (sweeprolog-arith-functor-completion-candidates beg end)
+         (sweeprolog-arith-completion-candidates beg end)))
       (_
        (if fnc
            (sweeprolog-compound-functor-completion-candidates beg end fnc)
@@ -1696,6 +1700,59 @@ Used for `completion-at-point' candidates in cases such 
as:
     foo :- 123 =-!- 100 + 20 + 3"
   nil)
 
+(defun sweeprolog-arith-functor-completion-candidates (beg end)
+  "Return completions for arithmetic function functors between BEG and END.
+
+Used for `completion-at-point' candidates in cases such as:
+
+    foo(T) :- T is f-!-t("
+  (list beg end
+        (sweeprolog--query-once
+         "sweep" "sweep_function_functors_collection"
+         (list (buffer-substring-no-properties beg (point))
+               (buffer-substring-no-properties (point) end)))
+        :exclusive 'no
+        :annotation-function (lambda (_) " Arithmetic function functor")))
+
+(defun sweeprolog-arith-completion-candidates (beg end)
+  "Return completions for arithmetic expression between BEG and END.
+
+Used for `completion-at-point' candidates in cases such as:
+
+    foo(T) :- T is f-!-"
+  (let ((col (sweeprolog--query-once
+              "sweep" "sweep_functions_collection"
+              (list (buffer-substring-no-properties beg (point))
+                    (buffer-substring-no-properties (point) end)))))
+    (list beg end col
+          :exclusive 'no
+          :annotation-function (lambda (_) " Arithmentic function")
+          :exit-function
+          (lambda (string status)
+            (pcase status
+              ('finished
+               (pcase (cdr (assoc-string string col))
+                 (`(compound
+                    "term_position"
+                    0 ,length
+                    ,_fbeg ,_fend
+                    ,holes)
+                  (with-silent-modifications
+                    (dolist (hole holes)
+                      (pcase hole
+                        (`(compound "-" ,hbeg ,hend)
+                         (add-text-properties
+                          (- (point) length (- hbeg))
+                          (- (point) length (- hend))
+                          (list
+                           'sweeprolog-hole t
+                           'font-lock-face (list 'sweeprolog-hole)
+                           'rear-nonsticky '(sweeprolog-hole
+                                             cursor-sensor-functions
+                                             font-lock-face)))))))
+                  (backward-char length)
+                  (sweeprolog-forward-hole)))))))))
+
 (defun sweeprolog-option-functor-completion-candidates (beg end pred ari)
   "Return completions for option functors for PRED/ARI between BEG and END.
 

Reply via email to