1:- module(lsp_changes, [handle_doc_changes/2,
    2                        doc_text_fallback/2,
    3                        doc_text/2]).

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 */
   12:- use_module(library(readutil), [read_file_to_codes/3]).   13
   14:- dynamic doc_text/2.
 handle_doc_changes(+File:atom, +Changes:list) is det
Track Changes to the file File.
   19handle_doc_changes(_, []) :- !.
   20handle_doc_changes(Path, [Change|Changes]) :-
   21    handle_doc_change(Path, Change),
   22    handle_doc_changes(Path, Changes).
   23
   24handle_doc_change(Path, Change) :-
   25    _{range: _{start: _{line: StartLine, character: StartChar},
   26               end:   _{line: _EndLine0,   character: _EndChar}},
   27      rangeLength: ReplaceLen, text: Text} :< Change,
   28    !,
   29    atom_codes(Text, ChangeCodes),
   30    doc_text_fallback(Path, OrigCodes),
   31    replace_codes(OrigCodes, StartLine, StartChar, ReplaceLen, ChangeCodes,
   32                  NewText),
   33    retractall(doc_text(Path, _)),
   34    assertz(doc_text(Path, NewText)).
   35handle_doc_change(Path, Change) :-
   36    retractall(doc_text(Path, _)),
   37    atom_codes(Change.text, TextCodes),
   38    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.
   45doc_text_fallback(Path, Text) :-
   46    doc_text(Path, Text), !.
   47doc_text_fallback(Path, Text) :-
   48    read_file_to_codes(Path, Text, []),
   49    assertz(doc_text(Path, Text)).
 replace_codes(Text, StartLine, StartChar, ReplaceLen, ReplaceText, -NewText) is det
   52replace_codes(Text, StartLine, StartChar, ReplaceLen, ReplaceText, NewText) :-
   53    phrase(replace(StartLine, StartChar, ReplaceLen, ReplaceText),
   54           Text,
   55           NewText).
   56
   57replace(0, 0, 0, NewText), NewText --> !, [].
   58replace(0, 0, Skip, NewText) -->
   59    !, skip(Skip),
   60    replace(0, 0, 0, NewText).
   61replace(0, Chars, Skip, NewText), Take -->
   62    { length(Take, Chars) },
   63    Take, !,
   64    replace(0, 0, Skip, NewText).
   65replace(Lines1, Chars, Skip, NewText), Line -->
   66    line(Line), !,
   67    { succ(Lines0, Lines1) },
   68    replace(Lines0, Chars, Skip, NewText).
   69
   70skip(0) --> !, [].
   71skip(N) --> [_], { succ(N0, N) }, skip(N0).
   72
   73line([0'\n]) --> [0'\n], !.
   74line([C|Cs]) --> [C], line(Cs)