[m-rev.] for review: warn about insts without matching types

Ian MacLarty maclarty at csse.unimelb.edu.au
Fri Jul 14 16:05:34 AEST 2006


On Tue, Jul 04, 2006 at 07:06:41PM +1000, Julien Fischer wrote:
> 
> On Tue, 4 Jul 2006, Ian MacLarty wrote:
> 
> > compiler/mercury_compile.m:
> > 	Check insts at stage 12, before type and mode checking.
> >
> > compiler/options.m:
> > 	Add an option to turn the new warning on or off.
> 
> You also need to add the new option to the user's guide.  You also need
> to mention the new module in compiler/notes/compiler_design.html.
> 

Done. Done.

> ...
> 
> > Index: compiler/inst_check.m
> > ===================================================================
> > RCS file: compiler/inst_check.m
> > diff -N compiler/inst_check.m
> > --- /dev/null	1 Jan 1970 00:00:00 -0000
> > +++ compiler/inst_check.m	4 Jul 2006 00:10:33 -0000
> > @@ -0,0 +1,291 @@
> > +%-----------------------------------------------------------------------------%
> > +% vim: ft=mercury ts=4 sw=4 et
> > +%-----------------------------------------------------------------------------%
> > +% Copyright (C) 2006 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: inst_check.m
> > +% Main author: maclarty.
> > +%
> > +% This module exports a predicate that checks that each user defined inst is
> > +% consistant with at least one type in scope.
> > +%
> > +% TODO:
> > +%   If we find an inst that is not consistent with any types in scope,
> 
> not consistent == inconsistent
> 

That would change the meaning of the sentence.  The sentence should be
parsed as "If we find an inst that is not (consistent with any types in
scope) ...".

Perhaps I should change it to "is inconsistent with all the types
in scope"?

> I would say "any of the types" in preference to "any" - if you're just
> skimming the comments it's too easy to confuse that with the any of any
> insts.  (change the other spots in the NEWS file etc as well.)

Done.

