[m-rev.] diff: [CTGC] perform variable renaming on imported answers

Peter Wang novalazy at gmail.com
Mon Jul 28 13:10:55 AEST 2008


Branches: main

In structure sharing and structure reuse analyses, we weren't renaming
variables from imported `sharing_as' and `reuse_as' structures to match the
variable names used in the current compiler run.  It was only by luck if a
particular variable number referred to the same thing in an imported answer
as in the procedure being analysed.

We *were* doing it for `--transitive-' and `--intermodule-optimisation'
but not for `--intermodule-analysis'.

compiler/structure_reuse.analysis.m:
compiler/structure_sharing.analysis.m:
	Change structure sharing and reuse answers to store
	`structure_sharing_domain', `structure_reuse_domain' structures instead
	of `sharing_as' and `reuse_as' structures.

	Rename the variables from imported answers.

	Bump analysis versions.

compiler/structure_sharing.domain.m:
	Hide `sharing_as' again as we no longer need it outside this module.

tests/analysis/ctgc/reuse_runtest.sh:
	Update test cases for changed answer formats.

diff --git a/compiler/structure_reuse.analysis.m b/compiler/structure_reuse.analysis.m
index 34fdabc..11f7e09 100644
--- a/compiler/structure_reuse.analysis.m
+++ b/compiler/structure_reuse.analysis.m
@@ -553,7 +553,8 @@ process_intermod_analysis_imported_reuse_answer(PPId, PredInfo, ProcInfo,
         ImportedResult, !ModuleInfo, !ReuseTable) :-
     ImportedResult = analysis_result(Call, Answer, ResultStatus),
     Call = structure_reuse_call(NoClobbers),
-    structure_reuse_answer_to_domain(PredInfo, ProcInfo, Answer, Domain),
+    pred_info_get_arg_types(PredInfo, HeadVarTypes),
+    structure_reuse_answer_to_domain(HeadVarTypes, ProcInfo, Answer, Domain),
     ReuseAs = from_structure_reuse_domain(Domain),
     ReuseAs_Status = reuse_as_and_status(ReuseAs, ResultStatus),
     (
@@ -573,11 +574,11 @@ process_intermod_analysis_imported_reuse_answer(PPId, PredInfo, ProcInfo,
             !ReuseTable)
     ).
 
-:- pred structure_reuse_answer_to_domain(pred_info::in,
+:- pred structure_reuse_answer_to_domain(list(mer_type)::in,
     proc_info::in, structure_reuse_answer::in, structure_reuse_domain::out)
     is det.
 
-structure_reuse_answer_to_domain(PredInfo, ProcInfo, Answer, Reuse) :-
+structure_reuse_answer_to_domain(HeadVarTypes, ProcInfo, Answer, Reuse) :-
     (
         Answer = structure_reuse_answer_no_reuse,
         Reuse = has_no_reuse
@@ -586,14 +587,12 @@ structure_reuse_answer_to_domain(PredInfo, ProcInfo, Answer, Reuse) :-
         Reuse = has_only_unconditional_reuse
     ;
         Answer = structure_reuse_answer_conditional(ImpHeadVars, ImpTypes,
-            ImpReuseAs),
+            ImpReuseConditions),
         proc_info_get_headvars(ProcInfo, HeadVars),
-        pred_info_get_arg_types(PredInfo, HeadVarTypes),
         map.from_corresponding_lists(ImpHeadVars, HeadVars, VarRenaming),
         ( type_unify_list(ImpTypes, HeadVarTypes, [], map.init, TypeSubst) ->
-            ImpReuseDomain = to_structure_reuse_domain(ImpReuseAs),
             rename_structure_reuse_domain(VarRenaming, TypeSubst,
-                ImpReuseDomain, Reuse)
+                has_conditional_reuse(ImpReuseConditions), Reuse)
         ;
             unexpected(this_file,
                 "structure_reuse_answer_to_domain: type_unify_list failed")
@@ -757,15 +756,19 @@ write_proc_reuse_info(ModuleInfo, PredId, PredInfo, ProcTable, PredOrFunc,
     --->    structure_reuse_answer_no_reuse
     ;       structure_reuse_answer_unconditional
     ;       structure_reuse_answer_conditional(
-                prog_vars,
-                list(mer_type),
-                reuse_as
+                srac_vars   :: prog_vars,
+                srac_types  :: list(mer_type),
+                srac_conds  :: structure_reuse_conditions
+                % We cannot keep this as a reuse_as.  When the analysis answers
+                % are loaded, we don't have enough information to rename the
+                % variables in the .analysis answer to the correct variables
+                % for the proc_info that the reuse_as will be used with.
             ).
 
 :- type structure_reuse_func_info
     --->    structure_reuse_func_info(
-                module_info,
-                proc_info
+                srfi_module :: module_info,
+                srfi_proc   :: proc_info
             ).
 
 :- func analysis_name = string.
@@ -776,7 +779,7 @@ analysis_name = "structure_reuse".
     structure_reuse_answer) where
 [
     analysis_name(_, _) = analysis_name,
-    analysis_version_number(_, _) = 2,
+    analysis_version_number(_, _) = 3,
     preferred_fixpoint_type(_, _) = greatest_fixpoint,
     bottom(_, _) = structure_reuse_answer_no_reuse,
     ( top(_, _) = _ :-
@@ -836,10 +839,18 @@ analysis_name = "structure_reuse".
             Answer1 = structure_reuse_answer_unconditional,
             Answer2 = structure_reuse_answer_no_reuse
         ;
-            Answer1 = structure_reuse_answer_conditional(_, _, ReuseAs1),
-            Answer2 = structure_reuse_answer_conditional(_, _, ReuseAs2),
-            % XXX can we implement this more efficiently?
+            Answer1 = structure_reuse_answer_conditional(_, _, _),
+            Answer2 = structure_reuse_answer_conditional(_, _, _),
             FuncInfo = structure_reuse_func_info(ModuleInfo, ProcInfo),
+            proc_info_get_headvars(ProcInfo, HeadVars),
+            proc_info_get_vartypes(ProcInfo, VarTypes),
+            map.apply_to_list(HeadVars, VarTypes, HeadVarTypes),
+            structure_reuse_answer_to_domain(HeadVarTypes, ProcInfo, Answer1,
+                Reuse1),
+            structure_reuse_answer_to_domain(HeadVarTypes, ProcInfo, Answer2,
+                Reuse2),
+            ReuseAs1 = from_structure_reuse_domain(Reuse1),
+            ReuseAs2 = from_structure_reuse_domain(Reuse2),
             reuse_as_subsumed_by(ModuleInfo, ProcInfo, ReuseAs1, ReuseAs2),
             not reuse_as_subsumed_by(ModuleInfo, ProcInfo, ReuseAs2, ReuseAs1)
         )
@@ -849,10 +860,18 @@ analysis_name = "structure_reuse".
         (
             Answer1 = Answer2
         ;
-            Answer1 = structure_reuse_answer_conditional(_, _, ReuseAs1),
-            Answer2 = structure_reuse_answer_conditional(_, _, ReuseAs2),
-            % XXX can we implement this more efficiently?
+            Answer1 = structure_reuse_answer_conditional(_, _, _),
+            Answer2 = structure_reuse_answer_conditional(_, _, _),
             FuncInfo = structure_reuse_func_info(ModuleInfo, ProcInfo),
+            proc_info_get_headvars(ProcInfo, HeadVars),
+            proc_info_get_vartypes(ProcInfo, VarTypes),
+            map.apply_to_list(HeadVars, VarTypes, HeadVarTypes),
+            structure_reuse_answer_to_domain(HeadVarTypes, ProcInfo, Answer1,
+                Reuse1),
+            structure_reuse_answer_to_domain(HeadVarTypes, ProcInfo, Answer2,
+                Reuse2),
+            ReuseAs1 = from_structure_reuse_domain(Reuse1),
+            ReuseAs2 = from_structure_reuse_domain(Reuse2),
             reuse_as_subsumed_by(ModuleInfo, ProcInfo, ReuseAs2, ReuseAs1),
             reuse_as_subsumed_by(ModuleInfo, ProcInfo, ReuseAs1, ReuseAs2)
         )
@@ -874,13 +893,13 @@ reuse_answer_to_term(Answer) = Term :-
         Answer = structure_reuse_answer_unconditional,
         Term = term.functor(atom("uncond"), [], term.context_init)
     ;
-        Answer = structure_reuse_answer_conditional(HeadVars, Types, ReuseAs),
-        ReuseDomain = to_structure_reuse_domain(ReuseAs),
+        Answer = structure_reuse_answer_conditional(HeadVars, Types,
+            Conditions),
         type_to_term(HeadVars, HeadVarsTerm),
         type_to_term(Types, TypesTerm),
-        type_to_term(ReuseDomain, ReuseDomainTerm),
+        type_to_term(Conditions, ConditionsTerm),
         Term = term.functor(atom("cond"),
-            [HeadVarsTerm, TypesTerm, ReuseDomainTerm], term.context_init)
+            [HeadVarsTerm, TypesTerm, ConditionsTerm], term.context_init)
     ).
 
 :- pred reuse_answer_from_term(term::in, structure_reuse_answer::out)
@@ -895,12 +914,12 @@ reuse_answer_from_term(Term, Answer) :-
         Answer = structure_reuse_answer_unconditional
     ;
         Term = functor(atom("cond"),
-            [HeadVarsTerm, TypesTerm, ReuseDomainTerm], _),
+            [HeadVarsTerm, TypesTerm, ConditionsTerm], _),
         term_to_type(HeadVarsTerm, HeadVars),
         term_to_type(TypesTerm, Types),
-        term_to_type(ReuseDomainTerm, ReuseDomain),
-        ReuseAs = from_structure_reuse_domain(ReuseDomain),
-        Answer = structure_reuse_answer_conditional(HeadVars, Types, ReuseAs)
+        term_to_type(ConditionsTerm, Conditions),
+        Answer = structure_reuse_answer_conditional(HeadVars, Types,
+            Conditions)
     ).
 
 %-----------------------------------------------------------------------------%
@@ -952,20 +971,21 @@ record_structure_reuse_results_2(ModuleInfo, PPId, NoClobbers, ReuseAs_Status,
     reuse_as::in, structure_reuse_answer::out) is det.
 
 reuse_as_to_structure_reuse_answer(ModuleInfo, PPId, ReuseAs, Answer) :-
-    ( reuse_as_no_reuses(ReuseAs) ->
+    Reuse = to_structure_reuse_domain(ReuseAs),
+    (
+        Reuse = has_no_reuse,
          Answer = structure_reuse_answer_no_reuse
-     ; reuse_as_all_unconditional_reuses(ReuseAs) ->
+    ;
+        Reuse = has_only_unconditional_reuse,
          Answer = structure_reuse_answer_unconditional
-     ; reuse_as_conditional_reuses(ReuseAs) ->
-         module_info_pred_proc_info(ModuleInfo, PPId, _PredInfo,
-             ProcInfo),
+    ;
+        Reuse = has_conditional_reuse(Conditions),
+        module_info_proc_info(ModuleInfo, PPId, ProcInfo),
          proc_info_get_headvars(ProcInfo, HeadVars),
          proc_info_get_vartypes(ProcInfo, VarTypes),
          map.apply_to_list(HeadVars, VarTypes, HeadVarTypes),
-         Answer = structure_reuse_answer_conditional(HeadVars,
-             HeadVarTypes, ReuseAs)
-     ;
-         unexpected(this_file, "reuse_as_to_structure_reuse_answer")
+        Answer = structure_reuse_answer_conditional(HeadVars, HeadVarTypes,
+            Conditions)
      ).
 
 :- pred handle_structure_reuse_dependency(module_info::in,
diff --git a/compiler/structure_sharing.analysis.m b/compiler/structure_sharing.analysis.m
index 580b1c8..348a739 100644
--- a/compiler/structure_sharing.analysis.m
+++ b/compiler/structure_sharing.analysis.m
@@ -285,8 +285,9 @@ process_intermod_analysis_imported_sharing_in_proc(ModuleInfo, AnalysisInfo,
         (
             MaybeBestResult = yes(analysis_result(_Call, Answer,
                 ResultStatus)),
-            structure_sharing_answer_to_domain(PPId, PredInfo, !.ProcInfo,
-                Answer, Sharing),
+            pred_info_get_arg_types(PredInfo, HeadVarTypes),
+            structure_sharing_answer_to_domain(yes(PPId), HeadVarTypes,
+                !.ProcInfo, Answer, Sharing),
             proc_info_set_structure_sharing(
                 structure_sharing_domain_and_status(Sharing, ResultStatus),
                 !ProcInfo),
@@ -296,29 +297,35 @@ process_intermod_analysis_imported_sharing_in_proc(ModuleInfo, AnalysisInfo,
         )
     ).
 
-:- pred structure_sharing_answer_to_domain(pred_proc_id::in, pred_info::in,
-    proc_info::in, structure_sharing_answer::in, structure_sharing_domain::out)
-    is det.
+:- pred structure_sharing_answer_to_domain(maybe(pred_proc_id)::in,
+    list(mer_type)::in, proc_info::in, structure_sharing_answer::in,
+    structure_sharing_domain::out) is det.
 
-structure_sharing_answer_to_domain(PPId, PredInfo, ProcInfo, Answer, Sharing)
-        :-
+structure_sharing_answer_to_domain(MaybePPId, HeadVarTypes, ProcInfo, Answer,
+        Sharing) :-
     (
         Answer = structure_sharing_answer_bottom,
         Sharing = structure_sharing_bottom
     ;
         Answer = structure_sharing_answer_top,
-        Sharing = structure_sharing_top(set.make_singleton_set(
-            top_from_lookup(shroud_pred_proc_id(PPId))))
+        (
+            MaybePPId = yes(PPId),
+            TopReason = set.make_singleton_set(
+                top_from_lookup(shroud_pred_proc_id(PPId)))
+        ;
+            MaybePPId = no,
+            TopReason = set.init
+        ),
+        Sharing = structure_sharing_top(TopReason)
     ;
         Answer = structure_sharing_answer_real(ImpHeadVars, ImpTypes,
-            ImpSharingAs),
+            ImpSharingPairs),
         proc_info_get_headvars(ProcInfo, HeadVars),
-        pred_info_get_arg_types(PredInfo, HeadVarTypes),
         map.from_corresponding_lists(ImpHeadVars, HeadVars, VarRenaming),
         ( type_unify_list(ImpTypes, HeadVarTypes, [], map.init, TypeSubst) ->
-            ImpSharingDomain = to_structure_sharing_domain( ImpSharingAs),
-            rename_structure_sharing_domain(VarRenaming, TypeSubst,
-                ImpSharingDomain, Sharing)
+            rename_structure_sharing(VarRenaming, TypeSubst, ImpSharingPairs,
+                SharingPairs),
+            Sharing = structure_sharing_real(SharingPairs)
         ;
             unexpected(this_file,
                 "structure_sharing_answer_to_domain: type_unify_list failed")
@@ -1003,15 +1010,20 @@ write_proc_sharing_info(ModuleInfo, PredId, PredInfo, ProcTable, PredOrFunc,
     --->    structure_sharing_answer_bottom
     ;       structure_sharing_answer_top
     ;       structure_sharing_answer_real(
-                prog_vars,
-                list(mer_type),
-                sharing_as
+                ssar_vars       :: prog_vars,
+                ssar_types      :: list(mer_type),
+                ssar_sharing    :: structure_sharing
+                % We cannot keep this as a sharing_as.  When the analysis
+                % answers are loaded, we don't have enough information to
+                % rename the variables in the .analysis answer to the correct
+                % variables for the proc_info that the sharing_as will be used
+                % with.
             ).
 
 :- type structure_sharing_func_info
     --->    structure_sharing_func_info(
-                module_info,
-                proc_info
+                ssfi_module     :: module_info,
+                ssfi_proc       :: proc_info
             ).
 
 :- func analysis_name = string.
@@ -1022,7 +1034,7 @@ analysis_name = "structure_sharing".
     structure_sharing_answer) where
 [
     analysis_name(_, _) = analysis_name,
-    analysis_version_number(_, _) = 1,
+    analysis_version_number(_, _) = 2,
     preferred_fixpoint_type(_, _) = greatest_fixpoint,
     bottom(_, _) = structure_sharing_answer_bottom,
     top(_, _) = structure_sharing_answer_top,
@@ -1063,10 +1075,16 @@ analysis_name = "structure_sharing".
         % Fast path (maybe).
         Answer1 \= Answer2,
 
-        % XXX can we implement this more efficiently?
         FuncInfo = structure_sharing_func_info(ModuleInfo, ProcInfo),
-        SharingAs1 = structure_sharing_answer_to_sharing_as(Answer1),
-        SharingAs2 = structure_sharing_answer_to_sharing_as(Answer2),
+        proc_info_get_headvars(ProcInfo, HeadVars),
+        proc_info_get_vartypes(ProcInfo, VarTypes),
+        map.apply_to_list(HeadVars, VarTypes, HeadVarTypes),
+        structure_sharing_answer_to_domain(no, HeadVarTypes, ProcInfo,
+            Answer1, Sharing1),
+        structure_sharing_answer_to_domain(no, HeadVarTypes, ProcInfo,
+            Answer2, Sharing2),
+        SharingAs1 = from_structure_sharing_domain(Sharing1),
+        SharingAs2 = from_structure_sharing_domain(Sharing2),
         sharing_as_is_subsumed_by(ModuleInfo, ProcInfo,
             SharingAs1, SharingAs2),
         not sharing_as_is_subsumed_by(ModuleInfo, ProcInfo,
@@ -1079,9 +1097,15 @@ analysis_name = "structure_sharing".
             Answer1 = Answer2
         ;
             FuncInfo = structure_sharing_func_info(ModuleInfo, ProcInfo),
-            SharingAs1 = structure_sharing_answer_to_sharing_as(Answer1),
-            SharingAs2 = structure_sharing_answer_to_sharing_as(Answer2),
-            % XXX can we implement this more efficiently?
+            proc_info_get_headvars(ProcInfo, HeadVars),
+            proc_info_get_vartypes(ProcInfo, VarTypes),
+            map.apply_to_list(HeadVars, VarTypes, HeadVarTypes),
+            structure_sharing_answer_to_domain(no, HeadVarTypes, ProcInfo,
+                Answer1, Sharing1),
+            structure_sharing_answer_to_domain(no, HeadVarTypes, ProcInfo,
+                Answer2, Sharing2),
+            SharingAs1 = from_structure_sharing_domain(Sharing1),
+            SharingAs2 = from_structure_sharing_domain(Sharing2),
             sharing_as_is_subsumed_by(ModuleInfo, ProcInfo,
                 SharingAs2, SharingAs1),
             sharing_as_is_subsumed_by(ModuleInfo, ProcInfo,
@@ -1090,21 +1114,6 @@ analysis_name = "structure_sharing".
     )
 ].
 
-:- func structure_sharing_answer_to_sharing_as(structure_sharing_answer) =
-    sharing_as.
-
-structure_sharing_answer_to_sharing_as(Answer) = SharingAs :-
-    (
-        Answer = structure_sharing_answer_bottom,
-        SharingAs = sharing_as_init
-    ;
-        Answer = structure_sharing_answer_top,
-        % No feedback is okay because we won't be using it.
-        SharingAs = sharing_as_top_no_feedback
-    ;
-        Answer = structure_sharing_answer_real(_, _, SharingAs)
-    ).
-
 :- instance to_term(structure_sharing_answer) where [
     func(to_term/1) is sharing_answer_to_term,
     pred(from_term/2) is sharing_answer_from_term
@@ -1120,13 +1129,12 @@ sharing_answer_to_term(Answer) = Term :-
         Answer = structure_sharing_answer_top,
         Term = term.functor(atom("t"), [], context_init)
     ;
-        Answer = structure_sharing_answer_real(HeadVars, Types, SharingAs),
-        SharingDomain = to_structure_sharing_domain(SharingAs),
+        Answer = structure_sharing_answer_real(HeadVars, Types, SharingPairs),
         type_to_term(HeadVars, HeadVarsTerm),
         type_to_term(Types, TypesTerm),
-        type_to_term(SharingDomain, SharingDomainTerm),
+        type_to_term(SharingPairs, SharingPairsTerm),
         Term = term.functor(atom("sharing"),
-            [HeadVarsTerm, TypesTerm, SharingDomainTerm], context_init)
+            [HeadVarsTerm, TypesTerm, SharingPairsTerm], context_init)
     ).
 
 :- pred sharing_answer_from_term(term::in, structure_sharing_answer::out)
@@ -1141,12 +1149,11 @@ sharing_answer_from_term(Term, Answer) :-
         Answer = structure_sharing_answer_top
     ;
         Term = term.functor(atom("sharing"),
-            [HeadVarsTerm, TypesTerm, SharingDomainTerm], _),
+            [HeadVarsTerm, TypesTerm, SharingPairsTerm], _),
         term_to_type(HeadVarsTerm, HeadVars),
         term_to_type(TypesTerm, Types),
-        term_to_type(SharingDomainTerm, SharingDomain),
-        SharingAs = from_structure_sharing_domain(SharingDomain),
-        Answer = structure_sharing_answer_real(HeadVars, Types, SharingAs)
+        term_to_type(SharingPairsTerm, SharingPairs),
+        Answer = structure_sharing_answer_real(HeadVars, Types, SharingPairs)
     ).
 
 %-----------------------------------------------------------------------------%
@@ -1183,25 +1190,25 @@ maybe_record_sharing_analysis_result_2(ModuleInfo, SharingAsTable, PredId,
             sharing_as_table_search(PPId, SharingAsTable,
                 sharing_as_and_status(SharingAsPrime, StatusPrime))
         ->
-            SharingAs = SharingAsPrime,
+            Sharing = to_structure_sharing_domain(SharingAsPrime),
             Status0 = StatusPrime
         ;
             % Probably an exported `:- external' procedure.
             bottom_sharing_is_safe_approximation(ModuleInfo, PredInfo,
                 ProcInfo)
         ->
