1:- module(lsp_checking, [check_errors/2]).
9:- use_module(library(apply_macros)). 10:- use_module(library(assoc), [list_to_assoc/2,
11 get_assoc/3]). 12:- use_module(library(apply), [maplist/3]). 13:- use_module(library(debug), [debug/3]). 14:- use_module(library(lists), [member/2]). 15:- use_module(library(prolog_xref), [xref_clean/1, xref_source/1]). 16:- use_module(library(dcg/high_order)). 17
18:- include('_lsp_path_add.pl'). 19:- use_module(lsp(lsp_utils), [clause_variable_positions/3,
20 usemod_filespec_position/4]). 21
22:- dynamic user:thread_message_hook/3. 23:- multifile user:thread_message_hook/3.
29check_errors(Path, Errors) :-
30 nb_setval(checking_errors, []),
31 Hook = (user:thread_message_hook(Term, Kind, Lines) :-
32 prolog_load_context(term_position, Pos),
33 stream_position_data(line_count, Pos, Line),
34 stream_position_data(line_position, Pos, Char),
35 nb_getval(checking_errors, ErrList),
36 nb_setval(checking_errors, [e(Term, Kind, Lines, Line, Char)|ErrList])
37 ),
38 setup_call_cleanup(
39 assertz(Hook, Ref),
40 ( xref_clean(Path), xref_source(Path, [silent(false)]) ),
41 erase(Ref)
42 ),
43 nb_getval(checking_errors, ErrList),
44 once(phrase(sequence(error_expansion(Path), ErrList), Errors)).
45
46singleton_warning_response(VarPoses, VarName) -->
47 { atom_length(VarName, VarLen),
48 get_assoc(VarName, VarPoses, [position(Line, Char)]),
49 EndChar is Char + VarLen,
50 format(string(Msg), "Singleton variable ~w", [VarName]) },
51 [ _{severity: 2,
52 source: "prolog_xref",
53 range: _{start: _{line: Line, character: Char},
54 end: _{line: Line, character: EndChar}},
55 message: Msg
56 } ].
57
58error_expansion(Path, e(singletons(_, SingletonVars), warning, _, ClauseLine, _)) --> !,
59 { clause_variable_positions(Path, ClauseLine, VariablePoses),
60 list_to_assoc(VariablePoses, VarPoses) },
61 sequence(singleton_warning_response(VarPoses), SingletonVars).
62error_expansion(Path, e(Term, warning, _Lines, Line, _Char)) -->
63 { Term = error(existence_error(file, FileSpec), _) },
64 !,
65 { usemod_filespec_position(Path, Line, FileSpec, Span),
66 format(string(Msg), "Module `~p` not found", [FileSpec]) },
67 [ _{severity: 2,
68 source: "prolog_xref",
69 range: Span,
70 message: Msg } ].
71error_expansion(_Path, e(_, silent, _, _, _)) --> !.
72error_expansion(_Path, e(_Term, error, Lines, _, _)) -->
73 { Lines = [url(_File:Line1:Col1), _, _, Msg0] },
74 !,
75 { ( Msg0 = Fmt-Params
76 -> format(string(Msg), Fmt, Params)
77 ; text_to_string(Msg0, Msg) ),
78 succ(Line0, Line1), ( succ(Col0, Col1) ; Col0 = 0 ) },
79 [_{severity: 1,
80 source: "prolog_xref",
81 range: _{start: _{line: Line0, character: Col0},
82 end: _{line: Line1, character: 0}},
83 message: Msg
84 }].
85error_expansion(Path, e(_Term, Kind, Lines, _, _)) -->
86 { kind_level(Kind, Level),
87 Lines = ['~w:~d:~d: '-[Path, Line1, Char1]|Msgs0], !,
88 maplist(expand_error_message, Msgs0, Msgs),
89 atomic_list_concat(Msgs, Msg),
90 succ(Line0, Line1),
91 ( succ(Char0, Char1) ; Char0 = 0 ) },
92 [_{severity: Level,
93 source: "prolog_xref",
94 range: _{start: _{line: Line0, character: Char0},
95 end: _{line: Line1, character: 0}},
96 message: Msg
97 }].
99error_expansion(_Path, _Msg) --> !.
100
101expand_error_message(Format-Args, Formatted) :-
102 !, format(string(Formatted), Format, Args).
103expand_error_message(Msg, Msg).
104
105kind_level(error, 1).
106kind_level(warning, 2)
LSP Checking
Module for checking Prolog source files for errors and warnings.