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)).
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),
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),
!,
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).
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.
(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-!-"
(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)
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.