[m-rev.] for review: [CTGC] direct structure reuse analysis (1/2)

Nancy Mazur Nancy.Mazur at cs.kuleuven.ac.be
Thu Apr 27 20:24:00 AEST 2006


Hi,

Here is a big chunk from the structure reuse analysis: the direct reuse
analysis.

Still missing (mainly): 
	- (structure reuse) indirect reuse analysis;
	- (structure reuse) the definition of the public representation for
	  reuse conditions and manipulating, printing and whatever operations
	  needed on that representation;
	- generating/loading structure reuse pragma's (trans_opt);
	- (structure sharing) pre-annotating foreign code with structure
	  sharing information; 
	
There are quite some "XXX"s. But I'd like to be able to submit all this
material before going on. 

Anybody in for reviewing this? 
Nancy


===================================================================


Estimated hours taken: 20
Branches: main

Provide the direct reuse analysis part of the structure reuse analysis (which
itself is part of the CTGC system). 

compiler/ctgc.datastruct.m:
compiler/ctgc.util.m:
	Additional predicates.

compiler/ctgc.m:
	Add structure reuse module.

compiler/handle_options.m:
compiler/options.m:
	Add new options "structure_reuse_analysis" and related ones.

compiler/handle_options.m:
compiler/hlds_out.m:
	Add dump option "R" to dump structure reuse related information
	in the hlds_dump files.

compiler/hlds_goal.m:
	Types to record structure reuse information at the level of each 
	goal.
	Additional "case_get_goal" function to extract the goal from an case.

compiler/mercury_compile.m:
	Add structure reuse analysis as a new compiler stage.

compiler/structure_reuse.analysis.m:
	The top level analysis predicates. 

compiler/structure_reuse.direct.m:
compiler/structure_reuse.direct.choose_reuse.m:
compiler/structure_reuse.direct.detect_garbage.m:
	Direct reuse analysis is split into 2 steps: determining when and how
	data structures become garbage, and then choosing how these dead 
	data structures might best be reused. 

compiler/structure_reuse.domain.m:
	The abstract domain for keeping track of reuse conditions, the main
	domain in the structure reuse analysis. 

compiler/structure_reuse.lbu.m:
compiler/structure_reuse.lfu.m:
	To determine whether data structures become dead or not, one needs to 
	know which variables in a goal are needed with respect to forward 
	execution (lfu = local forward use), and backward execution, i.e. 
	backtracking (lbu = local backward use). These two modules provide
	the necessary functionality to pre-annotate the goals with lfu and
	lbu information.

compiler/structure_sharing.analysis.m:
compiler/structure_sharing.domain.m:
	Remove the structure sharing table from the interface of the analysis
	predicate in structure_sharing.analysis.m;
	Move predicates to structure_sharing.domain.m so that they become 
	more easily accessible for the structure_reuse modules.



Index: compiler/ctgc.datastruct.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/ctgc.datastruct.m,v
retrieving revision 1.5
diff -u -d -r1.5 ctgc.datastruct.m
--- compiler/ctgc.datastruct.m	27 Mar 2006 09:36:04 -0000	1.5
+++ compiler/ctgc.datastruct.m	27 Apr 2006 09:29:45 -0000
@@ -55,8 +55,8 @@
     % Normalize the representation of the datastructure using its
     % type information.
     %
-:- pred normalize_datastruct_with_type_information(module_info::in, mer_type::in,
-    datastruct::in, datastruct::out) is det.
+:- pred normalize_datastruct_with_type_information(module_info::in, 
+    mer_type::in, datastruct::in, datastruct::out) is det.
 :- func normalize_datastruct_with_type_information(module_info, mer_type,
     datastruct) = datastruct.
 
@@ -66,11 +66,15 @@
     datastruct::in, datastruct::in) is semidet.
 :- pred datastruct_subsumed_by_list(module_info::in, proc_info::in,
     datastruct::in, list(datastruct)::in) is semidet.
+:- pred datastructs_subsumed_by_list(module_info::in, proc_info::in,
+    list(datastruct)::in, list(datastruct)::in) is semidet.
 
 :- pred datastruct_apply_widening(module_info::in, proc_info::in,
     datastruct::in, datastruct::out) is det.
 
-%-----------------------------------------------------------------------------%
+:- func datastructs_project(list(prog_var), 
+    list(datastruct)) = list(datastruct).
+
 %-----------------------------------------------------------------------------%
 
 :- implementation.
@@ -133,6 +137,17 @@
         datastruct_subsumed_by_list(ModuleInfo, ProcInfo, Data0, Rest)
     ).
 
+datastructs_subsumed_by_list(ModuleInfo, ProcInfo, PerhapsSubsumedData, 
+        Data) :- 
+    list.takewhile(datastructs_subsume_datastruct(ModuleInfo, ProcInfo, Data), 
+        PerhapsSubsumedData, _, NotSubsumed), 
+    NotSubsumed = [].
+
+:- pred datastructs_subsume_datastruct(module_info::in, proc_info::in, 
+    list(datastruct)::in, datastruct::in) is semidet.
+datastructs_subsume_datastruct(ModuleInfo, ProcInfo, Datastructs, Data):- 
+    datastruct_subsumed_by_list(ModuleInfo, ProcInfo, Data, Datastructs).
+
 datastruct_apply_widening(ModuleInfo, ProcInfo, !Data) :-
     Var = !.Data ^ sc_var,
     Sel0 = !.Data ^ sc_selector,
@@ -140,6 +155,12 @@
     map.lookup(VarTypes, Var, Type),
     selector_apply_widening(ModuleInfo, Type, Sel0, Sel),
     !:Data = datastruct_init_with_selector(Var, Sel).
+
+datastructs_project(Vars, DataIn) = 
+    list__filter(
+        pred(Data::in) is semidet :-
+          (list__member(Data^sc_var, Vars)),
+        DataIn).
 
 %-----------------------------------------------------------------------------%
 :- end_module transform_hlds.ctgc.datastruct.
Index: compiler/ctgc.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/ctgc.m,v
retrieving revision 1.4
diff -u -d -r1.4 ctgc.m
--- compiler/ctgc.m	1 Mar 2006 03:21:19 -0000	1.4
+++ compiler/ctgc.m	27 Apr 2006 09:29:45 -0000
@@ -21,6 +21,7 @@
 :- include_module fixpoint_table.
 :- include_module selector.
 :- include_module structure_sharing.
+:- include_module structure_reuse.
 :- include_module util.
 
 :- end_module transform_hlds.ctgc.
Index: compiler/ctgc.util.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/ctgc.util.m,v
retrieving revision 1.4
diff -u -d -r1.4 ctgc.util.m
--- compiler/ctgc.util.m	27 Mar 2006 09:36:04 -0000	1.4
+++ compiler/ctgc.util.m	27 Apr 2006 09:29:45 -0000
@@ -31,35 +31,41 @@
 :- pred preds_requiring_no_analysis(module_info::in, list(pred_proc_id)::in)
     is semidet.
 
-%-----------------------------------------------------------------------------%
+:- pred pred_requires_no_analysis(module_info::in, pred_id::in) is semidet.
+:- pred pred_requires_analysis(module_info::in, pred_id::in) is semidet.
+
 %-----------------------------------------------------------------------------%
 
 :- implementation.
 
 :- import_module bool.
+:- import_module list.
 :- import_module map.
 
+
 %-----------------------------------------------------------------------------%
 
-preds_requiring_no_analysis(ModuleInfo, PPIds) :-
+pred_requires_no_analysis(ModuleInfo, PredId) :- 
     module_info_get_special_pred_map(ModuleInfo, SpecialPredMap),
     map.values(SpecialPredMap, SpecialPreds),
     (
-        list.filter(pred_id_in(SpecialPreds), PPIds, SpecialPredProcs),
-        SpecialPredProcs = [_|_]
-    ;
-        % or some of the predicates are not defined in this
-        % module.
-        list.filter(not_defined_in_this_module(ModuleInfo),
-            PPIds, FilteredPPIds),
-        FilteredPPIds = [_|_]
+        list.member(PredId, SpecialPreds)
+    ;   
+        module_info_pred_info(ModuleInfo, PredId, PredInfo),
+        pred_info_get_import_status(PredInfo, Status),
+        status_defined_in_this_module(Status, no)
     ).
 
-:- pred pred_id_in(list(pred_id)::in, pred_proc_id::in) is semidet.
+pred_requires_analysis(ModuleInfo, PredId) :- 
+    \+ pred_requires_no_analysis(ModuleInfo, PredId).
 
-pred_id_in(PredIds, PPId):-
-    PPId = proc(PredId, _),
-    list.member(PredId, PredIds).
+:- func get_pred_id(pred_proc_id) = pred_id. 
+get_pred_id(proc(PredId, _)) = PredId. 
+
+preds_requiring_no_analysis(ModuleInfo, PPIds) :-
+    list.takewhile(pred_requires_analysis(ModuleInfo),
+        list.map(get_pred_id, PPIds), _RequiresAnalysis, RequiresNoAnalysis),
+    RequiresNoAnalysis = [_|_].
 
 :- pred not_defined_in_this_module(module_info::in, pred_proc_id::in)
     is semidet.
Index: compiler/handle_options.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/handle_options.m,v
retrieving revision 1.265
diff -u -d -r1.265 handle_options.m
--- compiler/handle_options.m	26 Apr 2006 03:05:34 -0000	1.265
+++ compiler/handle_options.m	27 Apr 2006 09:29:51 -0000
@@ -720,6 +720,8 @@
             globals.set_option(use_symlinks, bool(no), !Globals)
         ),
 
+        option_implies(structure_reuse_analysis, structure_sharing_analysis,
+            bool(yes), !Globals),
         option_implies(verbose_check_termination, check_termination,bool(yes),
             !Globals),
         option_implies(check_termination, termination, bool(yes), !Globals),
@@ -2329,7 +2331,7 @@
 
 :- pred convert_dump_alias(string::in, string::out) is semidet.
 
-convert_dump_alias("ALL", "abcdfgilmnprstuvBCDIMPSTU").
+convert_dump_alias("ALL", "abcdfgilmnprstuvBCDIMPRSTU").
 convert_dump_alias("allD", "abcdfgilmnprstuvBCDMPT").
 convert_dump_alias("all", "abcdfgilmnprstuvBCMPST").
 convert_dump_alias("most", "bcdfgilmnprstuvP").
@@ -2342,6 +2344,7 @@
 convert_dump_alias("mm", "bdgvP").      % for debugging minimal model
 convert_dump_alias("osv", "bcdglmnpruvP").  % for debugging
                                             % --optimize-saved-vars-cell
+convert_dump_alias("ctgc", "cdinpGDRS").
 
 %-----------------------------------------------------------------------------%
 :- end_module handle_options.
Index: compiler/hlds_goal.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/hlds_goal.m,v
retrieving revision 1.155
diff -u -d -r1.155 hlds_goal.m
--- compiler/hlds_goal.m	20 Apr 2006 05:36:52 -0000	1.155
+++ compiler/hlds_goal.m	27 Apr 2006 09:29:59 -0000
@@ -769,6 +769,8 @@
                 hlds_goal   % goal to execute if match succeeds.
             ).
 
+:- func case_get_goal(case) = hlds_goal.
+
 %-----------------------------------------------------------------------------%
 %
 % Information for all kinds of goals
@@ -1072,6 +1074,91 @@
 
 %-----------------------------------------------------------------------------%
 %
