1:- module(lsp_changes, [handle_doc_changes/2,
2 doc_text_fallback/2,
3 doc_text/2]).
12:- use_module(library(readutil), [read_file_to_codes/3]). 13
14:- dynamic doc_text/2.
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 _{range: _{start: _{line: StartLine, character: StartChar},
37 end: _{line: EndLine, character: EndChar}},
38 text: Text} :< Change,
39 !,
40 atom_codes(Text, ChangeCodes),
41 doc_text_fallback(Path, OrigCodes),
42 replace_codes_range(OrigCodes, StartLine, StartChar, EndLine, EndChar, ChangeCodes,
43 NewText),
44 retractall(doc_text(Path, _)),
45 assertz(doc_text(Path, NewText)).
46handle_doc_change(Path, Change) :-
47 retractall(doc_text(Path, _)),
48 atom_codes(Change.text, TextCodes),
49 assertz(doc_text(Path, TextCodes)).
56doc_text_fallback(Path, Text) :-
57 doc_text(Path, Text), !.
58doc_text_fallback(Path, Text) :-
59 read_file_to_codes(Path, Text, []),
60 assertz(doc_text(Path, Text)).
63replace_codes_range(Text, StartLine, StartChar, EndLine, EndChar, ReplaceText, NewText) :-
64 phrase(replace_range(start, 0, 0, StartLine, StartChar, EndLine, EndChar, ReplaceText),
65 Text,
66 NewText).
67
68replace_range(start, StartLine, StartChar, StartLine, StartChar, EndLine, EndChar, NewText), NewText -->
69 !,
70 replace_range(finish, StartLine, StartChar, StartLine, StartChar, EndLine, EndChar, NewText).
71replace_range(finish, EndLine, EndChar, _, _, EndLine, EndChar, _) --> !, [].
72replace_range(start, StartLine, 0, StartLine, StartChar, EndLine, EndChar, NewText), Take -->
73 { length(Take, StartChar) },
74 Take, !,
75 replace_range(start, StartLine, StartChar, StartLine, StartChar, EndLine, EndChar, NewText).
76replace_range(finish, EndLine, Char, StartLine, StartChar, EndLine, EndChar, NewText) -->
77 !, { ToSkip is EndChar - Char },
78 skip(ToSkip),
79 replace_range(finish, EndLine, EndChar, StartLine, StartChar, EndLine, EndChar, NewText).
80replace_range(start, Line0, _, StartLine, StartChar, EndLine, EndChar, NewText), Line -->
81 line(Line),
82 { succ(Line0, Line1) },
83 replace_range(start, Line1, 0, StartLine, StartChar, EndLine, EndChar, NewText).
84replace_range(finish, Line0, _, StartLine, StartChar, EndLine, EndChar, NewText) -->
85 line(_),
86 { succ(Line0, Line1) },
87 replace_range(finish, Line1, 0, StartLine, StartChar, EndLine, EndChar, NewText).
90replace_codes(Text, StartLine, StartChar, ReplaceLen, ReplaceText, NewText) :-
91 phrase(replace(StartLine, StartChar, ReplaceLen, ReplaceText),
92 Text,
93 NewText).
94
95replace(0, 0, 0, NewText), NewText --> !, [].
96replace(0, 0, Skip, NewText) -->
97 !, skip(Skip),
98 replace(0, 0, 0, NewText).
99replace(0, Chars, Skip, NewText), Take -->
100 { length(Take, Chars) },
101 Take, !,
102 replace(0, 0, Skip, NewText).
103replace(Lines1, Chars, Skip, NewText), Line -->
104 line(Line), !,
105 { succ(Lines0, Lines1) },
106 replace(Lines0, Chars, Skip, NewText).
107
108skip(0) --> !, [].
109skip(N) --> [_], { succ(N0, N) }, skip(N0).
110
111line([0'\n]) --> [0'\n], !.
112line([C|Cs]) --> [C], line(Cs)
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.