Files
mercury/compiler/implementation_defined_literals.m
Zoltan Somogyi c509c49bdc Add a mechanism for generating warnings when the various clauses of a predicate
Estimated hours taken: 24
Branches: main

Add a mechanism for generating warnings when the various clauses of a predicate
or function are not contiguous.

This mechanism consists of two options:

	--warn-non-contiguous-clauses
	--warn-non-contiguous-foreign-procs

The first option generates warnings when the Mercury clauses of a predicate
or function are not contiguous, but it ignores any foreign_procs of that
predicate or function, and thus allows these to be away from the Mercury
clauses and each other. This option is enabled by default.

The second option generating warnings unless both the Mercury clauses and
all the foreign_procs of the predicate or function are all contiguous.
This option is not enabled by default, because many library modules
group foreign_procs not by predicate, but by foreign language. (All C foreign
procs for a group of predicates, then all the Java foreign procs for that group
of predicates, etc.)

compiler/hlds_clauses.m:
	Store, next to the representation of each clause list, information
	about the locations (item numbers and context) of the clauses.
	We store two versions of this information, one version for each option.

	Make the predicates that access the clause list access the location
	information as well, to ensure that any code that adds clauses also
	records their location.

	Add a predicate that tests for non-contiguity.

	Add a specific type to represent the modes that a clause applies to.
	This replaces the error-prone scheme we used to use that represented
	the notion "this clause applies to all modes" with an empty list of
	modes. This allows us to remove the code in add_pragma.m that used
	to replace these empty lists with the list of actual modes they
	represented.

	Change the prefix on the fields of clauses_info to avoid ambiguities.
	Add a prefix to the names of the function symbols of the clauses_rep
	type to avoid ambiguities.

compiler/add_clause.m:
compiler/add_pragma.m:
	When adding Mercury clauses and pragma foreign_procs to a predicate or
	function, record the location of the clause or foreign_procs. We do so
	even if the clause or foreign_proc is overridden by another. For
	example, when compiling to C, a Mercury clause overrides an Erlang
	foreign_proc, and a C foreign_proc overrides a Mercury clause.

	Fix an old bug where a foreign_proc that should override Mercury
	clauses overrode only one Mercury clause, and left the others
	in the predicate, to yield a disjunction with some Mercury disjuncts
	and a foreign_proc disjunct. This disjunction would then yield
	determinism errors if it had outputs.

	The new code that fixes the bug has a much more direct implicit
	correctness argument, and should be significantly easier to understand.
	It also avoids doing unnecessary work. (The old code could make a
	decision to ignore a clause, yet still proceed to transform it,
	just to ignore the result of the transformation.)

compiler/options.m:
	Add the new options.

doc/user_guide.texi:
	Document the new options. Fix an inconsistency between options.m and
	user_guide.texi for a nearby option.

compiler/make_hlds_passes.m:
	Pass the information that add_clause.m and add_pragma.m need.

compiler/typecheck.m:
	Detect non-contiguous clauses and call typecheck_errors to generate
	error messages.

compiler/typecheck_errors.m:
	Add functions for formatting error messages about non-contiguous
	clauses.

compiler/hlds_out.m:
	Do not print the modes to which a clause applies for the usual case,
	in which the clause applies to all modes.

compiler/clause_to_proc.m:
	Simplify some code.

	Rename a predicate to better reflect its purpose.

	Conform to the changes above.

compiler/intermod.m:
	Rename a predicate to avoid ambiguities.

	Conform to the changes above.

compiler/add_class.m:
compiler/add_pred.m:
compiler/add_special_pred.m:
compiler/assertion.m:
compiler/build_mode_constraints.m:
compiler/dead_proc_elim.m:
compiler/dependency_graph.m:
compiler/goal_path.m:
compiler/headvar_names.m:
compiler/hhf.m:
compiler/higher_order.m:
compiler/hlds_pred.m:
compiler/implementation_defined_literals.m:
compiler/mode_constraints.m:
compiler/modes.m:
compiler/ordering_mode_constraints.m:
compiler/polymorphism.m:
compiler/post_typecheck.m:
compiler/proc_gen.m:
compiler/prop_mode_constraints.m:
compiler/purity.m:
compiler/type_constraints.m:
compiler/unify_proc.m:
compiler/unused_imports.m:
	Conform to the changes above.

compiler/goal_form.m:
	The new warnings pointed out a non-contiguous clause in goal_form.m.
	Since this clause happened to be a duplicate of another clause, this
	diff deletes it. The duplicate clause was not detected because the
	predicate is semidet, and has no outputs.

compiler/mlds_to_c.m:
compiler/rbmm.points_to_analysis.m:
deep_profiler/measurements.m:
library/library.m:
library/list.m:
	Fix non-contiguous clauses pointed out by the new warnings.

