[m-rev.] for review: work around bug 160

Zoltan Somogyi zs at csse.unimelb.edu.au
Thu Sep 9 18:11:43 AEST 2010


Work around Mantis bug 160. The bug arises because gcc mishandles this
code sequence:

	r1 = mkword(tag, base);
	r2 = tag(r1);

In this case, we know r2 == tag, but gcc screws up the optimization.

compiler/peephole.m:
	Add a peephole optimization pattern that replaces the second assignment
	above with r2 = tag. This should help avoid tickling the gcc bug.

compiler/options.m:
	Add a developer-only option, --no-optimize-peep-mkword, that disables
	the new pattern. The intention is that we can use this to check whether
	gcc has fixed the bug.

compiler/optimize.m:
	Get the value of the new option to peephole.m.

compiler/tag_switch.m:
	Fix some misleading comments that mmc generated for the bug test case
	file.

tests/hard_coded/bug160.{m,exp}:
	The test case for this bug.

tests/hard_coded/Mmakefile:
tests/hard_coded/Mercury.options:
	Enable the test case.

Zoltan.

cvs diff: Diffing .
cvs diff: Diffing analysis
cvs diff: Diffing bindist
cvs diff: Diffing boehm_gc
cvs diff: Diffing boehm_gc/Mac_files
cvs diff: Diffing boehm_gc/cord
cvs diff: Diffing boehm_gc/cord/private
cvs diff: Diffing boehm_gc/doc
cvs diff: Diffing boehm_gc/extra
cvs diff: Diffing boehm_gc/include
cvs diff: Diffing boehm_gc/include/extra
cvs diff: Diffing boehm_gc/include/private
cvs diff: Diffing boehm_gc/libatomic_ops
cvs diff: Diffing boehm_gc/libatomic_ops/doc
cvs diff: Diffing boehm_gc/libatomic_ops/src
cvs diff: Diffing boehm_gc/libatomic_ops/src/atomic_ops
cvs diff: Diffing boehm_gc/libatomic_ops/src/atomic_ops/sysdeps
cvs diff: Diffing boehm_gc/libatomic_ops/src/atomic_ops/sysdeps/armcc
cvs diff: Diffing boehm_gc/libatomic_ops/src/atomic_ops/sysdeps/gcc
cvs diff: Diffing boehm_gc/libatomic_ops/src/atomic_ops/sysdeps/hpc
cvs diff: Diffing boehm_gc/libatomic_ops/src/atomic_ops/sysdeps/ibmc
cvs diff: Diffing boehm_gc/libatomic_ops/src/atomic_ops/sysdeps/icc
cvs diff: Diffing boehm_gc/libatomic_ops/src/atomic_ops/sysdeps/msftc
cvs diff: Diffing boehm_gc/libatomic_ops/src/atomic_ops/sysdeps/sunc
cvs diff: Diffing boehm_gc/libatomic_ops/tests
cvs diff: Diffing boehm_gc/libatomic_ops-1.2
cvs diff: Diffing boehm_gc/libatomic_ops-1.2/doc
cvs diff: Diffing boehm_gc/libatomic_ops-1.2/src
cvs diff: Diffing boehm_gc/libatomic_ops-1.2/src/atomic_ops
cvs diff: Diffing boehm_gc/libatomic_ops-1.2/src/atomic_ops/sysdeps
cvs diff: Diffing boehm_gc/libatomic_ops-1.2/tests
cvs diff: Diffing boehm_gc/m4
cvs diff: Diffing boehm_gc/tests
cvs diff: Diffing browser
cvs diff: Diffing bytecode
cvs diff: Diffing compiler
Index: compiler/optimize.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/optimize.m,v
retrieving revision 1.69
diff -u -b -r1.69 optimize.m
--- compiler/optimize.m	5 Aug 2010 03:07:09 -0000	1.69
+++ compiler/optimize.m	8 Sep 2010 07:38:41 -0000
@@ -415,7 +415,8 @@
             VeryVerbose = no
         ),
         GC_Method = Info ^ lopt_gc_method,
-        peephole_optimize(GC_Method, !Instrs, Mod2),
+        OptPeepMkword = Info ^ lopt_opt_peep_mkword,
+        peephole_optimize(GC_Method, OptPeepMkword, !Instrs, Mod2),
         maybe_opt_debug(Info, !.Instrs, !.C, "peep", "after peephole",
             ProcLabel, !OptDebugInfo)
     ;
@@ -570,7 +571,8 @@
                 VeryVerbose = no
             ),
             GC_Method = Info ^ lopt_gc_method,
-            peephole_optimize(GC_Method, !Instrs, _Mod),
+            OptPeepMkword = Info ^ lopt_opt_peep_mkword,
+            peephole_optimize(GC_Method, OptPeepMkword, !Instrs, _Mod),
             maybe_opt_debug(Info, !.Instrs, !.C, "peep", "after peephole",
                 ProcLabel, !OptDebugInfo)
         ;
@@ -765,6 +767,7 @@
                 lopt_opt_fulljumps                  :: bool,
                 lopt_opt_labels                     :: bool,
                 lopt_opt_peep                       :: bool,
