[m-rev.] for review: Implement unify/compare of tuples in Mercury.

Peter Wang novalazy at gmail.com
Wed Jul 9 14:58:04 AEST 2014


Hi Julien,

On Tue, 8 Jul 2014 16:26:41 +1000 (EST), Julien Fischer <jfischer at opturion.com> wrote:
> 
> On Mon, 7 Jul 2014, Peter Wang wrote:
> 
> > Branches: master
> >
> > The hand-written C unify and compare predicates for tuples did not preserve
> > deep profiler invariants correctly across the recursive unify/compare of
> > tuple arguments.  I tried to do so, and failed.  Instead, implement the
> > predicates in Mercury so the compiler can perform the deep profiling
> > transformation on them.  Bug #3.
> >
> > A micro-benchmark on my machine is about twice as fast in asm_fast.gc
> > after this patch, and equally fast in hlc.gc.  The change to the
> > high-level C backend is only to reduce code duplication.
> 
> I doubt there is much performance critical code about that uses tuples
> anyway.

Right, though they may show up as keys to maps.

> > I seem to have hit an unrelated bug in compare_representation so I did
> > not implement the compare_representation predicate for tuples yet.

I was wrong about that, so I am implementing compare_representation in
the same vein.

> > diff --git a/NEWS b/NEWS
> > index 4c0a461..a6f5798 100644
> > --- a/NEWS
> > +++ b/NEWS
> > @@ -29,6 +29,9 @@ Changes to the Mercury standard library:
> >
> > Changes to the Mercury compiler:
> >
> > +* We have fixed a long-standing bug causing crashes in deep profiling
> > +  grades, related to unify/compare of tuples.  (Bug #3)
> 
> s/of tuples/for tuples/

Ok.

> 
> > diff --git a/runtime/mercury_ho_call.c b/runtime/mercury_ho_call.c
> > index f528925..3598e8f 100644
> > --- a/runtime/mercury_ho_call.c
> > +++ b/runtime/mercury_ho_call.c
> 
> ...
> 
> > @@ -163,7 +117,10 @@ mercury__builtin__unify_2_p_0(MR_Mercury_Type_Info ti, MR_Box x, MR_Box y)
> >     */
> >     type_ctor_rep = MR_type_ctor_rep(type_ctor_info);
> >     if (type_ctor_rep == MR_TYPECTOR_REP_TUPLE) {
> > -        return unify_tuples(ti, (MR_Tuple) x, (MR_Tuple) y);
> > +        if (MR_special_pred_hooks.MR_unify_tuple_pred != NULL) {
> > +            return MR_special_pred_hooks.MR_unify_tuple_pred(ti,
> > +                (MR_Word) x, (MR_Word) y);
> > +        }
> 
> So, if it is NULL we fall through and eventually call MR_fatal_error,
> right?

Yes.

> > --- a/runtime/mercury_ho_call.h
> > +++ b/runtime/mercury_ho_call.h
> > @@ -194,4 +194,24 @@ MR_declare_entry(mercury__builtin__compare_representation_3_0);
> >
> > #endif	/* MR_HIGHLEVEL_CODE */
> >
> > +/*
> > +** Special predicates implemented in the standard library
> > +**
> > +** The library sets the fields in this structure to the actual
> > +** implementations of the predicates during initialization.
> > +*/
> 
> Add a pointer to the relevant section of library/builtins.m that
> explains why we do things this way.

Done.

> 
> > +
> > +typedef struct MR_SpecialPredHooks_Struct {
> > +  #ifdef MR_HIGHLEVEL_CODE
> > +    MR_bool     (*MR_unify_tuple_pred)(MR_Word ti, MR_Word x, MR_Word y);
> > +    MR_bool     (*MR_compare_tuple_pred)(MR_Word ti, MR_Word *res,
> > +                    MR_Word x, MR_Word y);
> > +  #else
> > +    MR_ProcAddr MR_unify_tuple_pred;
> > +    MR_ProcAddr MR_compare_tuple_pred;
> > +  #endif
> > +} MR_SpecialPredHooks;
> > +
> > +extern MR_SpecialPredHooks  MR_special_pred_hooks;
> > +
> > #endif	/* not MERCURY_HO_CALL_H */
> > diff --git a/runtime/mercury_unify_compare_body.h b/runtime/mercury_unify_compare_body.h
> > index 08c3941..dfbaedb 100644
> 
> The change looks fine to me (modulo my remarks elsewhere in this thread
> about library initialisation).

I moved the overall initialisation into library.m.  Interdiff follows.
Let me know if it's okay.

Peter

diff --git a/NEWS b/NEWS
index a6f5798..979a35a 100644
--- a/NEWS
+++ b/NEWS
@@ -30,7 +30,7 @@ Changes to the Mercury standard library:
 Changes to the Mercury compiler:
 
 * We have fixed a long-standing bug causing crashes in deep profiling
-  grades, related to unify/compare of tuples.  (Bug #3)
+  grades, related to unify/compare for tuples.  (Bug #3)
 
 * We have removed legacy support for the following systems: 
     - IRIX
diff --git a/compiler/elds_to_erlang.m b/compiler/elds_to_erlang.m
index 55a205b..4e089dd 100644
--- a/compiler/elds_to_erlang.m
+++ b/compiler/elds_to_erlang.m
@@ -324,10 +324,10 @@ main_wrapper_code = "
 
     mercury__startup() ->
         mercury__erlang_builtin:'ML_start_global_server'(),
-        mercury__io:'ML_io_init_state'().
+        mercury__library:'ML_library_init'().
 
     mercury__shutdown(ForceBadExit) ->
-        mercury__io:'ML_io_finalize_state'(),
+        mercury__library:'ML_library_finalize'(),
         'ML_erlang_global_server' ! {get_exit_status, self()},
         receive
             {get_exit_status_ack, ExitStatus0} ->
diff --git a/library/builtin.m b/library/builtin.m
index 7b55ff0..0af281d 100644
--- a/library/builtin.m
+++ b/library/builtin.m
@@ -414,13 +414,6 @@
 % Everything below here is not intended to be part of the public interface,
 % and will not be included in the Mercury library reference manual.
 
-% This import is needed by the Mercury clauses for semidet_succeed/0
-% and semidet_fail/0.
-%
-:- import_module int.
-
-%-----------------------------------------------------------------------------%
-
 :- interface.
 
     % `get_one_solution' and `get_one_solution_io' are impure alternatives
@@ -457,8 +450,21 @@
 :- pred compare_representation(comparison_result, T, T).
 :- mode compare_representation(uo, in, in) is cc_multi.
 
+    % Set up Mercury runtime to call special predicates implemented in this
+    % module.
+    %
+:- impure pred init_runtime_hooks is det.
+
+%-----------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
+
 :- implementation.
 
+    % This import is needed by the Mercury clauses for semidet_succeed/0
+    % and semidet_fail/0.
+    %
+:- import_module int.
+
 %-----------------------------------------------------------------------------%
 
 false :-
@@ -557,30 +563,33 @@ X @>= Y :-
 %
 % Unify/compare of tuples
 %
-% These are implemented in Mercury mainly to allow the compiler to perform the
-% deep profiling transformation.
-%
 
-:- pragma foreign_decl("C", "#include ""mercury_ho_call.h""").
+% We implement these predicates in Mercury mainly to allow the compiler to
+% perform the deep profiling transformation on them. init_runtime_hooks sets
+% fields in `MR_special_pred_hooks' structure to point to the actual
+% implementations, because we do not want the runtime to have unresolved
+% references into the library when it is built.
 
-:- initialise(init_special_tuple_preds/0).
-
-:- impure pred init_special_tuple_preds is det.
+:- pragma foreign_decl("C", "#include ""mercury_ho_call.h""").
 
-init_special_tuple_preds.
+init_runtime_hooks.
 
 :- pragma foreign_proc("C",
-    init_special_tuple_preds,
-    [will_not_call_mercury, thread_safe],
+    init_runtime_hooks,
+    [will_not_call_mercury, thread_safe, may_not_duplicate],
 "
 #ifdef MR_HIGHLEVEL_CODE
     MR_special_pred_hooks.MR_unify_tuple_pred = ML_unify_tuple;
     MR_special_pred_hooks.MR_compare_tuple_pred = ML_compare_tuple;
+    MR_special_pred_hooks.MR_compare_rep_tuple_pred =
+        ML_compare_rep_tuple_pred;
 #else
     MR_special_pred_hooks.MR_unify_tuple_pred =
         MR_ENTRY(mercury__builtin__unify_tuple_2_0);
     MR_special_pred_hooks.MR_compare_tuple_pred =
         MR_ENTRY(mercury__builtin__compare_tuple_3_0);
+    MR_special_pred_hooks.MR_compare_rep_tuple_pred =
+        MR_ENTRY(mercury__builtin__compare_rep_tuple_3_0);
 #endif
 ").
 
@@ -638,6 +647,37 @@ compare_tuple_pos(Result, TermA, TermB, Index, Arity) :-
         )
     ).
 
+:- pred compare_rep_tuple(comparison_result::uo, T::in, T::in) is cc_multi.
+
+:- pragma foreign_export("C", compare_rep_tuple(uo, in, in),
+    "ML_compare_rep_tuple").
+
+compare_rep_tuple(Result, TermA, TermB) :-
+    tuple_arity(TermA, Arity),
+    compare_rep_tuple_pos(Result, TermA, TermB, 0, Arity).
+
+:- pred compare_rep_tuple_pos(comparison_result::uo, T::in, T::in,
+    int::in, int::in) is cc_multi.
+
+compare_rep_tuple_pos(Result, TermA, TermB, Index, Arity) :-
+    ( Index >= Arity ->
+        Result = (=)
+    ;
+        tuple_arg(TermA, Index, SubTermA),
+        tuple_arg(TermB, Index, SubTermB),
+        private_builtin.unsafe_type_cast(SubTermB, CastSubTermB),
+        builtin.compare_representation(SubResult, SubTermA, CastSubTermB),
+        (
+            SubResult = (=),
+            compare_rep_tuple_pos(Result, TermA, TermB, Index + 1, Arity)
+        ;
+            ( SubResult = (<)
+            ; SubResult = (>)
+            ),
+            Result = SubResult
+        )
+    ).
+
 :- pred tuple_arity(T::in, int::out) is det.
 
 :- pragma foreign_proc("C",
diff --git a/library/io.m b/library/io.m
index 697ed1e..0b03182 100644
--- a/library/io.m
+++ b/library/io.m
@@ -1531,6 +1531,13 @@
 :- interface.
 
 %
+% For use by library.m:
+%
+
+:- pred io.init_state(io::di, io::uo) is det.
+:- pred io.finalize_state(io::di, io::uo) is det.
+
+%
 % For use by dir.m:
 %
 
@@ -1877,6 +1884,99 @@
 
 %-----------------------------------------------------------------------------%
 %
+% Initialization
+%
+
+io.init_state(!IO) :-
+    init_std_streams(!IO),
+    %
+    % In C grades the "current" streams are thread-local values, so can only be
+    % set after the MR_Context has been initialised for the initial thread.
+    %
+    io.set_input_stream(io.stdin_stream, _, !IO),
+    io.set_output_stream(io.stdout_stream, _, !IO),
+    io.stdin_binary_stream(StdinBinary, !IO),
+    io.stdout_binary_stream(StdoutBinary, !IO),
+    io.set_binary_input_stream(StdinBinary, _, !IO),
+    io.set_binary_output_stream(StdoutBinary, _, !IO),
+
+    io.gc_init(type_of(StreamDb), type_of(Globals), !IO),
+    map.init(StreamDb),
+    type_to_univ("<globals>", Globals),
+    io.set_stream_db(StreamDb, !IO),
+    io.set_op_table(ops.init_mercury_op_table, !IO),
+    io.set_globals(Globals, !IO),
+    io.insert_std_stream_names(!IO).
+
+:- pred init_std_streams(io::di, io::uo) is det.
+
+init_std_streams(!IO).
+
+:- pragma foreign_proc("Erlang",
+    init_std_streams(_IO0::di, _IO::uo),
+    [will_not_call_mercury, promise_pure],
+"
+    F = (fun() -> mercury_stdio_file_server(group_leader()) end),
+    StdinPid = spawn(F),
+    StdoutPid = spawn(F),
+    StderrPid = spawn(F),
+    StdinBinaryPid = spawn(F),
+    StdoutBinaryPid = spawn(F),
+
+    Stdin = {'ML_stream', make_ref(), StdinPid},
+    Stdout = {'ML_stream', make_ref(), StdoutPid},
+    Stderr = {'ML_stream', make_ref(), StderrPid},
+    StdinBinary = {'ML_stream', make_ref(), StdinBinaryPid},
+    StdoutBinary = {'ML_stream', make_ref(), StdoutBinaryPid},
+
+    % Initialise the process dictionary.
+    put('ML_stdin_stream', Stdin),
+    put('ML_stdout_stream', Stdout),
+    put('ML_stderr_stream', Stderr),
+    put('ML_stdin_binary_stream', StdinBinary),
+    put('ML_stdout_binary_stream', StdoutBinary),
+
+    % Save the standard streams to the global server. When we spawn a new
+    % Mercury thread later we will need to look it up in order to initialise
+    % the new process's process dictionary.
+    StdStreams = {Stdin, Stdout, Stderr, StdinBinary, StdoutBinary},
+    'ML_erlang_global_server' ! {init_std_streams, StdStreams}
+").
+
+    % Currently no finalization needed...
+    % (Perhaps we should close all open Mercury files?
+    % That will happen on process exit anyway, so currently we don't bother.)
+io.finalize_state(!IO).
+
+:- pred io.gc_init(type_desc::in, type_desc::in, io::di, io::uo) is det.
+
+:- pragma foreign_proc("C",
+    io.gc_init(StreamDbType::in, UserGlobalsType::in, _IO0::di, _IO::uo),
+    [will_not_call_mercury, promise_pure, tabled_for_io,
+        does_not_affect_liveness, no_sharing],
+"
+    /* for Windows DLLs, we need to call GC_INIT() from each DLL */
+#ifdef MR_BOEHM_GC
+    GC_INIT();
+#endif
+    MR_add_root(&ML_io_stream_db, (MR_TypeInfo) StreamDbType);
+    MR_add_root(&ML_io_user_globals, (MR_TypeInfo) UserGlobalsType);
+").
+
+io.gc_init(_, _, !IO).
+
+:- pred io.insert_std_stream_names(io::di, io::uo) is det.
+
+io.insert_std_stream_names(!IO) :-
+    io.stdin_stream(input_stream(Stdin), !IO),
+    io.insert_stream_info(Stdin, stream(0, input, preopen, stdin), !IO),
+    io.stdout_stream(output_stream(Stdout), !IO),
+    io.insert_stream_info(Stdout, stream(1, output, preopen, stdout), !IO),
+    io.stderr_stream(output_stream(Stderr), !IO),
+    io.insert_stream_info(Stderr, stream(1, output, preopen, stderr), !IO).
+
+%-----------------------------------------------------------------------------%
+%
 % Input predicates
 %
 
@@ -5522,120 +5622,6 @@ io.report_stats(Selector, !IO) :-
 % Miscellaneous predicates
 %
 
-:- interface.
-
-    % XXX Since on the IL backend pragma export is NYI, this
-    % predicate must be placed in the interface.
-    %
-:- pred io.init_state(io::di, io::uo) is det.
-
-:- implementation.
-
-    % For use by the Mercury runtime.
-    %
-:- pragma foreign_export("C", io.init_state(di, uo), "ML_io_init_state").
-:- pragma foreign_export("IL", io.init_state(di, uo), "ML_io_init_state").
-:- pragma foreign_export("Erlang", io.init_state(di, uo), "ML_io_init_state").
-
-io.init_state(!IO) :-
-    init_std_streams(!IO),
-    %
-    % In C grades the "current" streams are thread-local values, so can only be
-    % set after the MR_Context has been initialised for the initial thread.
-    %
-    io.set_input_stream(io.stdin_stream, _, !IO),
-    io.set_output_stream(io.stdout_stream, _, !IO),
-    io.stdin_binary_stream(StdinBinary, !IO),
-    io.stdout_binary_stream(StdoutBinary, !IO),
-    io.set_binary_input_stream(StdinBinary, _, !IO),
-    io.set_binary_output_stream(StdoutBinary, _, !IO),
-
-    io.gc_init(type_of(StreamDb), type_of(Globals), !IO),
-    map.init(StreamDb),
-    type_to_univ("<globals>", Globals),
-    io.set_stream_db(StreamDb, !IO),
-    io.set_op_table(ops.init_mercury_op_table, !IO),
-    io.set_globals(Globals, !IO),
-    io.insert_std_stream_names(!IO).
-
-:- pred init_std_streams(io::di, io::uo) is det.
-
-init_std_streams(!IO).
-
-:- pragma foreign_proc("Erlang",
-    init_std_streams(_IO0::di, _IO::uo),
-    [will_not_call_mercury, promise_pure],
-"
-    F = (fun() -> mercury_stdio_file_server(group_leader()) end),
-    StdinPid = spawn(F),
-    StdoutPid = spawn(F),
-    StderrPid = spawn(F),
-    StdinBinaryPid = spawn(F),
-    StdoutBinaryPid = spawn(F),
-
-    Stdin = {'ML_stream', make_ref(), StdinPid},
-    Stdout = {'ML_stream', make_ref(), StdoutPid},
-    Stderr = {'ML_stream', make_ref(), StderrPid},
-    StdinBinary = {'ML_stream', make_ref(), StdinBinaryPid},
-    StdoutBinary = {'ML_stream', make_ref(), StdoutBinaryPid},
-
-    % Initialise the process dictionary.
-    put('ML_stdin_stream', Stdin),
-    put('ML_stdout_stream', Stdout),
-    put('ML_stderr_stream', Stderr),
-    put('ML_stdin_binary_stream', StdinBinary),
-    put('ML_stdout_binary_stream', StdoutBinary),
-
-    % Save the standard streams to the global server. When we spawn a new
-    % Mercury thread later we will need to look it up in order to initialise
-    % the new process's process dictionary.
-    StdStreams = {Stdin, Stdout, Stderr, StdinBinary, StdoutBinary},
-    'ML_erlang_global_server' ! {init_std_streams, StdStreams}
-").
-
-:- pred io.finalize_state(io::di, io::uo) is det.
-
-    % For use by the Mercury runtime.
-    %
-:- pragma foreign_export("C", io.finalize_state(di, uo),
-    "ML_io_finalize_state").
-:- pragma foreign_export("IL", io.finalize_state(di, uo),
-    "ML_io_finalize_state").
-:- pragma foreign_export("Erlang", io.finalize_state(di, uo),
-    "ML_io_finalize_state").
-
-    % Currently no finalization needed...
-    % (Perhaps we should close all open Mercury files?
-    % That will happen on process exit anyway, so currently we don't bother.)
-io.finalize_state(!IO).
-
-:- pred io.gc_init(type_desc::in, type_desc::in, io::di, io::uo) is det.
-
-:- pragma foreign_proc("C",
-    io.gc_init(StreamDbType::in, UserGlobalsType::in, _IO0::di, _IO::uo),
-    [will_not_call_mercury, promise_pure, tabled_for_io,
-        does_not_affect_liveness, no_sharing],
-"
-    /* for Windows DLLs, we need to call GC_INIT() from each DLL */
-#ifdef MR_BOEHM_GC
-    GC_INIT();
-#endif
-    MR_add_root(&ML_io_stream_db, (MR_TypeInfo) StreamDbType);
-    MR_add_root(&ML_io_user_globals, (MR_TypeInfo) UserGlobalsType);
-").
-
-io.gc_init(_, _, !IO).
-
-:- pred io.insert_std_stream_names(io::di, io::uo) is det.
-
-io.insert_std_stream_names(!IO) :-
-    io.stdin_stream(input_stream(Stdin), !IO),
-    io.insert_stream_info(Stdin, stream(0, input, preopen, stdin), !IO),
-    io.stdout_stream(output_stream(Stdout), !IO),
-    io.insert_stream_info(Stdout, stream(1, output, preopen, stdout), !IO),
-    io.stderr_stream(output_stream(Stderr), !IO),
-    io.insert_stream_info(Stderr, stream(1, output, preopen, stderr), !IO).
-
 io.call_system(Command, Result, !IO) :-
     io.call_system_return_signal(Command, Result0, !IO),
     (
diff --git a/library/library.m b/library/library.m
index e490443..3756b66 100644
--- a/library/library.m
+++ b/library/library.m
@@ -316,4 +316,32 @@ mercury_std_library_module("version_hash_table").
 mercury_std_library_module("version_store").
 
 %---------------------------------------------------------------------------%
+
+    % Overall library initializer called before any user code,
+    % including module local initializers.
+    %
+:- pred library_init(io::di, io::uo) is det.
+
+:- pragma foreign_export("C", library_init(di, uo), "ML_library_init").
+:- pragma foreign_export("Erlang", library_init(di, uo), "ML_library_init").
+
+library_init(!IO) :-
+    promise_pure (
+        impure builtin.init_runtime_hooks,
+        io.init_state(!IO)
+    ).
+
+    % Overall library finalizer.
+    %
+:- pred library_finalize(io::di, io::uo) is det.
+
+:- pragma foreign_export("C", library_finalize(di, uo),
+    "ML_library_finalize").
+:- pragma foreign_export("Erlang", library_finalize(di, uo),
+    "ML_library_finalize").
+
+library_finalize(!IO) :-
+    io.finalize_state(!IO).
+
+%---------------------------------------------------------------------------%
 %---------------------------------------------------------------------------%
diff --git a/runtime/mercury_ho_call.h b/runtime/mercury_ho_call.h
index 6c83809..555d738 100644
--- a/runtime/mercury_ho_call.h
+++ b/runtime/mercury_ho_call.h
@@ -196,9 +196,7 @@ MR_declare_entry(mercury__builtin__compare_representation_3_0);
 
 /*
 ** Special predicates implemented in the standard library
-**
-** The library sets the fields in this structure to the actual
-** implementations of the predicates during initialization.
+** The structure is initialized by init_runtime_hooks in builtin.m
 */
 
 typedef struct MR_SpecialPredHooks_Struct {
@@ -206,9 +204,12 @@ typedef struct MR_SpecialPredHooks_Struct {
     MR_bool     (*MR_unify_tuple_pred)(MR_Word ti, MR_Word x, MR_Word y);
     MR_bool     (*MR_compare_tuple_pred)(MR_Word ti, MR_Word *res,
                     MR_Word x, MR_Word y);
+    MR_bool     (*MR_compare_rep_tuple_pred)(MR_Word ti, MR_Word *res,
+                    MR_Word x, MR_Word y);
   #else
     MR_ProcAddr MR_unify_tuple_pred;
     MR_ProcAddr MR_compare_tuple_pred;
+    MR_ProcAddr MR_compare_rep_tuple_pred;
   #endif
 } MR_SpecialPredHooks;
 
diff --git a/runtime/mercury_init.h b/runtime/mercury_init.h
index 46de524..b35d714 100644
--- a/runtime/mercury_init.h
+++ b/runtime/mercury_init.h
@@ -123,8 +123,8 @@ extern	int	mercury_terminate(void);
 
 /* in library/io.mh */
 extern	void	mercury_init_io(void);
-extern	void	ML_io_init_state(void);
-extern	void	ML_io_finalize_state(void);
+extern	void	ML_library_init(void);
+extern	void	ML_library_finalize(void);
 extern	void	ML_io_stderr_stream(MercuryFilePtr *);
 extern	void	ML_io_stdout_stream(MercuryFilePtr *);
 extern	void	ML_io_stdin_stream(MercuryFilePtr *);
diff --git a/runtime/mercury_unify_compare_body.h b/runtime/mercury_unify_compare_body.h
index dfbaedb..5ac7fea 100644
--- a/runtime/mercury_unify_compare_body.h
+++ b/runtime/mercury_unify_compare_body.h
@@ -37,9 +37,9 @@
 ** because they implement the same task.
 **
 ** XXX does the rationale still hold? Only rarely used code paths still have
-** loop bodies in C and they are likely incorrect for deep profiling.  The
-** Mercury implementation of tuple unify/compare predicates is faster in
-** asm_fast.gc, and only slightly slower in hlc.gc grades. --pw
+** loop bodies in C and they are likely incorrect for deep profiling. Also,
+** the Mercury implementation of tuple unify/compare predicates is faster than
+** the hand-written version was, in asm_fast.gc. --pw
 **
 ** We need separate C functions for unifications and comparison because
 ** with --no-special-preds, a type with user-defined equality (but not
@@ -600,8 +600,11 @@ start_label:
             */
 #ifdef select_compare_code
     #ifdef include_compare_rep_code
-            MR_fatal_error("sorry, not implemented: "
-                "compare_representation for tuples");
+            if (MR_special_pred_hooks.MR_compare_rep_tuple_pred != NULL) {
+                tailcall(MR_special_pred_hooks.MR_compare_rep_tuple_pred);
+            } else {
+                MR_fatal_error(attempt_msg "tuples");
+            }
     #else
             if (MR_special_pred_hooks.MR_compare_tuple_pred != NULL) {
                 tailcall(MR_special_pred_hooks.MR_compare_tuple_pred);
diff --git a/runtime/mercury_wrapper.c b/runtime/mercury_wrapper.c
index f9c09ca..c3a94d9 100644
--- a/runtime/mercury_wrapper.c
+++ b/runtime/mercury_wrapper.c
@@ -470,9 +470,9 @@ MR_Code     *MR_program_entry_point;
 const char  *MR_runtime_flags = "";
 
 void        (*MR_library_initializer)(void);
-            /* normally ML_io_init_state (io.init_state/2)*/
+            /* normally ML_library_init */
 void        (*MR_library_finalizer)(void);
-            /* normally ML_io_finalize_state (io.finalize_state/2) */
+            /* normally ML_library_finalize */
 
 void        (*MR_io_stderr_stream)(MercuryFilePtr *);
 void        (*MR_io_stdout_stream)(MercuryFilePtr *);
diff --git a/util/mkinit.c b/util/mkinit.c
index 0309215..3679a59 100644
--- a/util/mkinit.c
+++ b/util/mkinit.c
@@ -451,8 +451,8 @@ static const char mercury_funcs2[] =
     "#ifdef MR_CONSERVATIVE_GC\n"
     "   MR_address_of_init_gc = init_gc;\n"
     "#endif\n"
-    "   MR_library_initializer = ML_io_init_state;\n"
-    "   MR_library_finalizer = ML_io_finalize_state;\n"
+    "   MR_library_initializer = ML_library_init;\n"
+    "   MR_library_finalizer = ML_library_finalize;\n"
     "   MR_io_stdin_stream = ML_io_stdin_stream;\n"
     "   MR_io_stdout_stream = ML_io_stdout_stream;\n"
     "   MR_io_stderr_stream = ML_io_stderr_stream;\n"



More information about the reviews mailing list