Skip to content

Commit

Permalink
Merge pull request #7 from jamesnvc/fix-metta-completion
Browse files Browse the repository at this point in the history
Fix metta completion
  • Loading branch information
TeamSPoon authored Feb 7, 2025
2 parents 49e6789 + d796af6 commit 2f3812f
Show file tree
Hide file tree
Showing 2 changed files with 30 additions and 17 deletions.
41 changes: 24 additions & 17 deletions libraries/lsp_server_metta/prolog/lsp_metta_completion.pl
Original file line number Diff line number Diff line change
Expand Up @@ -20,15 +20,14 @@
:- use_module(library(apply), [maplist/3]).
:- use_module(library(lists), [numlist/3]).
:- use_module(library(yall)).
:- use_module(library(filesex)).
%:- use_module(lsp_metta_utils, [linechar_offset/3]).
:- use_module(lsp_metta_changes, [doc_text_fallback_d4/2]).

% James added
:- use_module(library(prolog_xref), [xref_defined/3, xref_source/2]).

:- include(lsp_metta_include).

:- use_module(lsp_metta_workspace, [source_file_text/2]).
:- use_module(lsp_metta_workspace, [source_file_text/2, xref_metta_source/1]).

:- discontiguous(handle_completions/3).

Expand All @@ -52,6 +51,7 @@
%
prefix_at(File, Position, Prefix) :-
source_file_text(File, DocCodes),
xref_metta_source(File),
setup_call_cleanup(
open_string(DocCodes, Stream),
( linechar_offset(Stream, Position, _),
Expand All @@ -63,20 +63,27 @@
%
completions_at(File, Position, Completions) :-
prefix_at(File, Position, Prefix),
xref_source(File, [silent(true)]),
findall(
Result,
( xref_defined(File, Goal, _),
functor(Goal, Name, Arity),
atom_concat(Prefix, _, Name),
args_str(Arity, Args),
format(string(Func), "~w(~w)$0", [Name, Args]),
format(string(Label), "~w/~w", [Name, Arity]),
Result = _{label: Label,
insertText: Func,
insertTextFormat: 2}),
Completions
).
findall(Result,
% Use definitions from the current file, corelib, and stdlib
% TODO: also look at imported definitions?
( ( metta_atom_xref(Atom, File, _Loc)
; ( metta_atom_xref(Atom, Path, _),
directory_file_path(_, F, Path),
memberchk(F, ['corelib.metta', 'stdlib_mettalog.metta']) )
),
(( Atom = [':>', Defn|_]
; Atom = [':', [Defn|_]|_]
; Atom = [':', Defn|_]
; Atom = ['=', [Defn|_]|_]
; Atom = ['=', Defn|_]
)),
atom(Defn),
atom_concat(Prefix, _, Defn),
Result = _{label: Defn,
insertText: Defn,
insertTextFormat: 1}),
Completions
).
%
args_str(Arity, Str) :-
numlist(1, Arity, Args),
Expand Down
6 changes: 6 additions & 0 deletions libraries/lsp_server_metta/prolog/lsp_prolog_changes.pl
Original file line number Diff line number Diff line change
Expand Up @@ -10,8 +10,10 @@
*/

:- use_module(library(readutil), [read_file_to_codes/3]).
:- use_module(lsp_metta_workspace, [xref_maybe/2]).

:- dynamic doc_text/2.
:- dynamic lsp_state:full_text_next/2.

%! handle_doc_changes(+File:atom, +Changes:list) is det.
%
Expand All @@ -30,6 +32,10 @@
doc_text_fallback(Path, OrigCodes),
replace_codes(OrigCodes, StartLine, StartChar, ReplaceLen, ChangeCodes,
NewText),
transaction(( retractall(lsp_state:full_text_next(Path, _)),
assertz(lsp_state:full_text_next(Path, NewText))
)),
% TODO put the retractall/assertz in a transaction?
retractall(doc_text(Path, _)),
assertz(doc_text(Path, NewText)).
handle_doc_change(Path, Change) :-
Expand Down

0 comments on commit 2f3812f

Please sign in to comment.