+                lopt_opt_peep_mkword                :: bool,
                 lopt_opt_reassign                   :: bool,
                 lopt_pes_tailcalls                  :: bool,
                 lopt_std_labels                     :: bool,
@@ -799,6 +802,7 @@
     globals.lookup_bool_option(Globals, optimize_fulljumps, OptFullJumps),
     globals.lookup_bool_option(Globals, optimize_labels, OptLabels),
     globals.lookup_bool_option(Globals, optimize_peep, OptPeep),
+    globals.lookup_bool_option(Globals, optimize_peep_mkword, OptPeepMkword),
     globals.lookup_bool_option(Globals, optimize_reassign, OptReassign),
     globals.lookup_bool_option(Globals, pessimize_tailcalls,
         PessimizeTailCalls),
@@ -817,7 +821,7 @@
     Info = llds_opt_info(AutoComments, DetailedStatistics, VeryVerbose,
         CheckedNondetTailCalls, NumRealRRegs, GCMethod,
         OptDelaySlots, OptDups, OptFrames, FrameOptComments,
-        OptJumps, OptFullJumps, OptLabels, OptPeep, OptReassign,
+        OptJumps, OptFullJumps, OptLabels, OptPeep, OptPeepMkword, OptReassign,
         PessimizeTailCalls, StdLabels, UseLocalVars, LocalVarAccessThreshold,
         OptRepeat, DebugOpt, DebugOptPredIdStrs, DebugOptPredNames).
 
Index: compiler/options.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/options.m,v
retrieving revision 1.673
diff -u -b -r1.673 options.m
--- compiler/options.m	14 Jul 2010 16:26:03 -0000	1.673
+++ compiler/options.m	8 Sep 2010 07:23:49 -0000
@@ -745,6 +745,7 @@
     ;       common_layout_data
     ;       optimize            % Also used for MLDS->MLDS optimizations.
     ;       optimize_peep
+    ;       optimize_peep_mkword
     ;       optimize_jumps
     ;       optimize_fulljumps
     ;       pessimize_tailcalls
@@ -1577,6 +1578,7 @@
     common_layout_data                  -   bool(yes),
     optimize                            -   bool(no),
     optimize_peep                       -   bool(no),
+    optimize_peep_mkword                -   bool(no),
     optimize_jumps                      -   bool(no),
     optimize_fulljumps                  -   bool(no),
     pessimize_tailcalls                 -   bool(no),
@@ -2474,6 +2476,8 @@
 long_option("llds-optimise",        optimize).
 long_option("optimize-peep",        optimize_peep).
 long_option("optimise-peep",        optimize_peep).
+long_option("optimize-peep-mkword", optimize_peep_mkword).
+long_option("optimise-peep-mkword", optimize_peep_mkword).
 long_option("optimize-jumps",       optimize_jumps).
 long_option("optimise-jumps",       optimize_jumps).
 long_option("optimize-fulljumps",   optimize_fulljumps).
@@ -3041,6 +3045,7 @@
     optimize                    -   bool(yes),
     optimize_repeat             -   int(1),
     optimize_peep               -   bool(yes),
+    optimize_peep_mkword        -   bool(yes),
     static_ground_cells         -   bool(yes),
     smart_indexing              -   bool(yes),
     optimize_jumps              -   bool(yes),
@@ -5034,6 +5039,9 @@
         "\tEnable dead predicate elimination.",
         "--no-optimize-peep",
         "\tDisable local peephole optimizations.",
+% This is useful for developers only, to test whether a gcc bug has been fixed.
+%       "--no-optimize-peep-mkword",
+%       "\tDisable peephole optimizations of words created by mkword.",
         "--no-optimize-jumps",
         "\tDisable elimination of jumps to jumps.",
         "--no-optimize-fulljumps",
Index: compiler/peephole.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/peephole.m,v
retrieving revision 1.102
diff -u -b -r1.102 peephole.m
--- compiler/peephole.m	11 Feb 2010 04:36:09 -0000	1.102
+++ compiler/peephole.m	9 Sep 2010 08:04:23 -0000
@@ -24,7 +24,7 @@
 
     % Peephole optimize a list of instructions.
     %
