[m-dev.] for review: allow multiple clauses in instance decls

Fergus Henderson fjh at cs.mu.OZ.AU
Wed Sep 20 01:28:40 AEDT 2000


For review by anyone who cares to do so.
I'll commit this one within the next couple of days
if I don't get any review comments.

Estimated hours taken: 5

Allow typeclass instance declarations to contain more than one clause
for each method.

Also improve some error messages.

compiler/check_typeclass.m:
	Allow typeclass instance declarations to contain more than one
	clause for each method, by combining the different clauses
	for each method into a single definition.

	Rewrite the code to check for bogus method names in instance
	declarations.  This rewrite was necessitated by the change
	mentioned above, but also improved the quality of the error
	message (it now prints the name of the bogus method)
	and fixed some bugs that sometimes resulted in spurious
	flow-on error messages.

	Fix some problems where we were not passing the correct arity
	for functions (e.g. to make_introduced_pred_name).

tests/invalid/Mmakefile:
tests/invalid/typeclass_bogus_method.m:
tests/invalid/typeclass_bogus_method.err_exp:
	Add a new regression test.

tests/invalid/tc_err*.err_exp:
tests/invalid/typeclass_test_*.err_exp:
	Update the expected output for these test cases,
	to reflect the improved error messages.

doc/reference_manual.texi:
	Update the documentation to reflect this change.

NEWS:
	Mention that we now allow clauses in instance declarations.

Workspace: /home/pgrad/fjh/ws/hg
Index: compiler/check_typeclass.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/check_typeclass.m,v
retrieving revision 1.32
diff -u -d -r1.32 check_typeclass.m
--- compiler/check_typeclass.m	2000/09/08 06:01:53	1.32
+++ compiler/check_typeclass.m	2000/09/19 13:41:29
@@ -49,7 +49,8 @@
 
 :- interface.
 
-:- import_module hlds_module, make_hlds, bool, io.
+:- import_module hlds_module, make_hlds.
+:- import_module bool, io.
 
 :- pred check_typeclass__check_instance_decls(module_info, qual_info,
 	module_info, bool, io__state, io__state).
@@ -57,11 +58,16 @@
 
 :- implementation.
 
-:- import_module map, list, std_util, hlds_pred, hlds_data, prog_data, require.
-:- import_module type_util, assoc_list, mode_util, inst_match, hlds_module.
-:- import_module typecheck, int, globals, options, make_hlds, error_util. 
-:- import_module base_typeclass_info, string, hlds_goal, set, prog_out.
-:- import_module mercury_to_mercury, varset, term.
+:- import_module prog_data, prog_out.
+:- import_module hlds_pred, hlds_data, hlds_goal, hlds_out.
+:- import_module type_util, typecheck, mode_util, inst_match.
+:- import_module base_typeclass_info.
+:- import_module mercury_to_mercury, error_util.
+:- import_module globals, options. 
+
+:- import_module int, string.
+:- import_module list, assoc_list, map, set, term, varset.
+:- import_module std_util, require. 
 
 :- type error_message == pair(prog_context, list(format_component)).
 :- type error_messages == list(error_message).
@@ -190,66 +196,31 @@
 				MaybePredProcs1, G, H),
 		(
 			MaybePredProcs1 = yes(_),
-			MaybePredProcs2 = MaybePredProcs1
+			MaybePredProcs = MaybePredProcs1
 		;
 			MaybePredProcs1 = no,
-			MaybePredProcs2 = yes([])
+			MaybePredProcs = yes([])
 		),
 
 		%
 		% Make sure the list of instance methods is in the same
 		% order as the methods in the class definition. intermod.m
-		% relies on this. If there were errors, don't change the
-		% list of methods.
-		%
-		(
-			list__length(RevInstanceMethods,
-				list__length(InstanceMethods))
-		->	
-			OrderedInstanceMethods =
-				list__reverse(RevInstanceMethods)
-		;
-			OrderedInstanceMethods = InstanceMethods
-		),
-			
+		% relies on this
+		OrderedInstanceMethods = list__reverse(RevInstanceMethods),
+
 		InstanceDefn2 = hlds_instance_defn(A, B, C, D,
 				concrete(OrderedInstanceMethods),
-				MaybePredProcs2, G, H),
+				MaybePredProcs, G, H),
+
 		%
 		% Check if there are any instance methods left over,