+% Types and get/set predicates for the CTGC related information stored for each
+% goal.
+%
+
+
+    % Information describing possible kinds of reuse on a per goal basis.
+    % - 'empty': before CTGC analysis, every goal is annotated with the reuse
+    % description 'empty', ie. no information about any reuse. 
+    % - 'potential_reuse': the value 'potential_reuse' states that in a reuse
+    % version of the procedure to which the goal belongs, this goal may safely
+    % be replaced by a goal implementing structure reuse.
+    % - 'reuse': the value 'reuse' states that in the current procedure (either
+    % the specialised reuse version of a procedure, or the original procedure
+    % itself) the current goal can safely be replaced by a goal performing
+    % structure reuse. 
+    % - 'missed_reuse': the value 'missed_reuse' gives some feedback when an
+    % opportunity for reuse was missed for some reason (only used for calls).
+    %
+:- type reuse_description
+    --->    empty
+    ;       missed_reuse(list(missed_message))
+    ;       potential_reuse(short_reuse_description)
+    ;       reuse(short_reuse_description).
+
+    % A short description of the kind of reuse allowed in the associated
+    % goal:
+    % - 'cell_died' (only relevant for deconstructions): states that the cell
+    % of the deconstruction becomes dead after that deconstruction.
+    % - 'cell_reused' (only relevant for constructions): states that it is
+    % allowed to reuse a previously discovered dead term for constructing a
+    % new term in the given construction. Details of which term is reused are
+    % recorded.
+    % - 'reuse_call' (only applicable to procedure calls): the called 
+    % procedure is an optimised procedure w.r.t. CTGC. Records whether the 
+    % call is conditional or not. 
+    %
+:- type short_reuse_description 
+    --->    cell_died   
+    ;       cell_reused(
+                prog_var,       % The dead variable selected
+                                % for reusing.
+                is_conditional, % states if the reuse is conditional. 
+                list(cons_id),  % What are the possible cons_ids that the 
+                                % variable to be reused can have.
+                list(needs_update)   
+                                % Which of the fields of the cell to be 
+                                % reused already contain the correct value.
+            )
+    ;       reuse_call(is_conditional).
+
+:- type is_conditional 
+    --->    conditional_reuse
+    ;       unconditional_reuse.
+
+:- type needs_update
+    --->    needs_update
+    ;       does_not_need_update.
+
+:- type missed_message == string.
+
+    % The following functions produce an 'unexpected' error when the
+    % requested values have not been set.
+    %
+:- func goal_info_get_lfu(hlds_goal_info) = set(prog_var).
+:- func goal_info_get_lbu(hlds_goal_info) = set(prog_var).
+:- func goal_info_get_reuse(hlds_goal_info) = reuse_description.
+
+    % Same as above, but instead of producing an error, the predicate
+    % fails.
+:- pred goal_info_maybe_get_lfu(hlds_goal_info::in, set(prog_var)::out) is
+    semidet.
+:- pred goal_info_maybe_get_lbu(hlds_goal_info::in, set(prog_var)::out) is 
+    semidet.
+:- pred goal_info_maybe_get_reuse(hlds_goal_info::in, reuse_description::out) 
+    is semidet.
+
+:- pred goal_info_set_lfu(set(prog_var)::in, hlds_goal_info::in, 
+    hlds_goal_info::out) is det.
+:- pred goal_info_set_lbu(set(prog_var)::in, hlds_goal_info::in, 
+    hlds_goal_info::out) is det.
+:- pred goal_info_set_reuse(reuse_description::in, hlds_goal_info::in, 
+    hlds_goal_info::out) is det.
+
+%-----------------------------------------------------------------------------%
+%
 % Miscellaneous utility procedures for dealing with HLDS goals.
 %
 
@@ -2243,14 +2330,16 @@
 
 :- type hlds_goal_extra_info
     --->    extra_info(
-                extra_info_ho_vals :: ho_values
+                extra_info_ho_vals  :: ho_values,
+                maybe_reuse         :: maybe(ctgc_info)
+                    % Any information related to structure reuse (CTGC). 
             ).
 
 :- func hlds_goal_extra_info_init = hlds_goal_extra_info.
 
 hlds_goal_extra_info_init = ExtraInfo :-
     HO_Values = map.init,
-    ExtraInfo = extra_info(HO_Values).
+    ExtraInfo = extra_info(HO_Values, no).
 
 goal_info_get_ho_values(GoalInfo) =
     GoalInfo ^ extra_goal_info ^ extra_info_ho_vals.
@@ -2258,6 +2347,113 @@
 goal_info_set_ho_values(Values, !GoalInfo) :-
     !:GoalInfo = !.GoalInfo ^ extra_goal_info ^ extra_info_ho_vals := Values.
 
+%-----------------------------------------------------------------------------%
+% hlds_goal_reuse_info
+
+:- type ctgc_info
+    --->    ctgc_info(
+                lfu     :: set(prog_var),
+                    % The local forward use set: this set contains the
+                    % variables that are syntactically needed during forward
+                    % execution. 
+                    % It is computed as the set of instantiated vars (input
+                    % vars + sum(pre_births), minus the set of dead vars
+                    % (sum(post_deaths and pre_deaths).
+                    % The information is needed for determining the direct
+                    % reuses. 
+                lbu     :: set(prog_var),
+                    % The local backward use set. This set contains the
+                    % instantiated variables that are needed upon backtracking
+                    % (i.e. syntactically appearing in any nondet call
+                    % preceding this goal). 
+
+                reuse   :: reuse_description
+                    % Any structure reuse information
+                    % related to this call.
+        ).
+
+
+:- func ctgc_info_init = ctgc_info.
+ctgc_info_init = ctgc_info(set.init, set.init, empty).
+
+goal_info_get_lfu(GoalInfo) = LFU :- 
+    (
+        goal_info_maybe_get_lfu(GoalInfo, LFU0)
+    -> 
+        LFU = LFU0
+    ;
+        unexpected(this_file, "Requesting LFU information while " ++ 
+            "CTGC field not set.")
+    ).
+goal_info_get_lbu(GoalInfo) = LBU :- 
+    (
+        goal_info_maybe_get_lbu(GoalInfo, LBU0)
+    ->
+        LBU = LBU0
+    ;
+        unexpected(this_file, "Requesting LBU information while " ++ 
+            "CTGC field not set.")
+    ).
+goal_info_get_reuse(GoalInfo) = Reuse :- 
+    (
+        goal_info_maybe_get_reuse(GoalInfo, Reuse0)
+    -> 
+        Reuse = Reuse0
+    ;   
+        unexpected(this_file, "Requesting reuse information while " ++ 
+            "CTGC field not set.")
+    ).
+
+goal_info_maybe_get_lfu(GoalInfo, LFU) :- 
+    MaybeCTGC = GoalInfo ^ extra_goal_info ^ maybe_reuse,
+    MaybeCTGC = yes(CTGC),
+    LFU = CTGC ^ lfu. 
+goal_info_maybe_get_lbu(GoalInfo, LBU) :- 
+    MaybeCTGC = GoalInfo ^ extra_goal_info ^ maybe_reuse,
+    MaybeCTGC = yes(CTGC),
+    LBU = CTGC ^ lbu. 
+goal_info_maybe_get_reuse(GoalInfo, Reuse) :- 
+    MaybeCTGC = GoalInfo ^ extra_goal_info ^ maybe_reuse,
+    MaybeCTGC = yes(CTGC),
+    Reuse = CTGC ^ reuse. 
+    
+goal_info_set_lfu(LFU, !GoalInfo) :- 
+    MaybeCTGC0 = !.GoalInfo ^ extra_goal_info ^ maybe_reuse,
+    (
+        MaybeCTGC0 = yes(CTGC0)
+    ;
+        MaybeCTGC0 = no, 
+        CTGC0 = ctgc_info_init
+    ),
+    CTGC = CTGC0 ^ lfu := LFU,
+    MaybeCTGC = yes(CTGC),
+    !:GoalInfo = !.GoalInfo ^ extra_goal_info ^ maybe_reuse := MaybeCTGC.
+
+goal_info_set_lbu(LBU, !GoalInfo) :- 
+    MaybeCTGC0 = !.GoalInfo ^ extra_goal_info ^ maybe_reuse,
+    (
+        MaybeCTGC0 = yes(CTGC0)
+    ;
+        MaybeCTGC0 = no, 
+        CTGC0 = ctgc_info_init
+    ),
+    CTGC = CTGC0 ^ lbu := LBU,
+    MaybeCTGC = yes(CTGC),
+    !:GoalInfo = !.GoalInfo ^ extra_goal_info ^ maybe_reuse := MaybeCTGC.
+
+goal_info_set_reuse(Reuse, !GoalInfo) :- 
+    MaybeCTGC0 = !.GoalInfo ^ extra_goal_info ^ maybe_reuse,
+    (
+        MaybeCTGC0 = yes(CTGC0)
+    ;
+        MaybeCTGC0 = no, 
+        CTGC0 = ctgc_info_init
+    ),
+    CTGC = CTGC0 ^ reuse := Reuse,
+    MaybeCTGC = yes(CTGC),
+    !:GoalInfo = !.GoalInfo ^ extra_goal_info ^ maybe_reuse := MaybeCTGC.
+
+case_get_goal(case(_, Goal)) = Goal.
 %-----------------------------------------------------------------------------%
 
 :- func this_file = string.
Index: compiler/hlds_out.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/hlds_out.m,v
retrieving revision 1.391
diff -u -d -r1.391 hlds_out.m
--- compiler/hlds_out.m	20 Apr 2006 05:36:53 -0000	1.391
+++ compiler/hlds_out.m	27 Apr 2006 09:30:09 -0000
@@ -1402,6 +1402,53 @@
     ;
         true
     ),
+    ( string.contains_char(Verbose, 'R') ->
+        (
+            goal_info_maybe_get_lfu(GoalInfo, LFU),
+            goal_info_maybe_get_lbu(GoalInfo, LBU), 
+            goal_info_maybe_get_reuse(GoalInfo, ReuseDescription), 
+            set.to_sorted_list(LFU, ListLFU),
+            set.to_sorted_list(LBU, ListLBU)
+        ->
+            write_indent(Indent, !IO),
+            io.write_string("% LFU: ", !IO),
+            mercury_output_vars(ListLFU, VarSet, AppendVarNums, !IO),
+            io.write_string("\n", !IO),
+            write_indent(Indent, !IO),
+            io.write_string("% LBU: ", !IO),
+            mercury_output_vars(ListLBU, VarSet, AppendVarNums, !IO),
+            io.write_string("\n", !IO),
+
+            write_indent(Indent, !IO),
+            write_string("% Reuse: ", !IO),
+            (
+                ReuseDescription = empty,
+                io.write_string("no", !IO)
+            ;
+                ReuseDescription = missed_reuse(Messages),
+                io.write_string("missed (", !IO), 
+                io.write_list(Messages, ", ", io.write_string, !IO),
+                io.write_string(")", !IO)
+            ;
+                ReuseDescription = potential_reuse(ShortReuseDescr),
+                io.write_string("potential reuse (", !IO), 
+                write_short_reuse_description(ShortReuseDescr, VarSet, 
+                    AppendVarNums, !IO), 
+                io.write_string(")", !IO)
+            ;
+                ReuseDescription = reuse(ShortReuseDescr),
+                io.write_string("reuse (", !IO), 
+                write_short_reuse_description(ShortReuseDescr, VarSet,
+                    AppendVarNums, !IO), 
+                io.write_string(")", !IO)
+            ), 
+            io.write_string("\n", !IO)
+        ;
+            true
+        )
+    ;
+        true
+    ),
     goal_info_get_code_gen_info(GoalInfo, CodeGenInfo),
     (
         CodeGenInfo = no_code_gen_info
@@ -4101,6 +4148,34 @@
     mercury_format_inst(Inst,
         expanded_inst_info(VarSet, ModuleInfo, Expansions), "", String).
 
+:- pred write_short_reuse_description(short_reuse_description::in, 
+    prog_varset::in, bool::in, 
+    io::di, io::uo) is det.
+write_short_reuse_description(ShortDescription, VarSet, AppendVarnums, !IO):- 
+    (
+        ShortDescription = cell_died, 
+        io.write_string("cell died", !IO)
+    ;
+        ShortDescription = cell_reused(Var, IsConditional, _, _),
+        io.write_string("cell reuse - ", !IO),
+        mercury_output_var(Var, VarSet, AppendVarnums, !IO),
+        io.write_string(" - ", !IO), 
+        write_is_conditional(IsConditional, !IO)
+    ;
+        ShortDescription = reuse_call(IsConditional),
+        io.write_string("reuse call - ", !IO), 
+        write_is_conditional(IsConditional, !IO)
+    ).
+
+:- pred write_is_conditional(is_conditional::in, io::di, io::uo) is det.
+write_is_conditional(IsConditional, !IO) :- 
+    (
+        IsConditional = conditional_reuse,
+        io.write_string("with condition", !IO)
+    ;
+        IsConditional = unconditional_reuse,
+        io.write_string("always safe", !IO)
+    ).
 %-----------------------------------------------------------------------------%
 
 :- func this_file = string.
Index: compiler/mercury_compile.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/mercury_compile.m,v
retrieving revision 1.385
diff -u -d -r1.385 mercury_compile.m
--- compiler/mercury_compile.m	26 Apr 2006 03:05:36 -0000	1.385
+++ compiler/mercury_compile.m	27 Apr 2006 09:30:22 -0000
@@ -88,6 +88,8 @@
 :- import_module transform_hlds.unneeded_code.
 :- import_module transform_hlds.lco.
 :- import_module transform_hlds.ctgc.
+:- import_module transform_hlds.ctgc.structure_reuse.
+:- import_module transform_hlds.ctgc.structure_reuse.analysis.
 :- import_module transform_hlds.ctgc.structure_sharing.
 :- import_module transform_hlds.ctgc.structure_sharing.analysis.
 :- import_module transform_hlds.size_prof.
@@ -2038,6 +2040,8 @@
     globals.lookup_bool_option(Globals, termination2, Termination2),
     globals.lookup_bool_option(Globals, structure_sharing_analysis, 
         SharingAnalysis), 
+    globals.lookup_bool_option(Globals, structure_reuse_analysis, 
+        ReuseAnalysis), 
     globals.lookup_bool_option(Globals, analyse_exceptions,
         ExceptionAnalysis),
     globals.lookup_bool_option(Globals, analyse_closures,
@@ -2059,6 +2063,7 @@
             ; ExceptionAnalysis = yes
             ; TrailingAnalysis = yes
             ; SharingAnalysis = yes
+            ; ReuseAnalysis = yes
             )
         ->
             frontend_pass_by_phases(!HLDS, FoundModeError, !DumpInfo, !IO),
@@ -2106,6 +2111,13 @@
                     SharingAnalysis = no
                 ),
                 (
+                    ReuseAnalysis = yes, 
+                    maybe_structure_reuse_analysis(Verbose, Stats,
+                        !HLDS, !IO)
+                ;
+                    ReuseAnalysis = no
+                ),
+                (
                     TrailingAnalysis = yes,
                     maybe_analyse_trail_usage(Verbose, Stats, !HLDS, !IO)
                 ;
@@ -2178,6 +2190,8 @@
     maybe_dump_hlds(!.HLDS, 167, "trail_usage", !DumpInfo, !IO),
     maybe_structure_sharing_analysis(Verbose, Stats, !HLDS, !IO),
     maybe_dump_hlds(!.HLDS, 193, "structure_sharing", !DumpInfo, !IO),
+    maybe_structure_reuse_analysis(Verbose, Stats, !HLDS, !IO),
+    maybe_dump_hlds(!.HLDS, 194, "structure_reuse", !DumpInfo, !IO),
     trans_opt.write_optfile(!.HLDS, !IO).
 
 :- pred output_analysis_file(module_name::in,
@@ -2390,6 +2404,9 @@
 
     maybe_structure_sharing_analysis(Verbose, Stats, !HLDS, !IO), 
     maybe_dump_hlds(!.HLDS, 193, "structure_sharing", !DumpInfo, !IO), 
+
+    maybe_structure_reuse_analysis(Verbose, Stats, !HLDS, !IO), 
+    maybe_dump_hlds(!.HLDS, 194, "structure_reuse", !DumpInfo, !IO), 
     
     % If we are compiling in a deep profiling grade then now rerun simplify.
     % The reason for doing this now is that we want to take advantage of any
@@ -3624,13 +3641,30 @@
         maybe_write_string(Verbose, "% Structure sharing analysis...\n",
             !IO), 
         maybe_flush_output(Verbose, !IO), 
-        structure_sharing_analysis(!HLDS, _SharingTable, !IO), 
+        structure_sharing_analysis(!HLDS, !IO), 
         maybe_write_string(Verbose, "% done.\n", !IO),
         maybe_report_stats(Stats, !IO)
     ;
         Sharing = no
     ).
 
+:- pred maybe_structure_reuse_analysis(bool::in, bool::in,
+    module_info::in, module_info::out, io::di, io::uo) is det.
+
+maybe_structure_reuse_analysis(Verbose, Stats, !HLDS, !IO) :- 
+    globals.io_lookup_bool_option(structure_reuse_analysis, 
+        ReuseAnalysis, !IO), 
+    (
+        ReuseAnalysis = yes, 
+        maybe_write_string(Verbose, "% Structure reuse analysis...\n",
+            !IO), 
+        maybe_flush_output(Verbose, !IO), 
+        structure_reuse_analysis(!HLDS, !IO), 
+        maybe_write_string(Verbose, "% done.\n", !IO),
+        maybe_report_stats(Stats, !IO)
+    ;
+        ReuseAnalysis = no
+    ).
 
 :- pred maybe_term_size_prof(bool::in, bool::in,
     module_info::in, module_info::out, io::di, io::uo) is det.
Index: compiler/options.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/options.m,v
retrieving revision 1.511
diff -u -d -r1.511 options.m
--- compiler/options.m	26 Apr 2006 03:05:38 -0000	1.511
+++ compiler/options.m	27 Apr 2006 09:30:36 -0000
@@ -530,6 +530,9 @@
     % Stuff for the CTGC system (structure sharing / structure reuse).
     ;       structure_sharing_analysis
     ;           structure_sharing_widening
+    ;       structure_reuse_analysis
+    ;           structure_reuse_constraint
+    ;           structure_reuse_constraint_arg
 
     % Stuff for the new termination analyser.
     ;       termination2
@@ -1149,6 +1152,9 @@
     verbose_check_termination           -   bool(no),
     structure_sharing_analysis          -   bool(no), 
     structure_sharing_widening          -   int(0),
+    structure_reuse_analysis            -   bool(no), 
+    structure_reuse_constraint        -   string("within_n_cells_difference"),
+    structure_reuse_constraint_arg      -   int(0),
     termination                         -   bool(no),
     termination_single_args             -   int(0),
     termination_norm                    -   string("total"),
@@ -1981,6 +1987,12 @@
 % CTGC related options.
 long_option("structure-sharing",    structure_sharing_analysis).
 long_option("structure-sharing-widening", structure_sharing_widening).
+long_option("structure-reuse",      structure_reuse_analysis).
+long_option("ctgc",                 structure_reuse_analysis).
+long_option("structure-reuse-constraint", structure_reuse_constraint).
+long_option("ctgc-constraint",      structure_reuse_constraint).
+long_option("structure-reuse-constraint-arg", structure_reuse_constraint_arg).
+long_option("ctgc-constraint-arg",  structure_reuse_constraint_arg).
 
 % HLDS->LLDS optimizations
 long_option("smart-indexing",       smart_indexing).
@@ -3197,7 +3209,23 @@
         "--structure-sharing-widening <n>",
         "\tPerform widening when the set of structure sharing pairs becomes",
         "\tlarger than <n>. When n=0, widening is not enabled.",
-        "\t(default: 0)."
+        "\t(default: 0).",
+        "--structure-reuse, --ctgc",
+        "\tPerform structure reuse analysis for all encountered",
+        "\tpredicates (Compile Time Garbage Collection).",
+        "--structure-reuse-constraint, --ctgc-constraint",
+        "\tConstraint on the way we allow structure reuse. Either reuse",
+        "\tis only allowed for terms with the same type and same constructor",
+        "\t(option same_cons_id), or reuse is allowed between terms of",
+        "\tdifferent constructors as long as the difference between the",
+        "\tarities does not exceed a certain threshold (option ",
+        "\twithin_n_cells_difference(n), where n specifies the threshold,",
+        "\tn needs to be set using --structure-reuse-constraint-arg).",
+        "\t(default: within_n_cells_difference(0))",
+        "--structure-reuse-constraint-arg, --ctgc-constraint-arg",
+        "\tSpecify the allowed difference in arities between the terms that",
+        "\tcan be reused, and the terms that reuse these terms.",
+        "\t(default: 0)"
     ]).
 
 :- pred options_help_termination(io::di, io::uo) is det.
