[m-rev.] for review; typeclass decl introduces namespace

Peter Ross peter.ross at miscrit.be
Wed Oct 31 02:19:02 AEDT 2001


Hi,


===================================================================


Estimated hours taken: 4
Branches: main

Typeclass declarations now introduce a new namespace.  For example the
method, f, in typeclass, tc, in module, mod, has the fully qualified
name mod__tc__f instead of mod__f.  This allows typeclasses defined
at the same scope to have methods with the same name.

compiler/module_qual.m:
    Qualify instance declarations with the instance name as well.

compiler/prog_io_typeclass.m:
    Change the qualifier on typeclass and instance declarations to
    include the typeclass name.

doc/reference_manual.texi:
    Document the change.

tests/hard_coded/typeclasses/Mmakefile:
tests/hard_coded/typeclasses/overloaded_methods.exp:
tests/hard_coded/typeclasses/overloaded_methods.m:
    Add a test case.

Index: compiler/module_qual.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/module_qual.m,v
retrieving revision 1.69
diff -u -r1.69 module_qual.m
--- compiler/module_qual.m	24 Oct 2001 13:34:32 -0000	1.69
+++ compiler/module_qual.m	30 Oct 2001 15:13:11 -0000
@@ -1071,10 +1071,9 @@
 	( ClassName = unqualified(_) ->
 		Ms = M0s
 	;
-		sym_name_get_module_name(ClassName, unqualified(""), Module),
 		Qualify = lambda([M0::in, M::out] is det, (
 			M0 = instance_method(A, Method0, C, D, E),
-			add_module_qualifier(Module, Method0, Method),
+			add_module_qualifier(ClassName, Method0, Method),
 			M = instance_method(A, Method, C, D, E)
 		)),
 		list__map(Qualify, M0s, Ms)
Index: compiler/prog_io_typeclass.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/prog_io_typeclass.m,v
retrieving revision 1.21
diff -u -r1.21 prog_io_typeclass.m
--- compiler/prog_io_typeclass.m	25 Sep 2001 09:36:54 -0000	1.21
+++ compiler/prog_io_typeclass.m	30 Oct 2001 15:13:12 -0000
@@ -54,28 +54,28 @@
 
 parse_non_empty_class(ModuleName, Name, Methods, VarSet, Result) :-
 	varset__coerce(VarSet, TVarSet),
-	parse_class_methods(ModuleName, Methods, VarSet, ParsedMethods),
+	parse_class_name(ModuleName, Name, VarSet, ParsedNameAndVars),
 	(
-		ParsedMethods = ok(MethodList),
-		parse_class_name(ModuleName, Name, VarSet, ParsedNameAndVars),
+		ParsedNameAndVars = error(String, Term)
+	->
+		Result = error(String, Term)
+	;
+		ParsedNameAndVars = ok(typeclass(Constraints,
+			NameString, Vars, _, _))
+	->
+		parse_class_methods(NameString, Methods, VarSet, ParsedMethods),
 		(
-			ParsedNameAndVars = error(String, Term)
-		->
-			Result = error(String, Term)
-		;
-			ParsedNameAndVars = ok(typeclass(Constraints,
-				NameString, Vars, _, _))
-		->
+			ParsedMethods = ok(MethodList),
 			Result = ok(typeclass(Constraints, NameString, Vars,
 				concrete(MethodList), TVarSet))
 		;
-				% if the item we get back isn't a typeclass,
-				% something has gone wrong...
-			error("prog_io_typeclass.m: item should be a typeclass")
+			ParsedMethods = error(String, Term),
+			Result = error(String, Term)
 		)
 	;
-		ParsedMethods = error(String, Term),
-		Result = error(String, Term)
+			% if the item we get back isn't a typeclass,
+			% something has gone wrong...
+		error("prog_io_typeclass.m: item should be a typeclass")
 	).
 
 :- pred parse_class_name(module_name, term, varset, maybe1(item)).
@@ -179,7 +179,7 @@
 		maybe1(list(class_method))).
 :- mode parse_class_methods(in, in, in, out) is det.
 
