1:- module(lsp_completion, [completions_at/3]).

LSP Completion

This module implements code completion, based on defined predicates in the file & imports.

Uses lsp_changes in order to see the state of the buffer being edited.

author
- James Cash */
See also
- doc_text_fallback/2
   14:- use_module(library(apply), [maplist/3]).   15:- use_module(library(lists), [numlist/3]).   16:- use_module(library(prolog_xref), [xref_defined/3, xref_source/2]).   17:- use_module(library(yall)).   18:- use_module(lsp_utils, [linechar_offset/3]).   19:- use_module(lsp_changes, [doc_text_fallback/2]).   20
   21part_of_prefix(Code) :- code_type(Code, prolog_var_start).
   22part_of_prefix(Code) :- code_type(Code, prolog_atom_start).
   23part_of_prefix(Code) :- code_type(Code, prolog_identifier_continue).
   24
   25get_prefix_codes(Stream, Offset, Codes) :-
   26    get_prefix_codes(Stream, Offset, [], Codes).
   27
   28get_prefix_codes(Stream, Offset0, Codes0, Codes) :-
   29    peek_code(Stream, Code),
   30    part_of_prefix(Code), !,
   31    succ(Offset1, Offset0),
   32    seek(Stream, Offset1, bof, Offset),
   33    get_prefix_codes(Stream, Offset, [Code|Codes0], Codes).
   34get_prefix_codes(_, _, Codes, Codes).
   35
   36prefix_at(File, Position, Prefix) :-
   37    doc_text_fallback(File, DocCodes),
   38    setup_call_cleanup(
   39        open_string(DocCodes, Stream),
   40        ( linechar_offset(Stream, Position, _),
   41          seek(Stream, -1, current, Offset),
   42          get_prefix_codes(Stream, Offset, PrefixCodes),
   43          string_codes(Prefix, PrefixCodes) ),
   44        close(Stream)
   45    ).
   46
   47completions_at(File, Position, Completions) :-
   48    prefix_at(File, Position, Prefix),
   49    xref_source(File, [silent(true)]),
   50    findall(
   51        Result,
   52        ( xref_defined(File, Goal, _),
   53          functor(Goal, Name, Arity),
   54          atom_concat(Prefix, _, Name),
   55          ( predicate_arguments(File, Name, Args) -> true ; args_str(Arity, Args) ),
   56          format(string(Func), "~w(~w)$0", [Name, Args]),
   57          format(string(Label), "~w/~w", [Name, Arity]),
   58          Result = _{label: Label,
   59                     insertText: Func,
   60                     insertTextFormat: 2}),
   61        Completions,
   62        CompletionsTail
   63    ),
   64    findall(
   65        Result,
   66        ( predicate_property(system:Goal, built_in),
   67          functor(Goal, Name, Arity),
   68          atom_concat(Prefix, _, Name),
   69          \+ sub_atom(Name, 0, _, _, '$'),
   70          ( predicate_arguments(File, Name, Args) -> true ; args_str(Arity, Args) ),
   71          format(string(Func), "~w(~w)$0", [Name, Args]),
   72          format(string(Label), "~w/~w", [Name, Arity]),
   73          Result = _{label: Label,
   74                     insertText: Func,
   75                     insertTextFormat: 2}),
   76        CompletionsTail
   77    ).
   78
   79predicate_arguments(File, Pred, ArgsStr) :-
   80    lsp_utils:predicate_help(File, Pred, HelpText),
   81    string_concat(Pred, "(", PredName),
   82    sub_string(HelpText, BeforeName, NameLen, _, PredName),
   83    sub_string(HelpText, BeforeClose, _, _, ")"),
   84    BeforeClose > BeforeName, !,
   85    ArgsStart is BeforeName + NameLen,
   86    ArgsLength is BeforeClose - ArgsStart,
   87    sub_string(HelpText, ArgsStart, ArgsLength, _, ArgsStr0),
   88    atomic_list_concat(Args, ', ', ArgsStr0),
   89    length(Args, Length),
   90    numlist(1, Length, Nums),
   91    maplist([Arg, Num, S]>>format(string(S), "${~w:~w}", [Num, Arg]),
   92           Args, Nums, Args1),
   93    atomic_list_concat(Args1, ', ', ArgsStr).
   94
   95args_str(Arity, Str) :-
   96    numlist(1, Arity, Args),
   97    maplist([A, S]>>format(string(S), "${~w:_}", [A]),
   98           Args, ArgStrs),
   99    atomic_list_concat(ArgStrs, ', ', Str)