Skip to content

Commit

Permalink
Merge pull request #109 from royward/main
Browse files Browse the repository at this point in the history
zeroth cut of lsp server
  • Loading branch information
royward authored Sep 1, 2024
2 parents dc8b5b9 + b68411e commit f573e82
Show file tree
Hide file tree
Showing 13 changed files with 830 additions and 0 deletions.
114 changes: 114 additions & 0 deletions src/packs/lsp_server_metta/README.org
Original file line number Diff line number Diff line change
@@ -0,0 +1,114 @@
* MeTTaLog Language server

**Currently a fork of prolog Language server. Will update this README later.**

Still a work-in-progress -- please open an issue if you have any issues or feature requests!.

Currently supports showing documentation on hover, go to definition, go to callers, listing defined symbols in the file, and showing a limited number of diagnostics.

Only tested with SWI-Prolog, as it heavily uses its introspection facilities to do its stuff.
It should work with any relatively-recent version of SWI-Prolog, but for best results (for "find references" in particular), use a version with ~xref_called/5~ (8.1.5 or newer; past commit [[https://github.com/SWI-Prolog/swipl-devel/commit/303f6430de5c9d7e225d8eb6fb8bb8b59e7c5f8f][303f6430de5c]]).

Installable as a pack like ~?- pack_install(lsp_server).~

* Emacs

** [[https://github.com/emacs-lsp/lsp-mode][lsp-mode]]:

#+begin_src emacs-lisp
(lsp-register-client
(make-lsp-client
:new-connection
(lsp-stdio-connection (list "swipl"
"-g" "use_module(library(lsp_server))."
"-g" "lsp_server:main"
"-t" "halt"
"--" "stdio"))
:major-modes '(prolog-mode)
:priority 1
:multi-root t
:server-id 'prolog-ls))
#+end_src

* Vim/Neovim

** [[https://github.com/autozimu/LanguageClient-neovim][LanguageClient]]:

#+begin_src viml
let g:LanguageClient_serverCommands = {
\ 'prolog': ['swipl',
\ '-g', 'use_module(library(lsp_server)).',
\ '-g', 'lsp_server:main',
\ '-t', 'halt',
\ '--', 'stdio']
\ }
#+end_src

* Neovim

** [[https://github.com/neoclide/coc.nvim][CoC]]

Put the following in ~coc-settings.json~ (which you can access by using the command ~:CocConfig~).

#+begin_src json
{"languageserver": {
"prolog-lsp": {
"command": "swipl",
"args": ["-g", "use_module(library(lsp_server)).",
"-g", "lsp_server:main",
"-t", "halt",
"--", "stdio"
],
"filetypes": ["prolog"]
}}
}
#+end_src

** Native LSP (for Neovim >= 0.5)

Install the [[https://github.com/neovim/nvim-lspconfig][neovim/nvim-lspconfig]] package

Put the following in ~$XDG_CONFIG_DIR/nvim/lua/lspconfig/prolog_lsp.lua~:

#+begin_src lua
local configs = require 'lspconfig/configs'
local util = require 'lspconfig/util'

configs.prolog_lsp = {
default_config = {
cmd = {"swipl",
"-g", "use_module(library(lsp_server)).",
"-g", "lsp_server:main",
"-t", "halt",
"--", "stdio"};
filetypes = {"prolog"};
root_dir = util.root_pattern("pack.pl");
};
docs = {
description = [[
https://github.com/jamesnvc/prolog_lsp

Prolog Language Server
]];
}
}
-- vim:et ts=2 sw=2
#+end_src

Then add the following to ~init.vim~:

#+begin_src viml
lua << EOF
require('lspconfig/prolog_lsp')
require('lspconfig').prolog_lsp.setup{}
EOF
#+end_src

* VSCode

- download the latest ~.vsix~ file from the [[https://github.com/jamesnvc/lsp_server/releases][releases page]]
- clone this repo and copy/symlink the ~vscode/~ directory to ~~/.vscode/extensions/~
- clone and build the ~.vsix~ file yourself by the follwing steps:
1. install ~vsce~ (~npm install -g vsce~)
2. run ~vsce publish~ from the ~vscode/~ directory
3. add the resulting ~.vsix~ to VSCode.
6 changes: 6 additions & 0 deletions src/packs/lsp_server_metta/pack.pl
Original file line number Diff line number Diff line change
@@ -0,0 +1,6 @@
name(lsp_server_metta).
title('A MeTTa LSP Server').
version('0.0.2').
author('Roy Ward', '[email protected]').
home('https://github.com/trueagi-io/metta-wam').
provides(lsp_server_metta).
76 changes: 76 additions & 0 deletions src/packs/lsp_server_metta/prolog/lsp_metta_changes.pl
Original file line number Diff line number Diff line change
@@ -0,0 +1,76 @@
:- module(lsp_metta_changes, [handle_doc_changes/2,
doc_text_fallback/2,
doc_text/2]).
/** <module> LSP changes
Module for tracking edits to the source, in order to be able to act on
the code as it is in the editor buffer, before saving.
@author James Cash
*/

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

:- dynamic doc_text/2.

%! handle_doc_changes(+File:atom, +Changes:list) is det.
%
% Track =Changes= to the file =File=.

handle_doc_changes(_,_).

handle_doc_changes(_, []) :- !.
handle_doc_changes(Path, [Change|Changes]) :-
handle_doc_change(Path, Change),
handle_doc_changes(Path, Changes).

handle_doc_change(Path, Change) :-
_{range: _{start: _{line: StartLine, character: StartChar},
end: _{line: _EndLine0, character: _EndChar}},
rangeLength: ReplaceLen, text: Text} :< Change,
!,
atom_codes(Text, ChangeCodes),
doc_text_fallback(Path, OrigCodes),
replace_codes(OrigCodes, StartLine, StartChar, ReplaceLen, ChangeCodes,
NewText),
retractall(doc_text(Path, _)),
assertz(doc_text(Path, NewText)).
handle_doc_change(Path, Change) :-
retractall(doc_text(Path, _)),
atom_codes(Change.text, TextCodes),
assertz(doc_text(Path, TextCodes)).

%! doc_text_fallback(+Path:atom, -Text:text) is det.
%
% Get the contents of the file at =Path=, either with the edits we've
% been tracking in memory, or from the file on disc if no edits have
% occured.
doc_text_fallback(Path, Text) :-
doc_text(Path, Text), !.
doc_text_fallback(Path, Text) :-
read_file_to_codes(Path, Text, []),
assertz(doc_text(Path, Text)).

%! replace_codes(Text, StartLine, StartChar, ReplaceLen, ReplaceText, -NewText) is det.
replace_codes(Text, StartLine, StartChar, ReplaceLen, ReplaceText, NewText) :-
phrase(replace(StartLine, StartChar, ReplaceLen, ReplaceText),
Text,
NewText).

replace(0, 0, 0, NewText), NewText --> !, [].
replace(0, 0, Skip, NewText) -->
!, skip(Skip),
replace(0, 0, 0, NewText).
replace(0, Chars, Skip, NewText), Take -->
{ length(Take, Chars) },
Take, !,
replace(0, 0, Skip, NewText).
replace(Lines1, Chars, Skip, NewText), Line -->
line(Line), !,
{ succ(Lines0, Lines1) },
replace(Lines0, Chars, Skip, NewText).

skip(0) --> !, [].
skip(N) --> [_], { succ(N0, N) }, skip(N0).

line([0'\n]) --> [0'\n], !.
line([C|Cs]) --> [C], line(Cs).
26 changes: 26 additions & 0 deletions src/packs/lsp_server_metta/prolog/lsp_metta_checking.pl
Original file line number Diff line number Diff line change
@@ -0,0 +1,26 @@
:- module(lsp_metta_checking, [check_errors/2]).
/** <module> LSP Checking
Module for checking Prolog source files for errors and warnings.
@author Roy Ward
*/
% :- use_module(library(apply_macros)).
% :- use_module(library(assoc), [list_to_assoc/2,
% get_assoc/3]).
% :- use_module(library(apply), [maplist/3]).
% :- use_module(library(debug), [debug/3]).
% :- use_module(library(lists), [member/2]).
% :- use_module(library(prolog_xref), [xref_clean/1, xref_source/1]).
% :- use_module(lsp_metta_utils, [clause_variable_positions/3]).
%
% :- dynamic message_hook/3.
% :- multifile message_hook/3.
%
% %! check_errors(+Path:atom, -Errors:List) is det.
% %
% % =Errors= is a list of the errors in the file given by =Path=.
% % This predicate changes the =user:message_hook/3= hook.

% will do some real error checking later
check_errors(_,[]).


41 changes: 41 additions & 0 deletions src/packs/lsp_server_metta/prolog/lsp_metta_colours.pl
Original file line number Diff line number Diff line change
@@ -0,0 +1,41 @@
:- module(lsp_metta_colours, [
token_types/1,
token_modifiers/1]).

% these are Prolog token types/modifiers. Need to change to meTTa.

token_types([namespace,
type,
class,
enum,
interface,
struct,
typeParameter,
parameter,
variable,
property,
enumMember,
event,
function,
member,
macro,
keyword,
modifier,
comment,
string,
number,
regexp,
operator
]).
token_modifiers([declaration,
definition,
readonly,
static,
deprecated,
abstract,
async,
modification,
documentation,
defaultLibrary
]).

68 changes: 68 additions & 0 deletions src/packs/lsp_server_metta/prolog/lsp_metta_completion.pl
Original file line number Diff line number Diff line change
@@ -0,0 +1,68 @@
% :- module(lsp_metta_completion, [completions_at/3]).
% /** <module> LSP Completion
%
% This module implements code completion, based on defined predicates in
% the file & imports.
%
% Uses =lsp_metta_changes= in order to see the state of the buffer being edited.
%
% @see lsp_metta_changes:doc_text_fallback/2
%
% @author James Cash
% */
%
% :- use_module(library(apply), [maplist/3]).
% :- use_module(library(lists), [numlist/3]).
% :- use_module(library(prolog_xref), [xref_defined/3, xref_source/2]).
% :- use_module(library(yall)).
% :- use_module(lsp_metta_utils, [linechar_offset/3]).
% :- use_module(lsp_metta_changes, [doc_text_fallback/2]).
%
% part_of_prefix(Code) :- code_type(Code, prolog_var_start).
% part_of_prefix(Code) :- code_type(Code, prolog_atom_start).
% part_of_prefix(Code) :- code_type(Code, prolog_identifier_continue).
%
% get_prefix_codes(Stream, Offset, Codes) :-
% get_prefix_codes(Stream, Offset, [], Codes).
%
% get_prefix_codes(Stream, Offset0, Codes0, Codes) :-
% peek_code(Stream, Code),
% part_of_prefix(Code), !,
% succ(Offset1, Offset0),
% seek(Stream, Offset1, bof, Offset),
% get_prefix_codes(Stream, Offset, [Code|Codes0], Codes).
% get_prefix_codes(_, _, Codes, Codes).
%
% prefix_at(File, Position, Prefix) :-
% doc_text_fallback(File, DocCodes),
% setup_call_cleanup(
% open_string(DocCodes, Stream),
% ( linechar_offset(Stream, Position, _),
% seek(Stream, -1, current, Offset),
% get_prefix_codes(Stream, Offset, PrefixCodes),
% string_codes(Prefix, PrefixCodes) ),
% close(Stream)
% ).
%
% 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
% ).
%
% args_str(Arity, Str) :-
% numlist(1, Arity, Args),
% maplist([A, S]>>format(string(S), "${~w:_}", [A]),
% Args, ArgStrs),
% atomic_list_concat(ArgStrs, ', ', Str).
35 changes: 35 additions & 0 deletions src/packs/lsp_server_metta/prolog/lsp_metta_parser.pl
Original file line number Diff line number Diff line change
@@ -0,0 +1,35 @@
:- module(lsp_metta_parser, [lsp_metta_request//1]).
/** <module> LSP Parser
Module for parsing the body & headers from an LSP client.
@author James Cash
*/

:- use_module(library(assoc), [list_to_assoc/2, get_assoc/3]).
:- use_module(library(codesio), [open_codes_stream/2]).
:- use_module(library(dcg/basics), [string_without//2]).
:- use_module(library(http/json), [json_read_dict/3]).

header(Key-Value) -->
string_without(":", KeyC), ": ", string_without("\r", ValueC),
{ string_codes(Key, KeyC), string_codes(Value, ValueC) }.

headers([Header]) -->
header(Header), "\r\n\r\n", !.
headers([Header|Headers]) -->
header(Header), "\r\n",
headers(Headers).

json_chars(0, []) --> [].
json_chars(N, [C|Cs]) --> [C], { succ(Nn, N) }, json_chars(Nn, Cs).

lsp_metta_request(_{headers: Headers, body: Body}) -->
headers(HeadersList),
{ list_to_assoc(HeadersList, Headers),
get_assoc("Content-Length", Headers, LengthS),
number_string(Length, LengthS) },
json_chars(Length, JsonCodes),
{ ground(JsonCodes),
open_codes_stream(JsonCodes, JsonStream),
json_read_dict(JsonStream, Body, []) }.
Loading

0 comments on commit f573e82

Please sign in to comment.