library/bit_buffer.m:
	Fix programming style.

tests/invalid/types2.err_exp:
	This test has non-contiguous clauses, so expect the new warning.

tests/warnings/warn_contiguous.{m,exp}:
tests/warnings/warn_non_contiguous.{m,exp}:
tests/warnings/warn_non_contiguous_foreign.{m,exp}:
tests/warnings/warn_non_contiguous_foreign_group.{m,exp}:
	New test cases that exercise the new capability.

tests/warnings/Mmakefile:
tests/warnings/Mercury.options:
	Enable and specify the options for the new tests.
2009-08-19 07:45:13 +00:00

218 lines
8.3 KiB
Mathematica

%-----------------------------------------------------------------------------%
% vim: ft=mercury ts=4 sw=4 et
%-----------------------------------------------------------------------------%
% Copyright (C) 2008-2009 The University of Melbourne.
% This file may only be copied under the terms of the GNU General
% Public License - see the file COPYING in the Mercury distribution.
%-----------------------------------------------------------------------------%
%
% File: implementation_defined_literals.m.
% Author: wangp.
%
% This module replaces "implementation-defined literals" such as $file and
% $line by real constants. We transform clauses rather than procedures
% because, currently, clauses are written out to `.opt' files and $file and
% $line need to be substituted beforehand.
%
%-----------------------------------------------------------------------------%
:- module check_hlds.implementation_defined_literals.
:- interface.
:- import_module hlds.hlds_module.
:- pred subst_impl_defined_literals(module_info::in, module_info::out) is det.
%-----------------------------------------------------------------------------%
%-----------------------------------------------------------------------------%
:- implementation.
:- import_module hlds.
:- import_module hlds.hlds_clauses.
:- import_module hlds.hlds_goal.
:- import_module hlds.hlds_out.
:- import_module hlds.hlds_pred.
:- import_module libs.
:- import_module libs.compiler_util.
:- import_module libs.handle_options.
:- import_module mdbcomp.
:- import_module mdbcomp.prim_data.
:- import_module parse_tree.
:- import_module parse_tree.prog_data.
:- import_module list.
:- import_module map.
:- import_module term.
:- type subst_literals_info
---> subst_literals_info(
module_info,
pred_info,
pred_id
).
%-----------------------------------------------------------------------------%
subst_impl_defined_literals(!ModuleInfo) :-
module_info_preds(!.ModuleInfo, Preds0),
map.map_values(subst_literals_in_pred(!.ModuleInfo), Preds0, Preds),
module_info_set_preds(Preds, !ModuleInfo).
:- pred subst_literals_in_pred(module_info::in, pred_id::in, pred_info::in,
pred_info::out) is det.
subst_literals_in_pred(ModuleInfo, PredId, PredInfo0, PredInfo) :-
pred_info_get_clauses_info(PredInfo0, ClausesInfo0),
clauses_info_get_clauses_rep(ClausesInfo0, ClausesRep0, ItemNumbers),
get_clause_list(ClausesRep0, Clauses0),
Info = subst_literals_info(ModuleInfo, PredInfo0, PredId),
list.map(subst_literals_in_clause(Info), Clauses0, Clauses),
set_clause_list(Clauses, ClausesRep),
clauses_info_set_clauses_rep(ClausesRep, ItemNumbers,
ClausesInfo0, ClausesInfo),
pred_info_set_clauses_info(ClausesInfo, PredInfo0, PredInfo).
:- pred subst_literals_in_clause(subst_literals_info::in, clause::in,
clause::out) is det.
subst_literals_in_clause(Info, Clause0, Clause) :-
Body0 = Clause0 ^ clause_body,
subst_literals_in_goal(Info, Body0, Body),
Clause = Clause0 ^ clause_body := Body.
:- pred subst_literals_in_goal(subst_literals_info::in, hlds_goal::in,
hlds_goal::out) is det.
subst_literals_in_goal(Info, Goal0, Goal) :-
Goal0 = hlds_goal(GoalExpr0, GoalInfo0),
(
GoalExpr0 = unify(Var, RHS0, Mode, Kind, UnifyContext),
(
RHS0 = rhs_functor(ConsId, _, _),
(
ConsId = impl_defined_const(Name),
Context = goal_info_get_context(GoalInfo0),
make_impl_defined_literal(Var, Name, Context, Info, Goal1),
Goal1 = hlds_goal(GoalExpr, _),
Goal = hlds_goal(GoalExpr, GoalInfo0)
;
( ConsId = cons(_, _, _)
; ConsId = tuple_cons(_)
; ConsId = closure_cons(_, _)
; ConsId = int_const(_)
; ConsId = float_const(_)
; ConsId = char_const(_)
; ConsId = string_const(_)
; ConsId = type_ctor_info_const(_, _, _)
; ConsId = base_typeclass_info_const(_, _, _, _)
; ConsId = type_info_cell_constructor(_)
; ConsId = typeclass_info_cell_constructor
; ConsId = tabling_info_const(_)
; ConsId = deep_profiling_proc_layout(_)
; ConsId = table_io_decl(_)
),
Goal = Goal0
)
;
RHS0 = rhs_lambda_goal(LambdaPurity, Groundness, PredOrFunc,
EvalMethod, LambdaNonLocals, LambdaQuantVars,
LambdaModes, LambdaDetism, LambdaGoal0),
subst_literals_in_goal(Info, LambdaGoal0, LambdaGoal),
RHS = rhs_lambda_goal(LambdaPurity, Groundness, PredOrFunc,
EvalMethod, LambdaNonLocals, LambdaQuantVars,
LambdaModes, LambdaDetism, LambdaGoal),
GoalExpr = unify(Var, RHS, Mode, Kind, UnifyContext),
Goal = hlds_goal(GoalExpr, GoalInfo0)
;
RHS0 = rhs_var(_),
Goal = Goal0
)
;
GoalExpr0 = negation(SubGoal0),
subst_literals_in_goal(Info, SubGoal0, SubGoal),
GoalExpr = negation(SubGoal),
Goal = hlds_goal(GoalExpr, GoalInfo0)
;
GoalExpr0 = scope(Reason, SubGoal0),
% Implementation-defined literals may appear in
% from_ground_term_construct scopes.
subst_literals_in_goal(Info, SubGoal0, SubGoal),
GoalExpr = scope(Reason, SubGoal),
Goal = hlds_goal(GoalExpr, GoalInfo0)
;
GoalExpr0 = conj(ConjType, Goals0),
list.map(subst_literals_in_goal(Info), Goals0, Goals),
GoalExpr = conj(ConjType, Goals),
Goal = hlds_goal(GoalExpr, GoalInfo0)
;
GoalExpr0 = disj(Goals0),
list.map(subst_literals_in_goal(Info), Goals0, Goals),
GoalExpr = disj(Goals),
Goal = hlds_goal(GoalExpr, GoalInfo0)
;
GoalExpr0 = switch(Var, CanFail, Cases0),
list.map(subst_literals_in_case(Info), Cases0, Cases),
GoalExpr = switch(Var, CanFail, Cases),
Goal = hlds_goal(GoalExpr, GoalInfo0)
;
GoalExpr0 = if_then_else(Vars, Cond0, Then0, Else0),
subst_literals_in_goal(Info, Cond0, Cond),
subst_literals_in_goal(Info, Then0, Then),
subst_literals_in_goal(Info, Else0, Else),
GoalExpr = if_then_else(Vars, Cond, Then, Else),
Goal = hlds_goal(GoalExpr, GoalInfo0)
;
( GoalExpr0 = call_foreign_proc(_, _, _, _, _, _, _)
; GoalExpr0 = generic_call(_, _, _, _)
; GoalExpr0 = plain_call(_, _, _, _, _, _)
; GoalExpr0 = shorthand(_)
),
Goal = Goal0
).
:- pred subst_literals_in_case(subst_literals_info::in, case::in, case::out)
is det.
subst_literals_in_case(Info, Case0, Case) :-
Case0 = case(MainConsId, OtherConsIds, Goal0),
subst_literals_in_goal(Info, Goal0, Goal),
Case = case(MainConsId, OtherConsIds, Goal).
:- pred make_impl_defined_literal(prog_var::in, string::in,
term.context::in, subst_literals_info::in, hlds_goal::out) is det.
make_impl_defined_literal(Var, Name, Context, Info, Goal) :-
Context = term.context(File, Line),
Info = subst_literals_info(ModuleInfo, PredInfo, PredId),
( Name = "file" ->
make_string_const_construction(Var, File, Goal)
; Name = "line" ->
make_int_const_construction(Var, Line, Goal)
; Name = "module" ->
ModuleName = pred_info_module(PredInfo),
Str = sym_name_to_string(ModuleName),
make_string_const_construction(Var, Str, Goal)
; Name = "pred" ->
Str = pred_id_to_string(ModuleInfo, PredId),
make_string_const_construction(Var, Str, Goal)
; Name = "grade" ->
module_info_get_globals(ModuleInfo, Globals),
grade_directory_component(Globals, Grade),
make_string_const_construction(Var, Grade, Goal)
;
% These should have been caught during type checking.
unexpected(this_file,
"make_impl_defined_literal: unknown literal")
).
%-----------------------------------------------------------------------------%
:- func this_file = string.
this_file = "implementation_defined_literals.m".
%-----------------------------------------------------------------------------%
:- end_module implementation_defined_literals.
%-----------------------------------------------------------------------------%