for review: lcc compile the compiler
Peter Ross
petdr at cs.mu.OZ.AU
Mon Oct 26 15:27:49 AEDT 1998
Hi,
Fergus could you please review this.
It seems that the change from (const Word *) to (Word *), hasn't caused
a huge number of problems. Seeing that the change is so simple, I
thought that it would be better to try and incorporate the output of
consts in the correct places in a seperate change.
This bootchecks using lcc on kryten, and I am currently bootchecking
using cc on kryten. cc on murlibobo barfs because the runtime contains
lines like
#ifdef XXX
#define YYY /* causes the barf */
#endif
Pete.
===================================================================
Estimated hours taken: 30
Changes to compile the compiler using lcc.
compiler/llds_out.m:
Remove all remaining occurences of (const Word *).
compiler/mercury_compile.m:
Call transform_llds.
compiler/options.m:
Add the option max_jump_table_size. This option is needed because
lcc barfs when the jump_table for computed gotos size is over 128.
compiler/transform_llds.m:
Transform computed_gotos whose table size is over
max_jump_table_size to binary search down to computed gotos whose
table size is less then or equal to max_jump_table_size.
library/benchmarking.m:
library/math.m:
library/private_builtin.m:
library/std_util.m:
s/\\n/\\\\n/g so that we don't get line breaks in string constants.
library/io.m:
Change an LVALUE_CAST to type Word as RHS of the expression gets
cast to type Word.
trace/mercury_trace_internal.c:
Add a cast to (Word *) because LHS of the expression has type (Word *)
Index: compiler/llds_out.m
===================================================================
RCS file: /home/staff/zs/imp/mercury/compiler/llds_out.m,v
retrieving revision 1.93
diff -u -r1.93 llds_out.m
--- 1.93 1998/10/23 00:40:13
+++ llds_out.m 1998/10/24 01:20:18
@@ -2934,7 +2934,7 @@
types_match(bool, word).
types_match(integer, bool).
- % output a float rval, converted to type `const Word *'
+ % output a float rval, converted to type `Word *'
%
:- pred output_float_rval_as_data_ptr(rval, io__state, io__state).
:- mode output_float_rval_as_data_ptr(in, di, uo) is det.
@@ -2952,10 +2952,10 @@
{ UnboxFloat = no, StaticGroundTerms = yes },
{ llds_out__float_const_expr_name(Rval, FloatName) }
->
- io__write_string("(const Word *) &mercury_float_const_"),
+ io__write_string("(Word *) &mercury_float_const_"),
io__write_string(FloatName)
;
- io__write_string("(const Word *) float_to_word("),
+ io__write_string("(Word *) float_to_word("),
output_rval(Rval),
io__write_string(")")
).
@@ -3123,17 +3123,17 @@
output_rval(mem_addr(MemRef)) -->
(
{ MemRef = stackvar_ref(N) },
- io__write_string("(const Word *) &MR_stackvar("),
+ io__write_string("(Word *) &MR_stackvar("),
io__write_int(N),
io__write_string(")")
;
{ MemRef = framevar_ref(N) },
- io__write_string("(const Word *) &MR_framevar("),
+ io__write_string("(Word *) &MR_framevar("),
io__write_int(N),
io__write_string(")")
;
{ MemRef = heap_ref(Rval, Tag, FieldNum) },
- io__write_string("(const Word *) &field("),
+ io__write_string("(Word *) &field("),
output_tag(Tag),
io__write_string(", "),
output_rval(Rval),
Index: compiler/mercury_compile.m
===================================================================
RCS file: /home/staff/zs/imp/mercury/compiler/mercury_compile.m,v
retrieving revision 1.108
diff -u -r1.108 mercury_compile.m
--- 1.108 1998/10/16 06:17:35
+++ mercury_compile.m 1998/10/20 05:42:15
@@ -40,7 +40,8 @@
:- import_module lco, saved_vars, liveness.
:- import_module follow_code, live_vars, arg_info, store_alloc, goal_path.
:- import_module code_gen, optimize, export, base_type_info, base_type_layout.
-:- import_module llds_common, llds_out, continuation_info, stack_layout.
+:- import_module llds_common, transform_llds, llds_out.
+:- import_module continuation_info, stack_layout.
% miscellaneous compiler modules
:- import_module prog_data, hlds_module, hlds_pred, hlds_out, llds.
@@ -2020,7 +2021,7 @@
bool, bool, io__state, io__state).
:- mode mercury_compile__output_llds(in, in, in, in, in, di, uo) is det.
-mercury_compile__output_llds(ModuleName, LLDS, StackLayoutLabels,
+mercury_compile__output_llds(ModuleName, LLDS0, StackLayoutLabels,
Verbose, Stats) -->
maybe_write_string(Verbose,
"% Writing output to `"),
@@ -2028,6 +2029,7 @@
maybe_write_string(Verbose, FileName),
maybe_write_string(Verbose, "'..."),
maybe_flush_output(Verbose),
+ transform_llds(LLDS0, LLDS),
output_c_file(LLDS, StackLayoutLabels),
maybe_write_string(Verbose, " done.\n"),
maybe_flush_output(Verbose),
Index: compiler/options.m
===================================================================
RCS file: /home/staff/zs/imp/mercury/compiler/options.m,v
retrieving revision 1.246
diff -u -r1.246 options.m
--- 1.246 1998/10/18 07:11:37
+++ options.m 1998/10/23 00:04:38
@@ -152,6 +152,7 @@
; unboxed_float
; sync_term_size % in words
; type_layout
+ ; max_jump_table_size
% Options for internal use only
% (the values of these options are implied by the
% settings of other options)
@@ -449,6 +450,8 @@
% of writing) - will usually be over-
% ridden by a value from configure.
type_layout - bool(yes),
+ max_jump_table_size - int(0),
+ % 0 indicates any size.
basic_stack_layout - bool(no),
agc_stack_layout - bool(no),
procid_stack_layout - bool(no),
@@ -773,6 +776,7 @@
long_option("args", args).
long_option("arg-convention", args).
long_option("type-layout", type_layout).
+long_option("max-jump-table-size", max_jump_table_size).
long_option("agc-stack-layout", agc_stack_layout).
long_option("basic-stack-layout", basic_stack_layout).
long_option("procid-stack-layout", procid_stack_layout).
@@ -1641,7 +1645,11 @@
"\tDon't output base_type_layout structures or references",
"\tto them. (The C code also needs to be compiled with",
"\t`-DNO_TYPE_LAYOUT').",
-
+
+ "--max-jump-table-size",
+ "\tThe maximum number of entries a jump table can have.",
+ "\t0 indicates any size",
+
% This is a developer only option.
% "--basic-stack-layout",
% "(This option is not for general use.)",
Index: compiler/transform_llds.m
===================================================================
RCS file: transform_llds.m
diff -N transform_llds.m
--- /dev/null Mon Oct 26 14:58:05 1998
+++ transform_llds.m Mon Oct 26 14:16:43 1998
@@ -0,0 +1,279 @@
+%-----------------------------------------------------------------------------%
+% Copyright (C) 1998 The University of Melbourne.
+% This file may only be copied under the terms of the GNU General
+% Public License - see the file COPYING in the Mercury distribution.
+%-----------------------------------------------------------------------------%
+%
+% Module: transform_llds
+%
+% Main authors: petdr
+%
+% This module does source to source transformations of the llds data
+% structure. This is sometimes necessary to avoid limits in some
+% compilers.
+%
+% This module currently transforms computed gotos into a binary search
+% down to smaller computed gotos. This avoids a limitation in the lcc
+% compiler.
+%
+%-----------------------------------------------------------------------------%
+
+:- module transform_llds.
+
+:- interface.
+
+:- import_module llds.
+
+:- pred transform_llds(c_file, c_file, io__state, io__state).
+:- mode transform_llds(in, out, di, uo) is det.
+
+%-----------------------------------------------------------------------------%
+
+:- implementation.
+
+:- import_module globals, options, prog_data.
+:- import_module bool, int, list, require, std_util.
+
+transform_llds(LLDS0, LLDS) -->
+ globals__io_lookup_int_option(max_jump_table_size, Size),
+ (
+ { Size = 0 }
+ ->
+ { LLDS = LLDS0 }
+ ;
+ globals__io_lookup_bool_option(split_c_files, SplitFiles),
+ ( { SplitFiles = yes } ->
+ { LLDS0 = c_file(ModuleName, C_HeaderInfo,
+ C_Modules0) },
+ transform_c_modules(C_Modules0, ModuleName,
+ C_HeaderInfo, C_Modules),
+ { LLDS = c_file(ModuleName, C_HeaderInfo, C_Modules) }
+ ;
+ transform_c_file(LLDS0, LLDS)
+ )
+ ).
+
+%-----------------------------------------------------------------------------%
+
+:- pred transform_c_modules(list(c_module), module_name, list(c_header_code),
+ list(c_module), io__state, io__state).
+:- mode transform_c_modules(in, in, in, out, di, uo) is det.
+
+transform_c_modules([], _ModuleName, _C_HeaderLines, []) --> [].
+transform_c_modules([Module0 | Modules0], ModuleName, C_HeaderLines,
+ C_Modules) -->
+ transform_c_modules(Modules0, ModuleName, C_HeaderLines, Modules),
+ { C_File0 = c_file(ModuleName, C_HeaderLines, [Module0]) },
+ transform_c_file(C_File0, C_File),
+ (
+ { C_File = c_file(_, _, [Module]) }
+ ->
+ { C_Modules = [Module | Modules] }
+ ;
+ { error("transform_c_modules: [_|_]") }
+ ).
+
+%-----------------------------------------------------------------------------%
+
+:- pred transform_c_file(c_file, c_file, io__state, io__state).
+:- mode transform_c_file(in, out, di, uo) is det.
+
+transform_c_file(c_file(ModuleName, HeaderInfo, Modules0),
+ c_file(ModuleName, HeaderInfo, Modules)) -->
+ transform_c_module_list(Modules0, Modules).
+
+%-----------------------------------------------------------------------------%
+
+:- pred transform_c_module_list(list(c_module), list(c_module),
+ io__state, io__state).
+:- mode transform_c_module_list(in, out, di, uo) is det.
+
+transform_c_module_list([], []) --> [].
+transform_c_module_list([M0 | M0s], [M | Ms]) -->
+ transform_c_module(M0, M),
+ transform_c_module_list(M0s, Ms).
+
+%-----------------------------------------------------------------------------%
+
+:- pred transform_c_module(c_module, c_module, io__state, io__state).
+:- mode transform_c_module(in, out, di, uo) is det.
+
+transform_c_module(c_module(Name, Procedures0), c_module(Name, Procedures)) -->
+ transform_c_procedure_list(Procedures0, Procedures).
+transform_c_module(c_data(Name, DataName, Exported, Rvals, PredProcIds),
+ c_data(Name, DataName, Exported, Rvals, PredProcIds)) --> [].
+transform_c_module(c_code(Code, Context), c_code(Code, Context)) --> [].
+transform_c_module(c_export(Exports), c_export(Exports)) --> [].
+
+
+%-----------------------------------------------------------------------------%
+
+:- pred transform_c_procedure_list(list(c_procedure), list(c_procedure),
+ io__state, io__state).
+:- mode transform_c_procedure_list(in, out, di, uo) is det.
+
+transform_c_procedure_list([], []) --> [].
+transform_c_procedure_list([P0 | P0s], [P | Ps]) -->
+ transform_c_procedure(P0, P),
+ transform_c_procedure_list(P0s, Ps).
+
+%-----------------------------------------------------------------------------%
+
+:- pred transform_c_procedure(c_procedure, c_procedure, io__state, io__state).
+:- mode transform_c_procedure(in, out, di, uo) is det.
+
+transform_c_procedure(c_procedure(Name, Arity, PredProcId, Instructions0),
+ c_procedure(Name, Arity, PredProcId, Instructions)) -->
+ transform_instructions(Instructions0, Instructions).
+
+%-----------------------------------------------------------------------------%
+
+:- pred transform_instructions(list(instruction), list(instruction),
+ io__state, io__state).
+:- mode transform_instructions(in, out, di, uo) is det.
+
+transform_instructions(Instrs0, Instrs) -->
+ { proc_label(Instrs0, ProcLabel) },
+ { max_label_int(Instrs0, 0, N) },
+ transform_instructions_2(Instrs0, ProcLabel, N, Instrs).
+
+:- pred transform_instructions_2(list(instruction), proc_label, int,
+ list(instruction), io__state, io__state).
+:- mode transform_instructions_2(in, in, in, out, di, uo) is det.
+
+transform_instructions_2([], _, _, []) --> [].
+transform_instructions_2([Instr0 | Instrs0], ProcLabel, N0, Instrs) -->
+ transform_instruction(Instr0, ProcLabel, N0, InstrsA, N),
+ transform_instructions_2(Instrs0, ProcLabel, N, InstrsB),
+ { list__append(InstrsA, InstrsB, Instrs) }.
+
+
+%-----------------------------------------------------------------------------%
+
+:- pred transform_instruction(instruction, proc_label, int,
+ list(instruction), int, io__state, io__state).
+:- mode transform_instruction(in, in, in, out, out, di, uo) is det.
+
+transform_instruction(Instr0, ProcLabel, N0, Instrs, N) -->
+ globals__io_lookup_int_option(max_jump_table_size, Size),
+ (
+ { Instr0 = computed_goto(_Rval, Labels) - _},
+ { list__length(Labels, L) },
+ { L > Size }
+ ->
+ split_computed_goto(Instr0, Size, L, ProcLabel, N0, Instrs, N)
+ ;
+ { Instrs = [Instr0] },
+ { N = N0 }
+ ).
+
+%-----------------------------------------------------------------------------%
+
+ %
+ % split_computed_goto(I, S, L, P, N0, Is, N)
+ %
+ % If instruction, I, is a computed_goto whose jump_table size is
+ % greater then S, then split the table in half and insert the
+ % instructions, Is, to do a binary search down to a jump_table
+ % whose size is sufficiently small.
+ %
+:- pred split_computed_goto(instruction, int, int, proc_label, int,
+ list(instruction), int, io__state, io__state).
+:- mode split_computed_goto(in, in, in, in, in, out, out, di, uo) is det.
+
+split_computed_goto(Instr0, MaxSize, Length, ProcLabel, N0, Instrs, N) -->
+ (
+ { Length =< MaxSize }
+ ->
+ { Instrs = [Instr0] },
+ { N = N0 }
+ ;
+ { Instr0 = computed_goto(Rval, Labels) - _Comment }
+ ->
+ { N1 is N0 + 1},
+ { N2 is N1 + 1},
+ { Mid = Length // 2 },
+
+ (
+ { list__split_list(Mid, Labels, Start0, End0) }
+ ->
+ { Start = Start0, End = End0 }
+ ;
+ { error("split_computed_goto: list__split_list") }
+ ),
+
+ { Index = binop((-), Rval, const(int_const(Mid))) },
+ { Test = binop((>=), Rval, const(int_const(Mid))) },
+ { ElseAddr = label(local(ProcLabel, N1)) },
+ { ElseLabel = label(local(ProcLabel, N1)) - ""},
+ { IfInstr = if_val(Test, ElseAddr ) - "Binary search"},
+
+ { ThenInstr = computed_goto(Rval, Start) - "Then section" },
+ { ElseInstr = computed_goto(Index, End) - "Else section" },
+
+ split_computed_goto(ThenInstr, MaxSize, Mid, ProcLabel, N2,
+ ThenInstrs, N3),
+ split_computed_goto(ElseInstr, MaxSize, Length - Mid,
+ ProcLabel, N3, ElseInstrs, N),
+
+ { list__append(ThenInstrs, [ElseLabel | ElseInstrs], InstrsA) },
+ { Instrs = [IfInstr | InstrsA] }
+ ;
+ { error("split_computed_goto") }
+ ).
+
+%-----------------------------------------------------------------------------%
+
+ %
+ % proc_label(Is, P)
+ %
+ % Find the proc_label, P, which is to be used for local labels
+ % in the list of instructions, Is.
+ % XXX Fergus, I am sure there is a better way to do this. Any
+ % suggestions?
+ %
+:- pred proc_label(list(instruction), proc_label).
+:- mode proc_label(in, out) is det.
+
+proc_label([], _) :- error("proc_label").
+proc_label([Instr - _Comment | Instrs], ProcLabel) :-
+ (
+ (
+ Instr = label(local(ProcLabel0, _))
+ ;
+ Instr = label(local(ProcLabel0))
+ ;
+ Instr = label(exported(ProcLabel0))
+ ;
+ Instr = label(c_local(ProcLabel0))
+ )
+ ->
+ ProcLabel = ProcLabel0
+ ;
+ proc_label(Instrs, ProcLabel)
+ ).
+
+%-----------------------------------------------------------------------------%
+
+ %
+ % max_label_int(Is, M0, M)
+ %
+ % Find the highest integer, M, used in local labels from the list of
+ % intructions, Is, where M0 is the highest integer found so far.
+ %
+:- pred max_label_int(list(instruction), int, int).
+:- mode max_label_int(in, in, out) is det.
+
+max_label_int([], N, N).
+max_label_int([Instr - _Comment | Instrs], N0, N) :-
+ (
+ Instr = label(local(_, Num)),
+ Num > N0
+ ->
+ max_label_int(Instrs, Num, N)
+ ;
+ max_label_int(Instrs, N0, N)
+ ).
+
+%-----------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
Index: library/benchmarking.m
===================================================================
RCS file: /home/staff/zs/imp/mercury/library/benchmarking.m,v
retrieving revision 1.16
diff -u -r1.16 benchmarking.m
--- 1.16 1998/08/12 02:58:14
+++ benchmarking.m 1998/10/20 02:31:30
@@ -451,13 +451,13 @@
if (complete) {
if (ML_overall_counter.cells_at_period_end < 1.0
|| ML_overall_counter.words_at_period_end < 1.0) {
- fprintf(stderr, ""no allocations to report\n"");
+ fprintf(stderr, ""no allocations to report\\n"");
return;
}
} else {
if (ML_overall_counter.cells_since_period_start < 1.0
|| ML_overall_counter.words_since_period_start < 1.0) {
- fprintf(stderr, ""no allocations to report\n"");
+ fprintf(stderr, ""no allocations to report\\n"");
return;
}
}
Index: library/io.m
===================================================================
RCS file: /home/staff/zs/imp/mercury/library/io.m,v
retrieving revision 1.165
diff -u -r1.165 io.m
--- 1.165 1998/10/16 06:18:28
+++ io.m 1998/10/23 04:28:26
@@ -3209,7 +3209,7 @@
len = strlen(Dir) + 1 + 5 + 3 + 1 + 3 + 1;
/* Dir + / + Prefix + counter_high + . + counter_low + \\0 */
- incr_hp_atomic(LVALUE_CAST(Word *, FileName),
+ incr_hp_atomic(LVALUE_CAST(Word, FileName),
(len + sizeof(Word)) / sizeof(Word));
if (ML_io_tempnam_counter == 0) {
ML_io_tempnam_counter = getpid();
Index: library/math.m
===================================================================
RCS file: /home/staff/zs/imp/mercury/library/math.m,v
retrieving revision 1.20
diff -u -r1.20 math.m
--- 1.20 1998/09/30 07:06:54
+++ math.m 1998/10/20 04:36:31
@@ -227,7 +227,7 @@
{
fflush(stdout);
fprintf(stderr,
- ""Software error: Domain error in call to `%s'\n"",
+ ""Software error: Domain error in call to `%s'\\n"",
where);
MR_trace_report(stderr);
MR_dump_stack(MR_succip, MR_sp, MR_curfr);
Index: library/private_builtin.m
===================================================================
RCS file: /home/staff/zs/imp/mercury/library/private_builtin.m,v
retrieving revision 1.9
diff -u -r1.9 private_builtin.m
--- 1.9 1998/09/21 06:30:22
+++ private_builtin.m 1998/10/20 04:46:12
@@ -895,14 +895,15 @@
#ifdef MR_TABLE_DEBUG
if (MR_tabledebug) {
- printf(""suspension saves consumer stack: %d non, %d det\n"",
+ printf(""suspension saves consumer stack: %d non, %d det\\n"",
non_stack_delta, det_stack_delta);
- printf(""non region from %p to %p, det region from %p to %p\n"",
+ printf(""non region from %p to %p, det region from ""
+ ""%p to %p\\n"",
(void *) non_stack_bottom,
(void *) MR_maxfr,
(void *) det_stack_bottom,
(void *) MR_sp);
- printf(""succip = %p, sp = %p, maxfr = %p, curfr = %p\n"",
+ printf(""succip = %p, sp = %p, maxfr = %p, curfr = %p\\n"",
(void *) MR_succip, (void *) MR_sp,
(void *) MR_maxfr, (void *) MR_curfr);
}
@@ -1098,15 +1099,16 @@
#ifdef MR_TABLE_DEBUG
if (MR_tabledebug) {
- printf(""resumption saves generator stack: %d non, %d det\n"",
+ printf(""resumption saves generator stack: %d non, %d det\\n"",
ML_RESUME_VAR->non_stack_block_size,
ML_RESUME_VAR->det_stack_block_size);
- printf(""non region from %p to %p, det region from %p to %p\n"",
+ printf(""non region from %p to %p, det region ""
+ ""from %p to %p\\n"",
(void *) ML_RESUME_VAR->table->non_stack_bottom,
(void *) MR_maxfr,
(void *) ML_RESUME_VAR->table->det_stack_bottom,
(void *) MR_sp);
- printf(""succip = %p, sp = %p, maxfr = %p, curfr = %p\n"",
+ printf(""succip = %p, sp = %p, maxfr = %p, curfr = %p\\n"",
(void *) MR_succip, (void *) MR_sp,
(void *) MR_maxfr, (void *) MR_curfr);
}
@@ -1163,10 +1165,12 @@
#ifdef MR_TABLE_DEBUG
if (MR_tabledebug) {
- printf(""resumption restores consumer stack: %d non, %d det\n"",
+ printf(""resumption restores consumer stack: ""
+ ""%d non, %d det\\n"",
ML_RESUME_VAR->suspend_node->non_stack_block_size,
ML_RESUME_VAR->suspend_node->det_stack_block_size);
- printf(""non region from %p to %p, det region from %p to %p\n"",
+ printf(""non region from %p to %p, det region ""
+ ""from %p to %p\\n"",
(void *) ML_RESUME_VAR->table->non_stack_bottom,
(void *) (ML_RESUME_VAR->table->non_stack_bottom
+ ML_RESUME_VAR->suspend_node->
@@ -1175,7 +1179,7 @@
(void *) (ML_RESUME_VAR->table->det_stack_bottom
+ ML_RESUME_VAR->suspend_node->
det_stack_block_size));
- printf(""succip = %p, sp = %p, maxfr = %p, curfr = %p\n"",
+ printf(""succip = %p, sp = %p, maxfr = %p, curfr = %p\\n"",
(void *) MR_succip, (void *) MR_sp,
(void *) MR_maxfr, (void *) MR_curfr);
}
@@ -1257,17 +1261,18 @@
#ifdef MR_TABLE_DEBUG
if (MR_tabledebug) {
printf(""resumption restores generator stack:""
- "" %d non, %d det\n"",
+ "" %d non, %d det\\n"",
ML_RESUME_VAR->non_stack_block_size,
ML_RESUME_VAR->det_stack_block_size);
- printf(""non region from %p to %p, det region from %p to %p\n"",
+ printf(""non region from %p to %p, det region ""
+ ""from %p to %p\\n"",
(void *) ML_RESUME_VAR->table->non_stack_bottom,
(void *) (ML_RESUME_VAR->table->non_stack_bottom +
ML_RESUME_VAR->non_stack_block_size),
(void *) ML_RESUME_VAR->table->det_stack_bottom,
(void *) (ML_RESUME_VAR->table->det_stack_bottom +
ML_RESUME_VAR->det_stack_block_size));
- printf(""succip = %p, sp = %p, maxfr = %p, curfr = %p\n"",
+ printf(""succip = %p, sp = %p, maxfr = %p, curfr = %p\\n"",
(void *) MR_succip, (void *) MR_sp,
(void *) MR_maxfr, (void *) MR_curfr);
}
Index: library/std_util.m
===================================================================
RCS file: /home/staff/zs/imp/mercury/library/std_util.m,v
retrieving revision 1.130
diff -u -r1.130 std_util.m
--- 1.130 1998/10/16 06:18:33
+++ std_util.m 1998/10/23 03:49:32
@@ -559,8 +559,8 @@
#ifndef USE_TYPE_LAYOUT
fatal_error(""builtin_aggregate/4 not supported with this grade ""
- ""on this system.\n""
- ""Try using a `.gc' (conservative gc) grade.\n"");
+ ""on this system.\\n""
+ ""Try using a `.gc' (conservative gc) grade.\\n"");
#endif
/*
@@ -956,9 +956,9 @@
;
UnivTypeName = type_name(univ_type(Univ)),
ObjectTypeName = type_name(type_of(X)),
- string__append_list(["det_univ_to_type: conversion failed\n",
+ string__append_list(["det_univ_to_type: conversion failed\\n",
"\tUniv Type: ", UnivTypeName,
- "\n\tObject Type: ", ObjectTypeName], ErrorString),
+ "\\n\tObject Type: ", ObjectTypeName], ErrorString),
error(ErrorString)
).
Index: trace/mercury_trace_internal.c
===================================================================
RCS file: /home/mercury1/repository/mercury/trace/mercury_trace_internal.c,v
retrieving revision 1.5
diff -u -r1.5 mercury_trace_internal.c
--- 1.5 1998/10/23 00:42:02
+++ mercury_trace_internal.c 1998/10/24 01:30:37
@@ -1393,7 +1393,7 @@
}
this_frame = MR_saved_sp(saved_regs);
- MR_saved_succip(saved_regs) = MR_based_stackvar(this_frame,
+ MR_saved_succip(saved_regs) = (Word *) MR_based_stackvar(this_frame,
MR_LIVE_LVAL_NUMBER(location));
MR_saved_sp(saved_regs) -= entry->MR_sle_stack_slots;
MR_trace_event_number = MR_event_num_stackvar(this_frame);
----
+----------------------------------------------------------------------+
| Peter Ross M Sci/Eng Melbourne Uni |
| petdr at cs.mu.oz.au WWW: www.cs.mu.oz.au/~petdr/ ph: +61 3 9344 9158 |
+----------------------------------------------------------------------+
More information about the developers
mailing list