[m-rev.] for review: fix bad indirect reuse

Peter Wang novalazy at gmail.com
Thu Apr 17 15:28:28 AEST 2008


Branches: main

Fix problems with the verification of indirect structure reuse calls.
In many cases, a call to a procedure would be converted into reuse call even
though an input argument shares memory with another variable that is live
after the call.  As the test cases show, this even happened for trivial
programs.

compiler/ctgc.livedata.m:
compiler/structure_reuse.domain.m:
compiler/structure_sharing.domain.m:
	Reimplement `nodes_are_not_live' which is used to verify that
	datastructures which should be dead for a reuse call really are dead.
	I didn't understand how the original was supposed to work so I made up
	my own version which may or may not have any relation to the theory.

compiler/structure_reuse.indirect.m:
	When verifying an indirect reuse call site, don't project live data
	down to those about the callee arguments.  The call to
	`nodes_are_not_live' now depends on this.

tests/hard_coded/Mercury.options:
tests/hard_coded/Mmakefile:
tests/hard_coded/bad_indirect_reuse.exp:
tests/hard_coded/bad_indirect_reuse.m:
tests/hard_coded/bad_indirect_reuse2.exp:
tests/hard_coded/bad_indirect_reuse2.m:
tests/hard_coded/bad_indirect_reuse3.exp:
tests/hard_coded/bad_indirect_reuse3.m:
	Add test cases.  Switch off `--common-struct' as it tends to mask the
	problem.

Index: compiler/ctgc.livedata.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/ctgc.livedata.m,v
retrieving revision 1.3
diff -u -p -r1.3 ctgc.livedata.m
--- compiler/ctgc.livedata.m	31 Jul 2006 08:31:33 -0000	1.3
+++ compiler/ctgc.livedata.m	17 Apr 2008 05:14:31 -0000
@@ -74,7 +74,7 @@
 :- func livedata_add_liveness(module_info, proc_info, live_datastructs,
     sharing_as, livedata) = livedata.
 
-:- pred nodes_are_not_live(module_info::in, proc_info::in, 
+:- pred nodes_are_not_live(module_info::in, proc_info::in, sharing_as::in,
     list(datastruct)::in, livedata::in) is semidet.
 
 %-----------------------------------------------------------------------------%
@@ -286,7 +286,7 @@ extend_livedata(ModuleInfo, ProcInfo, Sh
             SharingAs, Data0))
     ).
 
-nodes_are_not_live(ModuleInfo, ProcInfo, Nodes, LiveData) :- 
+nodes_are_not_live(ModuleInfo, ProcInfo, SharingAs, DeadNodes, LiveData) :- 
     (
         LiveData = livedata_top,
         fail
@@ -294,8 +294,9 @@ nodes_are_not_live(ModuleInfo, ProcInfo,
         LiveData = livedata_bottom,
         true
     ;
-        LiveData = livedata_live(Data),
-        \+ datastructs_subsumed_by_list(ModuleInfo, ProcInfo, Nodes, Data)
+        LiveData = livedata_live(LiveDatastructs),
+        no_node_or_shared_subsumed_by_list(ModuleInfo, ProcInfo, SharingAs,
+            DeadNodes, LiveDatastructs)
     ).
 
 %-----------------------------------------------------------------------------%
Index: compiler/structure_reuse.domain.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/structure_reuse.domain.m,v
retrieving revision 1.11
diff -u -p -r1.11 structure_reuse.domain.m
--- compiler/structure_reuse.domain.m	21 Jan 2008 05:23:32 -0000	1.11
+++ compiler/structure_reuse.domain.m	17 Apr 2008 05:14:31 -0000
@@ -607,7 +607,7 @@ reuse_condition_satisfied(ModuleInfo, Pr
             SharingAs),
         UpdatedLiveData = livedata_add_liveness(ModuleInfo, ProcInfo, 
             InUseNodes, NewSharing, LiveData),
-        nodes_are_not_live(ModuleInfo, ProcInfo, DeadNodes,
+        nodes_are_not_live(ModuleInfo, ProcInfo, NewSharing, DeadNodes,
             UpdatedLiveData)
     ).
     
Index: compiler/structure_reuse.indirect.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/structure_reuse.indirect.m,v
retrieving revision 1.19
diff -u -p -r1.19 structure_reuse.indirect.m
--- compiler/structure_reuse.indirect.m	11 Apr 2008 02:00:49 -0000	1.19
+++ compiler/structure_reuse.indirect.m	17 Apr 2008 05:14:31 -0000
@@ -576,7 +576,16 @@ verify_indirect_reuse_2(BaseInfo, Analys
         FormalReuseAs, ActualReuseAs),
     LiveData = livedata_init_at_goal(ModuleInfo, ProcInfo, GoalInfo,
         SharingAs),
-    ProjectedLiveData = livedata_project(CalleeArgs, LiveData),
+
+    % Nancy's implementation:
+    % ProjectedLiveData = livedata_project(CalleeArgs, LiveData),
+    %
+    % However, that doesn't seem right.  Live data which are not arguments of
+    % the call may be affected by reuse if they share memory with CalleeArgs.
+    % In any case, the implementation of no_node_or_shared_subsumed_by_list
+    % expects live data not to be projected away. --pw
+    ProjectedLiveData = LiveData,
+
     StaticVars = set.to_sorted_list(AnalysisInfo ^ static_vars),
     (
         reuse_as_satisfied(ModuleInfo, ProcInfo, ProjectedLiveData,
Index: compiler/structure_sharing.domain.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/structure_sharing.domain.m,v
retrieving revision 1.29
diff -u -p -r1.29 structure_sharing.domain.m
--- compiler/structure_sharing.domain.m	27 Mar 2008 02:29:42 -0000	1.29
+++ compiler/structure_sharing.domain.m	17 Apr 2008 05:14:31 -0000
@@ -188,6 +188,15 @@
 :- func extend_datastructs(module_info, proc_info, sharing_as, 
     list(datastruct)) = list(datastruct).
 
+    % no_node_or_shared_subsumed_by_list(ModuleInfo, ProcInfo, SharingAs
+    %   Dead, Live)
+    %
+    % Succeed iff none of the Dead datastructures, or memory which shares
+    % with those datastructures, are subsumed by some Live datastructure.
+    %
+:- pred no_node_or_shared_subsumed_by_list(module_info::in, proc_info::in,
+    sharing_as::in, dead_datastructs::in, live_datastructs::in) is semidet.
+
     % apply_widening(ModuleInfo, ProcInfo, WideningLimit, WideningDone,
     %   SharingIn, SharingOut):
     %
@@ -736,6 +745,58 @@ extend_datastructs(ModuleInfo, ProcInfo,
         datastruct_lists_least_upper_bound(ModuleInfo, ProcInfo), 
         DataLists, []).
 
+no_node_or_shared_subsumed_by_list(ModuleInfo, ProcInfo, SharingAs,
+        DeadDatastructs, LiveDatastructs) :-
+    (
+        SharingAs = sharing_as_bottom,
+        not datastructs_subsumed_by_list(ModuleInfo, ProcInfo,
+            DeadDatastructs, LiveDatastructs)
+    ;
+        SharingAs = sharing_as_real_as(sharing_set(_, SharingMap)),
+        not some_node_or_shared_subsumed_by_list(ModuleInfo, ProcInfo,
+            SharingMap, DeadDatastructs, LiveDatastructs)
+    ;
+        SharingAs = sharing_as_top(_),
+        unexpected(this_file,
+            "no_node_or_shared_subsumed_by_list: sharing_as_top")
+    ).
+
+:- pred some_node_or_shared_subsumed_by_list(module_info::in, proc_info::in,
+    map(prog_var, selector_sharing_set)::in, dead_datastructs::in,
+    live_datastructs::in) is semidet.
+
+some_node_or_shared_subsumed_by_list(ModuleInfo, ProcInfo, SharingMap,
+        DeadDatastructs, LiveDatastructs) :-
+    % For each dead cell.
+    list.member(selected_cel(DeadVar, DeadSel), DeadDatastructs),
+    proc_info_get_vartypes(ProcInfo, VarTypes),
+    map.lookup(VarTypes, DeadVar, DeadVarType),
+
+    map.search(SharingMap, DeadVar, SelectorSharingSet),
+    SelectorSharingSet = selector_sharing_set(_, SelectorSharingMap),
+
+    % For some selector Sel such that Sel = DeadSel.Extension, check if some
+    % of the data structures which share with the dead datastructure are
+    % subsumed by live datastructures (which would be bad).
+    %
+    % Note that "extending" the dead datastructure and checking if the
+    % extension is subsumed by live datastructures doesn't work.  If a dead
+    % datastructure `cel(DV, [])' shares with `cel(V, [termsel(...)])' then
+    % the latter won't be included in the extension because the selector
+    % `[termsel(...)]' doesn't subsume `[]'. I don't know if the behaviour of
+    % `selector_sharing_set_extend_datastruct_2' is correct, but my attempts
+    % to change it resulted in breakages elsewhere. --pw
+    %
+    map.member(SelectorSharingMap, Sel, SelDataSet),
+    ( selector.subsumed_by(ModuleInfo, Sel, DeadSel, DeadVarType, _) ->
+        SelDataSet = datastructures(_, DeadDataSet),
+        set.member(DeadData, DeadDataSet),
+        datastruct_subsumed_by_list(ModuleInfo, ProcInfo, DeadData,
+            LiveDatastructs)
+    ;
+        true
+    ).
+
 apply_widening(ModuleInfo, ProcInfo, WideningLimit, WideningDone, !Sharing):-
     (
         !.Sharing = sharing_as_bottom,
Index: tests/hard_coded/Mercury.options
===================================================================
RCS file: /home/mercury/mercury1/repository/tests/hard_coded/Mercury.options,v
retrieving revision 1.30
diff -u -p -r1.30 Mercury.options
--- tests/hard_coded/Mercury.options	14 Nov 2007 03:45:12 -0000	1.30
+++ tests/hard_coded/Mercury.options	17 Apr 2008 05:14:31 -0000
@@ -1,5 +1,8 @@
 MCFLAGS-allow_stubs	=	--allow-stubs --no-warn-stubs --infer-all
 MCFLAGS-any_call_hoist_bug = --loop-invariants
+MCFLAGS-bad_indirect_reuse =	--ctgc --no-common-struct
+MCFLAGS-bad_indirect_reuse2 =	--ctgc --no-common-struct
+MCFLAGS-bad_indirect_reuse3 =	--ctgc --no-common-struct
 MCFLAGS-checked_nondet_tailcall	= --checked-nondet-tailcalls
 MCFLAGS-checked_nondet_tailcall_noinline = --checked-nondet-tailcalls --no-inlining
 MCFLAGS-big_array_from_list =   --optimize-tailcalls
Index: tests/hard_coded/Mmakefile
===================================================================
RCS file: /home/mercury/mercury1/repository/tests/hard_coded/Mmakefile,v
retrieving revision 1.345
diff -u -p -r1.345 Mmakefile
--- tests/hard_coded/Mmakefile	3 Apr 2008 05:26:47 -0000	1.345
+++ tests/hard_coded/Mmakefile	17 Apr 2008 05:14:31 -0000
@@ -10,6 +10,9 @@ ORDINARY_PROGS=	\
 	agg \
 	array_test \
 	backquoted_qualified_ops \
+	bad_indirect_reuse \
+	bad_indirect_reuse2 \
+	bad_indirect_reuse3 \
 	bag_various \
 	bidirectional \
 	big_array_from_list \
Index: tests/hard_coded/bad_indirect_reuse.exp
===================================================================
RCS file: tests/hard_coded/bad_indirect_reuse.exp
diff -N tests/hard_coded/bad_indirect_reuse.exp
--- /dev/null	1 Jan 1970 00:00:00 -0000
+++ tests/hard_coded/bad_indirect_reuse.exp	17 Apr 2008 05:14:31 -0000
@@ -0,0 +1,2 @@
+bar(3, 1)
+foo(0, bar(1, 2))
Index: tests/hard_coded/bad_indirect_reuse.m
===================================================================
RCS file: tests/hard_coded/bad_indirect_reuse.m
diff -N tests/hard_coded/bad_indirect_reuse.m
--- /dev/null	1 Jan 1970 00:00:00 -0000
+++ tests/hard_coded/bad_indirect_reuse.m	17 Apr 2008 05:14:31 -0000
@@ -0,0 +1,39 @@
+% Regression test.
+
+:- module bad_indirect_reuse.
+:- interface.
+
+:- import_module io.
+
+:- pred main(io::di, io::uo) is det.
+
+%-----------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
+
+:- implementation.
+
+main(!IO) :-
+    copy(bar(3, 1), Sub),
+    A = foo(2, Sub),
+    quux(A, _),                     % bad indirect reuse call
+    io.write(Sub, !IO),
+    io.nl(!IO),
+
+    copy(foo(1, bar(2, 0)), B),
+    quux(B, B1),                    % good indirect reuse call
+    io.write(B1, !IO),
+    io.nl(!IO).
+
+:- type foo
+    --->    foo(int, bar).
+
+:- type bar
+    --->    bar(int, int).
+
+:- pred quux(foo::in, foo::out) is det.
+:- pragma no_inline(quux/2).
+
+quux(foo(A, bar(B, C)), foo(C, bar(A, B))).
+
+%-----------------------------------------------------------------------------%
+% vim: ft=mercury ts=8 sw=4 et wm=0 tw=0
Index: tests/hard_coded/bad_indirect_reuse2.exp
===================================================================
RCS file: tests/hard_coded/bad_indirect_reuse2.exp
diff -N tests/hard_coded/bad_indirect_reuse2.exp
--- /dev/null	1 Jan 1970 00:00:00 -0000
+++ tests/hard_coded/bad_indirect_reuse2.exp	17 Apr 2008 05:14:31 -0000
@@ -0,0 +1,5 @@
+hide([1, 3, 3])
+hide([1, 3, 7])
+[1, 1, 3, 3, 3, 7]
+--------
+[0, 0, 1, 2, 2, 3, 4, 5]
Index: tests/hard_coded/bad_indirect_reuse2.m
===================================================================
RCS file: tests/hard_coded/bad_indirect_reuse2.m
diff -N tests/hard_coded/bad_indirect_reuse2.m
--- /dev/null	1 Jan 1970 00:00:00 -0000
+++ tests/hard_coded/bad_indirect_reuse2.m	17 Apr 2008 05:14:31 -0000
@@ -0,0 +1,58 @@
+% Regression test.
+
+:- module bad_indirect_reuse2.
+:- interface.
+
+:- import_module io.
+
+:- pred main(io::di, io::uo) is det.
+
+%-----------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
+
+:- implementation.
+
+:- import_module list.
+
+main(!IO) :-
+    copy([1,3,3], U1),
+    copy([1,3,7], U2),
+    H1 = hide(U1),
+    H2 = hide(U2),
+    my_merge(U1, U2, M),    % bad indirect reuse
+    io.write(H1, !IO),
+    nl(!IO),
+    io.write(H2, !IO),
+    nl(!IO),
+    io.write(M, !IO),
+    io.nl(!IO),
+
+    io.write_string("--------\n", !IO),
+
+    copy([0,0,3,5], U3),
+    copy([1,2,2,4], U4),
+    my_merge(U3, U4, MB),   % good indirect reuse
+    io.write(MB, !IO),
+    io.nl(!IO).
+
+:- type hide
+    --->    hide(list(int)).
+
+:- pred my_merge(list(int)::in, list(int)::in, list(int)::out) is det.
+:- pragma no_inline(my_merge/3).
+
+my_merge([], [], []).
+my_merge([A | As], [], [A | As]).
+my_merge([], [B | Bs], [B | Bs]).
+my_merge([A | As], [B | Bs], [C | Cs]) :-
+    ( compare(>, A, B) ->
+        C = B,
+        my_merge([A | As], Bs, Cs)
+    ;
+        % If compare((=), A, B), take A first.
+        C = A,
+        my_merge(As, [B | Bs], Cs)
+    ).
+
+%-----------------------------------------------------------------------------%
+% vim: ft=mercury ts=8 sw=4 et wm=0 tw=0
Index: tests/hard_coded/bad_indirect_reuse3.exp
===================================================================
RCS file: tests/hard_coded/bad_indirect_reuse3.exp
diff -N tests/hard_coded/bad_indirect_reuse3.exp
--- /dev/null	1 Jan 1970 00:00:00 -0000
+++ tests/hard_coded/bad_indirect_reuse3.exp	17 Apr 2008 05:14:31 -0000
@@ -0,0 +1 @@
+{foo(42, 43), foo(42, 43)}
Index: tests/hard_coded/bad_indirect_reuse3.m
===================================================================
RCS file: tests/hard_coded/bad_indirect_reuse3.m
diff -N tests/hard_coded/bad_indirect_reuse3.m
--- /dev/null	1 Jan 1970 00:00:00 -0000
+++ tests/hard_coded/bad_indirect_reuse3.m	17 Apr 2008 05:14:31 -0000
@@ -0,0 +1,36 @@
+% Regression test.
+
+:- module bad_indirect_reuse3.
+:- interface.
+
+:- import_module io.
+
+:- pred main(io::di, io::uo) is det.
+
+%-----------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
+
+:- implementation.
+
+main(!IO) :-
+    copy(foo(43, 42), A),
+    B = bar(-1, A, -2),
+    % Although neither A, B are used afterwards they do share memory so reuse
+    % is not possible.
+    quux(A, B, C, D),
+    io.write({C, D}, !IO),
+    io.nl(!IO).
+
+:- type foo
+    --->    foo(int, int).
+
+:- type bar
+    --->    bar(int, foo, int).
+
+:- pred quux(foo::in, bar::in, foo::out, foo::out) is det.
+:- pragma no_inline(quux/4).
+
+quux(foo(A, B), bar(_, foo(C, D), _), foo(B, A), foo(D, C)).
+
+%-----------------------------------------------------------------------------%
+% vim: ft=mercury ts=8 sw=4 et wm=0 tw=0


--------------------------------------------------------------------------
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