-		% for which we did not produce a pred_id/proc_id;
-		% if there are any, the instance declaration must have
-		% specified some methods that don't occur in the class.
+		% which did not match any of the methods from the
+		% class interface.
 		%
-		InstanceDefn2 = hlds_instance_defn(_, Context, _, _,
-				_, MaybePredProcs, _, _),
-		(
-			MaybePredProcs = yes(PredProcs),
-
-				% Check that we wind with a procedure for each
-				% proc in the type class interface.
-			list__same_length(PredProcs, ClassInterface),
-
-				% Check that we wind with a pred for each
-				% pred in the instance class interface.
-			list__map((pred(PP::in, P::out) is det :-
-				PP = hlds_class_proc(P, _)), PredProcs, Preds0),
-			list__remove_dups(Preds0, Preds),
-			list__same_length(Preds, InstanceMethods)
-		->
-			Errors2 = Errors1
-		;
-			ClassId = class_id(ClassName, ClassArity),
-			prog_out__sym_name_to_string(ClassName,
-				ClassNameString),
-			string__int_to_string(ClassArity, ClassArityString),
-			string__append_list([
-				"In instance declaration for `",
-				ClassNameString, "/", ClassArityString, "': ",
-				"incorrect method name(s)."],
-				NewError),
-			Errors2 = [Context - [words(NewError)] | Errors1]
-		)
+		InstanceDefn2 = hlds_instance_defn(_, Context,
+			_, _, _, _, _, _),
+		check_for_bogus_methods(InstanceMethods, ClassId, PredIds,
+			Context, ModuleInfo1, Errors1, Errors2)
 	),
 
 		% check that the superclass constraints are satisfied for the
@@ -258,6 +229,74 @@
 		InstanceDefn2, InstanceDefn,
 		Errors2 - ModuleInfo1, Errors - ModuleInfo).
 
+		%
+		% Check if there are any instance methods left over,
+		% which did not match any of the methods from the
+		% class interface.  If so, add an appropriate error
+		% message to the list of error messages.
+		%
+:- pred check_for_bogus_methods(list(instance_method), class_id, list(pred_id),
+		prog_context, module_info, error_messages, error_messages).
+:- mode check_for_bogus_methods(in, in, in, in, in, in, out) is det.
+
+check_for_bogus_methods(InstanceMethods, ClassId, ClassPredIds, Context,
+		ModuleInfo1, Errors0, Errors) :-
+	module_info_get_predicate_table(ModuleInfo1, PredTable),
+	DefnIsOK = (pred(Method::in) is semidet :-
+		% Find this method definition's p/f, name, arity
+		Method = instance_method(MethodPredOrFunc,
+			MethodName, _MethodDefn,
+			MethodArity, _Context),
+		% Search for pred_ids matching that p/f, name, arity,
+		% and succeed if the method definition p/f, name, and
+		% arity matches at least one of the methods from the
+		% class interface
+		adjust_func_arity(MethodPredOrFunc, MethodArity,
+			MethodPredArity),
+		predicate_table_search_pf_sym_arity(PredTable,
+			MethodPredOrFunc, MethodName, MethodPredArity,
+			MatchingPredIds),
+		some [PredId] (
+			list__member(PredId, MatchingPredIds),
+			list__member(PredId, ClassPredIds)
+		)
+	),
+	list__filter(DefnIsOK, InstanceMethods, _OKInstanceMethods,
+		BogusInstanceMethods),
+	(
+		BogusInstanceMethods = []
+	->
+		Errors = Errors0
+	;
+		%
+		% There were one or more bogus methods.
+		% Construct an appropriate error message.
+		%
+		ClassId = class_id(ClassName, ClassArity),
+		prog_out__sym_name_to_string(ClassName,
+			ClassNameString),
+		string__int_to_string(ClassArity, ClassArityString),
+		string__append_list([
+			"In instance declaration for `",
+			ClassNameString, "/", ClassArityString, "': ",
+			"incorrect method name(s): "],
+			ErrorMsgStart),
+		BogusInstanceMethodNames = list__map(format_method_name,
+			BogusInstanceMethods),
+		error_util__list_to_pieces(BogusInstanceMethodNames,
+			ErrorMsgBody0),
+		ErrorMsgBody = list__append(ErrorMsgBody0, [words(".")]),
+		NewError = Context - [words(ErrorMsgStart) | ErrorMsgBody],
+		Errors = [NewError | Errors0]
+	).
+
+:- func format_method_name(instance_method) = string.
+format_method_name(Method) = StringName :-
+	Method = instance_method(PredOrFunc, Name, _Defn, Arity, _Context),
+	adjust_func_arity(PredOrFunc, Arity, PredArity),
+	hlds_out__simple_call_id_to_string(
+		PredOrFunc - Name/PredArity, StringName).
+
 %----------------------------------------------------------------------------%
 
 :- type instance_check_info