> 
> > +%   except for one function symbol with a different arity, then we
> > +%   should communicate this in the warning message.
> > +%
> > +%-----------------------------------------------------------------------------%
> > +
> > +:- module check_hlds.inst_check.
> > +
> > +:- interface.
> > +
> > +:- import_module io.
> > +
> > +:- import_module hlds.hlds_module.
> > +
> > +    % This predicate issues a warning for each user defined bound insts
> > +    % that is not consistant with at least one type in scope.
> > +    %
> > +:- pred check_insts_have_matching_types(module_info::in,
> > +    io::di, io::uo) is det.
> > +
> 
> ...
> 
> > +check_insts_have_matching_types(Module, !IO) :-
> > +    module_info_get_inst_table(Module, InstTable),
> > +    inst_table_get_user_insts(InstTable, UserInstTable),
> > +    user_inst_table_get_inst_defns(UserInstTable, InstDefs),
> > +    module_info_get_type_table(Module, TypeTable),
> > +    TypeDefs = map.values(TypeTable),
> 
> You should exclude opt-imported type definitions here.  Otherwise we could end
> up with the situation where a program will compile with
> `--intermodule-optimization' enabled but won't compile otherwise.  ( You'll also
> need to add a test case for that as well - or extend the existing one.)

Done. Done.

> 
> ...
> 
> > +:- type functors_to_types == multi_map(sym_name_and_arity, hlds_type_defn).
> > +
> > +:- type bound_inst_functor
> > +    --->    name_and_arity(sym_name, int)
> 
> s/int/arity/
> 

Done.

> ...
> 
> > +:- pred maybe_issue_inst_check_warning(inst_id::in, hlds_inst_defn::in,
> > +    list(list(type_defn_or_builtin))::in, io::di, io::uo) is det.
> > +
> > +maybe_issue_inst_check_warning(InstId, InstDef, MatchingTypeLists,
> > +        !IO) :-
> > +    ( if
> > +        MatchingTypeLists = [MatchingTypeList | _],
> > +        not (some [Type] (
> > +            list.member(Type, MatchingTypeList),
> > +            all [TypeList] (
> > +                list.member(TypeList, MatchingTypeLists)
> > +            =>
> > +                list.member(Type, TypeList)
> > +            )
> > +        ))
> > +    then
> > +        Context = InstDef ^ inst_context,
> > +        InstId = inst_id(InstName, InstArity),
> > +        InstSymNameAndArity = InstName / InstArity,
> > +        report_warning(Context, 0, [words("warning: inst "),
> > +            sym_name_and_arity(InstSymNameAndArity),
> > +            words(" has no matching type in scope.")], !IO)
> 
> For consistency with the other warnings in the compiler: s/warning/Warning/.
> 

Grepping for "\"Warning:" in the compiler directory yields 40 hits,
while "\"warning:" yields 21 hits, so "Warning:" seems to be the
winner, but there's still a lot of inconsistency.

I've changed it to "Warning:".

> Just a formatting issue: I would rewrite that as
> 
> 	Warning = [
> 		words("Warning: inst"),
> 		sym_name_and_arity(InstName / InstArity),
> 		words("does not match any of the types in scope.")
> 	],
> 	report_warning(Context, 0, Warning, !IO).
> 
> The rationale is that it makes the warning message easier to modify.
> (Also you have extraneous spaces in the words format component.)
> 

Done.

> ...
> 
> > +long_option("warn-insts-without-matching-type",
> > +    warn_insts_without_matching_type).
> >
> >  % verbosity options
> >  long_option("verbose",                  verbose).
> > @@ -2766,6 +2770,9 @@
> >          "--no-warn-inferred-erroneous",
> >          "\tDon't warn about procedures whose determinism is inferred",
> >          "\terroneous but whose determinism declarations are laxer.",
> > +        "--no-warn-insts-without-matching-type",
> > +        "\tDon't warn about insts that are not consistent with any",
> > +        "\ttypes in scope.",
> 
> 
> 	Don't warn about insts that are inconsistent with any of the
> 	types in scope.
> 

No, that changes the meaning.

> 
> > Index: tests/warnings/inst_with_no_type.m
> > ===================================================================
> > RCS file: tests/warnings/inst_with_no_type.m
> > diff -N tests/warnings/inst_with_no_type.m
> > --- /dev/null	1 Jan 1970 00:00:00 -0000
> > +++ tests/warnings/inst_with_no_type.m	4 Jul 2006 00:10:33 -0000
> > @@ -0,0 +1,64 @@
> > +:- module inst_with_no_type.
> > +
> > +:- interface.
> > +
> > +:- inst chars
> > +	--->	a
> > +	;	b
> > +	;	c.
> > +
> > +:- inst i1
> > +	--->	t1_f1(ground, ground)
> > +	;	t1_f2(ground).
> > +
> > +:- inst i1_no_match
> > +	--->	t1_f1(ground)
> > +	;	t1_f2(ground).
> > +
> > +:- type t1
> > +	--->	t1_f1(int, int)
> > +	;	t1_f2(string).
> > +
> > +:- inst i2(I)
> > +	--->	i2_f1(ground, I)
> > +	;	i2_f2(ground, ground, ground)
> > +	;	i2_f3(ground)
> > +	;	i2_f4.
> > +
> > +:- type t2(T)
> > +	--->	i2_f1(character, T)
> > +	;	i2_f2(T, T, int)
> > +	;	i2_f3(float)
> > +	;	i2_f4
> > +	;	i2_f5.
> > +
> > +:- inst i2_no_match(I)
> > +	--->	i2_f1(ground, I)
> > +	;	i2_f2(ground, ground, ground, ground)
> > +	;	i2_f3(ground)
> > +	;	i2_f4.
> > +
> > +:- inst i3
> > +	--->	"a"
> > +	;	"b"
> > +	;	"c".
> > +
> > +:- inst i4_no_match
> > +	--->	1
> > +	;	2
> > +	;	"3".
> > +
> > +:- inst i5
> > +	--->	1
> > +	;	2.
> > +
> > +:- inst i6
> > +	--->	1.1
> > +	;	1.2.
> > +
> > +:- inst i7_no_match
> > +	--->	1.0
> > +	;	1.
> > +
> > +:- inst tuple
> > +	--->	{ground, ground}.
> 
> I suggest adding some other insts to this test case as well, e.g. some
> higher-order ones, any ones, (mostly-)uniques ones etc.
> 

Done.

> Also, we (currently) need to support the situation where an inst in the
> interface refers to constructors in the implementation (due to the
> implementation not supporting abstract insts), e.g.
> 
> 	:- interface.
> 
> 	:- type fruit.
> 	:- type citrus ---> lemon ; orange.

You mean ":- inst citrus ...".

> 
> 	:- implementation.
> 
> 	:- type fruit ---> apple ; orange ; lemon.
> 

Done.  It works.

Here is the interdiff (still pending bootcheck):

diff -u NEWS NEWS
--- NEWS	4 Jul 2006 00:10:33 -0000
+++ NEWS	14 Jul 2006 05:32:29 -0000
@@ -58,7 +58,7 @@
 * We have deleted the old --split-c-files option, as it conflicted with the
   implementation of module initialisation and finalisation.
 * The compiler now issues a warning when an inst declaration isn't
-  consistent with any types in scope.
+  consistent with any of the types in scope.
 
 Portability Improvements:
 * We've ported Mercury to the x86_64 (AMD64 / Intel EMT64) architecure.
@@ -324,7 +324,7 @@
   printed are not statically available.
 
 * The compiler now issues a warning when an inst declaration isn't
-  consistent with any types in scope.
+  consistent with any of the types in scope.
 
   This makes it easier to diagnose mode errors caused by insts that are not
   consistent with the type they are intended to be consistent with.
diff -u compiler/inst_check.m compiler/inst_check.m
--- compiler/inst_check.m	4 Jul 2006 00:10:33 -0000
+++ compiler/inst_check.m	14 Jul 2006 05:32:29 -0000
@@ -13,9 +13,9 @@
 % consistant with at least one type in scope.
 %
 % TODO:
-%   If we find an inst that is not consistent with any types in scope,
+%   If we find an inst that is not consistent with any of the types in scope,
 %   except for one function symbol with a different arity, then we
-%   should communicate this in the warning message.
+%   should include this information in the warning message.
 %
 %-----------------------------------------------------------------------------%
 
@@ -63,11 +63,13 @@
     inst_table_get_user_insts(InstTable, UserInstTable),
     user_inst_table_get_inst_defns(UserInstTable, InstDefs),
     module_info_get_type_table(Module, TypeTable),
-    TypeDefs = map.values(TypeTable),
+    AllTypeDefs = map.values(TypeTable),
+    list.filter(type_is_user_visible, AllTypeDefs, UserVisibleTypeDefs),
     InstIdDefPairs = map.to_assoc_list(InstDefs),
     list.filter(inst_is_defined_in_current_module, InstIdDefPairs,
         InstIdDefPairsForCurrentModule),
-    FunctorsToTypeDefs = index_types_by_unqualified_functors(TypeDefs),
+    FunctorsToTypeDefs = index_types_by_unqualified_functors(
+        UserVisibleTypeDefs),
     list.foldl_corresponding(check_inst(FunctorsToTypeDefs),
         assoc_list.keys(InstIdDefPairsForCurrentModule), 
         assoc_list.values(InstIdDefPairsForCurrentModule), !IO).
@@ -79,10 +81,16 @@
     ImportStatus = InstDef ^ inst_status,
     status_defined_in_this_module(ImportStatus, yes).
 
+:- pred type_is_user_visible(hlds_type_defn::in) is semidet.
+
+type_is_user_visible(TypeDef) :-
+    get_type_defn_status(TypeDef, ImportStatus),
+    status_is_user_visible(ImportStatus, yes).
+
 :- type functors_to_types == multi_map(sym_name_and_arity, hlds_type_defn).
 
 :- type bound_inst_functor
-    --->    name_and_arity(sym_name, int)
+    --->    name_and_arity(sym_name, arity)
     ;       string_constant
     ;       int_constant
     ;       float_constant.
@@ -145,10 +153,12 @@
     then
         Context = InstDef ^ inst_context,
         InstId = inst_id(InstName, InstArity),
-        InstSymNameAndArity = InstName / InstArity,
-        report_warning(Context, 0, [words("warning: inst "),
-            sym_name_and_arity(InstSymNameAndArity),
-            words(" has no matching type in scope.")], !IO)
+        Warning = [
+            words("Warning: inst "),
+            sym_name_and_arity(InstName / InstArity),
+            words("does not match any of the types in scope.")
+        ],
+        report_warning(Context, 0, Warning, !IO)
     else
         true
     ).
diff -u compiler/options.m compiler/options.m
--- compiler/options.m	4 Jul 2006 00:10:33 -0000
+++ compiler/options.m	14 Jul 2006 05:32:29 -0000
@@ -2772,7 +2772,7 @@
         "\terroneous but whose determinism declarations are laxer.",
         "--no-warn-insts-without-matching-type",
         "\tDon't warn about insts that are not consistent with any",
-        "\ttypes in scope.",
+        "\tof the types in scope.",
         "--no-warn-nothing-exported",
         "\tDon't warn about modules which export nothing.",
         "--warn-unused-args",
diff -u tests/warnings/Mercury.options tests/warnings/Mercury.options
--- tests/warnings/Mercury.options	4 Jul 2006 00:10:33 -0000
+++ tests/warnings/Mercury.options	14 Jul 2006 05:32:29 -0000
@@ -49 +49 @@
-MCFLAGS-inst_with_no_type = --warn-insts-without-matching-type
+MCFLAGS-inst_with_no_type = --warn-insts-without-matching-type --intermodule-optimization --no-intermodule-analysis
diff -u tests/warnings/inst_with_no_type.exp tests/warnings/inst_with_no_type.exp
--- tests/warnings/inst_with_no_type.exp	4 Jul 2006 00:10:33 -0000
+++ tests/warnings/inst_with_no_type.exp	14 Jul 2006 05:49:49 -0000
@@ -1,8 +1,15 @@
-inst_with_no_type.m:014: warning: inst `inst_with_no_type.i1_no_match'/0 has no
-inst_with_no_type.m:014:   matching type in scope.
-inst_with_no_type.m:035: warning: inst `inst_with_no_type.i2_no_match'/1 has no
-inst_with_no_type.m:035:   matching type in scope.
-inst_with_no_type.m:046: warning: inst `inst_with_no_type.i4_no_match'/0 has no
-inst_with_no_type.m:046:   matching type in scope.
-inst_with_no_type.m:059: warning: inst `inst_with_no_type.i7_no_match'/0 has no
-inst_with_no_type.m:059:   matching type in scope.
+inst_with_no_type.m:014: Warning: inst `inst_with_no_type.i1_no_match'/0 does
+inst_with_no_type.m:014:   not match any of the types in scope.
+inst_with_no_type.m:035: Warning: inst `inst_with_no_type.i2_no_match'/1 does
+inst_with_no_type.m:035:   not match any of the types in scope.
+inst_with_no_type.m:046: Warning: inst `inst_with_no_type.i4_no_match'/0 does
+inst_with_no_type.m:046:   not match any of the types in scope.
+inst_with_no_type.m:059: Warning: inst `inst_with_no_type.i7_no_match'/0 does
+inst_with_no_type.m:059:   not match any of the types in scope.
+inst_with_no_type.m:072: Warning: inst
+inst_with_no_type.m:072:   `inst_with_no_type.mostly_unique_no_match'/0 does
+inst_with_no_type.m:072:   not match any of the types in scope.
+inst_with_no_type.m:076: Warning: inst `inst_with_no_type.unique_no_match'/0
+inst_with_no_type.m:076:   does not match any of the types in scope.
+inst_with_no_type.m:092: Warning: inst `inst_with_no_type.t_no_match'/0 does
+inst_with_no_type.m:092:   not match any of the types in scope.
diff -u tests/warnings/inst_with_no_type.m tests/warnings/inst_with_no_type.m
--- tests/warnings/inst_with_no_type.m	4 Jul 2006 00:10:33 -0000
+++ tests/warnings/inst_with_no_type.m	14 Jul 2006 05:32:29 -0000
@@ -64,0 +65,34 @@
+
+:- inst ho == (pred(in, out) is det).
+
+:- inst any_inst == any.
+
+:- inst mostly_unique_inst == mostly_unique(apple ; lemon).
+
+:- inst mostly_unique_no_match == mostly_unique(apple ; banana).
+
+:- inst unique_inst == unique(apple ; lemon).
+
+:- inst unique_no_match == unique(apple ; banana).
+
+:- type fruit.
+:- inst citrus ---> lemon ; orange.
+
+:- implementation.
+
+:- import_module io.
+
+:- import_module inst_with_no_type_2.
+
+	% Even though t is defined in the implementation of
+	% inst_with_no_type_2 we should get a warning for the following
+	% insts, since the function symbol t is not user visible from 
+	% this scope.
+	%
+:- inst t_no_match ---> t.
+
+:- type fruit ---> apple ; orange ; lemon.
+
+:- pred q(t::in, io::di, io::uo) is det.
+
+q(T, !IO) :- p(T, !IO).
only in patch2:
unchanged:
--- compiler/hlds_pred.m	12 Jul 2006 02:51:00 -0000	1.200
+++ compiler/hlds_pred.m	14 Jul 2006 05:32:29 -0000
@@ -269,6 +269,12 @@
     %
 :- pred status_is_imported(import_status::in, bool::out) is det.
 