-            SharingAs = sharing_as_bottom,
+            Sharing = structure_sharing_bottom,
             Status0 = optimal
         ;
-            SharingAs = sharing_as_top(set.init),
+            Sharing = structure_sharing_top(set.init),
             Status0 = optimal
         ),
         (
-            SharingAs = sharing_as_bottom,
+            Sharing = structure_sharing_bottom,
             Answer = structure_sharing_answer_bottom,
             Status = optimal
         ;
-            SharingAs = sharing_as_top(Reasons),
+            Sharing = structure_sharing_top(Reasons),
             Answer = structure_sharing_answer_top,
             % If the procedure contains a generic or foreign foreign call, or
             % it calls a procedure in a non-local module for which we have no
@@ -1229,12 +1236,12 @@ maybe_record_sharing_analysis_result_2(ModuleInfo, SharingAsTable, PredId,
                 io.nl(!IO)
             )
         ;
-            SharingAs = sharing_as_real_as(_),
+            Sharing = structure_sharing_real(SharingPairs),
             proc_info_get_headvars(ProcInfo, HeadVars),
             proc_info_get_vartypes(ProcInfo, VarTypes),
             map.apply_to_list(HeadVars, VarTypes, HeadVarTypes),
             Answer = structure_sharing_answer_real(HeadVars, HeadVarTypes,
-                SharingAs),
+                SharingPairs),
             Status = Status0
         ),
         module_name_func_id(ModuleInfo, PPId, ModuleName, FuncId),