-parse_class_methods(ModuleName, Methods, VarSet, Result) :-
+parse_class_methods(TypeClassName, Methods, VarSet, Result) :-
 	(
 		list_term_to_term_list(Methods, MethodList)
 			% Convert the list of terms into a list of 
@@ -188,7 +188,7 @@
 		list__map(lambda([MethodTerm::in, Method::out] is det, 
 			(
 				% Turn the term into an item
-			parse_decl(ModuleName, VarSet, MethodTerm, Item),
+			parse_decl(TypeClassName, VarSet, MethodTerm, Item),
 				% Turn the item into a class_method
 			item_to_class_method(Item, MethodTerm, Method)
 			)),
@@ -475,31 +475,31 @@
 :- mode parse_non_empty_instance(in, in, in, in, in, out) is det.
 
 parse_non_empty_instance(ModuleName, Name, Methods, VarSet, TVarSet, Result) :-
-	parse_instance_methods(ModuleName, Methods, VarSet, ParsedMethods),
+	parse_instance_name(ModuleName, Name, TVarSet, ParsedNameAndTypes),
 	(
-		ParsedMethods = ok(MethodList),
-		parse_instance_name(ModuleName, Name, TVarSet,
-			ParsedNameAndTypes),
+		ParsedNameAndTypes = error(String, Term)
+	->
+		Result = error(String, Term)
+	;
+		ParsedNameAndTypes = ok(instance(Constraints,
+			NameString, Types, _, _, ModName))
+	->
+		parse_instance_methods(NameString, Methods,
+			VarSet, ParsedMethods),
 		(
-			ParsedNameAndTypes = error(String, Term)
-		->
-			Result = error(String, Term)
-		;
-			ParsedNameAndTypes = ok(instance(Constraints,
-				NameString, Types, _, _, ModName))
-		->
+			ParsedMethods = ok(MethodList),
 			Result0 = ok(instance(Constraints, NameString, Types,
 				concrete(MethodList), TVarSet, ModName)),
 			check_tvars_in_instance_constraint(Result0, Name,
 				Result)
 		;
-				% if the item we get back isn't a typeclass,
-				% something has gone wrong...
-			error("prog_io_typeclass.m: item should be an instance")
+			ParsedMethods = error(String, Term),
+			Result = error(String, Term)
 		)
 	;
-		ParsedMethods = error(String, Term),
-		Result = error(String, Term)
+			% if the item we get back isn't a typeclass,
+			% something has gone wrong...
+		error("prog_io_typeclass.m: item should be an instance")
 	).
 
 :- pred check_tvars_in_instance_constraint(maybe1(item), term, maybe1(item)).
@@ -536,13 +536,13 @@
 		maybe1(list(instance_method))).
 :- mode parse_instance_methods(in, in, in, out) is det.
 
-parse_instance_methods(ModuleName, Methods, VarSet, Result) :-
+parse_instance_methods(InstanceName, Methods, VarSet, Result) :-
 	(
 		list_term_to_term_list(Methods, MethodList)
 	->
 			% Convert the list of terms into a list of 
 			% maybe1(class_method)s.
-		list__map(term_to_instance_method(ModuleName, VarSet),
+		list__map(term_to_instance_method(InstanceName, VarSet),
 			MethodList, Interface),
 		find_errors(Interface, Result)
 	;
@@ -554,7 +554,7 @@
 		maybe1(instance_method)).
 :- mode term_to_instance_method(in, in, in, out) is det.
 
-term_to_instance_method(_ModuleName, VarSet, MethodTerm, Result) :-
+term_to_instance_method(InstanceName, VarSet, MethodTerm, Result) :-
 	(
 		MethodTerm = term__functor(term__atom("is"), [ClassMethodTerm,
 						InstanceMethod], TermContext)
@@ -625,12 +625,13 @@
 		% instance declaration for, but we don't necessarily
 		% know what module that is at this point, since the
 		% class name hasn't been fully qualified yet.
-		% So here we give the special module name ""
-		% as the default, which means that there is no default.
+		% So here we give the only part of the module name that
+		% we do know which is the unqualified instance name.
 		% (If the module qualifiers in the clauses don't match
 		% the module name of the class, we will pick that up later,
 		% in check_typeclass.m.)
-		DefaultModuleName = unqualified(""),
+		unqualify_name(InstanceName, UnqualifiedInstanceName),
+		DefaultModuleName = unqualified(UnqualifiedInstanceName),
 		parse_item(DefaultModuleName, VarSet, MethodTerm, Result0),
 		(
 			Result0 = ok(Item, Context),
@@ -655,4 +656,3 @@
 				MethodTerm)
 		)
 	).
-
Index: doc/reference_manual.texi
===================================================================
RCS file: /home/mercury1/repository/mercury/doc/reference_manual.texi,v
retrieving revision 1.220
diff -u -r1.220 reference_manual.texi
--- doc/reference_manual.texi	24 Oct 2001 13:34:41 -0000	1.220
+++ doc/reference_manual.texi	30 Oct 2001 15:13:25 -0000
@@ -3825,6 +3825,12 @@
 There must not be more than one type class declaration with the
 same name and arity in the same module.
 
+The @code{typeclass} declaration introduces a new namespace.
+The new namespace is the typeclass name.
+This allows distinct typeclasses to use methods with the same names.
+For example the fully qualified name for the method @code{f/1} defined
+in typeclass @code{tc} in the module @code{mod} is @code{mod__tc__f/1}.
+
 @node Instance declarations
 @section Instance declarations
 
Index: tests/hard_coded/typeclasses/Mmakefile
===================================================================
RCS file: /home/mercury1/repository/tests/hard_coded/typeclasses/Mmakefile,v
retrieving revision 1.44
diff -u -r1.44 Mmakefile
--- tests/hard_coded/typeclasses/Mmakefile	12 Feb 2001 05:14:57 -0000	1.44
+++ tests/hard_coded/typeclasses/Mmakefile	30 Oct 2001 15:13:25 -0000
@@ -41,6 +41,7 @@
 	multi_parameter_bug \
 	nondet_class_method \
 	operator_classname \
+	overloaded_methods \
 	record_syntax \
 	reordered_existential_constraint \
 	superclass_bug \
Index: tests/hard_coded/typeclasses/overloaded_methods.exp
===================================================================
RCS file: tests/hard_coded/typeclasses/overloaded_methods.exp
diff -N tests/hard_coded/typeclasses/overloaded_methods.exp
--- /dev/null	1 Jan 1970 00:00:00 -0000
+++ tests/hard_coded/typeclasses/overloaded_methods.exp	30 Oct 2001 15:13:25 -0000
@@ -0,0 +1,2 @@
+1
+2
Index: tests/hard_coded/typeclasses/overloaded_methods.m
===================================================================
RCS file: tests/hard_coded/typeclasses/overloaded_methods.m
diff -N tests/hard_coded/typeclasses/overloaded_methods.m
--- /dev/null	1 Jan 1970 00:00:00 -0000
+++ tests/hard_coded/typeclasses/overloaded_methods.m	30 Oct 2001 15:13:25 -0000
@@ -0,0 +1,36 @@
+:- module overloaded_methods.
+
+:- interface.
+
+:- import_module io.
+
+:- pred main(io__state::di, io__state::uo) is det.
+
+:- implementation.
+
+main -->
+	{ overloaded_methods__tc1__p("string", X) },
+	io__write_int(X),
+	io__nl,
+	{ overloaded_methods__tc2__p("string", Y) },
+	io__write_int(Y),
+	io__nl.
+
+:- typeclass tc1(T) where [
+	pred p(string::in, T::out) is det
+].
+
+:- typeclass tc2(T) where [
+	pred p(string::in, T::out) is det
+].
+
+:- instance tc1(int) where [
+	(p(_, 1))
+].
+:- instance tc2(int) where [
+	pred(p/2) is i2
+].
+
+:- pred i2(string::in, int::out) is det.
+
+i2(_, 2).

--------------------------------------------------------------------------
mercury-reviews mailing list
post:  mercury-reviews at cs.mu.oz.au
administrative address: owner-mercury-reviews at cs.mu.oz.au
unsubscribe: Address: mercury-reviews-request at cs.mu.oz.au Message: unsubscribe
subscribe:   Address: mercury-reviews-request at cs.mu.oz.au Message: subscribe
--------------------------------------------------------------------------



More information about the reviews mailing list