@@ -280,6 +319,10 @@
 							% introduced pred
 							% should be given.
 		arity,					% Arity of the method.
+							% (For funcs, this is
+							% the original arity,
+							% not the arity as a
+							% predicate.)
 		existq_tvars,				% Existentially quant.
 							% type variables
 		list(type),				% Expected types of
@@ -344,6 +387,7 @@
 	MethodName = qualified(PredModule, MethodName0),
 	pred_info_arity(PredInfo, PredArity),
 	pred_info_get_is_pred_or_func(PredInfo, PredOrFunc),
+	adjust_func_arity(PredOrFunc, Arity, PredArity),
 	pred_info_procedures(PredInfo, ProcTable),
 	list__map(
 		lambda([TheProcId::in, ModesAndDetism::out] is det, 
@@ -362,11 +406,11 @@
 
 		% Work out the name of the predicate that we will generate
 		% to check this instance method.
-	make_introduced_pred_name(ClassId, MethodName, PredArity, 
+	make_introduced_pred_name(ClassId, MethodName, Arity, 
 		InstanceTypes, PredName),
 	
 	Info0 = instance_method_info(ModuleInfo0, QualInfo0, PredName,
-		PredArity, ExistQVars, ArgTypes, ClassContext, ArgModes,
+		Arity, ExistQVars, ArgTypes, ClassContext, ArgModes,
 		Errors0, ArgTypeVars, Status, PredOrFunc),
 
 	check_instance_pred_procs(ClassId, ClassVars, MethodName, Markers,
@@ -374,7 +418,7 @@
 		Info0, Info, IO0, IO),
 
 	Info = instance_method_info(ModuleInfo, QualInfo, _PredName,
-		_PredArity, _ExistQVars, _ArgTypes, _ClassContext, _ArgModes,
+		_Arity, _ExistQVars, _ArgTypes, _ClassContext, _ArgModes,
 		Errors, _ArgTypeVars, _Status, _PredOrFunc),
 
 	InstanceCheckInfo = instance_check_info(InstanceDefn,
@@ -395,11 +439,11 @@
 				InstanceConstraints, InstanceTypes,
 				InstanceBody, MaybeInstancePredProcs,
 				InstanceVarSet, H),
-	Info0 = instance_method_info(ModuleInfo, QualInfo, PredName, PredArity,
+	Info0 = instance_method_info(ModuleInfo, QualInfo, PredName, Arity,
 		ExistQVars, ArgTypes, ClassContext, ArgModes, Errors0,
 		ArgTypeVars, Status, PredOrFunc),
-	get_matching_instance_names(InstanceBody, PredOrFunc, MethodName,
-		PredArity, MatchingInstanceMethods),
+	get_matching_instance_defns(InstanceBody, PredOrFunc, MethodName,
+		Arity, MatchingInstanceMethods),
 	(
 		MatchingInstanceMethods = [InstanceMethod]
 	->
@@ -435,22 +479,16 @@
 	;
 		MatchingInstanceMethods = [I1, I2 | Is]
 	->
-			% one kind of error
+		%
+		% duplicate method definition error
+		%
 		OrderedInstanceMethods = OrderedInstanceMethods0,
 		InstanceDefn = InstanceDefn0,
 		ClassId = class_id(ClassName, _ClassArity),
 		prog_out__sym_name_to_string(MethodName, MethodNameString),
 		prog_out__sym_name_to_string(ClassName, ClassNameString),
-		(
-			PredOrFunc = predicate,
-			PredOrFuncString = "predicate",
-			RealPredArity = PredArity
-		;
-			PredOrFunc = function,
-			PredOrFuncString = "function",
-			RealPredArity = PredArity - 1
-		),
-		string__int_to_string(RealPredArity, PredArityString),
+		pred_or_func_to_string(PredOrFunc, PredOrFuncString),
+		string__int_to_string(Arity, ArityString),
 		mercury_type_list_to_string(InstanceVarSet, InstanceTypes,
 			InstanceTypesString),
 		string__append_list([
@@ -458,7 +496,7 @@
 			ClassNameString, "(", InstanceTypesString, ")': ",
 			"multiple implementations of type class ",
 			PredOrFuncString, " method `",
-			MethodNameString, "/", PredArityString, "'."],
+			MethodNameString, "/", ArityString, "'."],
 			ErrorHeader),
 		I1 = instance_method(_, _, _, _, I1Context), 
 		Heading = 
@@ -475,26 +513,20 @@
 		list__append(SubsequentErrors, Heading, NewErrors),
 		list__append(NewErrors, Errors0, Errors),
 		Info = instance_method_info(ModuleInfo, QualInfo, PredName,
-			PredArity, ExistQVars, ArgTypes, ClassContext,
+			Arity, ExistQVars, ArgTypes, ClassContext,
 			ArgModes, Errors, ArgTypeVars, Status, PredOrFunc),
 		IO = IO0
 	;
-			% another kind of error
+		%
+		% undefined method error
+		%
 		OrderedInstanceMethods = OrderedInstanceMethods0,
 		InstanceDefn = InstanceDefn0,
 		ClassId = class_id(ClassName, _ClassArity),
 		prog_out__sym_name_to_string(MethodName, MethodNameString),
 		prog_out__sym_name_to_string(ClassName, ClassNameString),
-		(
-			PredOrFunc = predicate,
-			PredOrFuncString = "predicate",
-			RealPredArity = PredArity
-		;
-			PredOrFunc = function,
-			PredOrFuncString = "function",
-			RealPredArity = PredArity - 1
-		),
-		string__int_to_string(RealPredArity, PredArityString),
+		pred_or_func_to_string(PredOrFunc, PredOrFuncString),
+		string__int_to_string(Arity, ArityString),
 		mercury_type_list_to_string(InstanceVarSet, InstanceTypes,
 			InstanceTypesString),
 		string__append_list([
@@ -502,35 +534,73 @@
 			ClassNameString, "(", InstanceTypesString, ")': ",
 			"no implementation for type class ",
 			PredOrFuncString, " method `",
-			MethodNameString, "/", PredArityString, "'."],
+			MethodNameString, "/", ArityString, "'."],
 			NewError),
 		Errors = [InstanceContext - [words(NewError)] | Errors0],
 		Info = instance_method_info(ModuleInfo, QualInfo, PredName,
-			PredArity, ExistQVars, ArgTypes, ClassContext,
+			Arity, ExistQVars, ArgTypes, ClassContext,
 			ArgModes, Errors,
 			ArgTypeVars, Status, PredOrFunc),
 		IO = IO0
 	).
 
-:- pred get_matching_instance_names(instance_body, pred_or_func,
+	%
+	% Get all the instance definitions which match the specified
+	% predicate/function name/arity, with multiple clause definitions
+	% being combined into a single definition.
+	%
+:- pred get_matching_instance_defns(instance_body, pred_or_func,
 	sym_name, arity, list(instance_method)).
-:- mode get_matching_instance_names(in, in, in, in, out) is det.
+:- mode get_matching_instance_defns(in, in, in, in, out) is det.
 
-get_matching_instance_names(InstanceBody, PredOrFunc, MethodName,
-		MethodArity0, MatchingInstanceMethods) :-
-	adjust_func_arity(PredOrFunc, MethodArity, MethodArity0),
-	solutions(
-		(pred(Method::out) is nondet :-
-			InstanceBody = concrete(InstanceMethods),
-			list__member(Method, InstanceMethods),
+get_matching_instance_defns(abstract, _, _, _, []).
+get_matching_instance_defns(concrete(InstanceMethods), PredOrFunc, MethodName,
+		MethodArity, ResultList) :-
+	%
+	% First find the instance method definitions that match this
+	% predicate/function's name and arity
+	%
+	list__filter(
+		(pred(Method::in) is semidet :-
 			Method = instance_method(PredOrFunc,
-				MethodName, _InstanceMethodDefn,
+				MethodName, _MethodDefn,
 				MethodArity, _Context)
-	    ),
-	    MatchingInstanceMethods).
+		),
+		InstanceMethods, MatchingMethods),
+	(
+		MatchingMethods = [First, _Second | _],
+		First = instance_method(_, _, _, _, FirstContext),
+		\+ (
+			list__member(DefnViaName, MatchingMethods),
+			DefnViaName = instance_method(_, _, name(_), _, _)
+		)
+	->
+		%
+		% If all of the instance method definitions for this
+		% pred/func are clauses, and there are more than one
+		% of them, then we must combine them all into a
+		% single definition.
+		%
+		MethodToClause = (pred(Method::in, Clause::out) is semidet :-
+			Method = instance_method(_, _, Defn, _, _),
+			Defn = clauses([Clause])),
+		list__filter_map(MethodToClause, MatchingMethods, Clauses),
+		CombinedMethod = instance_method(PredOrFunc,
+			MethodName, clauses(Clauses),
+			MethodArity, FirstContext),
+		ResultList = [CombinedMethod]
+	;
+		%
+		% If there are less than two matching method definitions,
+		% or if any of the instance method definitions is a method
+		% name, then we're done.
+		%
+		ResultList = MatchingMethods
+	).
 	
-	% Just a bit simpler than using a pair of pairs
-:- type triple(T1, T2, T3) ---> triple(T1, T2, T3).
+:- pred pred_or_func_to_string(pred_or_func::in, string::out) is det.
+pred_or_func_to_string(predicate, "predicate").
+pred_or_func_to_string(function, "function").
 
 :- pred produce_auxiliary_procs(list(tvar), pred_markers, list(type),
 	list(class_constraint), tvarset, instance_proc_def, prog_context,
@@ -545,7 +615,7 @@
 		InstanceProcIds, Info0, Info, IO0, IO) :-
 
 	Info0 = instance_method_info(ModuleInfo0, QualInfo0, PredName,
-		PredArity, ExistQVars0, ArgTypes0, ClassContext0, ArgModes,
+		Arity, ExistQVars0, ArgTypes0, ClassContext0, ArgModes,
 		Errors, ArgTypeVars0, Status0, PredOrFunc),
 
 		% Rename the instance variables apart from the class variables
@@ -590,6 +660,7 @@
 	module_info_globals(ModuleInfo0, Globals),
 	globals__lookup_string_option(Globals, aditi_user, User),
 
+	adjust_func_arity(PredOrFunc, Arity, PredArity),
 	produce_instance_method_clauses(InstancePredDefn, PredOrFunc,
 		PredArity, ArgTypes, Markers, Context, ClausesInfo,
 		ModuleInfo0, ModuleInfo1, QualInfo0, QualInfo, IO0, IO),
@@ -629,7 +700,7 @@
 	module_info_set_predicate_table(ModuleInfo1, PredicateTable,
 		ModuleInfo),
 
-	Info = instance_method_info(ModuleInfo, QualInfo, PredName, PredArity,
+	Info = instance_method_info(ModuleInfo, QualInfo, PredName, Arity,
 		ExistQVars, ArgTypes, ClassContext, ArgModes, Errors,
 		ArgTypeVars, Status, PredOrFunc).
 
@@ -651,14 +722,14 @@
 	sym_name).
 :- mode make_introduced_pred_name(in, in, in, in, out) is det.
 
-make_introduced_pred_name(ClassId, MethodName, PredArity, 
+make_introduced_pred_name(ClassId, MethodName, Arity, 
 		InstanceTypes, PredName) :-
 	ClassId = class_id(ClassName, _ClassArity),
 	prog_out__sym_name_to_string(ClassName, "__", ClassNameString),
 	prog_out__sym_name_to_string(MethodName, "__", MethodNameString),
-		% Perhaps we should include the pred arity in this mangled
+		% Perhaps we should include the arity in this mangled
 		% string?
-	string__int_to_string(PredArity, PredArityString),
+	string__int_to_string(Arity, ArityString),
 	base_typeclass_info__make_instance_string(InstanceTypes, 
 		InstanceString),
 	string__append_list(
@@ -666,7 +737,7 @@
 		ClassNameString, "__",
 		InstanceString, "____",
 		MethodNameString, "_",
-		PredArityString], 
+		ArityString], 
 		PredNameString),
 	PredName = unqualified(PredNameString).
 
Index: doc/reference_manual.texi
===================================================================
RCS file: /home/mercury1/repository/mercury/doc/reference_manual.texi,v
retrieving revision 1.187
diff -u -d -r1.187 reference_manual.texi
--- doc/reference_manual.texi	2000/09/18 11:52:09	1.187
+++ doc/reference_manual.texi	2000/09/19 14:15:52
@@ -3451,11 +3451,17 @@
 can be facts, rules, or DCG rules.  The only difference is that in instance
 declarations, clauses are separated by commas rather than being terminated
 by periods, and so rules and DCG rules in instance declarations must
-normally be enclosed in parentheses.
+normally be enclosed in parentheses.  As with ordinary predicates,
+you can have more than one clause for each method.  The clauses must
+satisfy the declared type, modes, determinism and purity for the
+method, after the types of the arguments in the instance declaration
+have been substituted in place of the parameters in the type class
+declaration.
 
-Currently, each method must be defined by a single clause;
-we do not permit using more than than one clause per method.
-(We hope to lift this restriction at some point in the future.)
+These two ways are mutually exclusive: each method must be defined
+either by a single naming definition (using the @samp{pred(@dots{}) is
+ at var{predname}} or @samp{func(@dots{}) is @var{funcname}} form),
+or by a set of one or more clauses, but not both.
 
 Here's an example of an instance declaration and the different kinds
 of method definitions that it can contain:
@@ -3466,6 +3472,7 @@
 	func method2(T) = int,
 	pred method3(T::in, int::out) is det
 	pred method4(T::in, io__state::di, io__state::uo) is det
+	func method5(bool, T) = T
 ].
 
 :- instance foo(int) where [
@@ -3479,7 +3486,11 @@
 	(method3(X, Y) :- Y = X + 2),
 
 	% method defined by a DCG rule
-	(method4(X) --> io__print(X), io__nl)
+	(method4(X) --> io__print(X), io__nl),
+
+	% method defined by multiple clauses
+	method5(no, _) = 0,
+	method5(yes, X) = Y :- X + Y = 0
 ].
 @end example
 	
Index: NEWS
===================================================================
RCS file: /home/mercury1/repository/mercury/NEWS,v
retrieving revision 1.172
diff -u -d -r1.172 NEWS
--- NEWS	2000/09/18 11:51:05	1.172
+++ NEWS	2000/09/19 14:22:29
@@ -48,7 +48,11 @@
 
   The old syntax is still accepted but is deprecated.  Support for it may
   eventually be dropped.
- 
+
+* Type class methods can now be defined by listing the clauses
+  directly in the instance declaration.  You no longer need to define a
+  separate predicate or function for each type class method definition.
+
 Changes to the standard library:
 
 * We've added a new function to the Mercury standard library:
Index: tests/invalid/Mmakefile
===================================================================
RCS file: /home/mercury1/repository/tests/invalid/Mmakefile,v
retrieving revision 1.73
diff -u -d -r1.73 Mmakefile
--- tests/invalid/Mmakefile	2000/09/18 16:38:27	1.73
+++ tests/invalid/Mmakefile	2000/09/19 13:46:23
@@ -79,6 +79,7 @@
 	type_loop.m \
 	type_mismatch.m \
 	type_vars.m \
+	typeclass_bogus_method.m \
 	typeclass_mode.m \
 	typeclass_test_1.m \
 	typeclass_test_2.m \
Index: tests/invalid/tc_err1.err_exp
===================================================================
RCS file: /home/mercury1/repository/tests/invalid/tc_err1.err_exp,v
retrieving revision 1.1
diff -u -d -r1.1 tc_err1.err_exp
--- tests/invalid/tc_err1.err_exp	2000/05/11 06:29:36	1.1
+++ tests/invalid/tc_err1.err_exp	2000/09/19 13:51:51
@@ -4,5 +4,5 @@
 tc_err1.m:028:   no implementation for type class predicate method
 tc_err1.m:028:   `tc_err1:handle_typedefs/3'.
 tc_err1.m:028: In instance declaration for `tc_err1:actions/1': incorrect
-tc_err1.m:028:   method name(s).
+tc_err1.m:028:   method name(s): predicate `tc_err1:handle_typedefs/2' .
 For more information, try recompiling with `-E'.
Index: tests/invalid/tc_err2.err_exp
===================================================================
RCS file: /home/mercury1/repository/tests/invalid/tc_err2.err_exp,v
retrieving revision 1.1
diff -u -d -r1.1 tc_err2.err_exp
--- tests/invalid/tc_err2.err_exp	2000/05/11 06:29:37	1.1
+++ tests/invalid/tc_err2.err_exp	2000/09/19 13:51:46
@@ -2,5 +2,5 @@
 tc_err2.m:034:   no implementation for type class predicate method
 tc_err2.m:034:   `tc_err2:handle_typedefs/3'.
 tc_err2.m:034: In instance declaration for `tc_err2:actions/1': incorrect
-tc_err2.m:034:   method name(s).
+tc_err2.m:034:   method name(s): predicate `tc_err2:handle_typedefs/2' .
 For more information, try recompiling with `-E'.
Index: tests/invalid/typeclass_bogus_method.err_exp
===================================================================
RCS file: typeclass_bogus_method.err_exp
diff -N typeclass_bogus_method.err_exp
--- /dev/null	Thu Mar 30 14:06:13 2000
+++ typeclass_bogus_method.err_exp	Wed Sep 20 01:25:14 2000
@@ -0,0 +1,21 @@
+typeclass_bogus_method.m:022: In instance declaration for
+typeclass_bogus_method.m:022:   `typeclass_bogus_method:tc1/1': incorrect
+typeclass_bogus_method.m:022:   method name(s): function
+typeclass_bogus_method.m:022:   `typeclass_bogus_method:bar/2' .
+typeclass_bogus_method.m:026: In instance declaration for
+typeclass_bogus_method.m:026:   `typeclass_bogus_method:tc2/1': incorrect
+typeclass_bogus_method.m:026:   method name(s): function
+typeclass_bogus_method.m:026:   `typeclass_bogus_method:baz/1' .
+typeclass_bogus_method.m:029: In instance declaration for
+typeclass_bogus_method.m:029:   `typeclass_bogus_method:tc3(int)': no
+typeclass_bogus_method.m:029:   implementation for type class function method
+typeclass_bogus_method.m:029:   `typeclass_bogus_method:foo3/1'.
+typeclass_bogus_method.m:029: In instance declaration for
+typeclass_bogus_method.m:029:   `typeclass_bogus_method:tc3/1': incorrect
+typeclass_bogus_method.m:029:   method name(s): function
+typeclass_bogus_method.m:029:   `typeclass_bogus_method:foo5/1' .
+typeclass_bogus_method.m:033: In instance declaration for
+typeclass_bogus_method.m:033:   `typeclass_bogus_method:tc4/1': incorrect
+typeclass_bogus_method.m:033:   method name(s): function
+typeclass_bogus_method.m:033:   `typeclass_bogus_method:foo5/1' .
+For more information, try recompiling with `-E'.
Index: tests/invalid/typeclass_bogus_method.m
===================================================================
RCS file: typeclass_bogus_method.m
diff -N typeclass_bogus_method.m
--- /dev/null	Thu Mar 30 14:06:13 2000
+++ typeclass_bogus_method.m	Wed Sep 20 00:18:50 2000
@@ -0,0 +1,35 @@
+:- module typeclass_bogus_method.
+:- interface.
+
+:- typeclass tc1(T) where [ func foo1(T) = int ].
+:- typeclass tc2(T) where [ func foo2(T) = int ].
+:- typeclass tc3(T) where [ func foo3(T) = int ].
+:- typeclass tc4(T) where [ func foo4(T) = int ].
+:- typeclass tc5(T) where [ func foo5(T) = int ].
+
+:- instance tc1(int).
+:- instance tc2(int).
+:- instance tc3(int).
+:- instance tc4(int).
+
+:- implementation.
+:- import_module int.
+
+:- func incr(int) = int.
+incr(X) = X + 1.
+
+:- instance tc1(int) where [
+	func(foo1/1) is incr,
+	func(bar/2) is incr
+].
+:- instance tc2(int) where [
+	func(foo2/1) is incr,
+	baz(X) = X + 1
+].
+:- instance tc3(int) where [
+	func(foo5/1) is incr
+].
+:- instance tc4(int) where [
+	func(foo4/1) is incr,
+	func(foo5/1) is incr
+].
Index: tests/invalid/typeclass_test_3.err_exp
===================================================================
RCS file: /home/mercury1/repository/tests/invalid/typeclass_test_3.err_exp,v
retrieving revision 1.9
diff -u -d -r1.9 typeclass_test_3.err_exp
--- tests/invalid/typeclass_test_3.err_exp	1999/02/12 04:19:32	1.9
+++ tests/invalid/typeclass_test_3.err_exp	2000/09/19 13:48:17
@@ -4,5 +4,5 @@
 typeclass_test_3.m:014:   `typeclass_test_3:type_num/1'.
 typeclass_test_3.m:014: In instance declaration for
 typeclass_test_3.m:014:   `typeclass_test_3:numbered_type/1': incorrect method
-typeclass_test_3.m:014:   name(s).
+typeclass_test_3.m:014:   name(s): function `typeclass_test_3:type_num/0' .
 For more information, try recompiling with `-E'.
Index: tests/invalid/typeclass_test_4.err_exp
===================================================================
RCS file: /home/mercury1/repository/tests/invalid/typeclass_test_4.err_exp,v
retrieving revision 1.7
diff -u -d -r1.7 typeclass_test_4.err_exp
--- tests/invalid/typeclass_test_4.err_exp	1999/02/12 04:19:33	1.7
+++ tests/invalid/typeclass_test_4.err_exp	2000/09/19 13:48:24
@@ -4,5 +4,5 @@
 typeclass_test_4.m:014:   `typeclass_test_4:type_num/1'.
 typeclass_test_4.m:014: In instance declaration for
 typeclass_test_4.m:014:   `typeclass_test_4:numbered_type/1': incorrect method
-typeclass_test_4.m:014:   name(s).
+typeclass_test_4.m:014:   name(s): function `typeclass_test_4:type_num/0' .
 For more information, try recompiling with `-E'.
Index: tests/invalid/typeclass_test_5.err_exp
===================================================================
RCS file: /home/mercury1/repository/tests/invalid/typeclass_test_5.err_exp,v
retrieving revision 1.5
diff -u -d -r1.5 typeclass_test_5.err_exp
--- tests/invalid/typeclass_test_5.err_exp	1999/02/12 04:19:33	1.5
+++ tests/invalid/typeclass_test_5.err_exp	2000/09/19 13:49:22
@@ -3,8 +3,6 @@
 typeclass_test_5.m:015:   method `typeclass_test_5:p/1'.
 typeclass_test_5.m:016: First definition appears here.
 typeclass_test_5.m:017: Subsequent definition appears here.
-typeclass_test_5.m:015: In instance declaration for `typeclass_test_5:c2/1':
-typeclass_test_5.m:015:   incorrect method name(s).
 typeclass_test_5.m:015: In instance declaration for `typeclass_test_5:c2(int)':
 typeclass_test_5.m:015:   superclass constraint(s) not satisfied:
 typeclass_test_5.m:015:   `typeclass_test_5:c1(int)'.
Index: tests/invalid/typeclass_test_9.err_exp
===================================================================
RCS file: /home/mercury1/repository/tests/invalid/typeclass_test_9.err_exp,v
retrieving revision 1.2
diff -u -d -r1.2 typeclass_test_9.err_exp
--- tests/invalid/typeclass_test_9.err_exp	2000/08/16 09:19:43	1.2
+++ tests/invalid/typeclass_test_9.err_exp	2000/09/19 13:49:39
@@ -14,7 +14,9 @@
 typeclass_test_9.m:010: declarations for class `typeclass_test_9:foo/1'.
 typeclass_test_9.m:007: Previous instance declaration was here.
 typeclass_test_9.m:013: In instance declaration for `typeclass_test_9:bar/1':
-typeclass_test_9.m:013:   incorrect method name(s).
+typeclass_test_9.m:013:   incorrect method name(s): predicate
+typeclass_test_9.m:013:   `typeclass_test_9:p/0' .
 typeclass_test_9.m:018: In instance declaration for `typeclass_test_9:baz/1':
-typeclass_test_9.m:018:   incorrect method name(s).
+typeclass_test_9.m:018:   incorrect method name(s): predicate
+typeclass_test_9.m:018:   `typeclass_test_9:r/0' .
 For more information, try recompiling with `-E'.

-- 
Fergus Henderson <fjh at cs.mu.oz.au>  |  "I have always known that the pursuit
WWW: <http://www.cs.mu.oz.au/~fjh>  |  of excellence is a lethal habit"
PGP: finger fjh at 128.250.37.3        |     -- the last words of T. S. Garp.
--------------------------------------------------------------------------
mercury-developers mailing list
Post messages to:       mercury-developers at cs.mu.oz.au
Administrative Queries: owner-mercury-developers at cs.mu.oz.au
Subscriptions:          mercury-developers-request at cs.mu.oz.au
--------------------------------------------------------------------------



More information about the developers mailing list