+    % Returns yes if the item is user visible in the current module,
+    % i.e. that the item is defined locally or is imported, but not
+    % opt-imported.
+    %
+:- pred status_is_user_visible(import_status::in, bool::out) is det.
+
     % Returns yes if the status indicates that the item was
     % defined in this module.  This is the opposite of
     % status_is_imported.
@@ -858,6 +864,18 @@
 status_defined_in_this_module(exported_to_submodules,   yes).
 status_defined_in_this_module(local,                    yes).
 
+status_is_user_visible(imported(_),                     yes).
+status_is_user_visible(external(_),                     yes).
+status_is_user_visible(abstract_imported,               yes).
+status_is_user_visible(pseudo_imported,                 yes).
+status_is_user_visible(opt_imported,                    no).
+status_is_user_visible(exported,                        yes).
+status_is_user_visible(opt_exported,                    yes).
+status_is_user_visible(abstract_exported,               yes).
+status_is_user_visible(pseudo_exported,                 yes).
+status_is_user_visible(exported_to_submodules,          yes).
+status_is_user_visible(local,                           yes).
+
 calls_are_fully_qualified(Markers) =
     ( check_marker(Markers, calls_are_fully_qualified) ->
         is_fully_qualified
only in patch2:
unchanged:
--- compiler/notes/compiler_design.html	5 Jun 2006 02:26:12 -0000	1.119
+++ compiler/notes/compiler_design.html	14 Jul 2006 05:54:22 -0000
@@ -598,6 +598,19 @@
 	typeclass instance.
 	<p>
 
+<dt> check user defined insts for consistency with types
+	<dd>
+	inst_check.m checks that all user defined bound insts are consistent
+	with at least one type in scope
+	(i.e. that the set of function symbols
+	in the bound list for the inst are a subset of the allowed function
+	symbols for at least one type in scope).
+	
+	<p>
+	A warning is issued if it finds any user defined bound insts not
+	consistent with any types in scope.
+	<p>
+
 <dt> type checking
 
 	<dd>
only in patch2:
unchanged:
--- doc/user_guide.texi	13 Jun 2006 09:48:59 -0000	1.481
+++ doc/user_guide.texi	14 Jul 2006 05:32:29 -0000
@@ -5261,6 +5261,13 @@
 but whose determinism declarations are laxer.
 
 @sp 1
+ at item --no-warn-insts-without-matching-type
+ at findex --no-warn-insts-without-matching-type
+ at findex --warn-insts-without-matching-type
+Don't warn about insts that are not consistent with any
+types in scope.
+
+ at sp 1
 @item --no-warn-nothing-exported
 @findex --no-warn-nothing-exported
 @findex --warn-nothing-exported
only in patch2:
unchanged:
--- /dev/null	1 Jan 1970 00:00:00 -0000
+++ tests/warnings/inst_with_no_type_2.m	14 Jul 2006 05:33:32 -0000
@@ -0,0 +1,15 @@
+:- module inst_with_no_type_2.
+
+:- interface.
+
+:- import_module io.
+
+:- type t.
+
+:- pred p(t::in, io::di, io::uo) is det.
+
+:- implementation.
+
+:- type t ---> t.
+
+p(T, !IO) :- write(T, !IO).
--------------------------------------------------------------------------
mercury-reviews mailing list
post:  mercury-reviews at csse.unimelb.edu.au
administrative address: owner-mercury-reviews at csse.unimelb.edu.au
unsubscribe: Address: mercury-reviews-request at csse.unimelb.edu.au Message: unsubscribe
subscribe:   Address: mercury-reviews-request at csse.unimelb.edu.au Message: subscribe
--------------------------------------------------------------------------



More information about the reviews mailing list