diff --git a/compiler/structure_sharing.domain.m b/compiler/structure_sharing.domain.m
index 5998229..17ff275 100644
--- a/compiler/structure_sharing.domain.m
+++ b/compiler/structure_sharing.domain.m
@@ -324,19 +324,11 @@
 
 %-----------------------------------------------------------------------------%
 
-:- interface.
-
-    % The intention was for this type to be hidden, but we need to expose it
-    % for structure_sharing.m to convert between `structure_sharing_answer'
-    % and `sharing_as'.
-    %
 :- type sharing_as
     --->    sharing_as_real_as(sharing_set)
     ;       sharing_as_bottom
     ;       sharing_as_top(set(top_feedback)).
 
-:- implementation.
-
 %-----------------------------------------------------------------------------%
 
 sharing_as_init = sharing_as_bottom.
diff --git a/tests/analysis/ctgc/reuse_runtest.sh b/tests/analysis/ctgc/reuse_runtest.sh
index cf39299..f4a6058 100755
--- a/tests/analysis/ctgc/reuse_runtest.sh
+++ b/tests/analysis/ctgc/reuse_runtest.sh
@@ -17,7 +17,7 @@ $MMCMAKE reuse_m1.analyse --analysis-repeat 0 || failed
 
 check_result reuse_m1 "reuse.*main.*\[\].*no_reuse"
 check_result reuse_m2 "reuse.*fiddle2.*\[\].*no_reuse"