-:- pred peephole_optimize(gc_method::in, list(instruction)::in,
+:- pred peephole_optimize(gc_method::in, bool::in, list(instruction)::in,
     list(instruction)::out, bool::out) is det.
 
 :- pred combine_decr_sp(list(instruction)::in, list(instruction)::out) is det.
@@ -35,6 +35,7 @@
 :- implementation.
 
 :- import_module backend_libs.builtin_ops.
+:- import_module libs.compiler_util.
 :- import_module ll_backend.opt_util.
 
 :- import_module int.
@@ -48,7 +49,8 @@
     % Patterns that can be switched off.
     %
 :- type pattern
-    --->    incr_sp.
+    --->    pattern_incr_sp
+    ;       pattern_mkword.
 
     % We zip down to the end of the instruction list, and start attempting
     % to optimize instruction sequences. As long as we can continue
@@ -56,8 +58,8 @@
     % when we find a sequence we can't optimize, we back up and try
     % to optimize the sequence starting with the previous instruction.
     %
-peephole_optimize(GC_Method, Instrs0, Instrs, Mod) :-
-    invalid_peephole_opts(GC_Method, InvalidPatterns),
+peephole_optimize(GC_Method, OptPeepMkword, Instrs0, Instrs, Mod) :-
+    invalid_peephole_opts(GC_Method, OptPeepMkword, InvalidPatterns),
     peephole_optimize_2(InvalidPatterns, Instrs0, Instrs, Mod).
 
 :- pred peephole_optimize_2(list(pattern)::in, list(instruction)::in,
@@ -80,10 +82,8 @@
     list(pattern)::in, list(instruction)::out, bool::out) is det.
 
 peephole_opt_instr(Instr0, Instrs0, InvalidPatterns, Instrs, Mod) :-
-    (
         opt_util.skip_comments(Instrs0, Instrs1),
-        peephole_match(Instr0, Instrs1, InvalidPatterns, Instrs2)
-    ->
+    ( peephole_match(Instr0, Instrs1, InvalidPatterns, Instrs2) ->
         (
             Instrs2 = [Instr2 | Instrs3],
             peephole_opt_instr(Instr2, Instrs3, InvalidPatterns, Instrs, _)
@@ -92,6 +92,9 @@
             Instrs = Instrs2
         ),
         Mod = yes
+    ; peephole_match_norepeat(Instr0, Instrs1, InvalidPatterns, Instrs2) ->
+        Instrs = Instrs2,
+        Mod = yes
     ;
         Instrs = [Instr0 | Instrs0],
         Mod = no
@@ -138,7 +141,14 @@
         fail
     ).
 
+%-----------------------------------------------------------------------------%
+
     % Look for code patterns that can be optimized, and optimize them.
+    % Unlike peephole_match_norepeat, this predicate guarantees that the
+    % instruction sequence it returns on success won't be transformable
+    % by the same transformation as it applies. This allows peephole_opt_instr
+    % to call peephole_match repeatedly until it fails without the possibility
+    % of an infinite loop.
     %
 :- pred peephole_match(instruction::in, list(instruction)::in,
     list(pattern)::in, list(instruction)::out) is semidet.
@@ -427,7 +437,7 @@
 peephole_match(Instr0, Instrs0, InvalidPatterns, Instrs) :-
     Instr0 = llds_instr(Uinstr0, _Comment0),
     Uinstr0 = incr_sp(N, _, _),
-    \+ list.member(incr_sp, InvalidPatterns),
+    \+ list.member(pattern_incr_sp, InvalidPatterns),
     ( opt_util.no_stackvars_til_decr_sp(Instrs0, N, Between, Remain) ->
         Instrs = Between ++ Remain
     ;
@@ -436,14 +446,236 @@
 
 %-----------------------------------------------------------------------------%
 
+    % Look for code patterns that can be optimized, and optimize them.
+    % See the comment at the top of peephole_match for the difference
+    % between the two predicates.
+    %
+:- pred peephole_match_norepeat(instruction::in, list(instruction)::in,
+    list(pattern)::in, list(instruction)::out) is semidet.
+
+    % If none of the instructions in brackets can affect Lval, then
+    % we can transform references to tag(Lval) to Tag and body(Lval, Tag)
+    % to Base.
+    %
+    %   Lval = mkword(Tag, Base)        Lval = mkword(Tag, Base)
+    %   <...>                       =>  <...>
+    %   ... tag(Lval) ...               ... Tag ...
+    %   ... body(Lval, Tag) ...         ... Base ...
+    %
+peephole_match_norepeat(Instr0, Instrs0, InvalidPatterns, Instrs) :-
+    Instr0 = llds_instr(Uinstr0, _),
+    Uinstr0 = assign(Lval, mkword(Tag, Base)),
+    \+ list.member(pattern_mkword, InvalidPatterns),
+    replace_tagged_ptr_components_in_instrs(Lval, Tag, Base, Instrs0, Instrs1),
+    Instrs = [Instr0 | Instrs1].
+
+%-----------------------------------------------------------------------------%
+
+:- pred replace_tagged_ptr_components_in_instrs(lval::in, tag::in, rval::in,
+    list(instruction)::in, list(instruction)::out) is det.
+
+replace_tagged_ptr_components_in_instrs(_, _, _, [], []).
+replace_tagged_ptr_components_in_instrs(Lval, Tag, Base, Instrs0, Instrs) :-
+    Instrs0 = [HeadInstr0 | TailInstrs0],
+    replace_tagged_ptr_components_in_instr(Lval, Tag, Base,
+        HeadInstr0, MaybeHeadInstr),
+    (
+        MaybeHeadInstr = no,
+        Instrs = Instrs0
+    ;
+        MaybeHeadInstr = yes(HeadInstr),
+        replace_tagged_ptr_components_in_instrs(Lval, Tag, Base,
+            TailInstrs0, TailInstrs),
+        Instrs = [HeadInstr | TailInstrs]
+    ).
+
+:- pred replace_tagged_ptr_components_in_instr(lval::in, tag::in, rval::in,
+    instruction::in, maybe(instruction)::out) is det.
+
+replace_tagged_ptr_components_in_instr(OldLval, OldTag, OldBase,
+        Instr0, MaybeInstr) :-
+    Instr0 = llds_instr(Uinstr0, Comment),
+    (
+        Uinstr0 = assign(Lval, Rval0),
+        ( Lval = OldLval ->
+            MaybeInstr = no
+        ; Lval = mem_ref(_) ->
+            MaybeInstr = no
+        ;
+            replace_tagged_ptr_components_in_rval(OldLval, OldTag, OldBase,
+                Rval0, Rval),
+            Uinstr = assign(Lval, Rval),
+            Instr = llds_instr(Uinstr, Comment),
+            MaybeInstr = yes(Instr)
+        )
+    ;
+        Uinstr0 = keep_assign(Lval, Rval0),
+        ( Lval = OldLval ->
+            MaybeInstr = no
+        ; Lval = mem_ref(_) ->
+            MaybeInstr = no
+        ;
+            replace_tagged_ptr_components_in_rval(OldLval, OldTag, OldBase,
+                Rval0, Rval),
+            Uinstr = keep_assign(Lval, Rval),
+            Instr = llds_instr(Uinstr, Comment),
+            MaybeInstr = yes(Instr)
+        )
+    ;
+        Uinstr0 = computed_goto(Rval0, Targets),
+        replace_tagged_ptr_components_in_rval(OldLval, OldTag, OldBase,
+            Rval0, Rval),
+        Uinstr = computed_goto(Rval, Targets),
+        Instr = llds_instr(Uinstr, Comment),
+        MaybeInstr = yes(Instr)
+    ;
+        Uinstr0 = if_val(Rval0, Target),
+        replace_tagged_ptr_components_in_rval(OldLval, OldTag, OldBase,
+            Rval0, Rval),
+        Uinstr = if_val(Rval, Target),
+        Instr = llds_instr(Uinstr, Comment),
+        MaybeInstr = yes(Instr)
+    ;
+        Uinstr0 = incr_hp(Target, MaybeTag, MaybeOffset, SizeRval0,
+            TypeMsg, MayUseAtomicAlloc, MaybeRegionId, MaybeReuse),
+        ( Target = OldLval ->
+            MaybeInstr = no
+        ;
+            replace_tagged_ptr_components_in_rval(OldLval, OldTag, OldBase,
+                SizeRval0, SizeRval),
+            Uinstr = incr_hp(Target, MaybeTag, MaybeOffset, SizeRval,
+                TypeMsg, MayUseAtomicAlloc, MaybeRegionId, MaybeReuse),
+            Instr = llds_instr(Uinstr, Comment),
+            MaybeInstr = yes(Instr)
+        )
+    ;
+        Uinstr0 = restore_hp(Rval0),
+        replace_tagged_ptr_components_in_rval(OldLval, OldTag, OldBase,
+            Rval0, Rval),
+        Uinstr = restore_hp(Rval),
+        Instr = llds_instr(Uinstr, Comment),
+        MaybeInstr = yes(Instr)
+    ;
+        Uinstr0 = free_heap(Rval0),
+        replace_tagged_ptr_components_in_rval(OldLval, OldTag, OldBase,
+            Rval0, Rval),
+        Uinstr = free_heap(Rval),
+        Instr = llds_instr(Uinstr, Comment),
+        MaybeInstr = yes(Instr)
+    ;
+        Uinstr0 = reset_ticket(Rval0, Reason),
+        replace_tagged_ptr_components_in_rval(OldLval, OldTag, OldBase,
+            Rval0, Rval),
+        Uinstr = reset_ticket(Rval, Reason),
+        Instr = llds_instr(Uinstr, Comment),
+        MaybeInstr = yes(Instr)
+    ;
+        Uinstr0 = prune_tickets_to(Rval0),
+        replace_tagged_ptr_components_in_rval(OldLval, OldTag, OldBase,
+            Rval0, Rval),
+        Uinstr = prune_tickets_to(Rval),
+        Instr = llds_instr(Uinstr, Comment),
+        MaybeInstr = yes(Instr)
+    ;
+        ( Uinstr0 = save_maxfr(Lval0)
+        ; Uinstr0 = mark_hp(Lval0)
+        ; Uinstr0 = store_ticket(Lval0)
+        ; Uinstr0 = mark_ticket_stack(Lval0)
+        ),
+        ( Lval0 = OldLval ->
+            MaybeInstr = no
+        ;
+            MaybeInstr = yes(Instr0)
+        )
+    ;
+        ( Uinstr0 = comment(_)
+        ; Uinstr0 = livevals(_)
+        ; Uinstr0 = restore_maxfr(_)
+        ; Uinstr0 = prune_ticket
+        ; Uinstr0 = discard_ticket
+        ),
+        Uinstr = Uinstr0,
+        Instr = llds_instr(Uinstr, Comment),
+        MaybeInstr = yes(Instr)
+    ;
+        ( Uinstr0 = block(_, _, _)
+        ; Uinstr0 = llcall(_, _, _, _, _, _)
+        ; Uinstr0 = mkframe(_, _)
+        ; Uinstr0 = label(_)
+        ; Uinstr0 = goto(_)
+        ; Uinstr0 = arbitrary_c_code(_, _, _)
+        ; Uinstr0 = foreign_proc_code(_, _, _, _, _, _, _, _, _, _)
+        ; Uinstr0 = push_region_frame(_, _)
+        ; Uinstr0 = region_fill_frame(_, _, _, _, _)
+        ; Uinstr0 = region_set_fixed_slot(_, _, _)
+        ; Uinstr0 = use_and_maybe_pop_region_frame(_, _)
+        ; Uinstr0 = incr_sp(_, _, _)
+        ; Uinstr0 = decr_sp(_)
+        ; Uinstr0 = decr_sp_and_return(_)
+        ; Uinstr0 = init_sync_term(_, _)
+        ; Uinstr0 = fork_new_child(_, _)
+        ; Uinstr0 = join_and_continue(_, _)
+        ),
+        MaybeInstr = no
+    ).
+
+:- pred replace_tagged_ptr_components_in_rval(lval::in, tag::in, rval::in,
+    rval::in, rval::out) is det.
+
+replace_tagged_ptr_components_in_rval(OldLval, OldTag, OldBase, Rval0, Rval) :-
+    (
+        Rval0 = unop(UnOp, RvalA0),
+        (
+            UnOp = tag,
+            RvalA0 = lval(OldLval)
+        ->
+            Rval = unop(mktag, const(llconst_int(OldTag)))
+        ;
+            replace_tagged_ptr_components_in_rval(OldLval, OldTag, OldBase,
+                RvalA0, RvalA),
+            Rval = unop(UnOp, RvalA)
+        )
+    ;
+        Rval0 = binop(BinOp, RvalA0, RvalB0),
+        (
+            BinOp = body,
+            RvalA0 = lval(OldLval),
+            RvalB0 = unop(mktag, const(llconst_int(OldTag))),
+            OldBase = const(_)
+        ->
+            Rval = OldBase
+        ;
+            replace_tagged_ptr_components_in_rval(OldLval, OldTag, OldBase,
+                RvalA0, RvalA),
+            replace_tagged_ptr_components_in_rval(OldLval, OldTag, OldBase,
+                RvalB0, RvalB),
+            Rval = binop(BinOp, RvalA, RvalB)
+        )
+    ;
+        Rval0 = mkword(Tag, BaseRval0),
+        replace_tagged_ptr_components_in_rval(OldLval, OldTag, OldBase,
+            BaseRval0, BaseRval),
+        Rval = mkword(Tag, BaseRval)
+    ;
+        ( Rval0 = lval(_)
+        ; Rval0 = var(_)
+        ; Rval0 = const(_)
+        ; Rval0 = mem_addr(_)
+        ),
+        Rval = Rval0
+    ).
+
+%-----------------------------------------------------------------------------%
+
     % Given a GC method, return the list of invalid peephole optimizations.
     %
-:- pred invalid_peephole_opts(gc_method::in, list(pattern)::out) is det.
+:- pred invalid_peephole_opts(gc_method::in, bool::in, list(pattern)::out)
+    is det.
 
-invalid_peephole_opts(GC_Method, InvalidPatterns) :-
+invalid_peephole_opts(GC_Method, OptPeepMkword, InvalidPatterns) :-
     (
         GC_Method = gc_accurate,
-        InvalidPatterns = [incr_sp]
+        InvalidPatterns0 = [pattern_incr_sp]
     ;
         ( GC_Method = gc_automatic
         ; GC_Method = gc_none
@@ -452,7 +684,14 @@
         ; GC_Method = gc_mps
         ; GC_Method = gc_hgc
         ),
-        InvalidPatterns = []
+        InvalidPatterns0 = []
+    ),
+    (
+        OptPeepMkword = yes,
+        InvalidPatterns = InvalidPatterns0
+    ;
+        OptPeepMkword = no,
+        InvalidPatterns = [pattern_mkword | InvalidPatterns0]
     ).
 
 %-----------------------------------------------------------------------------%
@@ -476,5 +715,11 @@
     ).
 
 %-----------------------------------------------------------------------------%
+
+:- func this_file = string.
+
+this_file = "peephole.m".
+
+%-----------------------------------------------------------------------------%
 :- end_module peephole.
 %-----------------------------------------------------------------------------%
Index: compiler/tag_switch.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/tag_switch.m,v
retrieving revision 1.83
diff -u -b -r1.83 tag_switch.m
--- compiler/tag_switch.m	25 Aug 2009 23:46:50 -0000	1.83
+++ compiler/tag_switch.m	8 Sep 2010 02:21:57 -0000
@@ -839,7 +839,7 @@
         llds_instr(
             if_val(binop(ne, StagRval, const(llconst_int(Secondary))),
                 code_label(ElseLabel)),
-            "test remote sec tag only")
+            "test sec tag only")
     ),
     ElseLabelCode = singleton(
         llds_instr(label(ElseLabel), "handle next secondary tag")
@@ -894,7 +894,7 @@
         llds_instr(
             if_val(binop(eq, StagRval, const(llconst_int(Secondary))),
                 code_label(CaseLabel)),
-            "test remote sec tag only for " ++ Comment)
+            "test sec tag only for " ++ Comment)
     ),
     PrevTestsCode = PrevTestsCode0 ++ TestCode.
 
