[m-rev.] for review: --warn-non-tail-recursion in low-level grades

Peter Wang novalazy at gmail.com
Mon Jul 9 16:33:38 AEST 2012


Branches: main

Allow `--warn-non-tail-recursion' with the low-level backend.

compiler/handle_options.m:
	Do not require `--high-level-code' for `--warn-non-tail-recursion'.

	Emit an error if `--warn-non-tail-recursion' is used with
	`--pessimize-tailcalls'.

compiler/mark_tail_calls.m:
	Add a pass that uses the goal feature set by this module to report
	about directly recursive, but not tail-recursive, calls.

compiler/mercury_compile_llds_back_end.m:
	Run the new pass in the low-level backend, for both settings of
	`--trad-passes'.

compiler/options.m:
doc/user_guide.texi:
	Update documentation.

diff --git a/compiler/handle_options.m b/compiler/handle_options.m
index 29f0b23..1e53aee 100644
--- a/compiler/handle_options.m
+++ b/compiler/handle_options.m
@@ -2214,15 +2214,20 @@ convert_options_to_globals(OptionTable0, Target, GC_Method, TagsMethod0,
     option_implies(use_opt_files, warn_missing_opt_files, bool(no),
         !Globals),
 
-    % --warn-non-tail-recursion requires both --high-level-code
-    % and --optimize-tailcalls.  It also doesn't work if you use
-    % --errorcheck-only.
-    option_requires(warn_non_tail_recursion, highlevel_code, bool(yes),
-        "--warn-non-tail-recursion requires --high-level-code",
-        !.Globals, !Errors),
-    option_requires(warn_non_tail_recursion, optimize_tailcalls, bool(yes),
-        "--warn-non-tail-recursion requires --optimize-tailcalls",
-        !.Globals, !Errors),
+    % --warn-non-tail-recursion requires tail call optimization to be enabled.
+    % It also doesn't work if you use --errorcheck-only.
+    (
+        HighLevelCode = no,
+        option_requires(warn_non_tail_recursion, pessimize_tailcalls, bool(no),
+            "--warn-non-tail-recursion is incompatible with " ++
+            "--pessimize-tailcalls",
+            !.Globals, !Errors)
+    ;
+        HighLevelCode = yes,
+        option_requires(warn_non_tail_recursion, optimize_tailcalls, bool(yes),
+            "--warn-non-tail-recursion requires --optimize-tailcalls",
+            !.Globals, !Errors)
+    ),
     option_requires(warn_non_tail_recursion, errorcheck_only, bool(no),
         "--warn-non-tail-recursion is incompatible with " ++
         "--errorcheck-only",
diff --git a/compiler/mark_tail_calls.m b/compiler/mark_tail_calls.m
index cd8961e..b843be0 100644
--- a/compiler/mark_tail_calls.m
+++ b/compiler/mark_tail_calls.m
@@ -9,13 +9,16 @@
 % File: mark_tail_calls.m.
 % Main author: zs.
 %
-% This module adds feature_tailcall to all self-recursive calls that can be
+% This module adds a feature to all self-recursive calls that can be
 % implemented as tail calls.
 %
 % Since an assignment unification that simply renames an output of a recursive
 % call may prevent that call from being recognized as a tail call, you probably
 % want to run excess assign elimination just before invoking this module.
 %
+% This module also contains a pass that detects predicates which are directly
+% recursive, but not tail-recursive, and warns about them.
+%
 %-----------------------------------------------------------------------------%
 
 :- module hlds.mark_tail_calls.
@@ -24,20 +27,36 @@
 :- import_module hlds.hlds_goal.
 :- import_module hlds.hlds_module.
 :- import_module hlds.hlds_pred.
+:- import_module libs.globals.
+
+:- import_module io.
 
 :- pred mark_tail_calls(goal_feature::in, module_info::in, pred_proc_id::in,
     pred_info::in, proc_info::in, proc_info::out) is det.
 
+:- pred warn_non_tail_calls(module_info::in, io::di, io::uo) is det.
+
+:- pred warn_non_tail_calls_in_proc(globals::in, pred_id::in, proc_id::in,
+    pred_info::in, proc_info::in, io::di, io::uo) is det.
+
+%-----------------------------------------------------------------------------%
 %-----------------------------------------------------------------------------%
 
 :- implementation.
 
 :- import_module check_hlds.mode_util.
+:- import_module hlds.goal_util.
+:- import_module mdbcomp.prim_data.
+:- import_module parse_tree.error_util.
 :- import_module parse_tree.prog_data.
 
+:- import_module int.
 :- import_module list.
 :- import_module maybe.
 :- import_module require.
+:- import_module solutions.
+
+%-----------------------------------------------------------------------------%
 
 :- type found_tail_calls
     --->    found_tail_calls
@@ -299,5 +318,85 @@ match_output_args([MaybeOutputVar | MaybeOutputVars], [ArgVar | ArgVars]) :-
     match_output_args(MaybeOutputVars, ArgVars).
 
 %-----------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
+
+warn_non_tail_calls(ModuleInfo, !IO) :-
+    solutions.solutions(nontailcall_in_hlds(ModuleInfo), Warnings),
+    module_info_get_globals(ModuleInfo, Globals),
+    list.foldl(report_nontailcall_warning(Globals), Warnings, !IO).
+
+warn_non_tail_calls_in_proc(Globals, PredId, ProcId, PredInfo, ProcInfo,
+        !IO) :-
+    solutions.solutions(
+        nontailcall_in_proc(PredId, ProcId, PredInfo, ProcInfo), Warnings),
+    list.foldl(report_nontailcall_warning(Globals), Warnings, !IO).
+
+:- type tailcall_warning
+    --->    tailcall_warning(
+                pred_or_func,
+                sym_name,
+                arity,
+                proc_id,
+                prog_context
+            ).
+
+:- pred nontailcall_in_hlds(module_info::in, tailcall_warning::out) is nondet.
+
+nontailcall_in_hlds(!.ModuleInfo, Warning) :-
+    module_info_get_valid_predids(PredIds, !ModuleInfo),
+    list.member(PredId, PredIds),
+    nontailcall_in_pred(!.ModuleInfo, PredId, Warning).
+
+:- pred nontailcall_in_pred(module_info::in, pred_id::in,
+    tailcall_warning::out) is nondet.
+
+nontailcall_in_pred(ModuleInfo, PredId, Warning) :-
+    module_info_pred_info(ModuleInfo, PredId, PredInfo),
+    ProcIds = pred_info_non_imported_procids(PredInfo),
+    list.member(ProcId, ProcIds),
+    pred_info_proc_info(PredInfo, ProcId, ProcInfo),
+    nontailcall_in_proc(PredId, ProcId, PredInfo, ProcInfo, Warning).
+
+:- pred nontailcall_in_proc(pred_id::in, proc_id::in, pred_info::in,
+    proc_info::in, tailcall_warning::out) is nondet.
+
+nontailcall_in_proc(PredId, ProcId, PredInfo, ProcInfo, Warning) :-
+    proc_info_get_goal(ProcInfo, Goal),
+    goal_contains_goal(Goal, SubGoal),
+    SubGoal = hlds_goal(SubGoalExpr, SubGoalInfo),
+    SubGoalExpr = plain_call(CallPredId, CallProcId, CallArgs, Builtin,
+        _UnifyContext, SymName),
+    % Check if this call is a directly recursive call.
+    CallPredId = PredId,
+    CallProcId = ProcId,
+    Builtin = not_builtin,
+    not goal_has_feature(SubGoal, feature_debug_tail_rec_call),
+    % Don't warn about special predicates.
+    not is_unify_or_compare_pred(PredInfo),
+
+    PredOrFunc = pred_info_is_pred_or_func(PredInfo),
+    list.length(CallArgs, Arity),
+    Context = goal_info_get_context(SubGoalInfo),
+    Warning = tailcall_warning(PredOrFunc, SymName, Arity, CallProcId,
+        Context).
+
+:- pred report_nontailcall_warning(globals::in, tailcall_warning::in,
+    io::di, io::uo) is det.
+
+report_nontailcall_warning(Globals, Warning, !IO) :-
+    Warning = tailcall_warning(PredOrFunc, SymName, Arity, ProcId, Context),
+    Name = unqualify_name(SymName),
+    SimpleCallId = simple_call_id(PredOrFunc, unqualified(Name), Arity),
+    proc_id_to_int(ProcId, ProcNumber0),
+    ProcNumber = ProcNumber0 + 1,
+    Pieces =
+        [words("In mode number"), int_fixed(ProcNumber),
+        words("of"), simple_call(SimpleCallId), suffix(":"), nl,
+        words("warning: recursive call is not tail recursive."), nl],
+    Msg = simple_msg(Context, [always(Pieces)]),
+    Spec = error_spec(severity_warning, phase_code_gen, [Msg]),
+    write_error_spec(Spec, Globals, 0, _NumWarnings, 0, _NumErrors, !IO).
+
+%-----------------------------------------------------------------------------%
 :- end_module hlds.mark_tail_calls.
 %-----------------------------------------------------------------------------%
diff --git a/compiler/mercury_compile_llds_back_end.m b/compiler/mercury_compile_llds_back_end.m
index 9274fb2..580528d 100644
--- a/compiler/mercury_compile_llds_back_end.m
+++ b/compiler/mercury_compile_llds_back_end.m
@@ -166,6 +166,8 @@ llds_backend_pass_by_phases(!HLDS, !GlobalData, !:LLDS, !DumpInfo, !IO) :-
     maybe_mark_tail_rec_calls(Verbose, Stats, !HLDS, !IO),
     maybe_dump_hlds(!.HLDS, 332, "mark_debug_tailrec_calls", !DumpInfo, !IO),
 
+    maybe_warn_non_tail_recursion(Verbose, Stats, !.HLDS, !IO),
+
     compute_stack_vars(Verbose, Stats, !HLDS, !IO),
     maybe_dump_hlds(!.HLDS, 335, "stackvars", !DumpInfo, !IO),
 
@@ -357,15 +359,25 @@ llds_backend_pass_for_proc(!HLDS, ConstStructMap, PredId, PredInfo,
         !.HLDS, !IO),
     detect_liveness_proc(!.HLDS, PredProcId, !ProcInfo),
     globals.lookup_bool_option(Globals, exec_trace_tail_rec, ExecTraceTailRec),
+    globals.lookup_bool_option(Globals, warn_non_tail_recursion,
+        WarnTailCalls),
+    MarkTailCalls = bool.or(ExecTraceTailRec, WarnTailCalls),
     (
-        ExecTraceTailRec = yes,
+        MarkTailCalls = yes,
         write_proc_progress_message(
             "% Marking directly tail recursive calls in ", PredId, ProcId,
             !.HLDS, !IO),
         mark_tail_calls(feature_debug_tail_rec_call, !.HLDS, PredProcId,
             PredInfo, !ProcInfo)
     ;
-        ExecTraceTailRec = no
+        MarkTailCalls = no
+    ),
+    (
+        WarnTailCalls = yes,
+        warn_non_tail_calls_in_proc(Globals, PredId, ProcId, PredInfo,
+            !.ProcInfo, !IO)
+    ;
+        WarnTailCalls = no
     ),
     write_proc_progress_message("% Allocating stack slots in ", PredId,
         ProcId, !.HLDS, !IO),
@@ -487,8 +499,11 @@ compute_liveness(Verbose, Stats, !HLDS, !IO) :-
 maybe_mark_tail_rec_calls(Verbose, Stats, !HLDS, !IO) :-
     module_info_get_globals(!.HLDS, Globals),
     globals.lookup_bool_option(Globals, exec_trace_tail_rec, ExecTraceTailRec),
+    globals.lookup_bool_option(Globals, warn_non_tail_recursion,
+        WarnTailCalls),
+    MarkTailCalls = bool.or(ExecTraceTailRec, WarnTailCalls),
     (
-        ExecTraceTailRec = yes,
+        MarkTailCalls = yes,
         maybe_write_string(Verbose,
             "% Marking directly tail recursive calls...", !IO),
         maybe_flush_output(Verbose, !IO),
@@ -498,7 +513,25 @@ maybe_mark_tail_rec_calls(Verbose, Stats, !HLDS, !IO) :-
         maybe_write_string(Verbose, " done.\n", !IO),
         maybe_report_stats(Stats, !IO)
     ;
-        ExecTraceTailRec = no
+        MarkTailCalls = no
+    ).
+
+:- pred maybe_warn_non_tail_recursion(bool::in, bool::in,
+    module_info::in, io::di, io::uo) is det.
+
+maybe_warn_non_tail_recursion(Verbose, Stats, HLDS, !IO) :-
+    module_info_get_globals(HLDS, Globals),
+    globals.lookup_bool_option(Globals, warn_non_tail_recursion,
+        WarnTailCalls),
+    (
+        WarnTailCalls = yes,
+        maybe_write_string(Verbose,
+            "% Warning about non-tail recursive calls...\n", !IO),
+        warn_non_tail_calls(HLDS, !IO),
+        maybe_write_string(Verbose, "% done.\n", !IO),
+        maybe_report_stats(Stats, !IO)
+    ;
+        WarnTailCalls = no
     ).
 
 :- pred compute_stack_vars(bool::in, bool::in,
diff --git a/compiler/options.m b/compiler/options.m
index b94b043..363355e 100644
--- a/compiler/options.m
+++ b/compiler/options.m
@@ -3551,7 +3551,6 @@ options_help_warning -->
         "\toptions files with `--make'.",
         "--warn-non-tail-recursion",
         "\tWarn about any directly recursive calls that are not tail calls.",
-        "\tThis requires --high-level-code.",
         "--no-warn-up-to-date",
         "\tDon't warn if targets specified on the command line",
         "\twith `--make' are already up to date.",
diff --git a/doc/user_guide.texi b/doc/user_guide.texi
index f50aa97..93dbbc2 100644
--- a/doc/user_guide.texi
+++ b/doc/user_guide.texi
@@ -6564,7 +6564,6 @@ options files with @samp{--make}.
 @item --warn-non-tail-recursion
 @findex --warn-non-tail-recursion
 Warn about any directly recursive calls that are not tail recursive.
-This option also requires @samp{--high-level-code}.
 
 @sp 1
 @item --no-warn-target-code

--------------------------------------------------------------------------
mercury-reviews mailing list
Post messages to:       mercury-reviews at csse.unimelb.edu.au
Administrative Queries: owner-mercury-reviews at csse.unimelb.edu.au
Subscriptions:          mercury-reviews-request at csse.unimelb.edu.au
--------------------------------------------------------------------------



More information about the reviews mailing list