1:- module(lsp_checking, [check_errors/2]).

LSP Checking

Module for checking Prolog source files for errors and warnings.

author
- James Cash */
    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(lsp_utils, [clause_variable_positions/3]).   17
   18:- dynamic message_hook/3.   19:- 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.
   25check_errors(Path, Errors) :-
   26    nb_setval(checking_errors, []),
   27    Hook = (user:message_hook(Term, Kind, Lines) :-
   28                prolog_load_context(term_position, Pos),
   29                stream_position_data(line_count, Pos, Line),
   30                stream_position_data(line_position, Pos, Char),
   31                nb_getval(checking_errors, ErrList),
   32                nb_setval(checking_errors, [Term-Kind-Lines-Line-Char|ErrList])
   33           ),
   34    setup_call_cleanup(
   35        assertz(Hook),
   36        ( xref_clean(Path), xref_source(Path) ),
   37        retractall(user:message_hook(_, _, _))
   38    ),
   39    nb_getval(checking_errors, ErrList),
   40    expand_errors(Path, ErrList, Errors-Errors).
   41
   42expand_errors(Path, [singletons(_, SingletonVars)-warning-_-ClauseLine-_|InErrs],
   43              OutErrs-Tail0) :- !,
   44    clause_variable_positions(Path, ClauseLine, VariablePoses),
   45    list_to_assoc(VariablePoses, VarPoses),
   46    findall(
   47        NewErr,
   48        ( member(VarName, SingletonVars),
   49          atom_length(VarName, VarLen),
   50          get_assoc(VarName, VarPoses, [position(Line, Char)]),
   51          EndChar is Char + VarLen,
   52          format(string(Msg), "Singleton variable ~w", [VarName]),
   53          NewErr = _{severity: 2,
   54                     source: "prolog_xref",
   55                     range: _{start: _{line: Line, character: Char},
   56                              end: _{line: Line, character: EndChar}},
   57                     message: Msg} ),
   58        Tail0,
   59        Tail1
   60    ),
   61    expand_errors(Path, InErrs, OutErrs-Tail1).
   62expand_errors(Path, [_-silent-_-_-_|InErr], OutErrs-Tail) :- !,
   63    expand_errors(Path, InErr, OutErrs-Tail).
   64expand_errors(Path, [_Term-error-Lines-_-_|InErrs], OutErrs-[Err|Tail]) :-
   65    Lines = [url(_File:Line1:Col1), _, _, Msg], !,
   66    succ(Line0, Line1), ( succ(Col0, Col1) ; Col0 = 0 ),
   67    Err = _{severity: 1,
   68            source: "prolog_xref",
   69            range: _{start: _{line: Line0, character: Col0},
   70                     end: _{line: Line1, character: 0}},
   71            message: Msg
   72           },
   73    expand_errors(Path, InErrs, OutErrs-Tail).
   74expand_errors(Path, [_Term-Kind-Lines-_-_|InErr], OutErrs-[Err|Tail]) :-
   75    kind_level(Kind, Level),
   76    Lines = ['~w:~d:~d: '-[Path, Line1, Char1]|Msgs0], !,
   77    maplist(expand_error_message, Msgs0, Msgs),
   78    atomic_list_concat(Msgs, Msg),
   79    succ(Line0, Line1),
   80    ( succ(Char0, Char1) ; Char0 = 0 ),
   81    Err = _{severity: Level,
   82            source: "prolog_xref",
   83            range: _{start: _{line: Line0, character: Char0},
   84                     end: _{line: Line1, character: 0}},
   85            message: Msg
   86           },
   87    expand_errors(Path, InErr, OutErrs-Tail).
   88expand_errors(Path, [_Msg|InErr], OutErrs-Tail) :- !,
   89    expand_errors(Path, InErr, OutErrs-Tail).
   90expand_errors(_, [], _-[]) :- !.
   91
   92expand_error_message(Format-Args, Formatted) :-
   93    !, format(string(Formatted), Format, Args).
   94expand_error_message(Msg, Msg).
   95
   96kind_level(error, 1).
   97kind_level(warning, 2)