[m-rev.] For post-commit review: Automatic parallelism changes.

Paul Bone pbone at csse.unimelb.edu.au
Sat Oct 16 15:13:10 AEDT 2010


For post commit review.

---

Make variable use analysis assume that the compiler cannot push signals or
waits for futures across module boundaries, which is usually true.

Add a new option to the feedback tool
--implicit-parallelism-intermodule-var-use.  This option re-enables the old
behaviour.

Fix a number of bugs and improve the pretty-printing of candidate parallel
conjunctions.

deep_profiler/var_use_analysis.m:
    Implement the new behaviour and allow it to be controlled.

    Refactor some code to slightly reduce the number of arguments passed to
    predicates.

deep_profiler/mdprof_feedback.m:
    Implement the new command line option.

    Conform to changes in feedback.automatic_parallelism.m.

deep_profiler/recursion_patterns.m:
    Fixed a bug in the handling of can-fail switches.

deep_profiler/mdprof_fb.automatic_parallelism.m:
    Fix a bug in the calculation of dependency graphs.  All goals are
    represented by vertexes and dependencies are edges.  The program failed to
    create a vertex for a goal that had no edges.

    Fix a crash when trying to compute variable use information for a goal that
    is never called.  This was triggered by providing the new variable use
    information in the feedback format.

    Using the extra feedback information improve the pretty-printing of
    candidate parallelisations.

    Conform to changes in feedback.automatic_parallelism.m
    
    Conform to changes in var_use_analysis.m

mdbcomp/feedback.automatic_parallelism.m:
    Add the new option to control intermodule variable use analysis.

    Provided more information in the candidate parallel conjunctions feedback.

        The costs of the goals before and after the parallel conjunction are
        now provided.

        The cost of every goal is now provided (not just calls)

        Variable production and consumption times of the shared variables are
        provided for each goal if the analysis evaluated them.

    Modified convert_candidate_par_conjunctions_proc/3 and
    convert_candidate_par_conjunction/3 to pass a reference to the current
    parallel conjunction to their higher order argument.

mdbcomp/feedback.m:
    Increment feedback file version number.

deep_profiler/program_representation_utils.m:
    Improve the pretty-printing of goal representations, in particular, their
    annotations.

deep_profiler/create_report.m:
    Conform to changes in var_use_analysis.m.

deep_profiler/display_report.m:
    Conform to changes in program_representation_utils.m.

library/lazy.m:
    Added a new predicate, read_if_val(Lazy, Value) which is true of Lazy has
    already been forced and produced Value.
    (No update to NEWS necessary).

Index: deep_profiler/create_report.m
===================================================================
RCS file: /home/mercury1/repository/mercury/deep_profiler/create_report.m,v
retrieving revision 1.27
diff -u -p -b -r1.27 create_report.m
--- deep_profiler/create_report.m	11 Oct 2010 00:49:24 -0000	1.27
+++ deep_profiler/create_report.m	16 Oct 2010 04:07:06 -0000
@@ -1426,8 +1426,10 @@ call_site_dynamic_var_use_arg(Deep, CSDP
         HeadVar, MaybeUseAndName, !ArgNum) :-
     HeadVar = head_var_rep(Var, Mode),
     var_mode_to_var_use_type(Mode, UseType),
