Files
mercury/compiler/structure_reuse.lfu.m
Nancy Mazur d3e5a8eda4 Provide the direct reuse analysis part of the structure reuse analysis (which
Estimated hours taken: 25
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.

compiler/prog_data.m:
	New types "dead_var", "live_var" and alike.
2006-05-10 10:56:57 +00:00

197 lines
7.1 KiB
Mathematica

%-----------------------------------------------------------------------------%
% 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.lfu.m
% Main authors: nancy
%
% Implementation of the process of annotating each program point within
% a procedure with local forward use information.
%
% At a program point (a goal), a variable is called in local forward use iff
% * it was already instantiated before the goal
% * and it is (syntactically) used in the goals following the current goal in
% forward execution.
%
%-----------------------------------------------------------------------------%
:- module transform_hlds.ctgc.structure_reuse.lfu.
:- interface.
:- import_module hlds.hlds_pred.
:- pred forward_use_information(proc_info::in, proc_info::out) is det.
:- implementation.
:- import_module hlds.hlds_goal.
:- import_module hlds.hlds_llds.
:- import_module hlds.hlds_pred.
:- import_module libs.compiler_util.
:- import_module parse_tree.prog_data.
:- import_module list.
:- import_module set.
:- import_module pair.
:- import_module string.
forward_use_information(!ProcInfo) :-
proc_info_get_goal(!.ProcInfo, Goal0),
% Set of variables initially instantiated.
proc_info_get_liveness_info(!.ProcInfo, InstantiatedVars0),
% Set of variables initially "dead" = instantiated variables that
% syntactically do not occur in the remainder of the goal.
set.init(DeadVars0),
forward_use_in_goal(Goal0, Goal, InstantiatedVars0, _InstantiatedVars,
DeadVars0, _DeadVars),
proc_info_set_goal(Goal, !ProcInfo).
:- pred forward_use_in_goal(hlds_goal::in, hlds_goal::out, set(prog_var)::in,
set(prog_var)::out, set(prog_var)::in, set(prog_var)::out) is det.
forward_use_in_goal(!Goal, !InstantiatedVars, !DeadVars) :-
(
!.Goal = GoalExpr0 - GoalInfo0,
goal_is_atomic(GoalExpr0)
->
InstantiatedVars0 = !.InstantiatedVars,
compute_instantiated_and_dead_vars(GoalInfo0, !InstantiatedVars,
!DeadVars),
set.difference(InstantiatedVars0, !.DeadVars, LFU),
goal_info_set_lfu(LFU, GoalInfo0, GoalInfo),
!:Goal = GoalExpr0 - GoalInfo
;
forward_use_in_composite_goal(!Goal, !InstantiatedVars, !DeadVars)
).
:- pred compute_instantiated_and_dead_vars(hlds_goal_info::in,
set(prog_var)::in, set(prog_var)::out, set(prog_var)::in,
set(prog_var)::out) is det.
compute_instantiated_and_dead_vars(Info, !Inst, !Dead) :-
% Inst = Inst0 + birth-set
% Dead = Dead0 + death-set
goal_info_get_pre_births(Info, PreBirths),
goal_info_get_post_births(Info, PostBirths),
goal_info_get_post_deaths(Info, PostDeaths),
goal_info_get_pre_deaths(Info, PreDeaths),
!:Inst = set.union_list([PreBirths, PostBirths, !.Inst]),
!:Dead = set.union_list([PreDeaths, PostDeaths, !.Dead]).
:- pred forward_use_in_composite_goal(hlds_goal::in, hlds_goal::out,
set(prog_var)::in, set(prog_var)::out, set(prog_var)::in,
set(prog_var)::out) is det.
forward_use_in_composite_goal(!Goal, !InstantiatedVars, !DeadVars) :-
!.Goal = GoalExpr0 - GoalInfo0,
InstantiadedBefore = !.InstantiatedVars,
(
GoalExpr0 = conj(A,Goals0)
->
forward_use_in_conj(Goals0, Goals, !InstantiatedVars, !DeadVars),
GoalExpr = conj(A,Goals)
;
GoalExpr0 = switch(A, B, Cases0)
->
forward_use_in_cases(Cases0, Cases, !InstantiatedVars, !DeadVars),
GoalExpr = switch(A, B, Cases)
;
GoalExpr0 = disj(Disj0)
->
forward_use_in_disj(Disj0, Disj, !InstantiatedVars, !DeadVars),
GoalExpr = disj(Disj)
;
GoalExpr0 = not(Goal0)
->
forward_use_in_goal(Goal0, Goal, !InstantiatedVars, !DeadVars),
GoalExpr = not(Goal)
;
GoalExpr0 = scope(A, Goal0)
->
forward_use_in_goal(Goal0, Goal, !InstantiatedVars, !DeadVars),
GoalExpr = scope(A, Goal)
;
GoalExpr0 = if_then_else(V, Cond0, Then0, Else0)
->
Inst0 = !.InstantiatedVars,
Dead0 = !.DeadVars,
forward_use_in_goal(Cond0, Cond, !InstantiatedVars, !DeadVars),
forward_use_in_goal(Then0, Then, !InstantiatedVars, !DeadVars),
forward_use_in_goal(Else0, Else, Inst0, Inst1, Dead0, Dead1),
set.union(Inst1, !InstantiatedVars),
set.union(Dead1, !DeadVars),
GoalExpr = if_then_else(V, Cond, Then, Else)
;
unexpected(this_file,
"Atomic goal in forward_use_in_composite_goal.")
),
set.difference(InstantiadedBefore, !.DeadVars, LFU),
goal_info_set_lfu(LFU, GoalInfo0, GoalInfo),
!:Goal = GoalExpr - GoalInfo.
:- pred forward_use_in_conj(list(hlds_goal)::in, list(hlds_goal)::out,
set(prog_var)::in, set(prog_var)::out, set(prog_var)::in,
set(prog_var)::out) is det.
forward_use_in_conj(!Goals, !InstantiatedVars, !DeadVars) :-
list.map_foldl2(forward_use_in_goal, !Goals, !InstantiatedVars,
!DeadVars).
:- pred forward_use_in_cases(list(case)::in, list(case)::out,
set(prog_var)::in, set(prog_var)::out, set(prog_var)::in,
set(prog_var)::out) is det.
forward_use_in_cases(!Cases, !InstantiatedVars, !DeadVars) :-
Inst0 = !.InstantiatedVars,
Dead0 = !.DeadVars,
list.map_foldl2(forward_use_in_case(Inst0, Dead0),
!Cases, !InstantiatedVars, !DeadVars).
:- pred forward_use_in_case(set(prog_var)::in, set(prog_var)::in,
case::in, case::out, set(prog_var)::in, set(prog_var)::out,
set(prog_var)::in, set(prog_var)::out) is det.
forward_use_in_case(Inst0, Dead0, !Case, !InstantiatedVars, !DeadVars) :-
!.Case = case(Cons, Goal0),
forward_use_in_goal(Goal0, Goal, Inst0, Inst, Dead0, Dead),
!:Case = case(Cons, Goal),
set.union(Inst, !InstantiatedVars),
set.union(Dead, !DeadVars).
:- pred forward_use_in_disj(list(hlds_goal)::in, list(hlds_goal)::out,
set(prog_var)::in, set(prog_var)::out, set(prog_var)::in,
set(prog_var)::out) is det.
forward_use_in_disj(!Goals, !InstantiatedVars, !DeadVars):-
Inst0 = !.InstantiatedVars,
Dead0 = !.DeadVars,
list.map_foldl2(forward_use_in_disj_goal(Inst0, Dead0),
!Goals, !InstantiatedVars, !DeadVars).
:- pred forward_use_in_disj_goal(set(prog_var)::in, set(prog_var)::in,
hlds_goal::in, hlds_goal::out, set(prog_var)::in, set(prog_var)::out,
set(prog_var)::in, set(prog_var)::out) is det.
forward_use_in_disj_goal(Inst0, Dead0, !Goal, !InstantiatedVars, !DeadVars) :-
forward_use_in_goal(!Goal, Inst0, Inst, Dead0, Dead),
set.union(Inst, !InstantiatedVars),
set.union(Dead, !DeadVars).
%-----------------------------------------------------------------------------%
:- func this_file = string.
this_file = "structure_reuse.lfu.m".
:- end_module transform_hlds.ctgc.structure_reuse.lfu.