Index: compiler/structure_reuse.analysis.m
===================================================================
RCS file: compiler/structure_reuse.analysis.m
diff -N compiler/structure_reuse.analysis.m
--- /dev/null	1 Jan 1970 00:00:00 -0000
+++ compiler/structure_reuse.analysis.m	27 Apr 2006 09:30:36 -0000
@@ -0,0 +1,135 @@
+%-----------------------------------------------------------------------------%
+% vim: ft=mercury ts=4 sw=4 et
+%-----------------------------------------------------------------------------%
+% Copyright (C) 2006 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.
+%-----------------------------------------------------------------------------%
+%
+% File: structure_reuse.analysis.m
+% Main authors: nancy
+%
+% Implementation of the structure reuse analysis (compile-time garbage
+% collection system): each procedure is analysed to see whether some
+% of the terms it manipulates becomes garbage thus making it possible
+% to reuse that garbage straight away for creating new terms.
+%
+% Structure reuse is broken up into three phases: 
+%   * the direct reuse analysis (structure_reuse.direct.m) 
+%   * the indirect analysis (structure_reuse.indirect.m)
+%   * and the generation of the optimised procedures.
+% 
+% list__append(H1, H2, H3) :-
+%   (
+%       H1 => [],
+%       H3 := H2
+%   ;
+%           % Cell H1 dies provided some condition about the
+%           % structure sharing of H1 is true.  A deconstruction
+%           % generating a dead cell, followed by a
+%           % construction reusing that cell, is called a direct
+%           % reuse. 
+%       H1 => [X | Xs],
+%
+%           % If the condition about the structure sharing of H1
+%           % is true then we can call the version of list__append 
+%           % which does reuse. Calling the optimised version here leads
+%           % to a new condition to be met by the headvars of any
+%           % call to the resulting optimised version of append.
+%           % This is an indirect reuse.
+%       list__append(Xs, H2, Zs),
+%
+%           % Reuse the dead cell H1.  This is a direct reuse.
+%       H3 <= [X | Zs]
+%   ).
+%
+%-----------------------------------------------------------------------------%
+
+:- module transform_hlds.ctgc.structure_reuse.analysis.
+
+:- interface.
+
+:- import_module hlds.hlds_module.
+
+:- import_module io. 
+
+:- pred structure_reuse_analysis(module_info::in, module_info::out, 
+    io::di, io::uo) is det.
+
+:- implementation.
+
+:- import_module check_hlds.goal_path.
+:- import_module hlds.hlds_pred.
+:- import_module hlds.passes_aux.
+:- import_module libs.globals.
+:- import_module libs.options.
+:- import_module parse_tree.prog_out.
+:- import_module transform_hlds.ctgc.structure_reuse.direct.
+:- import_module transform_hlds.ctgc.structure_reuse.domain.
+:- import_module transform_hlds.ctgc.structure_reuse.lbu.
+:- import_module transform_hlds.ctgc.structure_reuse.lfu.
+:- import_module transform_hlds.ctgc.structure_sharing.domain.
+
+:- import_module string.
+
+
+structure_reuse_analysis(!ModuleInfo, !IO):- 
+    globals.io_lookup_bool_option(very_verbose, VeryVerbose, !IO),
+
+    % Load all available structure sharing information into a sharing table.
+    SharingTable = load_structure_sharing_table(!.ModuleInfo),
+
+    % Load all the available reuse information into a reuse table.
+    % XXX TO DO!
+    % ReuseTable0 = load_structure_reuse_table(!.ModuleInfo), 
+   
+    % Pre-annotate each of the goals with "Local Forward Use" and
+    % "Local Backward Use" information, and fill in all the goal_path slots
+    % as well. 
+
+    maybe_write_string(VeryVerbose, "% Annotating in use information...", !IO), 
+    process_all_nonimported_procs(update_proc_io(annotate_in_use_information),
+         !ModuleInfo, !IO),
+    maybe_write_string(VeryVerbose, "done.\n", !IO),
+
+    % Determine information about possible direct reuses.
+    maybe_write_string(VeryVerbose, "% Direct reuse...\n", !IO), 
+    DummyReuseTable = reuse_as_table_init, 
+    direct_reuse_pass(SharingTable, !ModuleInfo, 
+        DummyReuseTable, _ReuseTable, !IO),
+    maybe_write_string(VeryVerbose, "% Direct reuse: done.\n", !IO).
+
+    % Determine information about possible indirect reuses.
+    % XXX TO DO!
+    % indirect_reuse_pass(SharingTable, ReuseTable1, ReuseTable2, 
+    %   !ModuleInfo, !IO), 
+
+    % For every procedure that has some potential (conditional) reuse (either 
+    % direct or indirect), create a new procedure that actually implements
+    % that reuse. 
+    % XXX TO DO!
+    % split_reuse_procedures(ReuseTable2, ReuseTable3, !ModuleInfo, !IO), 
+
+    % Record the results of the reuse table into the HLDS.
+    % XXX TO DO!
+    % map.foldl(save_reuse_in_module_info, ReuseTable3, !ModuleInfo).
+    %
+    % Output some profiling information.
+    % XXX TO DO!
+    % profiling(!.ModuleInfo, ReuseTable3).
+
+:- pred annotate_in_use_information(pred_id::in, proc_id::in,
+    module_info::in, proc_info::in, proc_info::out, io::di, io::uo) is det.
+
+annotate_in_use_information(_PredId, _ProcId, ModuleInfo, !ProcInfo, !IO) :- 
+    forward_use_information(!ProcInfo), 
+    backward_use_information(ModuleInfo, !ProcInfo),
+    goal_path.fill_goal_path_slots(ModuleInfo, !ProcInfo).
+
+
+%-----------------------------------------------------------------------------%
+
+:- func this_file = string.
+this_file = "structure_reuse.analysis.m".
+
+:- end_module transform_hlds.ctgc.structure_reuse.analysis.
Index: compiler/structure_reuse.direct.choose_reuse.m
===================================================================
RCS file: compiler/structure_reuse.direct.choose_reuse.m
diff -N compiler/structure_reuse.direct.choose_reuse.m
--- /dev/null	1 Jan 1970 00:00:00 -0000
+++ compiler/structure_reuse.direct.choose_reuse.m	27 Apr 2006 09:30:40 -0000
@@ -0,0 +1,1363 @@
+%-----------------------------------------------------------------------------%
+% vim: ft=mercury ts=4 sw=4 et
+%-----------------------------------------------------------------------------%
+% Copyright (C) 2006 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.
+%-----------------------------------------------------------------------------%
+%
+% File: structure_reuse.direct.choose_reuse.m
+% Main authors: nancy
+%
+% Given a dead cell table listing the deconstructions that may leave garbage
+% (dead cells), we compute the concrete assignements of which constructions can
+% profit of these dead cells. Obviously, we want to find those assignments
+% which result in the 'best' form of memory reuse possible for the given goals.
+%
+% Hence, the assignment problem is translated into a mapping problem (inspired
+% from Debray's paper: "On copy avoidance in single assignment languages", and
+% restricted to reuse of dead cells by at most one new cell).
+%
+% When assigning constructions to dead deconstructions, a table is first
+% computed. For each dead cell, a value is computed that reflects the gain
+% a reuse might bring, and the list of constructions involved with reusing it.
+% The cell with highest value is selected first, the according constructions
+% are annotated, and the table is recomputed. This process is repeated until
+% no reusable dead deconstructions are left. 
+%
+% The value of a dead cell (a specific deconstruction) is computed taking 
+% into account the call graph which can be simplified to take only into account
+% construction-unifications, conjunctions, and disjunctions. 
+% The source of the graph is the deconstruction, the leaves are
+% either constructions, or empty. The branches are either conjunctions
+% or disjunctions. 
+% The value of the dead cell is then computed as follows: 
+% 	- value of a conjunction = maximum of the values of each of the 
+%		conjunct branches. 
+% 		Intuitively: if a dead deconstruction is followed by
+%		two constructions which might reuse the dead cell: pick
+%		the one which allows the most potential gain. 
+%	- value of a disjunction = average of the value of each of the
+%		disjunct branches. 
+%		Intuitively: if a dead deconstruction is followed by
+% 		a disjunction with 2 disjuncts. If reuse is only possible
+% 		in one of the branches, allowing this reuse means that 
+% 		a priori reuse will occur in only 50% of the cases. 
+%		The value of the disjunct should take this into account. 
+%		Without precise notion of which branches are executed
+%		more often, taking the simple average of the values is 
+%		a good approximation. 
+%	- value of a construction = a value that takes into account
+%	 	the cost of constructing a new cell and compares it
+%		to the cost of updating a dead cell. If the arities
+%		between the dead and new cell differ, a penalty cost
+%		is added (approximated as the gain one would have had if
+%		the unusable words would have been reused too). 
+%		Weights are used to estimate all of these costs and are
+%		hard-coded. I don't think there is any need in making
+%		these values an option. 
+%
+% Once the table is computed, usually the cell with highest value is selected.
+% To cut the decision between different dead cells with the same
+% value, we select the dead cell that has the least number of
+% opportunities to be reused. 
+% E.g. 
+%	X can be reused by 5 different constructions, 
+%		but reaches its highest value for a construction C1
+%		(value 10).
+%	Y can be reused by only one construction, also C1 (value 10). 
+%
+% First selecting X (and reusing it with construction C1) would 
+% jeopardize the reuse of Y and leaves us with only one cell reused. 
+% If, on the contrary, one would select Y first, chances are that
+% after recomputing the table, X can still be reused by other
+% constructions, hence possibly 2 cells reused. 
+% Even if Y would be of smaller value, selecting Y first would still 
+% be more interesting. Hence, instead of selecting the cell 
+% with highest value, we select the cell with highest
+% value/degree ratio, degree being the number of constructions at which
+% the cell could potentially be reused. 
+%	
+% Note that cells being deconstructed in the different branches of a
+% disjunction can now also be reused after the the disjunction. 
+% e.g.:
+%	( 
+%		..., X => f(... ), ... 		% X dies
+%	; 
+%		..., X => g(... ), ... 		% X dies
+%	), 
+%	Y <= f(... ), ... 			% Y can reuse X
+% In this example, it is allowed to reuse X for Y. And it will also be
+% discovered by the analysis. 
+%
+%-----------------------------------------------------------------------------%
+:- module transform_hlds.ctgc.structure_reuse.direct.choose_reuse.
+
+:- interface.
+
+:- pred determine_reuse(strategy::in, module_info::in, proc_info::in,
+    dead_cell_table::in, hlds_goal::in, hlds_goal::out, reuse_as::out, 
+    io::di, io::uo) is det.
+
+:- implementation.
+
+:- import_module check_hlds.type_util.
+:- import_module hlds.hlds_data.
+
+:- import_module float.
+:- import_module int.
+:- import_module maybe.
+:- import_module multi_map.
+:- import_module pair.
+
+determine_reuse(Strategy, ModuleInfo, ProcInfo, DeadCellTable, 
+    !Goal, ReuseAs, !IO):-
+    % Check for local reuse:
+    process_goal(
+        background_info_init(Strategy, ModuleInfo, ProcInfo), DeadCellTable, 
+        RemainingDeadCellTable, !Goal, reuse_as_init, ReuseAs, !IO),
+
+    % Check for cell caching.
+    check_for_cell_caching(RemainingDeadCellTable, !Goal, !IO).
+     
+%-----------------------------------------------------------------------------%
+:- type background_info 
+    --->    background(
+                strategy	:: strategy,
+                module_info	:: module_info, 
+                proc_info   :: proc_info, 
+                vartypes	:: vartypes
+            ).
+
+:- func background_info_init(strategy, module_info, proc_info) = 
+    background_info.
+
+background_info_init(Strategy, ModuleInfo, ProcInfo) = Background :- 
+    proc_info_get_vartypes(ProcInfo, VarTypes),
+    Background = background(Strategy, ModuleInfo, ProcInfo, VarTypes).
+
+%-----------------------------------------------------------------------------%
+% Some types and predicates for the administration of the deconstructions,
+% constructions and the 'matches' we want to derive from them.
+%
+
+    % Details of a deconstruction yielding garbage.
+    %
+:- type deconstruction_spec
+	---> 	decon(
+			decon_var	:: prog_var, 
+			decon_pp	:: program_point, 
+			decon_cons_id	:: cons_id, 
+			decon_args	:: prog_vars, 
+			decon_conds	:: reuse_as
+		).
+
+    % Details of a construction possibly reusing some specific garbage cells
+    % generated at a deconstruction.
+    %
+:- type construction_spec 
+	---> 	con(
+			con_pp		:: program_point, 
+			con_reuse	:: reuse_type
+		).
+
+    % The reuse-type is a basic identification of whether the cons-ids involved
+    % in the reuse are the same, what the arities of the old and new cells are,
+    % and which arguments don't have to be updated. 
+    %
+:- type reuse_type 
+	---> 	reuse_type(
+			same_cons	:: bool, 	
+			reuse_fields 	:: list(needs_update),
+                % States whether the corresponding argument in the list of
+                % arguments of the reused cons needs to be updated when reused
+                % or not. 
+				% Note that list.length(reuse_fields) is the arity of the
+                % reused term.
+			tmp_value	:: float
+                % A metrics measuring the value of the reuse. A high value
+                % should represent a 'good' reuse (yielding possibly good
+                % results on the general memory behaviour of the procedure)
+                % compared to a reuse with a lower value. 
+		). 
+
+        % One match is a description of a list of deconstructions and a list of
+        % constructions. The deconstructions and constructions can all be coded
+        % into reuses, as they are such that at run-time at most one
+        % deconstruction yielding the dead cell will occur on the same
+        % execution path as a construction that
+        % can reuse that cell. 
+        % This means that all the deconstructions can be coded as
+        % deconstructions yielding dead cell, and all the constructions can be
+        % coded as constructions reusing the cell that becomes available
+        % through one of the deconstructions.
+        %
+:- type match
+    --->    match(
+                decon_specs	:: list(deconstruction_spec),
+                con_specs	:: list(construction_spec),
+                match_value	:: float,
+                match_degree	:: int
+            ).
+	
+:- type match_table == multi_map(prog_var, match).
+
+    % Initialise a deconstruction_spec.
+    %
+:- func deconstruction_spec_init(prog_var, program_point, cons_id, 
+		list(prog_var), reuse_as) = deconstruction_spec.
+deconstruction_spec_init(Var, PP, ConsId, Args, Cond) =  DS :- 
+	DS = decon(Var, PP, ConsId, Args, Cond). 
+
+    % Pre-condition: the set of variables to which the list of deconstructions
+    % relate (the dead vars) should be a singleton set. In other words, 
+    % all of the deconstructions in a match relate to one and the same
+    % dying variable. 
+    %
+:- func match_init(list(deconstruction_spec)) = match.
+match_init(DS) =  match(DS, [], 0.00, 0).
+
+    % Verify that a match is still 'empty', ie. has no constructions that
+    % can reuse the dead cell available from the deconstructions listed
+    % in the match.
+    %
+:- pred match_has_no_construction_candidates(match::in) is semidet.
+match_has_no_construction_candidates(match(_, [], _, _)).
+
+    % Determine the variable whose term is involved in the reuse if the
+    % match would be implemented. 
+    %
+:- func match_get_dead_var(match) = prog_var. 
+match_get_dead_var(Match) = Var :- 
+	GetVar = (pred(D::in, V::out) is det :- 
+			V = D ^ decon_var), 
+	list.map(GetVar, Match ^ decon_specs, DeadVars0), 
+	list.remove_dups(DeadVars0, DeadVars), 
+	(
+		DeadVars = [Var|Rest], 
+		(
+			Rest = [_|_]
+		-> 
+			unexpected(choose_reuse.this_file, "match_get_dead_var: " ++
+                "too many dead vars.")
+		;
+			true
+		)
+	; 
+		DeadVars = [], 
+		unexpected(choose_reuse.this_file, "match_get_dead_vars: " ++
+            "empty list of vars.") 
+	).
+
+    % Get the list of cons_ids that the dead variable may have when it
+    % will be reused. 
+    %
+:- func match_get_dead_cons_ids(match) = list(cons_id).
+match_get_dead_cons_ids(Match) = ConsIds :- 
+	GetConsId = (pred(D::in, C::out) is det :- 
+			C = D ^ decon_cons_id), 
+	list.map(GetConsId, Match ^ decon_specs, ConsIds). 
+
+    % Determine the reuse condition of the match. 
+    %
+:- func match_get_condition(background_info, match) = reuse_as.
+match_get_condition(Background, Match) = Condition :- 
+	GetCond = (pred(D::in, C::out) is det :- 
+			C = D ^ decon_conds),
+	list.map(GetCond, Match ^ decon_specs, Conditions), 
+	(
+		Conditions = [First | Rest], 
+		list.foldl(
+            reuse_as_least_upper_bound(Background ^ module_info, 
+                Background ^ proc_info),
+            Rest, First, Condition)
+	; 
+		Conditions = [], 
+		unexpected(choose_reuse.this_file, "match_get_condition: " ++
+            "no reuse conditions.\n")
+	). 
+
+    % Add a construction as a potential place for reusing the garbage
+    % produced by any of the deconstructions listed in the match.
+    % This changes the value of the match.
+    %
+:- pred match_add_construction(construction_spec::in, match::in, 
+		match::out) is det.
+match_add_construction(ConSpec, Match0, Match) :- 
+	Match0 = match(DeconSpecs0, ConSpecs0, Value0, Degree0), 
+	ConSpecs = [ConSpec | ConSpecs0],
+	Degree = Degree0 + 1, 
+	FDegree0 = float(Degree0), 
+	FDegree = float(Degree), 
+	Value = (Value0 * FDegree0 + ConSpec ^ con_reuse ^ tmp_value) / FDegree,
+	Match = match(DeconSpecs0, ConSpecs, Value, Degree).
+
+%-----------------------------------------------------------------------------%
+% Manipulating the values of matches... 
+%
+
+:- func highest_match_degree_ratio(match_table) = match.
+highest_match_degree_ratio(MatchTable) = Match :-
+	multi_map.values(MatchTable, Matches), 
+	list.sort(reverse_compare_matches_value_degree, 
+			Matches, Sorted), 
+	(
+		Sorted = [Match|_]
+	; 
+		Sorted = [], 
+		unexpected(choose_reuse.this_file, "highest_match_degree_ratio: " ++
+            "empty multi_map.\n")
+	). 
+
+:- pred compare_matches_value_degree(match::in, match::in, 
+		comparison_result::out) is det. 
+compare_matches_value_degree(Match1, Match2, Result) :- 
+	match_value_degree(Match1, V1), 
+	match_value_degree(Match2, V2), 
+	compare(Result, V1, V2). 
+:- pred reverse_compare_matches_value_degree(match::in, match::in,
+		comparison_result::out) is det. 
+reverse_compare_matches_value_degree(Match1, Match2, Result) :- 
+	compare_matches_value_degree(Match2, Match1, Result). 
+
+:- pred match_value_degree(match::in, float::out) is det.
+match_value_degree(Match, V) :- 
+	(
+		Match ^ match_value \= 0.00
+	-> 
+		V = Match ^ match_value / float(Match ^ match_degree)
+	;
+		V = 0.00
+	).
+
+:- pred compare_matches_value(match::in, match::in, 
+		comparison_result::out) is det.
+compare_matches_value(Match1, Match2, Result) :- 
+	V1 = Match1 ^ match_value,
+	V2 = Match2 ^ match_value,
+	compare(Result, V1, V2).
+:- pred reverse_compare_matches_value(match::in, match::in, 
+		comparison_result::out) is det.
+reverse_compare_matches_value(Match1, Match2, Result) :- 
+	compare_matches_value(Match2, Match1, Result). 
+	
+:- pred match_allows_reuse(match::in) is semidet. 
+match_allows_reuse(Match) :- 
+	Constructions = Match ^ con_specs, 
+	Value = Match ^ match_value,  
+	Constructions = [_|_], 
+	Value > 0.00.
+	
+:- pred highest_match_in_list(list(match)::in, match::in, match::out) is det.
+highest_match_in_list(Matches, Match0, Match) :- 
+	list__sort(reverse_compare_matches_value, [Match0 | Matches], Sorted), 
+	(
+		Sorted = [Match|_]
+	;
+		Sorted = [], 
+		unexpected(choose_reuse.this_file, "highest_match_in_list: " ++
+            "empty list of matches.\n")
+	).
+
+	% Given a list of matches concerning the same (list of) deconstruction,
+	% compute the average reuse value of that deconstruction. This means
+	% merging all the constructions together into one list, and using the
+	% average value of the reuses of each of the matches. The final degree
+	% of the match is set to the sum of all degrees. 
+:- pred average_match(list(match)::in, match::out) is det.
+average_match(List, AverageMatch):- 
+	(
+		List = [First|Rest], 
+		list__length(List, Length), 
+		P = (pred(M::in, Acc0::in, Acc::out) is det :- 
+			DeconSpecs = Acc0 ^ decon_specs, 
+			ConSpecs = append(Acc0 ^ con_specs, M ^ con_specs),
+			Val = Acc0 ^ match_value + M ^ match_value, 
+			Deg = Acc0 ^ match_degree + M ^ match_degree, 
+			Acc = match(DeconSpecs, ConSpecs, Val, Deg)),
+		list__foldl(P, Rest, First, Match0), 
+		AverageMatch = (Match0 ^ match_value := 
+				(Match0 ^ match_value / float(Length)))
+	; 
+		List = [], 
+		unexpected(choose_reuse.this_file, "average_match: empty list.\n")
+	). 
+			
+%-----------------------------------------------------------------------------%
+% Process one single goal:
+%   * determine a match table
+%   * find the best match
+%   * annotate the goal with the reuse described by that match
+%   * and reprocess the goal until no matches are found.
+%
+
+:- pred process_goal(background_info::in, dead_cell_table::in,
+    dead_cell_table::out, hlds_goal::in, hlds_goal::out, reuse_as::in,
+    reuse_as::out, io::di, io::uo) is det.
+
+process_goal(Background, !DeadCellTable, !Goal, !ReuseAs, !IO):-
+    globals.io_lookup_bool_option(very_verbose, VeryVerbose, !IO),
+
+        % Compute a match table.
+	compute_match_table(Background, !.DeadCellTable, !.Goal, 
+        MatchTable, !IO),  
+
+        % As long as the match table is not empty, pick out the match
+        % with the highest value, annotate the goal accordingly, and
+        % repeat the procedure. 
+        % If the match table is empty, the work is finished.
+	(
+		multi_map__is_empty(MatchTable)
+	-> 
+        true
+	;
+        % 1. select the deconstructions-constructions with
+        % highest value. 
+        Match = highest_match_degree_ratio(MatchTable),
+
+        % 2. dump all the matches recorded in the table, highlight the
+        % match with the highest value. 
+        maybe_write_string(VeryVerbose, "% Reuse results: \n", 
+            !IO), 
+        maybe_dump_match_table(VeryVerbose, MatchTable, 
+            Match, !IO), 
+
+        % 3. realise the reuses by explicitly annotating the
+        % procedure goal. 
+        annotate_reuses_in_goal(Background, Match, !Goal), 
+        % remove the deconstructions from the available map of
+        % dead cells: 
+        remove_deconstructions_from_dead_cell_table(Match, !DeadCellTable),
+
+        % 4. Add the conditions involved in the reuses to the
+        % existing conditions. 
+        reuse_as_least_upper_bound(Background ^ module_info, 
+            Background ^ proc_info, match_get_condition(Background, Match),
+            !ReuseAs), 
+        % 5. Process the goal for further reuse-matches. 
+        process_goal(Background, !DeadCellTable, !Goal, 
+            !ReuseAs, !IO)
+	). 
+
+:- pred remove_deconstructions_from_dead_cell_table(match::in, 
+    dead_cell_table::in, dead_cell_table::out) is det.
+remove_deconstructions_from_dead_cell_table(Match, !DeadCellTable):- 
+    DeconSpecs = Match ^ decon_specs, 
+    list.foldl(remove_deconstruction_from_dead_cell_table, DeconSpecs, 
+        !DeadCellTable).
+
+:- pred remove_deconstruction_from_dead_cell_table(deconstruction_spec::in,
+    dead_cell_table::in, dead_cell_table::out) is det.
+remove_deconstruction_from_dead_cell_table(DeconSpec, !DeadCellTable):- 
+    dead_cell_table_remove(DeconSpec ^ decon_pp, !DeadCellTable).
+
+%-----------------------------------------------------------------------------%
+%
+% Compute the match table for a given goal. 
+%
+% The table is computed by traversing the whole goal. For each
+% deconstruction encountered that is also listed in the dead_cell_table,
+% compute a match. 
+%
+
+:- pred compute_match_table(background_info::in, dead_cell_table::in,
+    hlds_goal::in, match_table::out, io::di, io::uo) is det.
+
+compute_match_table(Background, DeadCellTable, Goal, MatchTable, !IO) :- 
+    ContinuationGoals = [], 
+	compute_match_table_with_continuation(Background, DeadCellTable, 
+		Goal, ContinuationGoals, multi_map.init, MatchTable, !IO).
+
+:- pred compute_match_table_goal_list(background_info::in, dead_cell_table::in,
+    list(hlds_goal)::in, match_table::in, match_table::out, io::di, 
+    io::uo) is det.
+
+compute_match_table_goal_list(Background, DeadCellTable, Goals, 
+        !Table, !IO) :- 
+    (
+        Goals = []
+    ;
+        Goals = [CurrentGoal | Cont],
+        compute_match_table_with_continuation(Background, DeadCellTable,
+            CurrentGoal, Cont, !Table, !IO)
+    ).
+
+:- pred compute_match_table_with_continuation(background_info::in,
+    dead_cell_table::in, hlds_goal::in, list(hlds_goal)::in, 
+    match_table::in, match_table::out, io::di, io::uo) is det.
+
+compute_match_table_with_continuation(Background, DeadCellTable, 
+        CurrentGoal, Cont, !Table, !IO) :- 
+    CurrentGoal = GoalExpr - GoalInfo, 
+    (
+        GoalExpr = unify(_, _, _, Unification, _),
+        (
+            Unification = deconstruct(Var, ConsId, Args, _, _, _)
+        ->
+
+            ProgramPoint = program_point_init(GoalInfo),
+            (
+                Condition = dead_cell_table_search(ProgramPoint, 
+                    DeadCellTable)
+            ->
+                ReuseAs = reuse_as_init_with_one_condition(Condition), 
+                DeconstructionSpec = deconstruction_spec_init(Var, 
+                    ProgramPoint, ConsId, Args, ReuseAs),
+                Match0 = match_init([DeconstructionSpec]),
+                find_best_match_in_conjunction(Background, Cont, Match0, Match),
+                multi_map.set(!.Table, Var, Match, !:Table)
+            ;
+                true
+            )
+        ;
+            true
+        ),
+        compute_match_table_goal_list(Background, DeadCellTable, Cont, !Table,
+            !IO)
+    ;
+        GoalExpr = call(_, _, _, _, _, _),
+        compute_match_table_goal_list(Background, DeadCellTable, 
+            Cont, !Table, !IO)
+    ;
+        GoalExpr = generic_call( _, _, _, _),
+        compute_match_table_goal_list(Background, DeadCellTable, 
+            Cont, !Table, !IO)
+    ;
+        GoalExpr = foreign_proc(_, _, _, _, _, _),
+        compute_match_table_goal_list(Background, DeadCellTable, 
+            Cont, !Table, !IO)
+    ;
+        GoalExpr = conj(_, Goals),
+        list.append(Goals, Cont, NewCont),
+        compute_match_table_goal_list(Background, DeadCellTable, 
+            NewCont, !Table, !IO)
+    ;
+        GoalExpr = disj(Goals),
+        compute_match_table_in_disjunction(Background, DeadCellTable, Goals, 
+            Cont, !Table, !IO),
+        compute_match_table_goal_list(Background, DeadCellTable, Cont, !Table,
+            !IO)
+    ;
+        GoalExpr = switch(_, _, Cases),
+        compute_match_table_in_disjunction(Background, DeadCellTable, 
+            list.map(case_get_goal, Cases), Cont, !Table, !IO),
+        compute_match_table_goal_list(Background, DeadCellTable, Cont, !Table,
+            !IO)
+    ;
+        GoalExpr = not(Goal),
+        % if Goal contains deconstructions, they should not be reused within
+        % Cont. 
+        compute_match_table_with_continuation(Background, DeadCellTable, 
+            Goal, [], !Table, !IO),
+        compute_match_table_goal_list(Background, DeadCellTable, Cont, 
+            !Table, !IO)
+    ;
+        GoalExpr = scope(_, Goal),
+        compute_match_table_with_continuation(Background, DeadCellTable, 
+            Goal, Cont, !Table, !IO)
+    ;
+        GoalExpr = if_then_else(_, CondGoal, ThenGoal, ElseGoal),
+        multi_map.init(Table0), 
+        compute_match_table_with_continuation(Background, DeadCellTable, 
+            CondGoal, [ThenGoal], Table0, TableThen, !IO),
+        compute_match_table_with_continuation(Background, DeadCellTable, 
+            ElseGoal, [], Table0, TableElse, !IO),
+        multi_map.merge(TableThen, !Table), 
+        multi_map.merge(TableElse, !Table), 
+        process_possible_common_dead_vars(Background, Cont, 
+            [TableThen, TableElse], CommonDeadVarsTables, !IO),
+        list.foldl(multi_map.merge, CommonDeadVarsTables, !Table),
+        compute_match_table_goal_list(Background, DeadCellTable, Cont, 
+            !Table, !IO)
+    ;
+        GoalExpr = shorthand(_),
+        unexpected(choose_reuse.this_file, "compute_match_table: " ++
+            "shorthand goal.")
+    ).
+
+:- pred compute_match_table_in_disjs(background_info::in, dead_cell_table::in,
+    hlds_goals::in, list(match_table)::out, io::di, io::uo) is det.
+compute_match_table_in_disjs(Background, DeadCellTable, Branches, Tables, 
+        !IO) :-     
+    list.map_foldl(compute_match_table(Background, DeadCellTable),
+        Branches, Tables, !IO).
+    
+:- pred compute_match_table_in_disjunction(background_info::in,
+    dead_cell_table::in, hlds_goals::in, hlds_goals::in, 
+    match_table::in, match_table::out, io::di, io::uo) is det.  
+compute_match_table_in_disjunction(Background, DeadCellTable, DisjGoals, Cont, 
+        !Table, !IO) :-
+    % Compute a match table for each of the branches of the disjunction.
+    % Each of these tables will contain information about local reuses
+    % w.r.t. the disjunction, i.e. a data structure is reused within the
+    % same branch in which it dies. 
+    compute_match_table_in_disjs(Background, DeadCellTable, DisjGoals, 
+        DisjTables, !IO),
+    list.foldl(multi_map.merge, DisjTables, !Table),
+
+    % It is possible that each of the branches of the disjunctions
+    % deconstructs the same (non local) dead variable. In such a case, we
+    % need to check if that dead variable can be reused outside of the
+    % disjunction.
+    process_possible_common_dead_vars(Background, Cont, DisjTables,
+        CommonDeadVarsDisjTables, !IO),
+    list.foldl(multi_map.merge, CommonDeadVarsDisjTables, !Table).
+
+:- pred process_possible_common_dead_vars(background_info::in, hlds_goals::in,
+    list(match_table)::in, list(match_table)::out, io::di, io::uo) is det.
+process_possible_common_dead_vars(Background, Cont, DisjTables, 
+        ExtraTables, !IO) :- 
+    CommonDeadVars = common_vars(DisjTables),
+    (
+        CommonDeadVars = [_|_]
+    ->
+        list.filter_map(process_common_var(Background, Cont, DisjTables),
+            CommonDeadVars, ExtraTables)
+    ;
+        ExtraTables = []
+    ).
+
+:- func common_vars(list(match_table)) = list(prog_var).
+common_vars(Tables) = CommonVars :- 
+    (  
+        Tables = [ First | RestTables ],
+        CommonVars = list.foldl(common_var_with_list, RestTables, 
+            map.keys(First))
+    ;
+        Tables = [], 
+        CommonVars = []
+    ).
+
+:- func common_var_with_list(match_table, list(prog_var)) = list(prog_var).
+common_var_with_list(Table, List0) = List :- 
+    map.keys(Table, Keys),
+    Set = set.intersect(list_to_set(List0), list_to_set(Keys)), 
+    List = set.to_sorted_list(Set).
+
+:- pred process_common_var(background_info::in, hlds_goals::in,
+    list(match_table)::in, prog_var::in, match_table::out) is semidet.
+process_common_var(Background, Cont, DisjTables, CommonDeadVar, Table) :- 
+    Match0 = match_init(deconstruction_specs(CommonDeadVar, DisjTables)),
+    find_best_match_in_conjunction(Background, Cont, Match0, Match),
+    match_allows_reuse(Match), % can fail
+    multi_map.init(Table0),
+    multi_map.det_insert(Table0, CommonDeadVar, Match, Table).
+   
+:- func deconstruction_specs(prog_var, list(match_table)) = 
+    list(deconstruction_spec).
+deconstruction_specs(DeadVar, Tables) = DeconstructionSpecs :- 
+    list.foldl(deconstruction_specs_2(DeadVar), Tables, [], 
+        DeconstructionSpecs).
+
+:- pred deconstruction_specs_2(prog_var::in, match_table::in, 
+    list(deconstruction_spec)::in, list(deconstruction_spec)::out) is det.
+deconstruction_specs_2(DeadVar, Table, !DeconstructionSpecs) :- 
+    multi_map.lookup(Table, DeadVar, Matches),
+    NewSpecs = list.condense(list.map(match_get_decon_specs, Matches)),
+    append(NewSpecs, !DeconstructionSpecs).
+
+:- func match_get_decon_specs(match) = list(deconstruction_spec). 
+match_get_decon_specs(Match) = Match ^ decon_specs. 
+
+%-----------------------------------------------------------------------------%
+%
+% Find construction unifications for dead cells, compute the values of the
+% matches.
+%
+
+    % 
+    % Compute the value of a dead cel with respect to its possible reusesi in a
+    % conjunction of goals. If reuse is possible, add the specification of the
+    % construction where it can be reused to the list of constructions recorded
+    % in the match. 
+    %
+    % In a conjunction, a dead cell can only be reused in at most one of its
+    % direct childs. This means that for each child a new value is computed. At
+    % the end of a conjunction, we immediately choose the reuse with the
+    % highest value.  
+    %
+    % XXX This may not be such a good idea, as the notion of "degree" is used
+    % to decide between reuses with the same value later on, once the full
+    % match_table is computed.  
+    %
+    %
+:- pred find_best_match_in_conjunction(background_info::in, 
+    hlds_goals::in, match::in, match::out) is det.
+
+find_best_match_in_conjunction(Background, Goals, !Match) :- 
+    Match0 = !.Match,
+	list.map(find_match_in_goal(Background, Match0), Goals, ExclusiveMatches), 
+	Degree = count_candidates(ExclusiveMatches),
+    highest_match_in_list(ExclusiveMatches, !Match),
+    !:Match = !.Match ^ match_degree := Degree.
+
+    % Compute the matches for a dead cell in the context of a disjunction. For
+    % each of the branches of the disjunction, a different match may be found.
+    % At the end, these matches are merged together into one single match,
+    % taking the average of match values to be the value of the final match. 
+    % Each construction involved in the reuses is counted as a possibility for
+    % reuse, hence is reflected in the degree of the final match description.
+    %
+:- pred find_match_in_disjunction(background_info::in, hlds_goals::in,
+    match::in, match::out) is det.
+find_match_in_disjunction(Background, Branches, !Match) :- 
+    (
+        Branches = []
+    ;
+        Branches = [_|_],
+        list.map(find_match_in_goal(Background, !.Match), Branches,
+            BranchMatches),
+        average_match(BranchMatches, !:Match)
+    ).
+
+:- pred find_match_in_goal(background_info::in, match::in, hlds_goal::in,
+    match::out) is det.
+
+find_match_in_goal(Background, Match0, Goal, Match) :- 
+    find_match_in_goal_2(Background, Goal, Match0, Match).
+
+:- pred find_match_in_goal_2(background_info::in, hlds_goal::in, 
+    match::in, match::out) is det.
+
+find_match_in_goal_2(Background, Goal, !Match) :- 
+    Goal = GoalExpr - GoalInfo, 
+    (
+        GoalExpr = unify(_, _, _, Unification, _),
+        (
+            Unification = construct(Var, Cons, Args, _, _, _, _),
+                % Is the construction still looking for reuse-possibilities...
+            empty_reuse_description(goal_info_get_reuse(GoalInfo))
+
+        ->
+                % Is it possible for the construction to reuse the dead cell
+                % specified by the match?
+            verify_match(Background, Var, Cons, Args, 
+                program_point_init(GoalInfo), !Match)
+        ;
+            true
+        )
+    ;
+        GoalExpr = call(_, _, _, _, _, _)
+    ;
+        GoalExpr = generic_call( _, _, _, _)
+    ;
+        GoalExpr = foreign_proc(_, _, _, _, _, _)
+    ;
+        GoalExpr = conj(_, Goals),
+        find_best_match_in_conjunction(Background, Goals, !Match)
+    ;
+        GoalExpr = disj(Goals),
+        find_match_in_disjunction(Background, Goals, !Match)
+    ;
+        GoalExpr = switch(_, _, Cases),
+        find_match_in_disjunction(Background, list.map(case_get_goal, Cases), 
+            !Match)
+    ;
+        GoalExpr = not(_)
+    ;
+        GoalExpr = scope(_, ScopeGoal),
+        find_match_in_goal_2(Background, ScopeGoal, !Match)
+    ;
+        GoalExpr = if_then_else(_, CondGoal, ThenGoal, ElseGoal),
+        Match0 = !.Match, 
+        find_best_match_in_conjunction(Background, [CondGoal, ThenGoal], 
+            !Match),
+        find_match_in_goal_2(Background, ElseGoal, Match0, MatchElse),
+        average_match([!.Match, MatchElse], !:Match)
+    ;
+        GoalExpr = shorthand(_),
+        unexpected(choose_reuse.this_file, "find_match_in_goal: " ++
+            "shorthand goal.")
+    ).
+
+:- func count_candidates(list(match)) = int.
+count_candidates(Matches) = list.foldl(add_degree, Matches, 0).
+
+:- func add_degree(match, int) = int. 
+add_degree(Match, Degree0) = Degree0 + Match ^ match_degree.
+
+:- pred empty_reuse_description(reuse_description::in) is semidet.
+empty_reuse_description(empty).
+
+%-----------------------------------------------------------------------------%
+% Verify the value of a match for a given construction.
+%
+% The value is computed using the following rule: 
+%
+% Gain = (Alfa + Gamma) * ArityNewCell + Beta
+%		- Gamma * (ArityNewCell - UptoDateFields)
+%		- Alfa * (ArityOldCell - ArityNewCell)
+%
+% where
+% * Alfa: cost of allocating one single memory cell on the heap; 
+% * Gamma: cost of setting the value of one single memory cell on the heap; 
+% * Beta: cost of setting the value of the cons_id field; 
+
+:- func alfa_value = int is det.
+:- func gamma_value = int is det.
+:- func beta_value = int is det.
+alfa_value = 5. 
+gamma_value = 1.
+beta_value = 1. 
+
+:- pred verify_match(background_info::in, prog_var::in, cons_id::in, 
+    list(prog_var)::in, program_point::in, match::in, match::out) is det.
+verify_match(Background, NewVar, NewCons, NewArgs, PP, !Match) :- 
+    DeconSpecs = !.Match ^ decon_specs, 
+    list.filter_map(compute_reuse_type(Background, NewVar, NewCons, NewArgs),
+        DeconSpecs, ReuseTypes),
+    (
+        ReuseType = glb_reuse_types(ReuseTypes) % Can Fail.
+    ->
+        ConSpec = con(PP, ReuseType),
+        match_add_construction(ConSpec, !Match)
+    ;
+        true
+    ).
+
+    % compute_reuse_type(Background, NewVar, NewCons, NewArgs, 
+    %   DeconstructionSpecification) = Cost (represented as a reuse_type).
+    %
+    % Compute a description (including its cost) of reusing the 
+    % specified deconstruction for the construction of the new var (NewVar),
+    % with cons_id NewCons, and arguments NewArgs.
+    %
+    % The predicate fails if the construction is incompatible with the
+    % deconstructed dead data structure.
+    %
+:- pred compute_reuse_type(background_info::in, prog_var::in, cons_id::in,
+    list(prog_var)::in, deconstruction_spec::in, 
+    reuse_type::out) is semidet.
+	
+compute_reuse_type(Background, NewVar, NewCons, NewCellArgs, DeconSpec, 
+			ReuseType) :- 
+	DeconSpec = decon(DeadVar, _, DeadCons, DeadCellArgs, _),
+
+	ModuleInfo = Background ^ module_info, 
+	Vartypes   = Background ^ vartypes, 
+	NewArity = list.length(NewCellArgs), 
+	DeadArity = list.length(DeadCellArgs), 
+
+    % Cells with arity zero can not reuse heap cells. 
+    NewArity \= 0, 
+
+	% The new cell must not be bigger than the dead cell. 
+	NewArity =< DeadArity,
+
+	% Verify wether the cons_ids and arities match the reuse constraint
+    % specified by the user. 
+	Constraint = Background ^ strategy, 
+	DiffArity = DeadArity - NewArity, 
+	( NewCons = DeadCons -> SameCons = yes ; SameCons = no), 
+	( 
+		Constraint = within_n_cells_difference(N),
+		DiffArity =< N
+	; 
+		Constraint = same_cons_id, 
+		SameCons = yes
+	),
+
+    % Upon success of all the previous checks, determine the number of
+    % fields that do not require an update if the construction unification 
+    % would reuse the deconstructed cell. 
+    %
+	has_secondary_tag(ModuleInfo, Vartypes, NewVar, 
+		NewCons, SecTag), 
+	has_secondary_tag(ModuleInfo, Vartypes, DeadVar, 
+		DeadCons, DeadSecTag), 
+	ReuseFields = already_correct_fields(SecTag, NewCellArgs, 
+		DeadSecTag - DeadCellArgs),
+	UpToDateFields = list.length(
+		list.delete_all(ReuseFields, needs_update)),
+
+	%
+	% Finally, compute the value of this reuse-configuration.
+    %
+	( SameCons = yes -> SameConsV = 0; SameConsV = 1),
+
+	Weight = ( (alfa_value + gamma_value) * NewArity + beta_value
+		- gamma_value * (NewArity - UpToDateFields)
+		- beta_value * SameConsV
+		- alfa_value * DiffArity ),
+	Weight > 0,
+	ReuseType = reuse_type(SameCons, ReuseFields, float(Weight)).
+
+
+:- func glb_reuse_types(list(reuse_type)) = reuse_type is semidet.
+
+glb_reuse_types([First|Rest]) = 
+	list.foldl(glb_reuse_types_2, Rest, First).
+
+:- func glb_reuse_types_2(reuse_type, reuse_type) = reuse_type.
+
+glb_reuse_types_2(R1, R2) = R :- 
+	R1 = reuse_type(SameCons1, Fields1, V1),
+	R2 = reuse_type(SameCons2, Fields2, V2),
+	R = reuse_type(SameCons1 `and` SameCons2, Fields1 `ands` Fields2, 
+		(V1 + V2) / 2.00 ).
+
+:- func ands(list(needs_update), list(needs_update)) = list(needs_update). 
+ands(L1, L2) = L :- 
+	(
+		length(L1) =< length(L2)
+	-> 
+		L1b = L1, 
+		L2b = take_upto(length(L1), L2)
+	;
+		L1b = take_upto(length(L2), L1),
+		L2b = L2
+	),
+	L = list.map_corresponding(needs_update_and, L1b, L2b).
+
+:- func needs_update_and(needs_update, needs_update) = needs_update.
+needs_update_and(needs_update, needs_update) = needs_update.
+needs_update_and(needs_update, does_not_need_update) = needs_update.
+needs_update_and(does_not_need_update, needs_update) = needs_update.
+needs_update_and(does_not_need_update, does_not_need_update) = 
+    does_not_need_update.
+	
+
+%-----------------------------------------------------------------------------%
+        %
+        % has_secondary_tag(Var, ConsId, HasSecTag) is true iff the
+        % variable, Var, with cons_id, ConsId, requires a remote
+        % secondary tag to distinguish between its various functors.
+        %
+:- pred has_secondary_tag(module_info::in, vartypes::in,
+                prog_var::in, cons_id::in, bool::out) is det.
+
+has_secondary_tag(ModuleInfo, VarTypes, Var, ConsId, SecondaryTag) :- 
+	(
+		map.lookup(VarTypes, Var, Type),
+        type_util.type_to_type_defn_body(ModuleInfo, Type, TypeBody),
+        TypeBody = du_type(_, ConsTagValues, _, _, _, _),
+        map.search(ConsTagValues, ConsId, ConsTag),
+        MaybeSecondaryTag = get_secondary_tag(ConsTag), 
+        MaybeSecondaryTag = yes(_)
+	->
+		SecondaryTag = yes
+	;
+		SecondaryTag = no
+	).
+
+	%
+	% already_correct_fields(HasSecTagC, VarsC, HasSecTagR - VarsR)
+    % takes a list of variables, VarsC, which are the arguments for the cell to
+    % be constructed and the list of variables, VarsR, which are the arguments
+    % for the cell to be reused and returns a list of 'needs_update' values.
+    % Each occurrence of 'does_not_need_update' indicates that the argument at
+    % the corresponding position in the list of arguments already has the
+    % correct value stored in it.  To do this correctly we
+    % need to know whether each cell has a secondary tag field.
+	%
+:- func already_correct_fields(bool, prog_vars,
+		pair(bool, prog_vars)) = list(needs_update).
+
+already_correct_fields(SecTagC, CurrentCellVars, SecTagR - ReuseCellVars)
+	    = NeedsNoUpdate ++ list.duplicate(LengthC - LengthB, needs_update) :-
+	NeedsNoUpdate = already_correct_fields_2(SecTagC, CurrentCellVars,
+		SecTagR, ReuseCellVars),
+	LengthC = list.length(CurrentCellVars),
+	LengthB = list.length(NeedsNoUpdate).
+
+:- func already_correct_fields_2(bool, prog_vars, bool, prog_vars) 
+    = list(needs_update).
+
+already_correct_fields_2(yes, CurrentCellVars, yes, ReuseCellVars)
+	= equals(CurrentCellVars, ReuseCellVars).
+already_correct_fields_2(yes, CurrentCellVars, no, ReuseCellVars)
+	= [needs_update | equals(CurrentCellVars, drop_one(ReuseCellVars))].
+already_correct_fields_2(no, CurrentCellVars, yes, ReuseCellVars) 
+	= [needs_update | equals(drop_one(CurrentCellVars), ReuseCellVars)].
+already_correct_fields_2(no, CurrentCellVars, no, ReuseCellVars) 
+	= equals(CurrentCellVars, ReuseCellVars).
+
+	%
+	% equals(ListA, ListB) produces a list of 'needs_update' that indicates
+    % whether the corresponding elements from ListA and ListB are equal.  If
+    % ListA and ListB are of different lengths, the resulting list is the
+    % length of the shorter of the two.
+	%
+:- func equals(list(T), list(T)) = list(needs_update).
+
+equals([], []) = [].
+equals([], [_|_]) = [].
+equals([_|_], []) = [].
+equals([X | Xs], [Y | Ys]) = [NeedsUpdate | equals(Xs, Ys)] :-
+	( X = Y ->
+		NeedsUpdate = does_not_need_update
+	;
+		NeedsUpdate = needs_update
+	).
+
+:- func drop_one(list(T)) = list(T).
+
+drop_one([]) = [].
+drop_one([_ | Xs]) = Xs.
+
+
+%-----------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
+%
+    % Once a match is selected (hence a set of deconstructions and matching
+    % constructions), annotate all the involved unifications in the goal.
+    %
+:- pred annotate_reuses_in_goal(background_info::in, match::in, hlds_goal::in, 
+    hlds_goal::out) is det.
+
+annotate_reuses_in_goal(Background, Match, !Goal) :- 
+    !.Goal = GoalExpr0 - GoalInfo0, 
+    (
+        GoalExpr0 = unify(_, _, _, Unification, _),
+        GoalExpr = GoalExpr0, 
+        annotate_reuse_for_unification(Background, Match, Unification, 
+            GoalInfo0, GoalInfo)
+    ;
+        GoalExpr0 = call(_, _, _, _, _, _),
+        GoalExpr = GoalExpr0, 
+        GoalInfo = GoalInfo0
+    ;
+        GoalExpr0 = generic_call( _, _, _, _),
+        GoalExpr = GoalExpr0, 
+        GoalInfo = GoalInfo0
+    ;
+        GoalExpr0 = foreign_proc(_, _, _, _, _, _),
+        GoalExpr = GoalExpr0, 
+        GoalInfo = GoalInfo0
+    ;
+        GoalExpr0 = conj(A, Goals0),
+        list.map(annotate_reuses_in_goal(Background, Match), Goals0, Goals),
+        GoalExpr = conj(A, Goals),
+        GoalInfo = GoalInfo0
+    ;
+        GoalExpr0 = disj(Goals0),
+        list.map(annotate_reuses_in_goal(Background, Match), Goals0, Goals),
+        GoalExpr = disj(Goals),
+        GoalInfo = GoalInfo0
+    ;
+        GoalExpr0 = switch(A, B, Cases0),
+        list.map(annotate_reuses_in_case(Background, Match), Cases0, Cases),
+        GoalExpr = switch(A, B, Cases),
+        GoalInfo = GoalInfo0
+    ;
+        GoalExpr0 = not(_),
+        GoalExpr = GoalExpr0, 
+        GoalInfo = GoalInfo0
+    ;
+        GoalExpr0 = scope(A, ScopeGoal0),
+        annotate_reuses_in_goal(Background, Match, ScopeGoal0, ScopeGoal),
+        GoalExpr = scope(A, ScopeGoal),
+        GoalInfo = GoalInfo0
+    ;
+        GoalExpr0 = if_then_else(A, CondGoal0, ThenGoal0, ElseGoal0),
+        annotate_reuses_in_goal(Background, Match, CondGoal0, CondGoal),
+        annotate_reuses_in_goal(Background, Match, ThenGoal0, ThenGoal), 
+        annotate_reuses_in_goal(Background, Match, ElseGoal0, ElseGoal),
+        GoalExpr = if_then_else(A, CondGoal, ThenGoal, ElseGoal),
+        GoalInfo = GoalInfo0
+    ;
+        GoalExpr0 = shorthand(_),
+        unexpected(choose_reuse.this_file, "annotate_reuses: " ++
+            "shorthand goal.")
+    ),
+    !:Goal = GoalExpr - GoalInfo.
+
+:- pred annotate_reuses_in_case(background_info::in, match::in, 
+    case::in, case::out) is det.
+annotate_reuses_in_case(Background, Match, !Case) :-
+    !.Case = case(A, Goal0),
+    annotate_reuses_in_goal(Background, Match, Goal0, Goal), 
+    !:Case = case(A, Goal).
+
+:- pred annotate_reuse_for_unification(background_info::in, 
+    match::in, unification::in, 
+    hlds_goal_info::in, hlds_goal_info::out) is det.
+annotate_reuse_for_unification(Background, Match, Unification, !GoalInfo):- 
+    CurrentProgramPoint = program_point_init(!.GoalInfo),
+    (
+        Unification = deconstruct(_, _, _, _, _, _),
+        (
+            match_find_deconstruction_spec(Match, CurrentProgramPoint, 
+                _DeconSpec)
+        -> 
+            goal_info_set_reuse(potential_reuse(cell_died), !GoalInfo)
+        ;
+            true
+        )
+    ;
+        Unification = construct(_, _, _, _, _, _, _),
+        (   
+            match_find_construction_spec(Match, CurrentProgramPoint, ConSpec)
+        ->
+            DeadVar = match_get_dead_var(Match),
+            DeadConsIds = match_get_dead_cons_ids(Match),
+            ReuseAs = match_get_condition(Background, Match),
+            ReuseFields = ConSpec ^ con_reuse ^ reuse_fields,
+
+            (
+                reuse_as_conditional_reuses(ReuseAs)
+            -> 
+                Kind = conditional_reuse
+            ;
+                reuse_as_all_unconditional_reuses(ReuseAs)
+            ->
+                Kind = unconditional_reuse
+            ;
+                % reuse_as_no_reuses(ReuseAs)
+                unexpected(choose_reuse.this_file, 
+                    "annotate_reuse_for_unification: no reuse conditions!")
+            ),
+            CellReused = cell_reused(DeadVar, Kind, DeadConsIds, 
+                ReuseFields),
+           
+            (
+                Kind = conditional_reuse,
+                KindReuse = potential_reuse(CellReused)
+            ;
+                % When the reuse is unconditional, we can safely annotate
+                % that the unification is always a reuse unification.
+                Kind = unconditional_reuse, 
+                KindReuse = reuse(CellReused)
+            ),
+            goal_info_set_reuse(KindReuse, !GoalInfo)
+        ;
+            true
+        )
+    ;
+        Unification = assign(_, _)
+    ;
+        Unification = simple_test(_, _)
+    ;
+        Unification = complicated_unify(_, _, _),
+        unexpected(choose_reuse.this_file, 
+            "annotate_reuse_for_unification: complicated_unify.")
+    ).
+
+:- pred match_find_deconstruction_spec(match::in, program_point::in, 
+    deconstruction_spec::out) is semidet.
+match_find_deconstruction_spec(Match, ProgramPoint, DeconstructionSpec) :-
+    list.filter(deconstruction_spec_with_program_point(ProgramPoint),
+        Match ^ decon_specs, [DeconstructionSpec]).
+
+:- pred match_find_construction_spec(match::in, program_point::in, 
+    construction_spec::out) is semidet.
+match_find_construction_spec(Match, ProgramPoint, ConstructionSpec) :-
+    list.filter(construction_spec_with_program_point(ProgramPoint),
+        Match ^ con_specs, [ConstructionSpec]).
+
+:- pred deconstruction_spec_with_program_point(program_point::in, 
+    deconstruction_spec::in) is semidet.
+deconstruction_spec_with_program_point(DeconstructionSpec ^ decon_pp, 
+    DeconstructionSpec).
+
+:- pred construction_spec_with_program_point(program_point::in, 
+    construction_spec::in) is semidet.
+construction_spec_with_program_point(ConstructionSpec ^ con_pp,
+    ConstructionSpec).
+
+%-----------------------------------------------------------------------------%
+% Predicates to print intermediate results as stored in a match_table.
+%
+
+:- func line_length = int. 
+line_length = 79.
+
+:- pred dump_line(string::in, io::di, io::uo) is det.
+dump_line(Msg, !IO) :- 
+	Prefix = "%---", 
+	Start = string.append(Prefix, Msg), 
+	Remainder = line_length - string.length(Start) - 1, 
+	Line = Start ++ string.duplicate_char('-', Remainder),
+	io.write_string(Line, !IO),
+	io.write_string("%\n", !IO).
+	
+:- pred maybe_dump_match_table(bool::in, match_table::in, match::in,
+		io::di, io::uo) is det.
+
+maybe_dump_match_table(VeryVerbose, MatchTable, HighestMatch, !IO) :- 
+	(
+		VeryVerbose = yes
+	->
+		dump_line("reuse table", !IO), 
+		io.write_string("%\t|\tvar\t|\tvalue\t|\tdegree\n", !IO),
+		dump_match("%-sel- ", HighestMatch, !IO),
+		dump_full_table(MatchTable, !IO),
+		dump_line("", !IO)
+	;
+		true
+	).
+
+:- pred dump_match(string::in, match::in, io::di, io::uo) is det.
+dump_match(Prefix, Match, !IO):- 
+	io.write_string(Prefix, !IO), 
+	io.write_string("\t|\t", !IO),
+	io.write_int(term.var_to_int(match_get_dead_var(Match)), !IO),
+	io.write_string("\t|\t", !IO),
+	Val = Match ^ match_value, 
+	(
+		Val \= 0.00 
+	-> 	
+		io.format("%.2f", [f(Val)], !IO)
+	; 
+		io.write_string("-", !IO)
+	),
+	Degree = Match ^ match_degree, 
+	io.write_string("\t|\t", !IO),
+	io.write_int(Degree, !IO),
+	io.write_string("\t", !IO), 
+	dump_match_details(Match, !IO),
+	io.nl(!IO).
+
+:- pred dump_match_details(match::in, io::di, io::uo) is det.
+dump_match_details(Match, !IO) :- 
+	Conds = list.map(
+		(func(DeconSpec) = Cond :- 
+			Cond = DeconSpec ^ decon_conds), 
+			Match ^ decon_specs),
+	(
+		list.takewhile(
+            reuse_as_all_unconditional_reuses, 
+			Conds, _, [])
+	-> 
+		CondsString = "A"
+	;
+		CondsString = "C"
+	), 
+
+	D = list.length(Match ^ decon_specs), 
+	C = list.length(Match ^ con_specs), 
+	string.append_list(["d: ", int_to_string(D), ", c: ", 
+		int_to_string(C), 
+		", Co: ", CondsString], Details), 
+	io.write_string(Details, !IO).
+
+:- pred dump_full_table(match_table::in, io::di, io::uo) is det.
+dump_full_table(MatchTable, !IO) :- 
+	(
+		multi_map.is_empty(MatchTable)
+	-> 
+		dump_line("empty match table", !IO)
+	; 
+		dump_line("full table (start)", !IO), 
+		multi_map.values(MatchTable, Matches), 
+		list.foldl(dump_match("%-----"), Matches, !IO),
+		dump_line("full table (end)", !IO)
+	).
+
+:- pred maybe_dump_full_table(bool::in, match_table::in, io::di,
+		io::uo) is det.
+maybe_dump_full_table(no, _M, !IO).
+maybe_dump_full_table(yes, M, !IO) :- dump_full_table(M, !IO).
+
+%-----------------------------------------------------------------------------%
+    % After determining all local reuses of dead datastructures (a data
+    % structure becomes dead and is reused in one and the same procedure), we
+    % determine the 'global reuses': deconstructions that yield dead data
+    % structures, without imposing any reuse constraints are annotated so that
+    % these cells can be cached whenever the user specifies that option. 
+    %
+:- pred check_for_cell_caching(dead_cell_table::in, hlds_goal::in, 
+    hlds_goal::out, io::di, io::uo) is det.
+
+check_for_cell_caching(DeadCellTable0, !Goal, !IO) :- 
+    dead_cell_table_remove_conditionals(DeadCellTable0, DeadCellTable),
+	globals__io_lookup_bool_option(very_verbose, VeryVerbose, !IO),
+    (
+        \+ dead_cell_table_is_empty(DeadCellTable)
+    -> 
+        maybe_write_string(VeryVerbose, "% Marking cacheable cells.\n", !IO),
+        check_cc(DeadCellTable, !Goal)
+    ;
+        maybe_write_string(VeryVerbose, "% No cells to be cached.\n", !IO)
+    ).
+
+:- pred check_cc(dead_cell_table::in, hlds_goal::in, hlds_goal::out) is det.
+check_cc(DeadCellTable, !Goal):- 
+    !.Goal = GoalExpr0 - GoalInfo0, 
+    (
+        GoalExpr0 = unify(A, B, C, Unification0, D),
+        check_cc_for_unification(DeadCellTable, 
+            Unification0, Unification, GoalInfo0, GoalInfo),
+        GoalExpr = unify(A, B, C, Unification, D)
+    ;
+        GoalExpr0 = call(_, _, _, _, _, _),
+        GoalExpr = GoalExpr0, 
+        GoalInfo = GoalInfo0
+    ;
+        GoalExpr0 = generic_call( _, _, _, _),
+        GoalExpr = GoalExpr0, 
+        GoalInfo = GoalInfo0
+    ;
+        GoalExpr0 = foreign_proc(_, _, _, _, _, _),
+        GoalExpr = GoalExpr0, 
+        GoalInfo = GoalInfo0
+    ;
+        GoalExpr0 = conj(A, Goals0),
+        list.map(check_cc(DeadCellTable), Goals0, Goals),
+        GoalExpr = conj(A, Goals),
+        GoalInfo = GoalInfo0
+    ;
+        GoalExpr0 = disj(Goals0),
+        list.map(check_cc(DeadCellTable), Goals0, Goals),
+        GoalExpr = disj(Goals),
+        GoalInfo = GoalInfo0
+    ;
+        GoalExpr0 = switch(A, B, Cases0),
+        list.map(check_cc_in_case(DeadCellTable), Cases0, Cases),
+        GoalExpr = switch(A, B, Cases),
+        GoalInfo = GoalInfo0
+    ;
+        GoalExpr0 = not(_),
+        GoalExpr = GoalExpr0, 
+        GoalInfo = GoalInfo0
+    ;
+        GoalExpr0 = scope(A, ScopeGoal0),
+        check_cc(DeadCellTable, ScopeGoal0, ScopeGoal),
+        GoalExpr = scope(A, ScopeGoal),
+        GoalInfo = GoalInfo0
+    ;
+        GoalExpr0 = if_then_else(A, CondGoal0, ThenGoal0, ElseGoal0),
+        check_cc(DeadCellTable, CondGoal0, CondGoal),
+        check_cc(DeadCellTable, ThenGoal0, ThenGoal), 
+        check_cc(DeadCellTable, ElseGoal0, ElseGoal),
+        GoalExpr = if_then_else(A, CondGoal, ThenGoal, ElseGoal),
+        GoalInfo = GoalInfo0
+    ;
+        GoalExpr0 = shorthand(_),
+        unexpected(choose_reuse.this_file, "check_cc: " ++
+            "shorthand goal.")
+    ),
+    !:Goal = GoalExpr - GoalInfo.
+
+:- pred check_cc_in_case(dead_cell_table::in, case::in, case::out) is det.
+check_cc_in_case(DeadCellTable, !Case) :-
+    !.Case = case(A, Goal0),
+    check_cc(DeadCellTable, Goal0, Goal), 
+    !:Case = case(A, Goal).
+
+:- pred check_cc_for_unification(dead_cell_table::in,
+    unification::in, unification::out, 
+    hlds_goal_info::in, hlds_goal_info::out) is det.
+
+check_cc_for_unification(DeadCellTable, !Unification, !GoalInfo):- 
+    (
+        !.Unification = deconstruct(A, B, C, D, E, _),
+        Condition = dead_cell_table_search(program_point_init(!.GoalInfo), 
+            DeadCellTable),
+        \+ reuse_condition_is_conditional(Condition)
+    -> 
+        !:Unification = deconstruct(A, B, C, D, E, can_cgc),
+        ReuseInfo = potential_reuse(cell_died),
+        goal_info_set_reuse(ReuseInfo, !GoalInfo)
+    ;
+        true
+    ).
+%-----------------------------------------------------------------------------%
+:- func this_file = string.
+this_file = "structure_reuse.direct.choose_reuse.m". 
+
+:- end_module transform_hlds.ctgc.structure_reuse.direct.choose_reuse.
+

-- 
nancy.mazur at cs.kuleuven.ac.be ------------ Katholieke Universiteit Leuven -
tel: +32-16-327596 - fax: +32-16-327996 ------- Dept. of Computer Science -

Disclaimer: http://www.kuleuven.be/cwis/email_disclaimer.htm

--------------------------------------------------------------------------
mercury-reviews mailing list
post:  mercury-reviews at cs.mu.oz.au
administrative address: owner-mercury-reviews at cs.mu.oz.au
unsubscribe: Address: mercury-reviews-request at cs.mu.oz.au Message: unsubscribe
subscribe:   Address: mercury-reviews-request at cs.mu.oz.au Message: subscribe
--------------------------------------------------------------------------



More information about the reviews mailing list