-check_result reuse_m3 "reuse.*fiddle3.*\[\].*conditional_reuse"
+check_result reuse_m3 "reuse.*fiddle3.*\[\].*reuse_condition"
 check_statuses "optimal.suboptimal.optimal."
 check_no_requests
 
@@ -26,8 +26,8 @@ check_no_requests
 $MMCMAKE reuse_m1.analyse --analysis-repeat 1 || failed
 
 check_result reuse_m1 "_reuse.*main.*\[\].*no_reuse"
-check_result reuse_m2 "_reuse.*fiddle2.*\[\].*conditional_reuse"
-check_result reuse_m3 "_reuse.*fiddle3.*\[\].*conditional_reuse"
+check_result reuse_m2 "_reuse.*fiddle2.*\[\].*reuse_condition"
+check_result reuse_m3 "_reuse.*fiddle3.*\[\].*reuse_condition"
 check_statuses "optimal.optimal.optimal."
 check_request reuse_m2 "reuse_m1.*_reuse.*fiddle2.*\[1\]"
 check_imdg reuse_m2 "reuse_m1.*reuse.*fiddle2.*\[\]"
@@ -38,10 +38,10 @@ check_imdg reuse_m3 "reuse_m2.*reuse.*fiddle3.*\[\]"
 $MMCMAKE reuse_m1.analyse --analysis-repeat 1 || failed
 
 check_result reuse_m1 "_reuse.*main.*\[\].*no_reuse"