cvs diff: Diffing compiler/notes
cvs diff: Diffing deep_profiler
cvs diff: Diffing deep_profiler/notes
cvs diff: Diffing doc
cvs diff: Diffing extras
cvs diff: Diffing extras/base64
cvs diff: Diffing extras/cgi
cvs diff: Diffing extras/complex_numbers
cvs diff: Diffing extras/complex_numbers/samples
cvs diff: Diffing extras/complex_numbers/tests
cvs diff: Diffing extras/concurrency
cvs diff: Diffing extras/curs
cvs diff: Diffing extras/curs/samples
cvs diff: Diffing extras/curses
cvs diff: Diffing extras/curses/sample
cvs diff: Diffing extras/dynamic_linking
cvs diff: Diffing extras/error
cvs diff: Diffing extras/fixed
cvs diff: Diffing extras/gator
cvs diff: Diffing extras/gator/generations
cvs diff: Diffing extras/gator/generations/1
cvs diff: Diffing extras/graphics
cvs diff: Diffing extras/graphics/easyx
cvs diff: Diffing extras/graphics/easyx/samples
cvs diff: Diffing extras/graphics/mercury_allegro
cvs diff: Diffing extras/graphics/mercury_allegro/examples
cvs diff: Diffing extras/graphics/mercury_allegro/samples
cvs diff: Diffing extras/graphics/mercury_allegro/samples/demo
cvs diff: Diffing extras/graphics/mercury_allegro/samples/mandel
cvs diff: Diffing extras/graphics/mercury_allegro/samples/pendulum2
cvs diff: Diffing extras/graphics/mercury_allegro/samples/speed
cvs diff: Diffing extras/graphics/mercury_cairo
cvs diff: Diffing extras/graphics/mercury_cairo/samples
cvs diff: Diffing extras/graphics/mercury_cairo/samples/data
cvs diff: Diffing extras/graphics/mercury_cairo/tutorial
cvs diff: Diffing extras/graphics/mercury_glut
cvs diff: Diffing extras/graphics/mercury_opengl
cvs diff: Diffing extras/graphics/mercury_tcltk
cvs diff: Diffing extras/graphics/samples
cvs diff: Diffing extras/graphics/samples/calc
cvs diff: Diffing extras/graphics/samples/gears
cvs diff: Diffing extras/graphics/samples/maze
cvs diff: Diffing extras/graphics/samples/pent
cvs diff: Diffing extras/lazy_evaluation
cvs diff: Diffing extras/lex
cvs diff: Diffing extras/lex/samples
cvs diff: Diffing extras/lex/tests
cvs diff: Diffing extras/log4m
cvs diff: Diffing extras/logged_output
cvs diff: Diffing extras/monte
cvs diff: Diffing extras/moose
cvs diff: Diffing extras/moose/samples
cvs diff: Diffing extras/moose/tests
cvs diff: Diffing extras/mopenssl
cvs diff: Diffing extras/morphine
cvs diff: Diffing extras/morphine/non-regression-tests
cvs diff: Diffing extras/morphine/scripts
cvs diff: Diffing extras/morphine/source
cvs diff: Diffing extras/net
cvs diff: Diffing extras/odbc
cvs diff: Diffing extras/posix
cvs diff: Diffing extras/posix/samples
cvs diff: Diffing extras/quickcheck
cvs diff: Diffing extras/quickcheck/tutes
cvs diff: Diffing extras/references
cvs diff: Diffing extras/references/samples
cvs diff: Diffing extras/references/tests
cvs diff: Diffing extras/solver_types
cvs diff: Diffing extras/solver_types/library
cvs diff: Diffing extras/trailed_update
cvs diff: Diffing extras/trailed_update/samples
cvs diff: Diffing extras/trailed_update/tests
cvs diff: Diffing extras/windows_installer_generator
cvs diff: Diffing extras/windows_installer_generator/sample
cvs diff: Diffing extras/windows_installer_generator/sample/images
cvs diff: Diffing extras/xml
cvs diff: Diffing extras/xml/samples
cvs diff: Diffing extras/xml_stylesheets
cvs diff: Diffing java
cvs diff: Diffing java/runtime
cvs diff: Diffing library
cvs diff: Diffing mdbcomp
cvs diff: Diffing profiler
cvs diff: Diffing robdd
cvs diff: Diffing runtime
cvs diff: Diffing runtime/GETOPT
cvs diff: Diffing runtime/machdeps
cvs diff: Diffing samples
cvs diff: Diffing samples/c_interface
cvs diff: Diffing samples/c_interface/c_calls_mercury
cvs diff: Diffing samples/c_interface/cplusplus_calls_mercury
cvs diff: Diffing samples/c_interface/mercury_calls_c
cvs diff: Diffing samples/c_interface/mercury_calls_cplusplus
cvs diff: Diffing samples/c_interface/mercury_calls_fortran
cvs diff: Diffing samples/c_interface/simpler_c_calls_mercury
cvs diff: Diffing samples/c_interface/simpler_cplusplus_calls_mercury
cvs diff: Diffing samples/c_interface/standalone_c
cvs diff: Diffing samples/diff
cvs diff: Diffing samples/java_interface
cvs diff: Diffing samples/java_interface/java_calls_mercury
cvs diff: Diffing samples/java_interface/mercury_calls_java
cvs diff: Diffing samples/muz
cvs diff: Diffing samples/rot13
cvs diff: Diffing samples/solutions
cvs diff: Diffing samples/solver_types
cvs diff: Diffing samples/tests
cvs diff: Diffing samples/tests/c_interface
cvs diff: Diffing samples/tests/c_interface/c_calls_mercury
cvs diff: Diffing samples/tests/c_interface/cplusplus_calls_mercury
cvs diff: Diffing samples/tests/c_interface/mercury_calls_c
cvs diff: Diffing samples/tests/c_interface/mercury_calls_cplusplus
cvs diff: Diffing samples/tests/c_interface/mercury_calls_fortran
cvs diff: Diffing samples/tests/c_interface/simpler_c_calls_mercury
cvs diff: Diffing samples/tests/c_interface/simpler_cplusplus_calls_mercury
cvs diff: Diffing samples/tests/diff
cvs diff: Diffing samples/tests/muz
cvs diff: Diffing samples/tests/rot13
cvs diff: Diffing samples/tests/solutions
cvs diff: Diffing samples/tests/toplevel
cvs diff: Diffing scripts
cvs diff: Diffing slice
cvs diff: Diffing ssdb
cvs diff: Diffing tests
cvs diff: Diffing tests/analysis
cvs diff: Diffing tests/analysis/ctgc
cvs diff: Diffing tests/analysis/excp
cvs diff: Diffing tests/analysis/ext
cvs diff: Diffing tests/analysis/sharing
cvs diff: Diffing tests/analysis/table
cvs diff: Diffing tests/analysis/trail
cvs diff: Diffing tests/analysis/unused_args
cvs diff: Diffing tests/benchmarks
cvs diff: Diffing tests/debugger
cvs diff: Diffing tests/debugger/declarative
cvs diff: Diffing tests/dppd
cvs diff: Diffing tests/general
cvs diff: Diffing tests/general/accumulator
cvs diff: Diffing tests/general/string_format
cvs diff: Diffing tests/general/structure_reuse
cvs diff: Diffing tests/grade_subdirs
cvs diff: Diffing tests/hard_coded
Index: tests/hard_coded/Mercury.options
===================================================================
RCS file: /home/mercury/mercury1/repository/tests/hard_coded/Mercury.options,v
retrieving revision 1.45
diff -u -b -r1.45 Mercury.options
--- tests/hard_coded/Mercury.options	21 Apr 2010 04:50:28 -0000	1.45
+++ tests/hard_coded/Mercury.options	9 Sep 2010 03:56:58 -0000
@@ -8,6 +8,7 @@
 MCFLAGS-big_array_from_list =   --optimize-tailcalls
 MCFLAGS-bigtest =		--intermodule-optimization -O3
 MCFLAGS-boyer =			--infer-all
