[m-rev.] for review: fix some problems with module qualification

David Overton dmo at cs.mu.OZ.AU
Fri Feb 21 14:32:29 AEDT 2003


On Thu, Feb 20, 2003 at 06:19:36PM +1100, Fergus Henderson wrote:
> On 20-Feb-2003, David Overton <dmo at cs.mu.OZ.AU> wrote:
> > 
> > Some changes related to module qualification.
> > 
> > These changes fix problems for the HAL library that were introduced by
> > the change to not module-qualify symbols when writing out interface
> > files.
> 
> Which change are you talking about?
> Could you point me to the log message?

See the log message for version 1.202 of mercury_to_mercury.m.  I made
these changes to our local copy of the Mercury compiler soon after Simon
committed this change because it broke several assumptions that HAL made
about the Mercury language.  It was really only intended to be a quick
fix and most of the problems can probably be fixed in the HAL compiler.
I just wanted to see how much of this would be acceptable before I
make the changes in HAL.

> 
> It would be helpful if for each of these changes you could explain
> why the right place to fix the problem is in the Mercury compiler
> rather than in the HAL implementation.
> 
> > compiler/prog_io_util.m:
> > 	When parsing an inst, if it has the module-qualifier `builtin'
> > 	try to parse it as a builtin inst.
> 
> Hmm.  In other words, allow things like "func(in, out) `builtin.is` det"?
> 
> The builtin insts such as the higher-order inst "func(in, out) is det"
> use special syntax.  They are not defined in the builtin module, they
> are defined by the language.  So I'm not really convinced that it makes
> sense to allow the use of module-qualifiers on those.
> 
> I wouldn't mind doing this for the insts that don't have special syntax,
> such as "free" and "ground", but for those which do, such as
> "bound(...)" and higher-order insts, I think allowing module qualifiers
> would just complicate Mercury's syntax.  Furthermore, it opens a can of
> worms -- if you allow "func(in, out) `builtin.is` det",
> shouldn't you also allow "builtin.func(in, out) is builtin.det"?
> What about clauses for foo/1 defined as "builtin.':-'(foo(X), ...)."?

It was insts such as `free' and `ground' that I was thinking of with
this change.  I will disallow it for insts with special syntax if you
like -- we don't need to allow these to be module-qualified.

> 
> > compiler/mercury_to_mercury.m:
> > 	When writing out inst declarations, if the inst on the
> > 	left-hand-side of the declaration could be interpreted as a
> > 	builtin inst when unqualified, then make sure it is output
> > 	module-qualified so that it can be read back in correctly
> > 	without generating an "attempt to redefine builtin inst" error.
> 
> Is that an error or a warning?
> The comment in the code below says it is a warning.

It's an error.  The comment is incorrect.  I'll fix it.

