From 4c26ec6f856c28ed712ca1d9991840e89f937401 Mon Sep 17 00:00:00 2001 From: Aleksy Grabowski Date: Sat, 5 Oct 2024 14:20:56 +0200 Subject: [PATCH 01/11] Warn on redefinition of builtin predicates --- src/lib/warnings.pl | 37 +++++++++++++++++++++++++++++++++++++ 1 file changed, 37 insertions(+) create mode 100644 src/lib/warnings.pl diff --git a/src/lib/warnings.pl b/src/lib/warnings.pl new file mode 100644 index 000000000..9056481ac --- /dev/null +++ b/src/lib/warnings.pl @@ -0,0 +1,37 @@ +:- module(warnings, []). + +:- use_module(library(lists)). +:- use_module(library(format)). + +%% warnings:output(+OutputStream). +% +% If defined – use `OutputStream` (eg. user_output) instead of standard error +% for message output. +% +:- dynamic(output_stream/1). + +output(OutputStream) :- output_stream(OutputStream), !. +output(user_error). + +builtin((_;_)). +builtin((_,_)). +builtin((_->_)). + +% Warn about builtin predicates re-definition. It can happen by mistake for +% example: +% x :- a. b, c. +% +user:term_expansion(G, _) :- + nonvar(G), + builtin(G), + functor(G, O, 2), + warn("(~q) attempts to re-define ~w", [G, O/2]). + +warn(Format, Vars) :- + output(S), + prolog_load_context(file, F), + prolog_load_context(term_position, position_and_lines_read(_,L)), + append(["% Warning: ", Format, " at line ~d of ~a~n"], FullFormat), + append(Vars, [L,F], AllVars), + format(S, FullFormat, AllVars), + false. From 659f9938ea2f30f58f609d6ec5ca23cdf99af65a Mon Sep 17 00:00:00 2001 From: Aleksy Grabowski Date: Sat, 5 Oct 2024 15:21:22 +0200 Subject: [PATCH 02/11] Add unit tests --- src/tests/warnings.pl | 6 ++++++ tests/scryer/cli/src_tests/warnings_tests.stderr | 1 + tests/scryer/cli/src_tests/warnings_tests.stdout | 1 + tests/scryer/cli/src_tests/warnings_tests.toml | 5 +++++ 4 files changed, 13 insertions(+) create mode 100644 src/tests/warnings.pl create mode 100644 tests/scryer/cli/src_tests/warnings_tests.stderr create mode 100644 tests/scryer/cli/src_tests/warnings_tests.stdout create mode 100644 tests/scryer/cli/src_tests/warnings_tests.toml diff --git a/src/tests/warnings.pl b/src/tests/warnings.pl new file mode 100644 index 000000000..bb9539f91 --- /dev/null +++ b/src/tests/warnings.pl @@ -0,0 +1,6 @@ +:- use_module(library(warnings)). + +x :- + a. + b, + c. diff --git a/tests/scryer/cli/src_tests/warnings_tests.stderr b/tests/scryer/cli/src_tests/warnings_tests.stderr new file mode 100644 index 000000000..f971859ac --- /dev/null +++ b/tests/scryer/cli/src_tests/warnings_tests.stderr @@ -0,0 +1 @@ +% Warning: (b,c) attempts to re-define (,)/2 at line 6 of warnings.pl diff --git a/tests/scryer/cli/src_tests/warnings_tests.stdout b/tests/scryer/cli/src_tests/warnings_tests.stdout new file mode 100644 index 000000000..3d41ffc1b --- /dev/null +++ b/tests/scryer/cli/src_tests/warnings_tests.stdout @@ -0,0 +1 @@ + error(permission_error(modify,static_procedure,(',')/2),load/1). diff --git a/tests/scryer/cli/src_tests/warnings_tests.toml b/tests/scryer/cli/src_tests/warnings_tests.toml new file mode 100644 index 000000000..86bbfc77a --- /dev/null +++ b/tests/scryer/cli/src_tests/warnings_tests.toml @@ -0,0 +1,5 @@ +args = [ + "-f", + "--no-add-history", + "src/tests/warnings.pl", + "-g", "halt"] From b66bb8e78b12c70812c92d3659615876fc077eca Mon Sep 17 00:00:00 2001 From: Aleksy Grabowski Date: Sat, 5 Oct 2024 15:26:10 +0200 Subject: [PATCH 03/11] Use phrase for warning formatting --- src/lib/warnings.pl | 8 +++++--- 1 file changed, 5 insertions(+), 3 deletions(-) diff --git a/src/lib/warnings.pl b/src/lib/warnings.pl index 9056481ac..c847c51d4 100644 --- a/src/lib/warnings.pl +++ b/src/lib/warnings.pl @@ -2,6 +2,7 @@ :- use_module(library(lists)). :- use_module(library(format)). +:- use_module(library(pio)). %% warnings:output(+OutputStream). % @@ -31,7 +32,8 @@ output(S), prolog_load_context(file, F), prolog_load_context(term_position, position_and_lines_read(_,L)), - append(["% Warning: ", Format, " at line ~d of ~a~n"], FullFormat), - append(Vars, [L,F], AllVars), - format(S, FullFormat, AllVars), + phrase_to_stream( + ("% Warning: ", format_(Format, Vars), format_(" at line ~d of ~a~n", [L,F])), + S + ), false. From c11d5fee6f8a0a26d75cd30ec70603f23ac38f97 Mon Sep 17 00:00:00 2001 From: Aleksy Grabowski Date: Mon, 7 Oct 2024 06:56:35 +0200 Subject: [PATCH 04/11] Reorganize code + remove useless output_stream --- src/lib/warnings.pl | 35 ++++++++++++++--------------------- 1 file changed, 14 insertions(+), 21 deletions(-) diff --git a/src/lib/warnings.pl b/src/lib/warnings.pl index c847c51d4..83cd2b502 100644 --- a/src/lib/warnings.pl +++ b/src/lib/warnings.pl @@ -1,19 +1,22 @@ :- module(warnings, []). -:- use_module(library(lists)). :- use_module(library(format)). :- use_module(library(pio)). -%% warnings:output(+OutputStream). -% -% If defined – use `OutputStream` (eg. user_output) instead of standard error -% for message output. -% -:- dynamic(output_stream/1). - -output(OutputStream) :- output_stream(OutputStream), !. -output(user_error). +warn_fail(Format, Vars) :- + warn_fail(user_error, Format, Vars). +warn_fail(Stream, Format, Vars) :- + prolog_load_context(file, File), + prolog_load_context(term_position, position_and_lines_read(_,Line)), + phrase_to_stream( + ( + "% Warning: ", format_(Format,Vars), format_(" at line ~d of ~a~n",[Line,File]) + ), + Stream + ), + false. +% FIXME: Replace with predicate_property(_, built_in) when #2600 will be ready builtin((_;_)). builtin((_,_)). builtin((_->_)). @@ -26,14 +29,4 @@ nonvar(G), builtin(G), functor(G, O, 2), - warn("(~q) attempts to re-define ~w", [G, O/2]). - -warn(Format, Vars) :- - output(S), - prolog_load_context(file, F), - prolog_load_context(term_position, position_and_lines_read(_,L)), - phrase_to_stream( - ("% Warning: ", format_(Format, Vars), format_(" at line ~d of ~a~n", [L,F])), - S - ), - false. + warn_fail("(~q) attempts to re-define ~w", [G, O/2]). From be3e011f835ba30d5a878a78a52e7db379df2c1b Mon Sep 17 00:00:00 2001 From: Aleksy Grabowski Date: Mon, 7 Oct 2024 07:18:18 +0200 Subject: [PATCH 05/11] Suggest using library(si) --- src/lib/warnings.pl | 22 +++++++++++++++++-- src/tests/warnings.pl | 3 +++ .../cli/src_tests/warnings_tests.stderr | 3 ++- 3 files changed, 25 insertions(+), 3 deletions(-) diff --git a/src/lib/warnings.pl b/src/lib/warnings.pl index 83cd2b502..ad9bbdab7 100644 --- a/src/lib/warnings.pl +++ b/src/lib/warnings.pl @@ -21,6 +21,10 @@ builtin((_,_)). builtin((_->_)). +unsound_type_test(atom(_)). +unsound_type_test(atomic(_)). +unsound_type_test(integer(_)). + % Warn about builtin predicates re-definition. It can happen by mistake for % example: % x :- a. b, c. @@ -28,5 +32,19 @@ user:term_expansion(G, _) :- nonvar(G), builtin(G), - functor(G, O, 2), - warn_fail("(~q) attempts to re-define ~w", [G, O/2]). + functor(G, F, 2), + warn_fail("(~q) attempts to re-define ~w", [G, F/2]). + +% Warn about unsound type test predicates and suggest using library(si). +% Observe that following queries yield different results: +% +% ?- X=1, integer(X). +% true. +% ?- integer(X), X=1. +% false. +% +user:goal_expansion(G, _) :- + nonvar(G), + unsound_type_test(G), + functor(G, F, 1), + warn_fail("~q is a constant source of bugs, use ~a_si/1 from library(si)", [F/1,F]). diff --git a/src/tests/warnings.pl b/src/tests/warnings.pl index bb9539f91..c84faae54 100644 --- a/src/tests/warnings.pl +++ b/src/tests/warnings.pl @@ -1,5 +1,8 @@ :- use_module(library(warnings)). +t :- + x; integer(_). + x :- a. b, diff --git a/tests/scryer/cli/src_tests/warnings_tests.stderr b/tests/scryer/cli/src_tests/warnings_tests.stderr index f971859ac..f1b4b3bc9 100644 --- a/tests/scryer/cli/src_tests/warnings_tests.stderr +++ b/tests/scryer/cli/src_tests/warnings_tests.stderr @@ -1 +1,2 @@ -% Warning: (b,c) attempts to re-define (,)/2 at line 6 of warnings.pl +% Warning: integer/1 is a constant source of bugs, use integer_si/1 from library(si) at line 4 of warnings.pl +% Warning: (b,c) attempts to re-define (,)/2 at line 9 of warnings.pl From 2d1ebf067287ae4eeb967a31ea046b0f36120b61 Mon Sep 17 00:00:00 2001 From: Aleksy Grabowski Date: Mon, 7 Oct 2024 07:31:30 +0200 Subject: [PATCH 06/11] Warn about deeply nested negation --- src/lib/warnings.pl | 8 ++++++++ src/tests/warnings.pl | 3 +++ tests/scryer/cli/src_tests/warnings_tests.stderr | 3 ++- 3 files changed, 13 insertions(+), 1 deletion(-) diff --git a/src/lib/warnings.pl b/src/lib/warnings.pl index ad9bbdab7..afacf3be8 100644 --- a/src/lib/warnings.pl +++ b/src/lib/warnings.pl @@ -48,3 +48,11 @@ unsound_type_test(G), functor(G, F, 1), warn_fail("~q is a constant source of bugs, use ~a_si/1 from library(si)", [F/1,F]). + +% Warn when more than 2 negations are nested. Double negation has legit +% use-case, but I don't think that more nested negations are ever useful. +% +user:goal_expansion(G, _) :- + nonvar(G), + G = (\+ \+ \+ _), + warn_fail("Nested negations can be reduced", []). diff --git a/src/tests/warnings.pl b/src/tests/warnings.pl index c84faae54..b95ac9471 100644 --- a/src/tests/warnings.pl +++ b/src/tests/warnings.pl @@ -3,6 +3,9 @@ t :- x; integer(_). +n :- + \+ \+ \+ foo(_). + x :- a. b, diff --git a/tests/scryer/cli/src_tests/warnings_tests.stderr b/tests/scryer/cli/src_tests/warnings_tests.stderr index f1b4b3bc9..46a3a7c1c 100644 --- a/tests/scryer/cli/src_tests/warnings_tests.stderr +++ b/tests/scryer/cli/src_tests/warnings_tests.stderr @@ -1,2 +1,3 @@ % Warning: integer/1 is a constant source of bugs, use integer_si/1 from library(si) at line 4 of warnings.pl -% Warning: (b,c) attempts to re-define (,)/2 at line 9 of warnings.pl +% Warning: Nested negations can be reduced at line 7 of warnings.pl +% Warning: (b,c) attempts to re-define (,)/2 at line 12 of warnings.pl From df99b4eea67ba54d40e46e2e76c0dc30d427d5ea Mon Sep 17 00:00:00 2001 From: Aleksy Grabowski Date: Mon, 7 Oct 2024 07:36:47 +0200 Subject: [PATCH 07/11] Fix warning text after review --- src/lib/warnings.pl | 2 +- tests/scryer/cli/src_tests/warnings_tests.stderr | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/src/lib/warnings.pl b/src/lib/warnings.pl index afacf3be8..a4b579a6b 100644 --- a/src/lib/warnings.pl +++ b/src/lib/warnings.pl @@ -47,7 +47,7 @@ nonvar(G), unsound_type_test(G), functor(G, F, 1), - warn_fail("~q is a constant source of bugs, use ~a_si/1 from library(si)", [F/1,F]). + warn_fail("~q is a constant source of wrong results, use ~a_si/1 from library(si)", [F/1,F]). % Warn when more than 2 negations are nested. Double negation has legit % use-case, but I don't think that more nested negations are ever useful. diff --git a/tests/scryer/cli/src_tests/warnings_tests.stderr b/tests/scryer/cli/src_tests/warnings_tests.stderr index 46a3a7c1c..c85aaf800 100644 --- a/tests/scryer/cli/src_tests/warnings_tests.stderr +++ b/tests/scryer/cli/src_tests/warnings_tests.stderr @@ -1,3 +1,3 @@ -% Warning: integer/1 is a constant source of bugs, use integer_si/1 from library(si) at line 4 of warnings.pl +% Warning: integer/1 is a constant source of wrong results, use integer_si/1 from library(si) at line 4 of warnings.pl % Warning: Nested negations can be reduced at line 7 of warnings.pl % Warning: (b,c) attempts to re-define (,)/2 at line 12 of warnings.pl From 43691eb409eb17bd50211919f446ba0440ecd523 Mon Sep 17 00:00:00 2001 From: Aleksy Grabowski Date: Mon, 7 Oct 2024 08:04:41 +0200 Subject: [PATCH 08/11] Reorganize code --- src/lib/warnings.pl | 42 +++++++++++++++++++++++------------------- 1 file changed, 23 insertions(+), 19 deletions(-) diff --git a/src/lib/warnings.pl b/src/lib/warnings.pl index a4b579a6b..ac8726c51 100644 --- a/src/lib/warnings.pl +++ b/src/lib/warnings.pl @@ -3,9 +3,9 @@ :- use_module(library(format)). :- use_module(library(pio)). -warn_fail(Format, Vars) :- - warn_fail(user_error, Format, Vars). -warn_fail(Stream, Format, Vars) :- +warn(Format, Vars) :- + warn(user_error, Format, Vars). +warn(Stream, Format, Vars) :- prolog_load_context(file, File), prolog_load_context(term_position, position_and_lines_read(_,Line)), phrase_to_stream( @@ -13,8 +13,7 @@ "% Warning: ", format_(Format,Vars), format_(" at line ~d of ~a~n",[Line,File]) ), Stream - ), - false. + ). % FIXME: Replace with predicate_property(_, built_in) when #2600 will be ready builtin((_;_)). @@ -29,11 +28,9 @@ % example: % x :- a. b, c. % -user:term_expansion(G, _) :- - nonvar(G), - builtin(G), - functor(G, F, 2), - warn_fail("(~q) attempts to re-define ~w", [G, F/2]). +term_warning(term, Term, "(~q) attempts to re-define ~w", [Term,F/2]) :- + builtin(Term), + functor(Term, F, 2). % Warn about unsound type test predicates and suggest using library(si). % Observe that following queries yield different results: @@ -43,16 +40,23 @@ % ?- integer(X), X=1. % false. % -user:goal_expansion(G, _) :- - nonvar(G), - unsound_type_test(G), - functor(G, F, 1), - warn_fail("~q is a constant source of wrong results, use ~a_si/1 from library(si)", [F/1,F]). +term_warning(goal, Term, "~q is a constant source of wrong results, use ~a_si/1 from library(si)", [F/1,F]) :- + unsound_type_test(Term), + functor(Term, F, 1). % Warn when more than 2 negations are nested. Double negation has legit % use-case, but I don't think that more nested negations are ever useful. % -user:goal_expansion(G, _) :- - nonvar(G), - G = (\+ \+ \+ _), - warn_fail("Nested negations can be reduced", []). +term_warning(goal, \+ \+ \+_, "Nested negations can be reduced", []). + +expansion_warning(ExpansionKind, Term) :- + nonvar(Term), + term_warning(ExpansionKind, Term, Msg, Vars), + warn(Msg, Vars), + false. + +user:term_expansion(Term, _) :- + expansion_warning(term, Term). + +user:goal_expansion(Term, _) :- + expansion_warning(goal, Term). From af3c654cdef63ecf322b21f82b2cea6d84438bb0 Mon Sep 17 00:00:00 2001 From: Aleksy Grabowski Date: Mon, 7 Oct 2024 12:14:42 +0200 Subject: [PATCH 09/11] Extend builtins check to \+ --- src/lib/warnings.pl | 5 +++-- src/tests/warnings.pl | 7 ++----- src/tests/warnings1.pl | 6 ++++++ src/tests/warnings2.pl | 6 ++++++ tests/scryer/cli/src_tests/warnings_tests.stderr | 7 ++++--- tests/scryer/cli/src_tests/warnings_tests.stdout | 1 + tests/scryer/cli/src_tests/warnings_tests.toml | 5 ++++- 7 files changed, 26 insertions(+), 11 deletions(-) create mode 100644 src/tests/warnings1.pl create mode 100644 src/tests/warnings2.pl diff --git a/src/lib/warnings.pl b/src/lib/warnings.pl index ac8726c51..33f06dbd8 100644 --- a/src/lib/warnings.pl +++ b/src/lib/warnings.pl @@ -19,6 +19,7 @@ builtin((_;_)). builtin((_,_)). builtin((_->_)). +builtin(\+_). unsound_type_test(atom(_)). unsound_type_test(atomic(_)). @@ -28,9 +29,9 @@ % example: % x :- a. b, c. % -term_warning(term, Term, "(~q) attempts to re-define ~w", [Term,F/2]) :- +term_warning(term, Term, "(~q) attempts to re-define ~w", [Term,F/A]) :- builtin(Term), - functor(Term, F, 2). + functor(Term, F, A). % Warn about unsound type test predicates and suggest using library(si). % Observe that following queries yield different results: diff --git a/src/tests/warnings.pl b/src/tests/warnings.pl index b95ac9471..9447f1e02 100644 --- a/src/tests/warnings.pl +++ b/src/tests/warnings.pl @@ -1,3 +1,5 @@ +% This file is only for test cases that don't break compilation + :- use_module(library(warnings)). t :- @@ -5,8 +7,3 @@ n :- \+ \+ \+ foo(_). - -x :- - a. - b, - c. diff --git a/src/tests/warnings1.pl b/src/tests/warnings1.pl new file mode 100644 index 000000000..bb9539f91 --- /dev/null +++ b/src/tests/warnings1.pl @@ -0,0 +1,6 @@ +:- use_module(library(warnings)). + +x :- + a. + b, + c. diff --git a/src/tests/warnings2.pl b/src/tests/warnings2.pl new file mode 100644 index 000000000..9a8bbaac1 --- /dev/null +++ b/src/tests/warnings2.pl @@ -0,0 +1,6 @@ +:- use_module(library(warnings)). + +x :- + a, + b. + \+ c. diff --git a/tests/scryer/cli/src_tests/warnings_tests.stderr b/tests/scryer/cli/src_tests/warnings_tests.stderr index c85aaf800..457446520 100644 --- a/tests/scryer/cli/src_tests/warnings_tests.stderr +++ b/tests/scryer/cli/src_tests/warnings_tests.stderr @@ -1,3 +1,4 @@ -% Warning: integer/1 is a constant source of wrong results, use integer_si/1 from library(si) at line 4 of warnings.pl -% Warning: Nested negations can be reduced at line 7 of warnings.pl -% Warning: (b,c) attempts to re-define (,)/2 at line 12 of warnings.pl +% Warning: integer/1 is a constant source of wrong results, use integer_si/1 from library(si) at line 6 of warnings.pl +% Warning: Nested negations can be reduced at line 9 of warnings.pl +% Warning: (b,c) attempts to re-define (,)/2 at line 6 of warnings1.pl +% Warning: (/+c) attempts to re-define (/+)/1 at line 6 of warnings2.pl diff --git a/tests/scryer/cli/src_tests/warnings_tests.stdout b/tests/scryer/cli/src_tests/warnings_tests.stdout index 3d41ffc1b..da05dfa15 100644 --- a/tests/scryer/cli/src_tests/warnings_tests.stdout +++ b/tests/scryer/cli/src_tests/warnings_tests.stdout @@ -1 +1,2 @@ error(permission_error(modify,static_procedure,(',')/2),load/1). + error(permission_error(modify,static_procedure,(/+)/1),load/1). diff --git a/tests/scryer/cli/src_tests/warnings_tests.toml b/tests/scryer/cli/src_tests/warnings_tests.toml index 86bbfc77a..5bcfb0c2b 100644 --- a/tests/scryer/cli/src_tests/warnings_tests.toml +++ b/tests/scryer/cli/src_tests/warnings_tests.toml @@ -2,4 +2,7 @@ args = [ "-f", "--no-add-history", "src/tests/warnings.pl", - "-g", "halt"] + "src/tests/warnings1.pl", + "src/tests/warnings2.pl", + "-g", "halt" +] From 8eb906a0cb628d131c2db2caf833235ce3798954 Mon Sep 17 00:00:00 2001 From: Aleksy Grabowski Date: Mon, 7 Oct 2024 17:45:04 +0200 Subject: [PATCH 10/11] Detect undeclared meta-predicates --- src/lib/warnings.pl | 25 +++++++++++++++++++ src/loader.pl | 4 +++ src/tests/warnings.pl | 11 ++++++++ .../cli/src_tests/warnings_tests.stderr | 7 ++++-- 4 files changed, 45 insertions(+), 2 deletions(-) diff --git a/src/lib/warnings.pl b/src/lib/warnings.pl index 33f06dbd8..dad19b578 100644 --- a/src/lib/warnings.pl +++ b/src/lib/warnings.pl @@ -2,6 +2,7 @@ :- use_module(library(format)). :- use_module(library(pio)). +:- use_module(library(lists)). warn(Format, Vars) :- warn(user_error, Format, Vars). @@ -50,6 +51,30 @@ % term_warning(goal, \+ \+ \+_, "Nested negations can be reduced", []). +%% expansion_hook(?Goal, +MetaVarSpecs). +% +% TLDR: Warn if currently expanded predicate calls one of its arguments, but it +% isn't declared as a meta-predicate. +% +% This hook is invoked just before goal expansion. `Goal` is an unexpanded +% goal, same as first argument of goal_expansion/2. `MetaVarSpecs` is a list of +% pairs of callable variables together with their qualifiers extracted from +% meta-predicate declaration of currently processed clause. In particular if it +% is an empty list then current head doesn't have any such variables: it is +% either not declared as a meta-predicate or its meta-predicate specification +% doesn't specify any callable variables (like `p(?)`). +% +% TODO: Be smarter and detect wrong meta-predicate declarations. +% +expansion_hook(Goal, []) :- + % Detect if calling Goal leads to calling a free variable + ( var(Goal) -> + true + ; % Goal is a meta-predicate that calls free variable + loader:module_expanded_head_variables(Goal, [_|_]) + ), + warn("Meta-predicate detected, but no qualified variables found", []). + expansion_warning(ExpansionKind, Term) :- nonvar(Term), term_warning(ExpansionKind, Term, Msg, Vars), diff --git a/src/loader.pl b/src/loader.pl index 0de805cfc..8642d5a08 100644 --- a/src/loader.pl +++ b/src/loader.pl @@ -848,6 +848,10 @@ :- non_counted_backtracking expand_goal/5. expand_goal(UnexpandedGoals, Module, ExpandedGoals, HeadVars, TGs) :- + ( catch(warnings:expansion_hook(UnexpandedGoals, HeadVars), _, true) -> + true + ; true + ), ( var(UnexpandedGoals) -> expand_module_names(call(UnexpandedGoals), [0], Module, ExpandedGoals, HeadVars, TGs) ; goal_expansion(UnexpandedGoals, Module, UnexpandedGoals1), diff --git a/src/tests/warnings.pl b/src/tests/warnings.pl index 9447f1e02..19c2c0931 100644 --- a/src/tests/warnings.pl +++ b/src/tests/warnings.pl @@ -1,9 +1,20 @@ % This file is only for test cases that don't break compilation +:- use_module(library(lists)). :- use_module(library(warnings)). +% Should warn regarding unsound type tests t :- x; integer(_). +% Should warn about deeply nested negations n :- \+ \+ \+ foo(_). + +% Should trigger meta-predicate warning +x(G) :- G. +y(G) :- call(G, 1). +z(G) :- maplist(G, "abc"). + +% Shouldn't trigger meta-predicate warning +a(L) :- maplist(=(_), L). diff --git a/tests/scryer/cli/src_tests/warnings_tests.stderr b/tests/scryer/cli/src_tests/warnings_tests.stderr index 457446520..08e711a76 100644 --- a/tests/scryer/cli/src_tests/warnings_tests.stderr +++ b/tests/scryer/cli/src_tests/warnings_tests.stderr @@ -1,4 +1,7 @@ -% Warning: integer/1 is a constant source of wrong results, use integer_si/1 from library(si) at line 6 of warnings.pl -% Warning: Nested negations can be reduced at line 9 of warnings.pl +% Warning: integer/1 is a constant source of wrong results, use integer_si/1 from library(si) at line 8 of warnings.pl +% Warning: Nested negations can be reduced at line 12 of warnings.pl +% Warning: Meta-predicate detected, but no qualified variables found at line 15 of warnings.pl +% Warning: Meta-predicate detected, but no qualified variables found at line 16 of warnings.pl +% Warning: Meta-predicate detected, but no qualified variables found at line 17 of warnings.pl % Warning: (b,c) attempts to re-define (,)/2 at line 6 of warnings1.pl % Warning: (/+c) attempts to re-define (/+)/1 at line 6 of warnings2.pl From c6d59213a270e4dabccfdd4530ad59a227830f65 Mon Sep 17 00:00:00 2001 From: Aleksy Grabowski Date: Tue, 8 Oct 2024 18:52:06 +0200 Subject: [PATCH 11/11] Warn about invalid arithmetic relations --- src/lib/warnings.pl | 45 ++++++++++++++++++- src/tests/warnings.pl | 3 ++ src/tests/warnings3.pl | 4 ++ .../cli/src_tests/warnings_tests.stderr | 1 + .../cli/src_tests/warnings_tests.stdout | 1 + .../scryer/cli/src_tests/warnings_tests.toml | 1 + 6 files changed, 54 insertions(+), 1 deletion(-) create mode 100644 src/tests/warnings3.pl diff --git a/src/lib/warnings.pl b/src/lib/warnings.pl index dad19b578..34afc1520 100644 --- a/src/lib/warnings.pl +++ b/src/lib/warnings.pl @@ -26,6 +26,45 @@ unsound_type_test(atomic(_)). unsound_type_test(integer(_)). +:- meta_predicate maplistdif(3, ?, ?, ?). + +maplistdif(_, [], [], L-L). +maplistdif(G__2, [H1|T1], [H2|T2], L0-LX) :- + call(G__2, H1, H2, L0-L1), + maplistdif(G__2, T1, T2, L1-LX). + +%% arithmetic_expansion(+Type, ?Term, -ExpandedTerm, -Unifier-Rest). +% +% `ExpandedTerm` is the minimal generalization of `Term` which makes a valid +% arithmetic relation (`Type = rela`) or functional expression (`Type = func`). +% That means if all unifications from `Unifier` hold then `ExpandedTerm == Term`. +% `Unifier-Rest` form together a list difference. `Term` is traversed from left +% to right, depth-first. Given an invalid arithmetic term, as seen in the +% example below, `E` becomes valid arithmetic term, `L` - unifier: +% +% ``` +% ?- arithmetic_expansion(rela, X is sqrt([]+Y*foo(e/2)), E, L-[]). +% E = (X is sqrt(_A+Y*_B)), L = [[]=_A,foo(e/2)=_B]. +% ``` +% +% NOTE: Order of clauses is important for correctness. +arithmetic_expansion(func, T, T, L-L) :- + (var(T); number(T)), !. +arithmetic_expansion(Set, T, R, LD) :- + functor(T, F, A), + arithmetic_term(Set, A, Fs), + member(F, Fs), !, + functor(R, F, A), + T =.. [F|Ts], + R =.. [F|Rs], + maplistdif(arithmetic_expansion(func), Ts, Rs, LD). +arithmetic_expansion(func, T, R, [T=R|L]-L). + +arithmetic_term(func, 0, [e,pi,epsilon]). +arithmetic_term(func, 1, [+,-,\,sqrt,exp,log,sin,cos,tan,asin,acos,atan,sign,abs,round,ceiling,floor,truncate,float,float_integer_part,float_fractional_part]). +arithmetic_term(func, 2, [+,-,/,*,**,^,/\,\/,xor,div,//,rdiv,<<,>>,mod,rem,max,min,gcd,atan2]). +arithmetic_term(rela, 2, [is,>,<,>=,=<,=:=,=\=]). + % Warn about builtin predicates re-definition. It can happen by mistake for % example: % x :- a. b, c. @@ -51,6 +90,10 @@ % term_warning(goal, \+ \+ \+_, "Nested negations can be reduced", []). +% Warn about invalid arithmetic relation and show all incorrect sub-expression +term_warning(goal, Term, "Arithmetic expression ~w contains invalid terms ~q", [R, [H|T]]) :- + arithmetic_expansion(rela, Term, R, [H|T]-[]). + %% expansion_hook(?Goal, +MetaVarSpecs). % % TLDR: Warn if currently expanded predicate calls one of its arguments, but it @@ -77,7 +120,7 @@ expansion_warning(ExpansionKind, Term) :- nonvar(Term), - term_warning(ExpansionKind, Term, Msg, Vars), + once(term_warning(ExpansionKind, Term, Msg, Vars)), warn(Msg, Vars), false. diff --git a/src/tests/warnings.pl b/src/tests/warnings.pl index 19c2c0931..edccbe288 100644 --- a/src/tests/warnings.pl +++ b/src/tests/warnings.pl @@ -18,3 +18,6 @@ % Shouldn't trigger meta-predicate warning a(L) :- maplist(=(_), L). + +% Shouldn't trigger invalid arithmetic expression warning +l :- _ is 1+2. diff --git a/src/tests/warnings3.pl b/src/tests/warnings3.pl new file mode 100644 index 000000000..60118d680 --- /dev/null +++ b/src/tests/warnings3.pl @@ -0,0 +1,4 @@ +:- use_module(library(warnings)). + +j(X, B) :- + X is [1] + sqrt(-phi*B + max(3+5)). diff --git a/tests/scryer/cli/src_tests/warnings_tests.stderr b/tests/scryer/cli/src_tests/warnings_tests.stderr index 08e711a76..56c6ce6bc 100644 --- a/tests/scryer/cli/src_tests/warnings_tests.stderr +++ b/tests/scryer/cli/src_tests/warnings_tests.stderr @@ -5,3 +5,4 @@ % Warning: Meta-predicate detected, but no qualified variables found at line 17 of warnings.pl % Warning: (b,c) attempts to re-define (,)/2 at line 6 of warnings1.pl % Warning: (/+c) attempts to re-define (/+)/1 at line 6 of warnings2.pl +% Warning: Arithmetic expression A is B+sqrt(-C*D+E) contains invalid terms [[1]=B,phi=C,max(3+5)=E] at line 4 of warnings3.pl diff --git a/tests/scryer/cli/src_tests/warnings_tests.stdout b/tests/scryer/cli/src_tests/warnings_tests.stdout index da05dfa15..984424813 100644 --- a/tests/scryer/cli/src_tests/warnings_tests.stdout +++ b/tests/scryer/cli/src_tests/warnings_tests.stdout @@ -1,2 +1,3 @@ error(permission_error(modify,static_procedure,(',')/2),load/1). error(permission_error(modify,static_procedure,(/+)/1),load/1). + error(type_error(evaluable,'.'/2),load/1). diff --git a/tests/scryer/cli/src_tests/warnings_tests.toml b/tests/scryer/cli/src_tests/warnings_tests.toml index 5bcfb0c2b..942fa1f0e 100644 --- a/tests/scryer/cli/src_tests/warnings_tests.toml +++ b/tests/scryer/cli/src_tests/warnings_tests.toml @@ -4,5 +4,6 @@ args = [ "src/tests/warnings.pl", "src/tests/warnings1.pl", "src/tests/warnings2.pl", + "src/tests/warnings3.pl", "-g", "halt" ]