+MCFLAGS-bug160 =		-w --optimize-peep-mkword
 MCFLAGS-checked_nondet_tailcall	= --checked-nondet-tailcalls
 MCFLAGS-checked_nondet_tailcall_noinline = --checked-nondet-tailcalls --no-inlining
 MCFLAGS-cc_and_non_cc_test = 	--no-inlining
Index: tests/hard_coded/Mmakefile
===================================================================
RCS file: /home/mercury/mercury1/repository/tests/hard_coded/Mmakefile,v
retrieving revision 1.389
diff -u -b -r1.389 Mmakefile
--- tests/hard_coded/Mmakefile	19 Aug 2010 06:33:42 -0000	1.389
+++ tests/hard_coded/Mmakefile	9 Sep 2010 03:58:29 -0000
@@ -15,6 +15,7 @@
 	bidirectional \
 	boyer \
 	brace \
+	bug160 \
 	builtin_inst_rename \
 	c_write_string \
 	calendar_test \
Index: tests/hard_coded/bug160.exp
===================================================================
RCS file: tests/hard_coded/bug160.exp
diff -N tests/hard_coded/bug160.exp
--- /dev/null	1 Jan 1970 00:00:00 -0000
+++ tests/hard_coded/bug160.exp	9 Sep 2010 03:57:09 -0000
@@ -0,0 +1 @@
+RESULT: OK
Index: tests/hard_coded/bug160.m
===================================================================
RCS file: tests/hard_coded/bug160.m
diff -N tests/hard_coded/bug160.m
--- /dev/null	1 Jan 1970 00:00:00 -0000
+++ tests/hard_coded/bug160.m	9 Sep 2010 03:56:27 -0000
@@ -0,0 +1,82 @@
+% vim: ts=4 sw=4 et
+%
+% This is regression test for bug 160 in the Mantis database.
+%
+% The bug it tests for is in gcc. Compiling this source file in grade
+% asm_fast.gc with the option --no-optimize-peep-mkword yields a .c file
+% that gcc 4.4.1 generates incorrect code for at the default optimization level
+% unless you give it the option --fno-tree-loop-im.
+%
+% Mercury.options specifies --optimize-peep-mkword for this program, so
+% we should pass this test case even on systems with buggy gcc installations.
+
+:- module bug160.
+:- interface.
+:- import_module io.
+
+:- pred main(io::di, io::uo) is det.
+
+:- implementation.
+:- import_module list, require.
+
+main(!IO) :-
+    bug(R),
+    io.write_string(R, !IO),
+    io.nl(!IO).
+
+:- type t1
+    --->    a
+    ;       b.
+
+:- type t2
+    --->    c(t3)
+    ;       d
+    ;       e.
+
+:- type t3
+    --->    f(t1, t1).
+
+:- pred bug(string::out) is det.
+
+bug(R) :-
+    ( p ->
+        R = "RESULT: BAD A"
+    ; 
+        ( q(R0) ->
+            R1 = R0
+        ;
+            R1 = c(f(a, a))
+        ),
+        % Enabling the following causes R1 to be bound to the correct value.
+        % trace [io(!IO)] io.print(R1, !IO),
+        (
+            R1 = c(_),
+            R = "RESULT: OK"
+        ;
+            R1 = d,
+            R = "RESULT: BAD D"
+        ;
+            R1 = e,
+            R = "RESULT: BAD E"
+        )
+    ).
+
+:- pred p is semidet.
+
+p :-
+    ( 1 = 2 ->
+        true
+    ;
+        fail
+    ).
+
+:- pred q(t2::out) is semidet.
+
+q(Out) :-
+    ( 1 = 2 ->
+        Out = d
+    ;
+        fail
+    ).
+
+:- end_module bug160.
cvs diff: Diffing tests/hard_coded/exceptions
cvs diff: Diffing tests/hard_coded/purity
cvs diff: Diffing tests/hard_coded/sub-modules
cvs diff: Diffing tests/hard_coded/typeclasses
cvs diff: Diffing tests/invalid
cvs diff: Diffing tests/invalid/purity
cvs diff: Diffing tests/misc_tests
cvs diff: Diffing tests/mmc_make
cvs diff: Diffing tests/mmc_make/lib
cvs diff: Diffing tests/par_conj
cvs diff: Diffing tests/recompilation
cvs diff: Diffing tests/stm
cvs diff: Diffing tests/stm/orig
cvs diff: Diffing tests/stm/orig/stm-compiler
cvs diff: Diffing tests/stm/orig/stm-compiler/test1
cvs diff: Diffing tests/stm/orig/stm-compiler/test10
cvs diff: Diffing tests/stm/orig/stm-compiler/test2
cvs diff: Diffing tests/stm/orig/stm-compiler/test3
cvs diff: Diffing tests/stm/orig/stm-compiler/test4
cvs diff: Diffing tests/stm/orig/stm-compiler/test5
cvs diff: Diffing tests/stm/orig/stm-compiler/test6
cvs diff: Diffing tests/stm/orig/stm-compiler/test7
cvs diff: Diffing tests/stm/orig/stm-compiler/test8
cvs diff: Diffing tests/stm/orig/stm-compiler/test9
cvs diff: Diffing tests/stm/orig/stm-compiler-par
cvs diff: Diffing tests/stm/orig/stm-compiler-par/bm1
cvs diff: Diffing tests/stm/orig/stm-compiler-par/bm2
cvs diff: Diffing tests/stm/orig/stm-compiler-par/stmqueue
cvs diff: Diffing tests/stm/orig/stm-compiler-par/test1
cvs diff: Diffing tests/stm/orig/stm-compiler-par/test10
cvs diff: Diffing tests/stm/orig/stm-compiler-par/test11
cvs diff: Diffing tests/stm/orig/stm-compiler-par/test2
cvs diff: Diffing tests/stm/orig/stm-compiler-par/test3
cvs diff: Diffing tests/stm/orig/stm-compiler-par/test4
cvs diff: Diffing tests/stm/orig/stm-compiler-par/test5
cvs diff: Diffing tests/stm/orig/stm-compiler-par/test6
cvs diff: Diffing tests/stm/orig/stm-compiler-par/test7
cvs diff: Diffing tests/stm/orig/stm-compiler-par/test8
cvs diff: Diffing tests/stm/orig/stm-compiler-par/test9
cvs diff: Diffing tests/stm/orig/stm-compiler-par-asm_fast
cvs diff: Diffing tests/stm/orig/stm-compiler-par-asm_fast/test1
cvs diff: Diffing tests/stm/orig/stm-compiler-par-asm_fast/test2
cvs diff: Diffing tests/stm/orig/stm-compiler-par-asm_fast/test3
cvs diff: Diffing tests/stm/orig/stm-compiler-par-asm_fast/test4
cvs diff: Diffing tests/stm/orig/stm-compiler-par-asm_fast/test5
cvs diff: Diffing tests/stm/orig/stm-compiler-par-asm_fast/test6
cvs diff: Diffing tests/stm/orig/stm-compiler-par-asm_fast/test7
cvs diff: Diffing tests/stm/orig/stm-compiler-par-asm_fast/test8
cvs diff: Diffing tests/stm/orig/stm-compiler-par-asm_fast/test9
cvs diff: Diffing tests/tabling
cvs diff: Diffing tests/term
cvs diff: Diffing tests/trailing
cvs diff: Diffing tests/valid
cvs diff: Diffing tests/warnings
cvs diff: Diffing tools
cvs diff: Diffing trace
cvs diff: Diffing util
cvs diff: Diffing vim
cvs diff: Diffing vim/after
cvs diff: Diffing vim/ftplugin
cvs diff: Diffing vim/syntax
--------------------------------------------------------------------------
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