[m-rev.] for review: XML documentation of DU types pass

Peter Ross pro at missioncriticalit.com
Wed Nov 1 17:21:37 AEDT 2006


diff -u compiler/add_clause.m compiler/add_clause.m
--- compiler/add_clause.m	31 Oct 2006 04:52:45 -0000
+++ compiler/add_clause.m	1 Nov 2006 06:13:05 -0000
@@ -896,8 +896,8 @@
     MutableHLDS = trace_mutable_var_hlds(MutableName, StateVarName),
     GetPredName = unqualified("get_" ++ MutableName),
     SetPredName = unqualified("set_" ++ MutableName),
-    SetVar = functor(atom("!:"), [variable(StateVar, context_init)], Context),
-    UseVar = functor(atom("!."), [variable(StateVar, context_init)], Context),
+    SetVar = functor(atom("!:"), [variable(StateVar, Context)], Context),
+    UseVar = functor(atom("!."), [variable(StateVar, Context)], Context),
     GetPurity = purity_semipure,
     SetPurity = purity_impure,
     GetGoal = call_expr(GetPredName, [SetVar], GetPurity) - Context,
@@ -910,8 +910,8 @@
     Builtin = mercury_private_builtin_module,
     GetPredName = qualified(Builtin, "trace_get_io_state"),
     SetPredName = qualified(Builtin, "trace_set_io_state"),
-    SetVar = functor(atom("!:"), [variable(StateVar, context_init)], Context),
-    UseVar = functor(atom("!."), [variable(StateVar, context_init)], Context),
+    SetVar = functor(atom("!:"), [variable(StateVar, Context)], Context),
+    UseVar = functor(atom("!."), [variable(StateVar, Context)], Context),
     GetPurity = purity_semipure,
     SetPurity = purity_impure,
     GetGoal = call_expr(GetPredName, [SetVar], GetPurity) - Context,
diff -u compiler/make_hlds_passes.m compiler/make_hlds_passes.m
--- compiler/make_hlds_passes.m	31 Oct 2006 04:52:45 -0000
+++ compiler/make_hlds_passes.m	1 Nov 2006 06:13:05 -0000
@@ -1586,7 +1586,7 @@
     % Construct the semipure get predicate.
     %
     UnsafeGetPredName = mutable_unsafe_get_pred_sym_name(ModuleName, Name),
-    UnsafeGetCallArgs = [variable(X, context_init)],
+    UnsafeGetCallArgs = [variable(X, Context)],
     CallUnsafeGet = call_expr(UnsafeGetPredName, UnsafeGetCallArgs,
         purity_semipure) - Context,
     
diff -u compiler/options.m compiler/options.m
--- compiler/options.m	31 Oct 2006 04:52:46 -0000
+++ compiler/options.m	1 Nov 2006 06:13:06 -0000
@@ -1660,6 +1660,7 @@
         make_transitive_opt_interface).
 long_option("make-trans-opt",       make_transitive_opt_interface).
 long_option("make-analysis-registry",   make_analysis_registry).
+long_option("make-xml-doc",         make_xml_documentation).
 long_option("make-xml-documentation",   make_xml_documentation).
 long_option("convert-to-mercury",   convert_to_mercury).
 long_option("convert-to-Mercury",   convert_to_mercury).
@@ -3053,7 +3054,7 @@
         "\tOutput transitive optimization information",
         "\tinto the `<module>.trans_opt' file.",
         "\tThis option should only be used by mmake.",
-        "-x,--make-xml-documentation",
+        "-x,--make-xml-doc,--make-xml-documentation",
         "\tOutput XML documentation of the module",
         "\tinto the `<module>.xml' file.",
         "\tThis option should only be used by mmake.",
diff -u compiler/prog_io_dcg.m compiler/prog_io_dcg.m
--- compiler/prog_io_dcg.m	31 Oct 2006 04:52:46 -0000
+++ compiler/prog_io_dcg.m	1 Nov 2006 06:13:06 -0000
@@ -112,9 +112,9 @@
 parse_dcg_goal(Term, MaybeGoal, !VarSet, !Counter, !Var) :-
     % First, figure out the context for the goal.
     (
-        Term = term.functor(_, _, Ctxt)
+        Term = term.functor(_, _, Context)
     ;
-        Term = term.variable(_, Ctxt)
+        Term = term.variable(_, Context)
     ),
     % Next, parse it.
     (
@@ -125,7 +125,7 @@
         (
             SymName = unqualified(Functor),
             list.map(term.coerce, Args0, Args1),
-            parse_dcg_goal_2(Functor, Args1, Ctxt, MaybeGoalPrime,
+            parse_dcg_goal_2(Functor, Args1, Context, MaybeGoalPrime,
                 !VarSet, !Counter, !Var)
         ->
             MaybeGoal = MaybeGoalPrime
@@ -135,8 +135,8 @@
             % pair to the non-terminal's argument list.
             new_dcg_var(!VarSet, !Counter, Var),
             Args = Args0 ++
-                [term.variable(!.Var, Ctxt), term.variable(Var, Ctxt)],
-            Goal = call_expr(SymName, Args, purity_pure) - Ctxt,
+                [term.variable(!.Var, Context), term.variable(Var, Context)],
+            Goal = call_expr(SymName, Args, purity_pure) - Context,
             MaybeGoal = ok1(Goal),
             !:Var = Var
         )
@@ -147,8 +147,8 @@
         new_dcg_var(!VarSet, !Counter, Var),
         term.coerce(Term, ProgTerm),
         Goal = call_expr(unqualified("call"),
-            [ProgTerm, term.variable(!.Var, Ctxt), term.variable(Var, Ctxt)],
-            purity_pure) - Ctxt,
+            [ProgTerm, variable(!.Var, Context), variable(Var, Context)],
+            purity_pure) - Context,
         MaybeGoal = ok1(Goal),
         !:Var = Var
     ).