> 
> > 	In `maybe_unqualify_sym_name', do not unqualify names containing
> > 	`__'.  This ensures that such names are output to the interface
> > 	files module-qualified and can then be read back in correctly
> > 	without interpreting the `__' as a module qualifier.
> 
> I think a better approach would be to change the Mercury compiler to
> report an error "mixing different module qualifiers" if any symbol
> contains "__", and to change the HAL implementation to avoid generating
> such symbols.
> 
> The compiler's name mangling algorithms assume that no symbol contains "__".
> With your proposed change, it may *appear* to work, but I'm pretty sure the
> compiler will do the wrong thing if you define two functions (or types,
> typeclasses, etc.) named "foo.bar__baz" and "foo.bar.baz".
> Also I think the demangler will not demangle such symbols correctly.

Okay, that's fine.  I'll change the HAL compiler to not produce symbols
containing "__".

The change to disallow mixed module qualifiers should be a separate
change IMHO.

> 
> > Index: compiler/mercury_to_mercury.m
> > @@ -435,7 +436,15 @@
> >  mercury_output_item(UnqualifiedItemNames,
> >  		inst_defn(VarSet, Name0, Args, InstDefn, _Cond),
> >  		Context) -->
> > -	{ maybe_unqualify_sym_name(UnqualifiedItemNames, Name0, Name) },
> > +	{ maybe_unqualify_sym_name(UnqualifiedItemNames, Name0, Name1) },
> > +	% If the unqualified name is a builtin inst, then output the qualified
> > +	% name.  This prevents the compiler giving a warning about redefining
> > +	% builtin insts when an interface file is read back in.
> > +	{ builtin_inst_name(Name1, Args) ->
> > +		Name = Name0
> > +	;
> > +		Name = Name1
> > +	},
> 
> The call to maybe_unqualify_sym_name/3 should be in the body of the
> if-then-else.

But we need to unqualify the name before checking whether it is builtin
inst name.


Relative diff:

--- /u/poole/dmo/ws/bug/mercury/compiler/prog_io_util.m	Wed Jul 10 16:13:47 2002
+++ ./prog_io_util.m	Fri Feb 21 12:25:38 2003
@@ -359,34 +359,11 @@
 convert_inst(_, term__variable(V0), inst_var(V)) :-
 	term__coerce_var(V0, V).
 convert_inst(AllowConstrainedInstVar, Term, Result) :-
-	Term = term__functor(Name, Args0, Context),
-	% `free' insts
-	( Name = term__atom("free"), Args0 = [] ->
-		Result = free
-
-	% `any' insts
-	; Name = term__atom("any"), Args0 = [] ->
-		Result = any(shared)
-	; Name = term__atom("unique_any"), Args0 = [] ->
-		Result = any(unique)
-	; Name = term__atom("mostly_unique_any"), Args0 = [] ->
-		Result = any(mostly_unique)
-	; Name = term__atom("clobbered_any"), Args0 = [] ->
-		Result = any(clobbered)
-	; Name = term__atom("mostly_clobbered_any"), Args0 = [] ->
-		Result = any(mostly_clobbered)
-
-	% `ground' insts
-	; Name = term__atom("ground"), Args0 = [] ->
-		Result = ground(shared, none)
-	; Name = term__atom("unique"), Args0 = [] ->
-		Result = ground(unique, none)
-	; Name = term__atom("mostly_unique"), Args0 = [] ->
-		Result = ground(mostly_unique, none)
-	; Name = term__atom("clobbered"), Args0 = [] ->
-		Result = ground(clobbered, none)
-	; Name = term__atom("mostly_clobbered"), Args0 = [] ->
-		Result = ground(mostly_clobbered, none)
+	Term = term__functor(term__atom(Name), Args0, _Context),
+	(
+		convert_simple_builtin_inst(Name, Args0, Result0)
+	->
+		Result = Result0
 	;
 		% The syntax for a higher-order pred inst is
 		%
@@ -395,7 +372,7 @@
 		% where <Mode1>, <Mode2>, ... are a list of modes,
 		% and <Detism> is a determinism.
 
-		Name = term__atom("is"), Args0 = [PredTerm, DetTerm],
+		Name = "is", Args0 = [PredTerm, DetTerm],
 		PredTerm = term__functor(term__atom("pred"), ArgModesTerm, _)
 	->
 		DetTerm = term__functor(term__atom(DetString), [], _),
@@ -413,7 +390,7 @@
 		% where <Mode1>, <Mode2>, ... are a list of modes,
 		% <RetMode> is a mode, and <Detism> is a determinism.
 
-		Name = term__atom("is"), Args0 = [EqTerm, DetTerm],
+		Name = "is", Args0 = [EqTerm, DetTerm],
 		EqTerm = term__functor(term__atom("="),
 					[FuncTerm, RetModeTerm], _),
 		FuncTerm = term__functor(term__atom("func"), ArgModesTerm, _)
@@ -427,25 +404,21 @@
 		FuncInst = pred_inst_info(function, ArgModes, Detism),
 		Result = ground(shared, higher_order(FuncInst))
 
-	% `not_reached' inst
-	; Name = term__atom("not_reached"), Args0 = [] ->
-		Result = not_reached
-
 	% `bound' insts
-	; Name = term__atom("bound"), Args0 = [Disj] ->
+	; Name = "bound", Args0 = [Disj] ->
 		parse_bound_inst_list(AllowConstrainedInstVar, Disj, shared,
 			Result)
 /* `bound_unique' is for backwards compatibility - use `unique' instead */
-	; Name = term__atom("bound_unique"), Args0 = [Disj] ->
+	; Name = "bound_unique", Args0 = [Disj] ->
 		parse_bound_inst_list(AllowConstrainedInstVar, Disj, unique,
 			Result)
-	; Name = term__atom("unique"), Args0 = [Disj] ->
+	; Name = "unique", Args0 = [Disj] ->
 		parse_bound_inst_list(AllowConstrainedInstVar, Disj, unique,
 			Result)
-	; Name = term__atom("mostly_unique"), Args0 = [Disj] ->
+	; Name = "mostly_unique", Args0 = [Disj] ->
 		parse_bound_inst_list(AllowConstrainedInstVar, Disj,
 			mostly_unique, Result)
-	; Name = term__atom("=<"), Args0 = [VarTerm, InstTerm] ->
+	; Name = "=<", Args0 = [VarTerm, InstTerm] ->
 		AllowConstrainedInstVar = allow_constrained_inst_var,
 		VarTerm = term__variable(Var),
 		% Do not allow nested constrained_inst_vars.
@@ -461,13 +434,10 @@
 			sym_name_get_module_name(QualifiedName, unqualified(""),
 				BuiltinModule),
 			% If the term is qualified with the `builtin' module
-			% then it may be one of the builtin insts.
+			% then it may be one of the simple builtin insts.
 			% We call convert_inst recursively to check for this.
 			unqualify_name(QualifiedName, UnqualifiedName),
-			UnqualifiedTerm =
-				term__functor(term__atom(UnqualifiedName),
-					Args1, Context),
-			convert_inst(AllowConstrainedInstVar, UnqualifiedTerm,
+			convert_simple_builtin_inst(UnqualifiedName, Args1,
 				Result0),
 
 			% However, if the inst is a user_inst defined inside
@@ -481,6 +451,38 @@
 			Result = defined_inst(user_inst(QualifiedName, Args))
 		)
 	).
+
+	% A "simple" builtin inst is one that has no arguments and no special
+	% syntax.
+:- pred convert_simple_builtin_inst(string, list(term), inst).
+:- mode convert_simple_builtin_inst(in, in, out) is semidet.
+
+convert_simple_builtin_inst(Name, [], Inst) :-
+	convert_simple_builtin_inst_2(Name, Inst).
+
+:- pred convert_simple_builtin_inst_2(string, inst).
+:- mode convert_simple_builtin_inst_2(in, out) is semidet.
+
+	% `free' insts
+convert_simple_builtin_inst_2("free", free).
+
+	% `any' insts
+convert_simple_builtin_inst_2("any",			any(shared)).
+convert_simple_builtin_inst_2("unique_any",		any(unique)).
+convert_simple_builtin_inst_2("mostly_unique_any",	any(mostly_unique)).
+convert_simple_builtin_inst_2("clobbered_any",		any(clobbered)).
+convert_simple_builtin_inst_2("mostly_clobbered_any",	any(mostly_clobbered)).
+
+	% `ground' insts
+convert_simple_builtin_inst_2("ground",		ground(shared, none)).
+convert_simple_builtin_inst_2("unique",		ground(unique, none)).
+convert_simple_builtin_inst_2("mostly_unique",	ground(mostly_unique, none)).
+convert_simple_builtin_inst_2("clobbered",	ground(clobbered, none)).
+convert_simple_builtin_inst_2("mostly_clobbered",
+						ground(mostly_clobbered, none)).
+
+	% `not_reached' inst
+convert_simple_builtin_inst_2("not_reached", not_reached).
 
 standard_det("det", det).
 standard_det("cc_nondet", cc_nondet).
--- /u/poole/dmo/ws/bug/mercury/compiler/mercury_to_mercury.m	Thu Feb 20 09:22:08 2003
+++ ./mercury_to_mercury.m	Fri Feb 21 14:29:12 2003
@@ -438,7 +438,7 @@
 		Context) -->
 	{ maybe_unqualify_sym_name(UnqualifiedItemNames, Name0, Name1) },
 	% If the unqualified name is a builtin inst, then output the qualified
-	% name.  This prevents the compiler giving a warning about redefining
+	% name.  This prevents the compiler giving an error about redefining
 	% builtin insts when an interface file is read back in.
 	{ builtin_inst_name(Name1, Args) ->
 		Name = Name0
@@ -3793,18 +3793,8 @@
 :- mode maybe_unqualify_sym_name(in, in, out) is det.
 
 maybe_unqualify_sym_name(no, Name, Name).
-maybe_unqualify_sym_name(yes, Name0, Name) :-
-	unqualify_name(Name0, Name1),
-	( string__sub_string_search(Name1, "__", _) ->
-		% Do not unqualify a name that contains "__".  This prevents the
-		% "__" being treated a module qualifier when the name is read
-		% back in.
-		% XXX this whole `__' module qualifier thing is a bit of a hack
-		% isn't it.
-		Name = Name0
-	;
-		Name = unqualified(Name1)
-	).
+maybe_unqualify_sym_name(yes, Name0, unqualified(Name)) :-
+	unqualify_name(Name0, Name).
 
 %-----------------------------------------------------------------------------%
 

-- 
David Overton                  Uni of Melbourne     +61 3 8344 1354
dmo at cs.mu.oz.au                Monash Uni (Clayton) +61 3 9905 5779
http://www.cs.mu.oz.au/~dmo    Mobile Phone         +61 4 0337 4393
--------------------------------------------------------------------------
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