-    call_site_dynamic_var_use_info(Deep, CSDPtr, !.ArgNum, RecursionType, 
-        Cost, UseType, MaybeUse),
+    % XXX: Allow user to configure var use options.
+    UseOptions = var_use_options(Deep, follow_any_call, UseType),
+    call_site_dynamic_var_use_info(CSDPtr, !.ArgNum, RecursionType, 
+        Cost, UseOptions, MaybeUse),
     (
         MaybeUse = ok(Use),
         lookup_var_name(VarTable, Var, Name),
Index: deep_profiler/display_report.m
===================================================================
RCS file: /home/mercury1/repository/mercury/deep_profiler/display_report.m,v
retrieving revision 1.30
diff -u -p -b -r1.30 display_report.m
--- deep_profiler/display_report.m	7 Oct 2010 02:38:09 -0000	1.30
+++ deep_profiler/display_report.m	16 Oct 2010 04:07:06 -0000
@@ -2021,15 +2021,16 @@ display_report_procrep_coverage_info(Pre
     Display = display(yes(Title), [CoverageInfoItem] ++ Controls).
 
 :- instance goal_annotation(coverage_info) where [
-        pred(print_goal_annotation_to_strings/2) is coverage_to_cord_string
+        pred(print_goal_annotation_to_strings/3) is coverage_to_cord_string
     ].
 
     % Print the coverage information for a goal, this is used by
     % print_proc_to_strings.
     %
-:- pred coverage_to_cord_string(coverage_info::in, cord(string)::out) is det.
+:- pred coverage_to_cord_string(var_table::in, coverage_info::in, 
+    cord(cord(string))::out) is det.
 
-coverage_to_cord_string(Coverage, cord.singleton(String)) :-
+coverage_to_cord_string(_, Coverage, singleton(singleton(String))) :-
     (
         Coverage = coverage_unknown,
         String0 = "_ - _"
Index: deep_profiler/mdprof_fb.automatic_parallelism.m
===================================================================
RCS file: /home/mercury1/repository/mercury/deep_profiler/mdprof_fb.automatic_parallelism.m,v
retrieving revision 1.19
diff -u -p -b -r1.19 mdprof_fb.automatic_parallelism.m
--- deep_profiler/mdprof_fb.automatic_parallelism.m	14 Oct 2010 04:02:22 -0000	1.19
+++ deep_profiler/mdprof_fb.automatic_parallelism.m	16 Oct 2010 04:07:06 -0000
@@ -122,28 +122,56 @@ candidate_parallel_conjunctions(Params, 
             ConjunctionsAssocList),
     put_feedback_data(CandidateParallelConjunctions, !Feedback).
 
-:- pred pard_goal_detail_to_pard_goal(pard_goal_detail::in, pard_goal::out) 
-    is det.
+:- pred pard_goal_detail_to_pard_goal(
+    candidate_par_conjunction(pard_goal_detail)::in,
+    pard_goal_detail::in, pard_goal::out) is det.
 
-pard_goal_detail_to_pard_goal(!Goal) :-
-    transform_goal_rep(pard_goal_detail_annon_to_pard_goal_annon, !Goal).
+pard_goal_detail_to_pard_goal(CPC, !Goal) :-
+    IsDependent = CPC ^ cpc_is_dependent,
+    (
+        IsDependent = conjuncts_are_dependent(SharedVars)
+    ;
+        IsDependent = conjuncts_are_independent,
+        SharedVars = set.init
+    ),
+    transform_goal_rep(pard_goal_detail_annon_to_pard_goal_annon(SharedVars), 
+        !Goal).
 
-:- pred pard_goal_detail_annon_to_pard_goal_annon(
+:- pred pard_goal_detail_annon_to_pard_goal_annon(set(var_rep)::in,
     pard_goal_detail_annotation::in, pard_goal_annotation::out) is det.
 
-pard_goal_detail_annon_to_pard_goal_annon(PGD, PG) :-
-    PGT = PGD ^ pgd_pg_type,
-    (
-        PGT = pgt_call(_, _),
+pard_goal_detail_annon_to_pard_goal_annon(SharedVarsSet, PGD, PG) :-
         CostPercall = goal_cost_get_percall(PGD ^ pgd_cost),
         CostAboveThreshold = PGD ^ pgd_cost_above_threshold,
-        PG = pard_goal_call(CostPercall, CostAboveThreshold)
+    SharedVars = to_sorted_list(SharedVarsSet),
+   
+    Coverage = PGD ^ pgd_coverage,
+    get_coverage_before_det(Coverage, Calls),
+    ( Calls > 0 ->
+        foldl(build_var_use_list(PGD ^ pgd_var_production_map), SharedVars, 
+            [], Productions),
+        foldl(build_var_use_list(PGD ^ pgd_var_consumption_map), SharedVars, 
+            [], Consumptions)
     ;
-        PGT = pgt_other_atomic_goal,
-        PG = pard_goal_other_atomic
+        Productions = [],
+        Consumptions = []
+    ),
+
+    PG = pard_goal_annotation(CostPercall, CostAboveThreshold, Productions,
+        Consumptions).
+
+:- pred build_var_use_list(map(var_rep, lazy(var_use_info))::in, var_rep::in,
+    assoc_list(var_rep, float)::in, assoc_list(var_rep, float)::out) is det.
+
+build_var_use_list(Map, Var, !List) :-
+    (
+        map.search(Map, Var, LazyUse),
+        read_if_val(LazyUse, Use)
+    ->
+        UseTime = Use ^ vui_cost_until_use,
+        !:List = [Var - UseTime | !.List]
     ;
-        PGT = pgt_non_atomic_goal,
-        PG = pard_goal_non_atomic
+        true
     ).
 
 %----------------------------------------------------------------------------%
@@ -894,9 +922,13 @@ pardgoals_build_candidate_conjunction(In
     BestParallelisation = bp_parallel_execution(GoalsBefore, ParConjs,
         GoalsAfter, IsDependent, Metrics),
     Speedup = parallel_exec_metrics_get_speedup(Metrics),
+    conj_calc_cost(GoalsBefore, GoalsBeforeCost0),
+    GoalsBeforeCost = goal_cost_get_percall(GoalsBeforeCost0),
+    conj_calc_cost(GoalsAfter, GoalsAfterCost0),
+    GoalsAfterCost = goal_cost_get_percall(GoalsAfterCost0),
     Candidate = candidate_par_conjunction(goal_path_to_string(GoalPath),
-        FirstConjNum, IsDependent, GoalsBefore, ParConjs, GoalsAfter,
-        Metrics),
+        FirstConjNum, IsDependent, GoalsBefore, GoalsBeforeCost, ParConjs,
+        GoalsAfter, GoalsAfterCost, Metrics),
     (
         Speedup > 1.0,
         (
@@ -2048,9 +2080,12 @@ build_dependency_graph([PG | PGs], ConjN
     % and not those that are set.  This is safe because we only bother
     % analysing single assignment code.
     RefedVars = InstMapInfo ^ im_consumed_vars,
+    digraph.add_vertex(ConjNum, ThisConjKey, !Graph),
     list.foldl((pred(RefedVar::in, GraphI0::in, GraphI::out) is det :-
         map.search(!.VarDepMap, RefedVar, DepConj) ->
-            digraph.add_vertices_and_edge(DepConj, ConjNum, GraphI0, GraphI)
+            % DepConj should already be in the graph.
+            digraph.lookup_key(GraphI0, DepConj, DepConjKey),
+            digraph.add_edge(DepConjKey, ThisConjKey, GraphI0, GraphI)
         ;
             GraphI = GraphI0
         ), to_sorted_list(RefedVars), !Graph),
@@ -2397,6 +2432,7 @@ earliest_use(A, B, Ealiest) :-
     var_use_info::out) is multi.
 
 compute_var_use_lazy_arg(Info, Var, Args, CostAndCallee, Cost, VarUseType, Use) :-
+    ( 0.0 < cs_cost_get_calls(Cost) ->
     CostPercall = cs_cost_get_percall(Cost),
     ( member_index0(Var, Args, ArgNum) ->
         HigherOrder = CostAndCallee ^ cac_call_site_is_ho,
@@ -2427,6 +2463,10 @@ compute_var_use_lazy_arg(Info, Var, Args
         Use = var_use_info(0.0, CostPercall, VarUseType),
         require(unify(VarUseType, var_use_consumption), this_file ++ 
             "Var use type most be consumption if \\+ member(Var, Args)")
+        )
+    ;
+        % This call site is never called.
+        pessimistic_var_use_info(VarUseType, 0.0, Use)
     ).
 
 :- pred compute_var_use_2(implicit_parallelism_info::in, int::in,
@@ -2439,8 +2479,11 @@ compute_var_use_2(Info, ArgNum, Recursio
     !:Messages = empty,
     Deep = Info ^ ipi_deep,
     CliquePtr = Info ^ ipi_clique,
-    call_site_dynamic_var_use_info(Deep, CliquePtr, CSDPtr, ArgNum,
-        RecursionType, MaybeCurDepth, Cost, set.init, VarUseType, MaybeUse),
+    implicit_par_info_intermodule_var_use(Info, FollowCallsAcrossModules),
+    VarUseOptions = var_use_options(Deep, FollowCallsAcrossModules,
+        VarUseType),
+    call_site_dynamic_var_use_info(CliquePtr, CSDPtr, ArgNum,
+        RecursionType, MaybeCurDepth, Cost, set.init, VarUseOptions, MaybeUse),
     (
         MaybeUse = ok(Use)
     ;
@@ -2477,9 +2520,12 @@ compute_goal_var_use_lazy(Goal, GoalPath
         ),
         recursion_type_get_interesting_parallelisation_depth(RecursionType,
             yes(RecDepth)),
-        var_first_use(Deep, CliquePtr, CallSiteMap, RecursiveCallSiteMap,
+        implicit_par_info_intermodule_var_use(Info, FollowCallsAcrossModules),
+        VarUseOptions = var_use_options(Deep, FollowCallsAcrossModules,
+            VarUseType),
+        var_first_use(CliquePtr, CallSiteMap, RecursiveCallSiteMap,
             RecursionType, RecDepth, Goal, GoalPath, CostPercall, Var,
-            VarUseType, Use)
+            VarUseOptions, Use)
     ;
         ( RecursionType = rt_divide_and_conquer(_, _)
         ; RecursionType = rt_mutual_recursion(_)
@@ -2501,6 +2547,23 @@ compute_goal_var_use_lazy(Goal, GoalPath
         (get_coverage(Goal) = Goal ^ goal_annotation ^ cai_coverage)
     ].
 
+:- pred implicit_par_info_intermodule_var_use(implicit_parallelism_info::in,
+    intermodule_var_use::out) is det.
+
+implicit_par_info_intermodule_var_use(Info, FollowCallsAcrossModules) :-
+    IntermoduleVarUse = Info ^ ipi_opts ^ cpcp_intermodule_var_use,
+    (
+        IntermoduleVarUse = yes,
+        FollowCallsAcrossModules = follow_any_call
+    ;
+        IntermoduleVarUse = no,
+        ProcLabel = Info ^ ipi_proc_label,
+        ( ProcLabel = str_ordinary_proc_label(_, _, Module, _, _, _)
+        ; ProcLabel = str_special_proc_label(_, _, Module, _, _, _)
+        ),
+        FollowCallsAcrossModules = follow_calls_into_module(Module)
+    ).
+
 :- pred recursion_type_get_interesting_parallelisation_depth(
     recursion_type, maybe(recursion_depth)).
 :- mode recursion_type_get_interesting_parallelisation_depth(
@@ -3123,8 +3186,8 @@ create_candidate_parallel_conj_report(Va
         Report) :-
     print_proc_label_to_string(Proc, ProcString),
     CandidateParConjunction = candidate_par_conjunction(GoalPathString,
-        FirstConjNum, IsDependent, GoalsBefore, Conjs, GoalsAfter,
-        ParExecMetrics),
+        FirstConjNum, IsDependent, GoalsBefore, GoalsBeforeCost, Conjs,
+        GoalsAfter, GoalsAfterCost, ParExecMetrics),
     ParExecMetrics = parallel_exec_metrics(NumCalls, SeqTime, ParTime,
         ParOverheads, FirstConjDeadTime, FutureDeadTime),
     
@@ -3174,18 +3237,25 @@ create_candidate_parallel_conj_report(Va
     ),
     some [!ConjNum] (
         !:ConjNum = FirstConjNum,
-        format_sequential_conjuncts(VarTable, 3, GoalPath, GoalsBefore, 
-            !ConjNum, empty, ReportGoalsBefore),
-        format_parallel_conjunction(VarTable, 3, GoalPath, !.ConjNum, Conjs,
-            ReportParConj),
+        format_sequential_conjunction(VarTable, 4, GoalPath, GoalsBefore, 
+            GoalsBeforeCost, !.ConjNum, ReportGoalsBefore0),
+        ReportGoalsBefore = indent(3) ++ singleton("Goals before:\n") ++
+            ReportGoalsBefore0,
+        
+        !:ConjNum = !.ConjNum + length(GoalsBefore),
+        format_parallel_conjunction(VarTable, 4, GoalPath, !.ConjNum, Conjs,
+            ReportParConj0),
+        ReportParConj = indent(3) ++ singleton("Parallel conjunction:\n") ++
+            ReportParConj0,
+        
         !:ConjNum = !.ConjNum + 1,
-        format_sequential_conjuncts(VarTable, 3, GoalPath, GoalsAfter,
-            !ConjNum, empty, ReportGoalsAfter),
-        _ = !.ConjNum
+        format_sequential_conjunction(VarTable, 4, GoalPath, GoalsAfter,
+            GoalsAfterCost, !.ConjNum, ReportGoalsAfter0),
+        ReportGoalsAfter = indent(3) ++ singleton("Goals after:\n") ++
+            ReportGoalsAfter0
     ),
-
-    Report = snoc(ReportHeader ++ ReportGoalsBefore ++ ReportParConj ++ 
-        ReportGoalsAfter, "\n").
+    Report = ReportHeader ++ ReportGoalsBefore ++ nl ++ ReportParConj ++ nl ++
+        ReportGoalsAfter ++ nl.
 
 :- pred format_parallel_conjunction(var_table::in, int::in,
     goal_path::in, int::in,
@@ -3222,8 +3292,12 @@ format_parallel_conjuncts(VarTable, Inde
                 ConjReport) 
         ;
             GoalsTail = [_ | _],
+            Cost = foldl(
+                (func(GoalI, Acc) = 
+                    Acc + GoalI ^ goal_annotation ^ pga_cost_percall),
+                Goals, 0.0),
             format_sequential_conjunction(VarTable, Indent + 1, GoalPath,
-                Goals, ConjReport)
+                Goals, Cost, 1, ConjReport)
         )
     ),
     !:Report = !.Report ++ ConjReport,
@@ -3238,11 +3312,24 @@ format_parallel_conjuncts(VarTable, Inde
         !Report).
 
 :- pred format_sequential_conjunction(var_table::in, int::in, goal_path::in,
-    list(pard_goal)::in, cord(string)::out) is det.
+    list(pard_goal)::in, float::in, int::in, cord(string)::out) is det.
 
-format_sequential_conjunction(VarTable, Indent, GoalPath, Goals, Report) :-
-    format_sequential_conjuncts(VarTable, Indent, GoalPath, Goals, 1, _,
-        empty, Report).
+format_sequential_conjunction(VarTable, Indent, GoalPath, Goals, Cost,
+        FirstConjNum, !:Report) :-
+    !:Report = empty,
+    ( FirstConjNum = 1 ->
+        !:Report = !.Report ++
+            indent(Indent) ++
+            singleton(format("%% conjunction: %s",
+                [s(goal_path_to_string(GoalPath))])) ++
+            nl_indent(Indent) ++ 
+            singleton(format("%% Cost: %s", [s(two_decimal_fraction(Cost))])) ++
+            nl ++ nl
+    ;
+        true
+    ),
+    format_sequential_conjuncts(VarTable, Indent, GoalPath, Goals, 
+        FirstConjNum, _, !Report).
 
 :- pred format_sequential_conjuncts(var_table::in, int::in, goal_path::in,
     list(pard_goal)::in, int::in, int::out, 
@@ -3259,22 +3346,22 @@ format_sequential_conjuncts(VarTable, In
         Conjs = []
     ;
         Conjs = [_ | _],
-        !:Report = !.Report ++ nl,
+        !:Report = !.Report ++ indent(Indent) ++ singleton(",\n"),
         format_sequential_conjuncts(VarTable, Indent, GoalPath0, Conjs,
             !ConjNum, !Report)
     ).
 
 :- instance goal_annotation(pard_goal_annotation) where [
-        pred(print_goal_annotation_to_strings/2) is 
+        pred(print_goal_annotation_to_strings/3) is 
             format_pard_goal_annotation
     ].
 
-:- pred format_pard_goal_annotation(pard_goal_annotation::in, 
-    cord(string)::out) is det.
+:- pred format_pard_goal_annotation(var_table::in, pard_goal_annotation::in, 
+    cord(cord(string))::out) is det.
 
-format_pard_goal_annotation(GoalAnnotation, Report) :-
-    (
-        GoalAnnotation = pard_goal_call(CostPercall, CostAboveThreshold),
+format_pard_goal_annotation(VarTable, GoalAnnotation, Report) :-
+    GoalAnnotation = pard_goal_annotation(CostPercall, CostAboveThreshold,
+        Productions, Consumptions),
         (
             CostAboveThreshold = cost_above_par_threshold,
             CostAboveThresholdStr = "above threshold"
@@ -3282,16 +3369,43 @@ format_pard_goal_annotation(GoalAnnotati
             CostAboveThreshold = cost_not_above_par_threshold,
             CostAboveThresholdStr = "not above threshold"
         ),
-        Report = singleton(format("cost: %s ", 
-                [s(two_decimal_fraction(CostPercall))])) ++ 
-            singleton(CostAboveThresholdStr) ++ singleton(")")
+    CostLine = singleton(format("cost: %s (%s)", 
+            [s(two_decimal_fraction(CostPercall)),
+             s(CostAboveThresholdStr)])),
+    format_var_use_report(VarTable, productions, Productions,
+        ProductionsReport), 
+    format_var_use_report(VarTable, consumptions, Consumptions,
+        ConsumptionsReport), 
+    Report = singleton(CostLine) ++ ProductionsReport ++ ConsumptionsReport.
+
+:- func productions = string.
+
+productions = "Productions".
+
+:- func consumptions = string.
+
+consumptions = "Consumptions".
+
+:- pred format_var_use_report(var_table::in, string::in, 
+    assoc_list(var_rep, float)::in, cord(cord(string))::out) is det.
+
+format_var_use_report(VarTable, Label, List, Report) :-
+    (
+        List = [_ | _],
+        map(format_var_use_line(VarTable), List, Lines),
+        Report = singleton(singleton(Label ++ ":")) ++ cord.from_list(Lines)
     ;
-        ( GoalAnnotation = pard_goal_other_atomic
-        ; GoalAnnotation = pard_goal_non_atomic
-        ),
-        Report = cord.empty
+        List = [],
+        Report = empty
     ).
 
+:- pred format_var_use_line(var_table::in, pair(var_rep, float)::in,
+    cord(string)::out) is det.
+
+format_var_use_line(VarTable, Var - Use, singleton(String)) :-
+    format("    %s: %s", [s(VarName), s(two_decimal_fraction(Use))], String),
+    lookup_var_name(VarTable, Var, VarName).
+
 %-----------------------------------------------------------------------------%
 
 :- pred debug_cliques_below_threshold(candidate_child_clique::in,
Index: deep_profiler/mdprof_feedback.m
===================================================================
RCS file: /home/mercury1/repository/mercury/deep_profiler/mdprof_feedback.m,v
retrieving revision 1.29
diff -u -p -b -r1.29 mdprof_feedback.m
--- deep_profiler/mdprof_feedback.m	11 Oct 2010 00:49:24 -0000	1.29
+++ deep_profiler/mdprof_feedback.m	16 Oct 2010 04:07:06 -0000
@@ -177,12 +177,13 @@ create_feedback_report(feedback_data_can
         Parameters, Conjs), Report) :-
     NumConjs = length(Conjs),
     Parameters = candidate_par_conjunctions_params(DesiredParallelism,
-        SparkingCost, SparkingDelay, SignalCost, WaitCost, 
+        IntermoduleVarUse, SparkingCost, SparkingDelay, SignalCost, WaitCost, 
         ContextWakeupDelay, CliqueThreshold, CallSiteThreshold,
         ParalleliseDepConjs, BestParAlgorithm),
     best_par_algorithm_string(BestParAlgorithm, BestParAlgorithmStr),
     ReportHeader = singleton(format("  Candidate Parallel Conjunctions:\n" ++
             "    Desired parallelism: %f\n" ++
+            "    Intermodule var use: %s\n" ++
             "    Sparking cost: %d\n" ++
             "    Sparking delay: %d\n" ++
             "    Future signal cost: %d\n" ++
@@ -194,8 +195,8 @@ create_feedback_report(feedback_data_can
             "    BestParallelisationAlgorithm: %s\n" ++
             "    Number of Parallel Conjunctions: %d\n" ++
             "    Parallel Conjunctions:\n\n",
-        [f(DesiredParallelism), i(SparkingCost), i(SparkingDelay),
-         i(SignalCost), i(WaitCost), i(ContextWakeupDelay), 
+        [f(DesiredParallelism), s(string(IntermoduleVarUse)), i(SparkingCost),
+         i(SparkingDelay), i(SignalCost), i(WaitCost), i(ContextWakeupDelay),
          i(CliqueThreshold), i(CallSiteThreshold), s(ParalleliseDepConjsStr),
          s(BestParAlgorithmStr), i(NumConjs)])),
     (
@@ -255,6 +256,9 @@ help_message =
                 The amount of desired parallelism for implicit parallelism,
                 value must be a floating point number above 1.0.
                 Note: This option is currently ignored.
+    --implicit-parallelism-intermodule-var-use
+                Assume that the compiler will be able to push signals and waits
+                for futures across module boundaries. 
     --implicit-parallelism-sparking-cost <value>
                 The cost of creating a spark, measured in the deep profiler's
                 call sequence counts.
@@ -389,6 +393,7 @@ read_deep_file(Input, Debug, MaybeDeep, 
             % Provide suitable feedback information for implicit parallelism
     ;       implicit_parallelism
     ;       desired_parallelism
+    ;       implicit_parallelism_intermodule_var_use
     ;       implicit_parallelism_sparking_cost
     ;       implicit_parallelism_sparking_delay
     ;       implicit_parallelism_future_signal_cost
@@ -428,6 +433,8 @@ long("candidate-parallel-conjunctions", 
 long("implicit-parallelism",                implicit_parallelism).
 
 long("desired-parallelism",                 desired_parallelism).
+long("implicit-parallelism-intermodule-var-use",
+    implicit_parallelism_intermodule_var_use).
 long("implicit-parallelism-sparking-cost",  implicit_parallelism_sparking_cost).
 long("implicit-parallelism-sparking-delay", implicit_parallelism_sparking_delay).
 long("implicit-parallelism-future-signal-cost",
@@ -464,6 +471,7 @@ defaults(implicit_parallelism,          
 defaults(desired_parallelism,                               string("4.0")).
 % XXX: These values have been chosen arbitrarily, appropriately values should
 % be tested for.
+defaults(implicit_parallelism_intermodule_var_use,          bool(no)).
 defaults(implicit_parallelism_sparking_cost,                int(100)).
 defaults(implicit_parallelism_sparking_delay,               int(1000)).
 defaults(implicit_parallelism_future_signal_cost,           int(100)).
@@ -565,6 +573,8 @@ check_options(Options0, RequestedFeedbac
             error("Invalid value for desired_parallelism: " ++ 
                 DesiredParallelismStr)
         ),
+        lookup_bool_option(Options, implicit_parallelism_intermodule_var_use,
+            IntermoduleVarUse),
         lookup_int_option(Options, implicit_parallelism_sparking_cost,
             SparkingCost),
         lookup_int_option(Options, implicit_parallelism_sparking_delay,
@@ -622,6 +632,7 @@ check_options(Options0, RequestedFeedbac
         ),
         CandidateParallelConjunctionsOpts =
             candidate_par_conjunctions_params(DesiredParallelism, 
+                IntermoduleVarUse,
                 SparkingCost,
                 SparkingDelay,
                 FutureSignalCost,
Index: deep_profiler/program_representation_utils.m
===================================================================
RCS file: /home/mercury1/repository/mercury/deep_profiler/program_representation_utils.m,v
retrieving revision 1.26
diff -u -p -b -r1.26 program_representation_utils.m
--- deep_profiler/program_representation_utils.m	14 Oct 2010 04:02:22 -0000	1.26
+++ deep_profiler/program_representation_utils.m	16 Oct 2010 04:07:06 -0000
@@ -61,7 +61,8 @@
     % Print the goal annotation for inclusion by print_proc_to_strings
     % above.
     %
-    pred print_goal_annotation_to_strings(T::in, cord(string)::out) is det
+    pred print_goal_annotation_to_strings(var_table::in, T::in, 
+        cord(cord(string))::out) is det
 ].
 
     % A goal with no particular annotation has empty strings printed for goal
@@ -310,44 +311,38 @@ print_goal_to_strings(VarTable, Indent, 
         ExprString = indent(Indent) ++ ExprString0
     ),
     
-    detism_to_string(DetismRep, DetismString0),
-    print_goal_annotation_to_strings(GoalAnnotation, GoalAnnotationString0),
+    ( GoalExprRep = conj_rep(_) ->
+        LinePrefix = indent(Indent) ++ singleton("% conjunction: "),
+        ExtraLineForConjunctions = nl
+    ;
+        LinePrefix = indent(Indent) ++ singleton("% "),
+        ExtraLineForConjunctions = empty
+    ),
+    detism_to_string(DetismRep, DetismString),
+    DetismLine = LinePrefix ++ DetismString ++ nl,
+    print_goal_annotation_to_strings(VarTable, GoalAnnotation,
+        GoalAnnotationLines0),
+    ( is_empty(GoalAnnotationLines0) ->
+        GoalAnnotationLines = empty
+    ;
+        GoalAnnotationLines1 = map((func(Line) = LinePrefix ++ Line ++ nl),
+            GoalAnnotationLines0),
+        GoalAnnotationLines = foldr(++, GoalAnnotationLines1, empty)
+    ),
    
-    AnnotationPrefix = cord.singleton("% "),
     GoalPathString0 = goal_path_to_string(GoalPath),
     ( GoalPathString0 = "" ->
-        GoalPathString1 = "root goal"
+        GoalPathString = "root goal"
     ;
-        GoalPathString1 = GoalPathString0
+        GoalPathString = GoalPathString0
     ),
-    GoalPathString = AnnotationPrefix ++ cord.singleton(GoalPathString1),
-    DetismString = AnnotationPrefix ++ DetismString0,
+    GoalPathLine = LinePrefix ++ cord.singleton(GoalPathString) ++ nl,
 
-    % Don't print empty annotations, including their newline.
-    ( not is_empty(GoalAnnotationString0) ->
-        ( GoalExprRep = conj_rep(_) ->
-            % If this annotation belongs to a conjunction make sure that this
-            % is clear.
-            GoalAnnotationString = indent(Indent) ++ AnnotationPrefix 
-                ++ cord.singleton("conjunction: ") ++ GoalAnnotationString0 
-                ++ nl
-        ;
-            GoalAnnotationString = indent(Indent) ++ AnnotationPrefix 
-                ++ GoalAnnotationString0 ++ nl
-        )
-    ;
-        GoalAnnotationString = cord.empty
-    ),
-    ( GoalExprRep = conj_rep(_) ->
-        % Don't print determinism information or the goal path for conjunctions.
-        Strings = GoalAnnotationString
-            ++ ExprString
-    ; 
-        Strings = indent(Indent) ++ GoalPathString ++ nl
-            ++ indent(Indent) ++ DetismString ++ nl 
-            ++ GoalAnnotationString
-            ++ ExprString
-    ).
+    Strings = GoalPathLine
+        ++ DetismLine
+        ++ GoalAnnotationLines
+        ++ ExtraLineForConjunctions
+        ++ ExprString.
 
 :- pred print_conj_to_strings(var_table::in, int::in,
     goal_path::in, list(goal_rep(GoalAnn))::in, cord(string)::out) is det
@@ -379,7 +374,14 @@ print_conj_2_to_strings(VarTable, Indent
     print_goal_to_strings(VarTable, Indent, GoalPath, GoalRep, GoalString),
     print_conj_2_to_strings(VarTable, Indent, GoalPath0, ConjNum+1, 
         GoalReps, ConjString),
-    Strings = GoalString ++ ConjString.
+    (
+        GoalReps = [],
+        Seperator = empty
+    ;
+        GoalReps = [_ | _],
+        Seperator = indent(Indent) ++ singleton(",\n")
+    ),
+    Strings = GoalString ++ Seperator ++ ConjString.
 
 :- pred print_disj_to_strings(var_table::in, int::in, goal_path::in, 
     int::in, list(goal_rep(GoalAnn))::in, bool::in, cord(string)::out) 
@@ -629,12 +631,13 @@ nl = cord.singleton("\n").
 %----------------------------------------------------------------------------%
 
 :- instance goal_annotation(unit) where [
-    pred(print_goal_annotation_to_strings/2) is print_unit_to_strings
+    pred(print_goal_annotation_to_strings/3) is print_unit_to_strings
 ].
 
-:- pred print_unit_to_strings(unit::in, cord(string)::out) is det.
+:- pred print_unit_to_strings(var_table::in, unit::in, cord(cord(string))::out)
+    is det.
 
-print_unit_to_strings(_, cord.empty).
+print_unit_to_strings(_, _, cord.empty).
 
 %----------------------------------------------------------------------------%
 
Index: deep_profiler/recursion_patterns.m
===================================================================
RCS file: /home/mercury1/repository/mercury/deep_profiler/recursion_patterns.m,v
retrieving revision 1.7
diff -u -p -b -r1.7 recursion_patterns.m
--- deep_profiler/recursion_patterns.m	10 Oct 2010 04:19:53 -0000	1.7
+++ deep_profiler/recursion_patterns.m	16 Oct 2010 04:07:06 -0000
@@ -313,7 +313,7 @@ goal_recursion_data(ThisClique, CallSite
         ;
             GoalExpr = switch_rep(_, _, Cases),
             switch_recursion_data(ThisClique, CallSiteMap, GoalPath, 1, Cases,
-                float(Calls), !:RecursionData)
+                float(Calls), Calls, !:RecursionData)
         ;
             GoalExpr = ite_rep(Cond, Then, Else),
             ite_recursion_data(ThisClique, CallSiteMap, GoalPath, 
@@ -504,12 +504,17 @@ ite_recursion_data(ThisClique, CallSiteM
 
 :- pred switch_recursion_data(clique_ptr::in, 
     map(goal_path, cost_and_callees)::in, goal_path::in, int::in, 
-    list(case_rep(coverage_info))::in, float::in,
+    list(case_rep(coverage_info))::in, float::in, int::in,
     recursion_data::out) is det.
 
-switch_recursion_data(_, _, _, _, [], _, proc_dead_code).
+switch_recursion_data(_, _, _, _, [], TotalCalls, CallsRemaining,
+        RecursionData) :-
+    % Can fail switches will have a nonzero probability of reaching this case.
+    FailProb = probable(float(CallsRemaining) / TotalCalls),
+    RecursionData0 = simple_recursion_data(0.0, 0),
+    recursion_data_and_probability(FailProb, RecursionData0, RecursionData).
 switch_recursion_data(ThisClique, CallSiteMap, GoalPath, CaseNum, 
-        [Case | Cases], TotalCalls, RecursionData) :-
+        [Case | Cases], TotalCalls, CallsRemaining, RecursionData) :-
     Case = case_rep(_, _, Goal),
     goal_recursion_data(ThisClique, CallSiteMap, 
         goal_path_add_at_end(GoalPath, step_switch(CaseNum, no)), Goal, 
@@ -523,7 +528,7 @@ switch_recursion_data(ThisClique, CallSi
     recursion_data_and_probability(CaseProb, CaseRecursionData0,
         CaseRecursionData),
     switch_recursion_data(ThisClique, CallSiteMap, GoalPath, CaseNum+1,
-        Cases, TotalCalls, CasesRecursionData),
+        Cases, TotalCalls, CallsRemaining - Calls, CasesRecursionData),
     merge_recursion_data_after_branch(CaseRecursionData, CasesRecursionData,
         RecursionData).
 
Index: deep_profiler/var_use_analysis.m
===================================================================
RCS file: /home/mercury1/repository/mercury/deep_profiler/var_use_analysis.m,v
retrieving revision 1.7
diff -u -p -b -r1.7 var_use_analysis.m
--- deep_profiler/var_use_analysis.m	14 Oct 2010 04:02:22 -0000	1.7
+++ deep_profiler/var_use_analysis.m	16 Oct 2010 04:10:22 -0000
@@ -40,6 +40,17 @@
                 vui_use_type                :: var_use_type
             ).
 
+:- type var_use_options
+    --->    var_use_options(
+                vuo_deep                    :: deep,
+                vuo_intermodule_var_use     :: intermodule_var_use,
+                vuo_var_use_type            :: var_use_type
+            ).
+
+:- type intermodule_var_use
+    --->    follow_calls_into_module(string)
+    ;       follow_any_call.
+
 :- type var_use_type
     --->    var_use_production
             % The variable is produced: free >> ground
@@ -73,11 +84,11 @@
     % The first mode avoids a check to ensure that this recursion type provides
     % enough information.
     %
-:- pred call_site_dynamic_var_use_info(deep, call_site_dynamic_ptr, int,
-    recursion_type, float, var_use_type, maybe_error(var_use_info)).
-:- mode call_site_dynamic_var_use_info(in, in, in,
+:- pred call_site_dynamic_var_use_info(call_site_dynamic_ptr, int,
+    recursion_type, float, var_use_options, maybe_error(var_use_info)).
+:- mode call_site_dynamic_var_use_info(in, in,
     in(recursion_type_known_costs), in, in, out) is det.
-:- mode call_site_dynamic_var_use_info(in, in, in,
+:- mode call_site_dynamic_var_use_info(in, in,
     in, in, in, out) is det.
 
     % call_site_dynamic_var_use_info(Deep, CliquePtr, CSDPtr, ArgPos, RT,
@@ -92,22 +103,22 @@
     %
     % Cost is the cost of the call.
     %
-:- pred call_site_dynamic_var_use_info(deep, clique_ptr, call_site_dynamic_ptr,
+:- pred call_site_dynamic_var_use_info(clique_ptr, call_site_dynamic_ptr,
     int, recursion_type, maybe(recursion_depth), float, set(proc_dynamic_ptr),
-    var_use_type, maybe_error(var_use_info)).
-:- mode call_site_dynamic_var_use_info(in, in, in, in,
+    var_use_options, maybe_error(var_use_info)).
+:- mode call_site_dynamic_var_use_info(in, in, in,
     in(recursion_type_known_costs), in(maybe_yes(ground)), in, in, in, out) 
     is det. 
-:- mode call_site_dynamic_var_use_info(in, in, in, in, 
+:- mode call_site_dynamic_var_use_info(in, in, in, 
     in, in, in, in, in, out) is det.
 
-:- pred clique_var_use_info(deep::in, clique_ptr::in, int::in,
-    var_use_type::in, maybe_error(var_use_info)::out) is det.
+:- pred clique_var_use_info(clique_ptr::in, int::in,
+    var_use_options::in, maybe_error(var_use_info)::out) is det.
 
-:- pred proc_dynamic_var_use_info(deep::in, clique_ptr::in,
+:- pred proc_dynamic_var_use_info(clique_ptr::in,
     proc_dynamic_ptr::in, int::in, 
     recursion_type::in(recursion_type_known_costs), recursion_depth::in,
-    float::in, set(proc_dynamic_ptr)::in, var_use_type::in,
+    float::in, set(proc_dynamic_ptr)::in, var_use_options::in,
     maybe_error(var_use_info)::out) is det.
 
 %-----------------------------------------------------------------------------%
@@ -120,11 +131,11 @@
 
     % Find the first use of a variable in an arbitrary goal.
     %
-:- pred var_first_use(deep::in, clique_ptr::in,
+:- pred var_first_use(clique_ptr::in,
     map(goal_path, cost_and_callees)::in, map(goal_path, cs_cost_csq)::in, 
     recursion_type::in(recursion_type_known_costs), recursion_depth::in,
     goal_rep(T)::in, goal_path::in, float::in, var_rep::in, 
-    var_use_type::in, var_use_info::out) is det 
+    var_use_options::in, var_use_info::out) is det 
     <= goal_annotation_with_coverage(T).
 
 %-----------------------------------------------------------------------------%
@@ -208,33 +219,43 @@ pessimistic_var_use_time(VarUseType, Pro
     % compiler will not push signals and waits into higher order calls.
     % Therefore this should never be called for a higher order call site.
     %
-call_site_dynamic_var_use_info(Deep, CSDPtr, ArgPos, RT, Cost, VarUseType,
+call_site_dynamic_var_use_info(CSDPtr, ArgPos, RT, Cost, VarUseOptions,
         MaybeVarUseInfo) :-
+    Deep = VarUseOptions ^ vuo_deep,
     deep_lookup_call_site_dynamics(Deep, CSDPtr, CSD),
     deep_lookup_clique_index(Deep, CSD ^ csd_caller, ParentCliquePtr),
     recursion_type_get_maybe_avg_max_depth(RT, MaybeCurDepth),
-    call_site_dynamic_var_use_info(Deep, ParentCliquePtr, CSDPtr, ArgPos, RT, 
-        MaybeCurDepth, Cost, set.init, VarUseType, MaybeVarUseInfo).
+    call_site_dynamic_var_use_info(ParentCliquePtr, CSDPtr, ArgPos, RT, 
+        MaybeCurDepth, Cost, set.init, VarUseOptions, MaybeVarUseInfo).
 
-call_site_dynamic_var_use_info(Deep, ParentCliquePtr, CSDPtr, ArgNum,
-        RecursionType, MaybeDepth0, Cost, CallStack, VarUseType,
+call_site_dynamic_var_use_info(ParentCliquePtr, CSDPtr, ArgNum,
+        RecursionType, MaybeDepth0, Cost, CallStack, VarUseOptions,
         MaybeVarUseInfo) :-
+    Deep = VarUseOptions ^ vuo_deep,
     deep_lookup_clique_maybe_child(Deep, CSDPtr, MaybeCalleeCliquePtr),
     ( 
         MaybeCalleeCliquePtr = yes(CalleeCliquePtr),
         % This is a non-recursive call site.
-        clique_var_use_info(Deep, CalleeCliquePtr, ArgNum, VarUseType,
+        clique_var_use_info(CalleeCliquePtr, ArgNum, VarUseOptions,
             MaybeVarUseInfo)
     ;
         MaybeCalleeCliquePtr = no,
         % This is a recursive call site.
         deep_lookup_call_site_dynamics(Deep, CSDPtr, CSD),
         CalleePDPtr = CSD ^ csd_callee,
-        ( member(CalleePDPtr, CallStack) ->
+        (
+            (
             % Don't follow this recursive call, doing so would make this
             % analysis recurse forever.  XXX: There should be a way to
             % compute and solve a finite series for this.
-            pessimistic_var_use_info(VarUseType, Cost, VarUseInfo),
+                member(CalleePDPtr, CallStack)
+            ;
+                not intermodule_var_use_should_follow_call(VarUseOptions,
+                    CSDPtr)
+            )
+        ->
+            pessimistic_var_use_info(VarUseOptions ^ vuo_var_use_type, Cost,
+                VarUseInfo), 
             MaybeVarUseInfo = ok(VarUseInfo)
         ;
             (
@@ -248,9 +269,9 @@ call_site_dynamic_var_use_info(Deep, Par
                         "A depth must be provided for known recursion types")
                 ),
                 recursion_depth_descend(Depth0, Depth),
-                proc_dynamic_var_use_info(Deep, ParentCliquePtr, CalleePDPtr,
+                proc_dynamic_var_use_info(ParentCliquePtr, CalleePDPtr,
                     ArgNum, RecursionType, Depth, Cost, CallStack,
-                    VarUseType, MaybeVarUseInfo)
+                    VarUseOptions, MaybeVarUseInfo)
             ;
                 ( RecursionType = rt_divide_and_conquer(_, _)
                 ; RecursionType = rt_mutual_recursion(_)
@@ -264,7 +285,8 @@ call_site_dynamic_var_use_info(Deep, Par
         )
     ).
 
-clique_var_use_info(Deep, CliquePtr, ArgNum, VarUseType, MaybeVarUseInfo) :-
+clique_var_use_info(CliquePtr, ArgNum, VarUseOptions, MaybeVarUseInfo) :-
+    Deep = VarUseOptions ^ vuo_deep,
     deep_lookup_clique_parents(Deep, CliquePtr, CSDPtr),
     deep_lookup_csd_desc(Deep, CSDPtr, CSDDesc),
     Cost = float(inherit_callseqs(CSDDesc)),
@@ -286,8 +308,8 @@ clique_var_use_info(Deep, CliquePtr, Arg
             ; RecursionType = rt_single(_, _, _, _, _)
             ),
             recursion_type_get_maybe_avg_max_depth(RecursionType, yes(Depth)),
-            proc_dynamic_var_use_info(Deep, CliquePtr, FirstPDPtr, ArgNum,
-                RecursionType, Depth, Cost, set.init, VarUseType,
+            proc_dynamic_var_use_info(CliquePtr, FirstPDPtr, ArgNum,
+                RecursionType, Depth, Cost, set.init, VarUseOptions,
                 MaybeVarUseInfo)
         ;
             ( RecursionType = rt_divide_and_conquer(_, _)
@@ -295,6 +317,7 @@ clique_var_use_info(Deep, CliquePtr, Arg
             ; RecursionType = rt_other(_)
             ; RecursionType = rt_errors(_)
             ),
+            VarUseType = VarUseOptions ^ vuo_var_use_type,
             pessimistic_var_use_info(VarUseType, Cost, VarUseInfo),
             MaybeVarUseInfo = ok(VarUseInfo)
         )
@@ -303,9 +326,10 @@ clique_var_use_info(Deep, CliquePtr, Arg
         error(this_file ++ "Clique has no first procedure")
     ).
 
-proc_dynamic_var_use_info(Deep, CliquePtr, PDPtr, ArgNum, RecursionType,
-        Depth0, ProcCost, CallStack0, VarUseType, MaybeVarUseInfo) :-
+proc_dynamic_var_use_info(CliquePtr, PDPtr, ArgNum, RecursionType,
+        Depth0, ProcCost, CallStack0, VarUseOptions, MaybeVarUseInfo) :-
     set.insert(CallStack0, PDPtr, CallStack),
+    Deep = VarUseOptions ^ vuo_deep,
     create_dynamic_procrep_coverage_report(Deep, PDPtr, MaybeProcrepCoverage),
     (
         MaybeProcrepCoverage = ok(ProcrepCoverage),
@@ -313,6 +337,7 @@ proc_dynamic_var_use_info(Deep, CliquePt
         HeadVars = ProcDefn ^ pdr_head_vars,
         ( index0(HeadVars, ArgNum, head_var_rep(Var, Mode)) ->
             var_mode_to_var_use_type(Mode, ComputedUse),
+            VarUseType = VarUseOptions ^ vuo_var_use_type,
             ( VarUseType = ComputedUse ->
                 true
             ;
@@ -337,9 +362,9 @@ proc_dynamic_var_use_info(Deep, CliquePt
 
             % Do the actual computation.
             Goal = ProcDefn ^ pdr_goal,
-            goal_var_first_use_wrapper(Deep, CliquePtr, CallStack,
+            goal_var_first_use_wrapper(CliquePtr, CallStack,
                 CallSiteCostMap, RecursiveCallSiteCostMap, RecursionType,
-                Depth, Goal, ProcCost, Var, VarUseType, VarUseInfo),
+                Depth, Goal, ProcCost, Var, VarUseOptions, VarUseInfo),
             MaybeVarUseInfo = ok(VarUseInfo)
         ;
             PDPtr = proc_dynamic_ptr(PDNum),
@@ -369,12 +394,11 @@ proc_dynamic_var_use_info(Deep, CliquePt
 
 :- type var_first_use_static_info
     --->    var_first_use_static_info(
-                fui_deep                :: deep,
                 fui_clique              :: clique_ptr,
                 fui_call_site_map       :: map(goal_path, cost_and_callees),
                 fui_rec_call_site_map   :: map(goal_path, cs_cost_csq),
                 fui_var                 :: var_rep,
-                fui_var_use             :: var_use_type,
+                fui_var_use_opts        :: var_use_options,
 
                 % A set of call sites whose analysis has started but not yet
                 % completed. We keep this set to prevent infinite recursion
@@ -387,7 +411,7 @@ proc_dynamic_var_use_info(Deep, CliquePt
 
 :- inst var_first_use_static_info
     --->    var_first_use_static_info(
-                ground, ground, ground, ground, ground, ground, ground,
+                ground, ground, ground, ground, ground, ground,
                 recursion_type_known_costs,
                 ground
             ).
@@ -415,7 +439,8 @@ goal_var_first_use(GoalPath, Goal, Stati
         (
             get_coverage_before(Coverage, 0)
         ;
-            StaticInfo ^ fui_var_use = var_use_production, 
+            VarUseType = StaticInfo ^ fui_var_use_opts ^ vuo_var_use_type,
+            VarUseType = var_use_production, 
             (
                 Detism = erroneous_rep
             ;
@@ -498,9 +523,10 @@ goal_var_first_use(GoalPath, Goal, Stati
 
 call_var_first_use(AtomicGoal, BoundVars, GoalPath, StaticInfo,
         CostSoFar, NextCostSoFar, FoundFirstUse) :-
-    StaticInfo = var_first_use_static_info(_Deep, CliquePtr, CostMap,
-        RecCostMap, Var, VarUseType, _CallStack, _RecursionType,
+    StaticInfo = var_first_use_static_info(CliquePtr, CostMap,
+        RecCostMap, Var, VarUseOptions, _CallStack, _RecursionType,
         _MaybeCurDepth),
+    VarUseType = VarUseOptions ^ vuo_var_use_type,
     map.lookup(CostMap, GoalPath, CostAndCallees),
 
     % Get the cost of the call.
@@ -607,8 +633,9 @@ consume_ho_arg(method_call_rep(Var, _, _
     cost_and_callees::in, float::out) is nondet.
 
 call_args_first_use(Args, Cost, StaticInfo, CostAndCallees, Time) :-
-    StaticInfo = var_first_use_static_info(Deep, CliquePtr, _CostMap,
-        _RecCostMap, Var, VarUseType, CallStack, RecursionType, CurDepth),
+    StaticInfo = var_first_use_static_info(CliquePtr, _CostMap,
+        _RecCostMap, Var, VarUseOptions, CallStack, RecursionType, CurDepth),
+    VarUseType = VarUseOptions ^ vuo_var_use_type,
     HigherOrder = CostAndCallees ^ cac_call_site_is_ho,
     Callees = CostAndCallees ^ cac_callees,
     member_index0(Var, Args, ArgNum), 
@@ -619,9 +646,9 @@ call_args_first_use(Args, Cost, StaticIn
             pessimistic_var_use_time(VarUseType, Cost, Time)
         ; singleton_set(Callees, SingletonCallee) ->
             CSDPtr = SingletonCallee ^ c_csd,
-            call_site_dynamic_var_use_info(Deep, CliquePtr, CSDPtr,
+            call_site_dynamic_var_use_info(CliquePtr, CSDPtr,
                 ArgNum, RecursionType, yes(CurDepth), Cost, CallStack,
-                VarUseType, MaybeVarUseInfo),
+                VarUseOptions, MaybeVarUseInfo),
             (
                 MaybeVarUseInfo = ok(VarUseInfo),
                 VarUseInfo = var_use_info(Time, _, _)
@@ -659,7 +686,7 @@ call_args_first_use(Args, Cost, StaticIn
 atomic_trivial_var_first_use(AtomicGoal, BoundVars, CostSoFar, StaticInfo,
         FoundFirstUse) :-
     Var = StaticInfo ^ fui_var,
-    VarUseType = StaticInfo ^ fui_var_use,
+    VarUseType = StaticInfo ^ fui_var_use_opts ^ vuo_var_use_type,
     atomic_goal_get_vars(AtomicGoal, Vars),
     (
         member(Var, Vars),
@@ -729,7 +756,7 @@ disj_var_first_use(GoalPath, Disjuncts, 
         detism_get_solutions(Detism) = at_most_many_rep,
         FoundFirstUse0 = found_first_use(_)
     ->
-        VarUseType = StaticInfo ^ fui_var_use,
+        VarUseType = StaticInfo ^ fui_var_use_opts ^ vuo_var_use_type,
         (
             VarUseType = var_use_consumption,
             FoundFirstUse = found_first_use(CostBeforeConsumption)
@@ -753,7 +780,7 @@ disj_var_first_use_2(_, _, [], _, !CostS
 disj_var_first_use_2(GoalPath, DisjNum, [Disj | Disjs], StaticInfo, !CostSoFar,
         FoundFirstUse) :-
     DisjGoalPath = goal_path_add_at_end(GoalPath, step_disj(DisjNum)),
-    VarUseType = StaticInfo ^ fui_var_use,
+    VarUseType = StaticInfo ^ fui_var_use_opts ^ vuo_var_use_type,
     goal_var_first_use(DisjGoalPath, Disj, StaticInfo, !CostSoFar,
         HeadFoundFirstUse),
     disj_var_first_use_2(GoalPath, DisjNum + 1, Disjs, StaticInfo,
@@ -827,7 +854,7 @@ switch_var_first_use(GoalPath, SwitchedO
             % No case contained a first-use of this variable.
             FoundFirstUse = have_not_found_first_use
         ;
-            VarUseType = StaticInfo ^ fui_var_use,
+            VarUseType = StaticInfo ^ fui_var_use_opts ^ vuo_var_use_type,
             (
                 VarUseType = var_use_consumption,
                 DefaultCost = CostAfterSwitch
@@ -886,7 +913,7 @@ ite_var_first_use(GoalPath, Cond, Then, 
     CondGoalPath = goal_path_add_at_end(GoalPath, step_ite_cond),
     ThenGoalPath = goal_path_add_at_end(GoalPath, step_ite_then),
     ElseGoalPath = goal_path_add_at_end(GoalPath, step_ite_else),
-    VarUseType = StaticInfo ^ fui_var_use,
+    VarUseType = StaticInfo ^ fui_var_use_opts ^ vuo_var_use_type,
     CostBeforeITE = !.CostSoFar,
     goal_var_first_use(CondGoalPath, Cond, StaticInfo,
         CostBeforeITE, CostAfterCond, CondFoundFirstUse),
@@ -939,21 +966,20 @@ ffu_to_float(_, found_first_use(CostBefo
 
 %----------------------------------------------------------------------------%
 
-:- pred goal_var_first_use_wrapper(deep::in, clique_ptr::in,
-    set(proc_dynamic_ptr)::in, 
+:- pred goal_var_first_use_wrapper(clique_ptr::in, set(proc_dynamic_ptr)::in, 
     map(goal_path, cost_and_callees)::in, map(goal_path, cs_cost_csq)::in, 
     recursion_type::in(recursion_type_known_costs), recursion_depth::in,
     goal_rep(coverage_info)::in, float::in, var_rep::in, 
-    var_use_type::in, var_use_info::out) is det.
+    var_use_options::in, var_use_info::out) is det.
 
-goal_var_first_use_wrapper(Deep, CliquePtr, CallStack, CallSiteMap,
+goal_var_first_use_wrapper(CliquePtr, CallStack, CallSiteMap,
         RecursiveCallSiteMap, RT, CurDepth, Goal, ProcCost, Var,
-        VarUseType, VarUseInfo) :-
+        VarUseOptions, VarUseInfo) :-
     goal_var_first_use(empty_goal_path, Goal,
-        var_first_use_static_info(Deep, CliquePtr, CallSiteMap,
-            RecursiveCallSiteMap, Var, VarUseType, CallStack, RT,
-            CurDepth),
+        var_first_use_static_info(CliquePtr, CallSiteMap, RecursiveCallSiteMap,
+            Var, VarUseOptions, CallStack, RT, CurDepth),
         0.0, _Cost, FoundFirstUse),
+    VarUseType = VarUseOptions ^ vuo_var_use_type,
     found_first_use_to_use_info(FoundFirstUse, ProcCost, VarUseType,
         VarUseInfo).
 
@@ -961,12 +987,13 @@ goal_var_first_use_wrapper(Deep, CliqueP
         (get_coverage(Goal) = Goal ^ goal_annotation)
     ].
 
-var_first_use(Deep, CliquePtr, CallSiteMap, RecursiveCallSiteMap, RT, CurDepth,
-        Goal, GoalPath, Cost, Var, VarUseType, VarUseInfo) :-
+var_first_use(CliquePtr, CallSiteMap, RecursiveCallSiteMap, RT, CurDepth,
+        Goal, GoalPath, Cost, Var, VarUseOptions, VarUseInfo) :-
     goal_var_first_use(GoalPath, Goal,
-        var_first_use_static_info(Deep, CliquePtr, CallSiteMap,
-            RecursiveCallSiteMap, Var, VarUseType, set.init, RT, CurDepth), 
+        var_first_use_static_info(CliquePtr, CallSiteMap, RecursiveCallSiteMap,
+            Var, VarUseOptions, set.init, RT, CurDepth), 
         0.0, _, FoundFirstUse),
+    VarUseType = VarUseOptions ^ vuo_var_use_type,
     found_first_use_to_use_info(FoundFirstUse, Cost, VarUseType, VarUseInfo).
 
 :- pred found_first_use_to_use_info(found_first_use::in, float::in,
@@ -979,8 +1006,8 @@ found_first_use_to_use_info(FoundFirstUs
     ;
         FoundFirstUse = have_not_found_first_use,
         % If the first use has not been found then:
-        %  a) for productions, they must have been produced, this is an error.
-        %  b) For consumptions. the compiler will insert a wait so any calls
+        %  a) for productions: they must have been produced, this is an error.
+        %  b) For consumptions: the compiler will insert a wait so any calls
         %     following this one can assume that a wait has already been
         %     performed.
         (
@@ -998,6 +1025,29 @@ found_first_use_to_use_info(FoundFirstUs
 
 %-----------------------------------------------------------------------------%
 
+:- pred intermodule_var_use_should_follow_call(var_use_options::in,
+    call_site_dynamic_ptr::in) is semidet.
+
+intermodule_var_use_should_follow_call(VarUseOptions, CSDPtr) :-
+    FollowCall = VarUseOptions ^ vuo_intermodule_var_use,
+    (
+        FollowCall = follow_calls_into_module(Module),
+        Deep = VarUseOptions ^ vuo_deep,
+        deep_lookup_call_site_dynamics(Deep, CSDPtr, CSD),
+        PDPtr = CSD ^ csd_callee,
+        deep_lookup_proc_dynamics(Deep, PDPtr, PD),
+        PSPtr = PD ^ pd_proc_static,
+        deep_lookup_proc_statics(Deep, PSPtr, PS),
+        Label = PS ^ ps_id,
+        ( Label = str_ordinary_proc_label(_, _, Module, _, _, _)
+        ; Label = str_special_proc_label(_, _, Module, _, _, _)
+        )
+    ;
+        FollowCall = follow_any_call
+    ).
+
+%-----------------------------------------------------------------------------%
+
 :- func this_file = string.
 
 this_file = "var_use_analysis.m".
Index: library/lazy.m
===================================================================
RCS file: /home/mercury1/repository/mercury/library/lazy.m,v
retrieving revision 1.1
diff -u -p -b -r1.1 lazy.m
--- library/lazy.m	7 Oct 2010 02:38:10 -0000	1.1
+++ library/lazy.m	16 Oct 2010 04:07:06 -0000
@@ -65,6 +65,12 @@
     %
 :- func force(lazy(T)) = T.
 
+    % Get the value of a lazy expression if it has already been made available
+    % with force/1 This is useful as it can provide information without
+    % incurring (much) cost.
+    %
+:- pred read_if_val(lazy(T)::in, T::out) is semidet.
+
     % Test lazy values for equality.
     %
 :- pred equal_values(lazy(T)::in, lazy(T)::in) is semidet.
@@ -158,3 +164,14 @@ force(Lazy) = Value :-
     ).
 
 %-----------------------------------------------------------------------------%
+
+read_if_val(Lazy, Value) :-
+    promise_equivalent_solutions [Mutvar] (
+        Lazy = lazy(Mutvar)
+    ),
+    promise_pure (
+        impure get_mutvar(Mutvar, State),
+        State = value(Value)
+    ).
+
+%-----------------------------------------------------------------------------%
Index: mdbcomp/feedback.automatic_parallelism.m
===================================================================
RCS file: /home/mercury1/repository/mercury/mdbcomp/feedback.automatic_parallelism.m,v
retrieving revision 1.4
diff -u -p -b -r1.4 feedback.automatic_parallelism.m
--- mdbcomp/feedback.automatic_parallelism.m	14 Oct 2010 04:02:22 -0000	1.4
+++ mdbcomp/feedback.automatic_parallelism.m	16 Oct 2010 04:07:06 -0000
@@ -21,6 +21,7 @@
 
 :- import_module mdbcomp.program_representation.
 
+:- import_module bool.
 :- import_module list.
 :- import_module set.
 :- import_module string.
@@ -36,6 +37,9 @@
                 % The number of desired busy sparks.
                 cpcp_desired_parallelism    :: float,
 
+                % Follow variable use across module boundaries.
+                cpcp_intermodule_var_use    :: bool,
+
                 % The cost of creating a spark and adding it to the local
                 % work queue, measured in call sequence counts.
                 cpcp_sparking_cost          :: int,
@@ -147,6 +151,7 @@
                 cpc_is_dependent        :: conjuncts_are_dependent,
 
                 cpc_goals_before        :: list(GoalType),
+                cpc_goals_before_cost   :: float,
 
                 % A list of parallel conjuncts, each is a sequential
                 % conjunction of inner goals. All inner goals that are
@@ -162,6 +167,7 @@
                 cpc_conjs               :: list(seq_conj(GoalType)),
 
                 cpc_goals_after         :: list(GoalType),
+                cpc_goals_after_cost    :: float,
 
                 cpc_par_exec_metrics    :: parallel_exec_metrics
             ).
@@ -189,20 +195,16 @@
 :- type pard_goal == goal_rep(pard_goal_annotation).
 
 :- type pard_goal_annotation
-    --->    pard_goal_call(
-                % A call goal,  These are the most interesting goals WRT
-                % parallelisation.
-
+    --->    pard_goal_annotation(
                 % The per-call cost of this call in call sequence counts.
-                pgc_cost_percall            :: float,
+                pga_cost_percall            :: float,
 
-                pgc_coat_above_threshold    :: cost_above_par_threshold
-            )
-    ;       pard_goal_other_atomic
-            % Some other (cheap) atomic goal.
+                pga_coat_above_threshold    :: cost_above_par_threshold,
 
-    ;       pard_goal_non_atomic.
-            % A non-atomic goal.
+                % Variable use information.
+                pga_var_productions         :: assoc_list(var_rep, float),
+                pga_var_consumptions        :: assoc_list(var_rep, float)
+            ).
 
 :- type cost_above_par_threshold
     --->    cost_above_par_threshold
@@ -219,16 +221,17 @@
     ;       conjuncts_are_independent.
 
 :- pred convert_candidate_par_conjunctions_proc(
-    pred(A, B)::in(pred(in, out) is det), 
+    pred(candidate_par_conjunction(A), A, B)::in(pred(in, in, out) is det), 
     candidate_par_conjunctions_proc(A)::in,
     candidate_par_conjunctions_proc(B)::out) is det.
 
 :- pred convert_candidate_par_conjunction(
-    pred(A, B)::in(pred(in, out) is det),
+    pred(candidate_par_conjunction(A), A, B)::in(pred(in, in, out) is det), 
     candidate_par_conjunction(A)::in, candidate_par_conjunction(B)::out)
     is det.
 
-:- pred convert_seq_conj(pred(A, B)::in(pred(in, out) is det),
+:- pred convert_seq_conj(
+    pred(A, B)::in(pred(in, out) is det), 
     seq_conj(A)::in, seq_conj(B)::out) is det.
 
 %-----------------------------------------------------------------------------%
@@ -315,14 +318,19 @@ convert_candidate_par_conjunctions_proc(
     map(convert_candidate_par_conjunction(Conv), CPCA, CPCB),
     CPCProcB = candidate_par_conjunctions_proc(VarTable, CPCB).
 
-convert_candidate_par_conjunction(Conv, CPC0, CPC) :-
+convert_candidate_par_conjunction(Conv0, CPC0, CPC) :-
     CPC0 = candidate_par_conjunction(GoalPath, FirstGoalNum,
-        IsDependent, GoalsBefore0, Conjs0, GoalsAfter0, Metrics),
+        IsDependent, GoalsBefore0, GoalsBeforeCost, Conjs0, GoalsAfter0,
+        GoalsAfterCost, Metrics),
+    Conv = (pred(A::in, B::out) is det :-
+            Conv0(CPC0, A, B)
+        ),
     map(convert_seq_conj(Conv), Conjs0, Conjs),
     map(Conv, GoalsBefore0, GoalsBefore),
     map(Conv, GoalsAfter0, GoalsAfter),
     CPC = candidate_par_conjunction(GoalPath, FirstGoalNum,
-        IsDependent, GoalsBefore, Conjs, GoalsAfter, Metrics).
+        IsDependent, GoalsBefore, GoalsBeforeCost, Conjs, GoalsAfter,
+        GoalsAfterCost, Metrics).
 
 convert_seq_conj(Conv, seq_conj(Conjs0), seq_conj(Conjs)) :-
     map(Conv, Conjs0, Conjs).
Index: mdbcomp/feedback.m
===================================================================
RCS file: /home/mercury1/repository/mercury/mdbcomp/feedback.m,v
retrieving revision 1.18
diff -u -p -b -r1.18 feedback.m
--- mdbcomp/feedback.m	14 Oct 2010 04:02:22 -0000	1.18
+++ mdbcomp/feedback.m	16 Oct 2010 04:07:06 -0000
@@ -535,7 +535,7 @@ feedback_first_line = "Mercury Compiler 
 
 :- func feedback_version = string.
 
-feedback_version = "13".
+feedback_version = "14".
 
 %-----------------------------------------------------------------------------%
 
-------------- next part --------------
A non-text attachment was scrubbed...
Name: signature.asc
Type: application/pgp-signature
Size: 490 bytes
Desc: Digital signature
URL: <http://lists.mercurylang.org/archives/reviews/attachments/20101016/494e8ba4/attachment.sig>


More information about the reviews mailing list