1:- module(diagnostics, 2 [ 3 diagnose/1, % +Path 4 diagnosis_hook/3 % +Term, -Kind, -Message 5 ]). 6 7:- use_module(library(main)). 8:- use_module(library(prolog_colour)). 9 10:- multifile 11 prolog:xref_source_identfier/2, 12 prolog:xref_open_source/2, 13 prolog:xref_close_source/2. 14 15 16:- dynamic diagnostics_input/2. 17 18 19prologxref_source_identifier(Source, diagnostics_input(Source)) :- 20 diagnostics_input(Source, _), !. 21prologxref_source_identifier(diagnostics_input(Source), diagnostics_input(Source)). 22 23prologxref_open_source(diagnostics_input(Source), Stream) :- 24 diagnostics_input(Source, Current), 25 !, 26 open(Current, read, Stream). 27 28prologxref_close_source(diagnostics_input(_), Stream) :- 29 close(Stream). 30 31 32:- initialization(main, main).
64main(['-', Path]) :- 65 !, 66 set_stream(current_input, tty(false)), 67 set_stream(current_input, buffer(full)), 68 tmp_file_stream(Temp, Stream, [extension(pl)]), 69 copy_stream_data(current_input, Stream), 70 close(Stream), 71 absolute_file_name(Path, Abs), 72 asserta(diagnostics_input(Abs, Temp)), 73 diagnose(Path, diagnostics_input(Abs)). 74main(Paths) :- 75 maplist(absolute_file_name, Paths, Abs), 76 maplist(diagnose, Abs).
Detected issues are reported via print_message/2, and can be intercepted via message_hook/3.
84diagnose(Path) :- 85 diagnose(Path, Path). 86 87diagnose(Path, Source) :- 88 xref_source(Source), 89 setup_call_cleanup(prolog_open_source(Source, Stream), 90 prolog_colourise_stream(Stream, Source, diagnosis(Path)), 91 prolog_close_source(Stream)).
Item is a term describing a source fragment to be diagnosed, it follows the same format as the first argument of ColourItem in prolog_colourise_stream/3.
If this predicate succeeds, Kind must be unified with a message kind term that will be used as the first argument of print_message/2, while Message must be unified with a pair Format-Args where Format is a format string that will be formatted using Args. If this predicate fails, the default diagnosis logic will be used to diagnose Item.
109:- multifile diagnosis_hook/3. 110 111 112diagnosis(Path, Term, Start, Length) :- 113 diagnosis_hook(Term, Kind, Message), 114 !, 115 print_message(Kind, diagnostic(Path, Start, Length, Message)). 116diagnosis(Path, Term, Start, Length) :- 117 diagnostic(Term, Kind, Message), 118 !, 119 print_message(Kind, diagnostic(Path, Start, Length, Message)). 120diagnosis(_, _, _, _). 121 122 123diagnostic(head(unreferenced, Head) , warning, "Unreferenced definition for ~w"-[PI]) :- !, pi_head(PI, Head). 124diagnostic(syntax_error(Description, _), error , "Syntax error ~w"-[Description] ) :- !. 125diagnostic(type_error(Description) , error , "Type error ~w"-[Description] ) :- !. 126diagnostic(instantiation_error , error , "Instantiation error" ) :- !. 127diagnostic(singleton , warning, "Singleton variable" ) :- !. 128diagnostic(undefined_import , warning, "Undefined import" ) :- !. 129diagnostic(unused_import , warning, "Unused import" ) :- !. 130diagnostic(error , error , "Unspecified error" ) :- !. 131diagnostic(error(Error) , error , "Error ~w"-[Error] ) :- !. 132diagnostic(goal(undefined, Head) , error , "Undefined predicate ~w"-[PI] ) :- !, pi_head(PI, Head). 133diagnostic(no_option_name , warning, "No such option" ) :- !. 134diagnostic(nofile , error , "No such file" ) :- !. 135diagnostic(no_flag_name(Flag) , warning, "No such flag ~w"-[Flag] ) :- !. 136 137 138prologmessage(diagnostic(Path, Start, Length, Message)) --> 139 [ '~w:~w:~w: '-[Path, Start, Length], Message, nl ]
SWI-Prolog source code diagnostics
This module provides a simple and extensible diagnostics interface based on prolog_colourise_stream/3 from
library(prolog_colour)
.Diagnostics can be ran on multiple source files from the command line like so:
There is also support for diagnosing Prolog source code originating from
stdin
, by providing "-" as the first command line argument, followed by a path to a Prolog source file that will be regarded as the "current file" during the analysis for resolving relative paths in source files:*/