[m-rev.] for review: fix some problems with module qualification
David Overton
dmo at cs.mu.OZ.AU
Mon Mar 3 13:14:25 AEDT 2003
On Fri, Feb 21, 2003 at 03:32:48PM +1100, Fergus Henderson wrote:
> On 21-Feb-2003, David Overton <dmo at cs.mu.OZ.AU> wrote:
> > On Thu, Feb 20, 2003 at 06:19:36PM +1100, Fergus Henderson wrote:
> > > 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.
>
> I'm still not exactly a *fan* of this idea on language design principles,
> but if it will make your life easier then I'm OK with it.
>
> > The change to disallow mixed module qualifiers should be a separate
> > change IMHO.
>
> Sure.
>
> > > 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.
>
> Sorry, my mistake.
>
> > Relative diff:
>
> Could you please post a new full diff too?
Index: compiler/mercury_to_mercury.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/mercury_to_mercury.m,v
retrieving revision 1.225
diff -u -r1.225 mercury_to_mercury.m
--- compiler/mercury_to_mercury.m 12 Feb 2003 22:58:09 -0000 1.225
+++ compiler/mercury_to_mercury.m 3 Mar 2003 02:12:15 -0000
@@ -353,11 +353,12 @@
:- implementation.
:- import_module parse_tree__prog_out, parse_tree__prog_util, hlds__hlds_pred.
+:- import_module parse_tree__prog_io_util.
:- import_module hlds__hlds_out, hlds__instmap.
:- import_module recompilation__version.
:- import_module check_hlds__purity, check_hlds__mode_util.
:- import_module transform_hlds__term_util.
-:- import_module libs__options, transform_hlds__termination.
+:- import_module libs__globals, libs__options, transform_hlds__termination.
:- import_module backend_libs__foreign.
:- import_module assoc_list, char, int, string, set, lexer, ops, require.
@@ -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 an error about redefining
+ % builtin insts when an interface file is read back in.
+ { builtin_inst_name(Name1, Args) ->
+ Name = Name0
+ ;
+ Name = Name1
+ },
maybe_output_line_number(Context),
mercury_output_inst_defn(VarSet, Name, Args, InstDefn, Context).
@@ -3964,5 +3973,17 @@
output_string(Sep, Str1, Str2),
output_list(Items, Sep, Pred, Str2, Str)
).
+
+%-----------------------------------------------------------------------------%
+
+% Succeed if the sym_name describes a builtin inst.
+
+:- pred builtin_inst_name(sym_name::in, list(inst_var)::in) is semidet.
+
+builtin_inst_name(unqualified(Name), Args0) :-
+ Args1 = list__map(func(V) = term__variable(term__coerce_var(V)), Args0),
+ Term = term__functor(term__atom(Name), Args1, term__context_init),
+ convert_inst(no_allow_constrained_inst_var, Term, Inst),
+ Inst \= defined_inst(user_inst(_, _)).
%-----------------------------------------------------------------------------%
Index: compiler/prog_io_util.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/prog_io_util.m,v
retrieving revision 1.25
diff -u -r1.25 prog_io_util.m
--- compiler/prog_io_util.m 9 Jul 2002 01:29:58 -0000 1.25
+++ compiler/prog_io_util.m 3 Mar 2003 02:12:15 -0000
@@ -167,8 +167,9 @@
:- implementation.
-:- import_module parse_tree__prog_io, parse_tree__prog_io_goal, libs__options.
-:- import_module libs__globals.
+:- import_module parse_tree__prog_io, parse_tree__prog_io_goal.
+:- import_module parse_tree__prog_util.
+:- import_module libs__options, libs__globals.
% XXX we should not need to import hlds*.m here.
% But currently we need to import hlds_data.m for the `cons_id' type
@@ -358,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
%
@@ -394,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), [], _),
@@ -412,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, _)
@@ -426,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.
@@ -455,9 +429,60 @@
;
parse_qualified_term(Term, Term, "inst",
ok(QualifiedName, Args1)),
- convert_inst_list(AllowConstrainedInstVar, Args1, Args),
- Result = defined_inst(user_inst(QualifiedName, Args))
+ (
+ mercury_public_builtin_module(BuiltinModule),
+ sym_name_get_module_name(QualifiedName, unqualified(""),
+ BuiltinModule),
+ % If the term is qualified with the `builtin' module
+ % then it may be one of the simple builtin insts.
+ % We call convert_inst recursively to check for this.
+ unqualify_name(QualifiedName, UnqualifiedName),
+ convert_simple_builtin_inst(UnqualifiedName, Args1,
+ Result0),
+
+ % However, if the inst is a user_inst defined inside
+ % the `builtin' module then we need to make sure it is
+ % properly module-qualified.
+ Result0 \= defined_inst(user_inst(_, _))
+ ->
+ Result = Result0
+ ;
+ convert_inst_list(AllowConstrainedInstVar, Args1, Args),
+ 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).
Index: tests/hard_coded/builtin_inst_rename.m
===================================================================
RCS file: tests/hard_coded/builtin_inst_rename.m
diff -N tests/hard_coded/builtin_inst_rename.m
--- /dev/null 1 Jan 1970 00:00:00 -0000
+++ tests/hard_coded/builtin_inst_rename.m 3 Mar 2003 02:12:15 -0000
@@ -0,0 +1,22 @@
+:- module builtin_inst_rename.
+
+:- interface.
+
+:- import_module builtin_inst_rename2.
+:- import_module io.
+
+:- pred p(builtin_inst_rename2.my__int, builtin_inst_rename2.my__int).
+:- mode p(builtin_inst_rename2__ground >> builtin_inst_rename2__ground,
+ builtin_inst_rename2__free >> builtin_inst_rename2__ground)
+ is det.
+
+:- pred main(io::di, io::uo) is det.
+
+:- implementation.
+
+p(X, X).
+
+main -->
+ { p(42, X) },
+ io__write_int(X),
+ io__nl.
Index: tests/hard_coded/builtin_inst_rename2.m
===================================================================
RCS file: tests/hard_coded/builtin_inst_rename2.m
diff -N tests/hard_coded/builtin_inst_rename2.m
--- /dev/null 1 Jan 1970 00:00:00 -0000
+++ tests/hard_coded/builtin_inst_rename2.m 3 Mar 2003 02:12:15 -0000
@@ -0,0 +1,8 @@
+:- module builtin_inst_rename2.
+
+:- interface.
+
+:- inst builtin_inst_rename2__free == builtin__free.
+:- inst builtin_inst_rename2__ground == builtin__ground.
+
+:- type builtin_inst_rename2.my__int == int.
Index: tests/hard_coded/Mmakefile
===================================================================
RCS file: /home/mercury1/repository/tests/hard_coded/Mmakefile,v
retrieving revision 1.192
diff -u -r1.192 Mmakefile
--- tests/hard_coded/Mmakefile 24 Feb 2003 03:46:11 -0000 1.192
+++ tests/hard_coded/Mmakefile 3 Mar 2003 02:12:15 -0000
@@ -8,6 +8,7 @@
address_of_builtins \
agg \
bidirectional \
+ builtin_inst_rename \
boyer \
c_write_string \
cc_and_non_cc_test \
--
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