-check_result reuse_m2 "_reuse.*fiddle2.*\[\].*conditional_reuse"
+check_result reuse_m2 "_reuse.*fiddle2.*\[\].*reuse_condition"
 check_result reuse_m2 "_reuse.*fiddle2.*\[1\].*no_reuse"
-check_result reuse_m3 "_reuse.*fiddle3.*\[\].*conditional_reuse"
-check_result reuse_m3 "_reuse.*fiddle3.*\[1\].*conditional_reuse"
+check_result reuse_m3 "_reuse.*fiddle3.*\[\].*reuse_condition"
+check_result reuse_m3 "_reuse.*fiddle3.*\[1\].*reuse_condition"
 check_statuses "optimal.suboptimal.optimal."
 check_no_requests
 check_imdg reuse_m2 "reuse_m1.*reuse.*fiddle2.*\[\]"
@@ -52,10 +52,10 @@ check_imdg reuse_m3 "reuse_m2.*reuse.*fiddle3.*\[\]"
 $MMCMAKE reuse_m1.analyse --analysis-repeat 1 || failed
 
 check_result reuse_m1 "_reuse.*main.*\[\].*uncond"
-check_result reuse_m2 "_reuse.*fiddle2.*\[\].*conditional_reuse"
-check_result reuse_m2 "_reuse.*fiddle2.*\[1\].*conditional_reuse"
-check_result reuse_m3 "_reuse.*fiddle3.*\[\].*conditional_reuse"
-check_result reuse_m3 "_reuse.*fiddle3.*\[1\].*conditional_reuse"
+check_result reuse_m2 "_reuse.*fiddle2.*\[\].*reuse_condition"
+check_result reuse_m2 "_reuse.*fiddle2.*\[1\].*reuse_condition"
+check_result reuse_m3 "_reuse.*fiddle3.*\[\].*reuse_condition"
+check_result reuse_m3 "_reuse.*fiddle3.*\[1\].*reuse_condition"
 check_statuses "optimal.optimal.optimal."
 check_no_requests
 check_imdg reuse_m2 "reuse_m1.*reuse.*fiddle2.*\[\]"


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