@@ -686,6 +686,6 @@
 
-process_dcg_clause(ok2(Name, Args0), VarSet, Var0, Var, Body, Ctxt,
+process_dcg_clause(ok2(Name, Args0), VarSet, Var0, Var, Body, Context,
         ok1(item_clause(user, VarSet, predicate, Name, Args, Body))) :-
     list.map(term.coerce, Args0, Args1),
-    Args = Args1 ++ [term.variable(Var0, Ctxt), term.variable(Var, Ctxt)].
+    Args = Args1 ++ [variable(Var0, Context), variable(Var, Context)].
 process_dcg_clause(error2(Errors), _, _, _, _, _, error1(Errors)).
diff -u library/term_io.m library/term_io.m
--- library/term_io.m	31 Oct 2006 04:52:47 -0000
+++ library/term_io.m	1 Nov 2006 06:13:07 -0000
@@ -328,7 +328,7 @@
         % gets parsed as ''(Var, Arg). When writing it out, we want to use
         % the nice syntax.
         Functor = term.atom(""),
-        Args = [term.variable(Var, context_init), FirstArg | OtherArgs]
+        Args = [term.variable(Var, _), FirstArg | OtherArgs]
     ->
         term_io.write_variable_2(Ops, Var, !VarSet, !N, !IO),
         io.write_char('(', !IO),
only in patch2:
unchanged:
--- NEWS	30 Oct 2006 06:43:36 -0000	1.429
+++ NEWS	1 Nov 2006 06:13:05 -0000
@@ -27,6 +27,11 @@
 * We have added string.c_pointer_to_string/{1,2} and string.from_c_pointer/1
   to convert c_pointers to a human readable form.
 
+* We have changed term.variable so that it records the context where
+  the variable was used.  This required the backward mode of
+  term.var_list_to_term_list to be removed.  The backwards mode is
+  now accessed via term.term_list_to_var_list.
+
 * We have renamed some library predicates whose names were ambiguous.
 
 Changes to the Mercury compiler:
only in patch2:
unchanged:
--- compiler/error_util.m	16 Oct 2006 01:55:08 -0000	1.57
+++ compiler/error_util.m	1 Nov 2006 06:13:05 -0000
@@ -402,6 +402,13 @@
     io::di, io::uo) is det.
 
 %-----------------------------------------------------------------------------%
+
+    % Report why the file is not able to be opened,
+    % and set the exit status to be 1.
+    %
+:- pred unable_to_open_file(string::in, io.error::in, io::di, io::uo) is det.
+
+%-----------------------------------------------------------------------------%
 %-----------------------------------------------------------------------------%
 
 :- implementation.
@@ -1275,6 +1282,18 @@
 report_warning(Context, Indent, Components, !IO) :-
     record_warning(!IO),
     write_error_pieces(Context, Indent, Components, !IO).
+
+%-----------------------------------------------------------------------------%
+
+unable_to_open_file(FileName, IOErr, !IO) :-
+    io.stderr_stream(StdErr, !IO),
+    io.write_string(StdErr, "Unable to open file: '", !IO),
+    io.write_string(StdErr, FileName, !IO),
+    io.write_string(StdErr, "' because\n", !IO),
+    io.write_string(StdErr, io.error_message(IOErr), !IO),
+    io.nl(StdErr, !IO),
+
+    io.set_exit_status(1, !IO).
 
 %-----------------------------------------------------------------------------%
 
only in patch2:
unchanged:
--- compiler/notes/compiler_design.html	15 Sep 2006 11:14:37 -0000	1.123
+++ compiler/notes/compiler_design.html	1 Nov 2006 06:13:07 -0000
@@ -866,6 +866,14 @@
 	implementation.
 	<p>
 
+<dt> xml documentation (xml_documentation.m)
+
+	<dd>
+	xml_documentation.m outputs a XML representation of all the
+	declarations in the module.  This XML representation is designed
+	to be transformed via XSL into more human readable documentation.
+	<p>
+
 </dl>
 
 <h4> 3. High-level transformations </h4>
only in patch2:
unchanged:
--- doc/user_guide.texi	2 Oct 2006 10:14:38 -0000	1.496
+++ doc/user_guide.texi	1 Nov 2006 06:13:07 -0000
@@ -6008,6 +6008,14 @@
 from the corresponding @samp{.m} file.
 
 @sp 1
+ at item --make-xml-documentation
+ at findex --make-xml-documentation
+Output an XML representation of all the declarations in the module
+into the `<module>.xml' file.
+This XML file can then be transformed via a XSL transform into
+another documentation format.
+
+ at sp 1
 @item -P
 @itemx --pretty-print
 @itemx --convert-to-mercury
--------------------------------------------------------------------------
mercury-reviews mailing list
Post messages to:       mercury-reviews at csse.unimelb.edu.au
Administrative Queries: owner-mercury-reviews at csse.unimelb.edu.au
Subscriptions:          mercury-reviews-request at csse.unimelb.edu.au
--------------------------------------------------------------------------



More information about the reviews mailing list