[m-rev.] For review: Filling in rbmm_goal_info field in goal_info

Quan Phan quan.phan at cs.kuleuven.be
Thu Sep 6 00:54:57 AEST 2007


Hi Julien,

Thank you for your comments. I fixed errors in the log message as per
your previous email. My anwsers for the last email can be found below.

Do you prefer a new diff or an interdiff of the changes? We change the
name of the new file (rbmm_goal_info_analysis.m ->
add_rbmm_goal_infos.m) so if using the interdiff I would need to use the
old file name to generate it.

Regards,
Quan.

On Wed, Sep 05, 2007 at 03:33:21AM +1000, Julien Fischer wrote:
> 
> On Wed, 15 Aug 2007, Quan Phan wrote:
> 
> 
> >Index: rbmm.rbmm_goal_info_analysis.m
> >===================================================================
> >RCS file: rbmm.rbmm_goal_info_analysis.m
> >diff -N rbmm.rbmm_goal_info_analysis.m
> >--- /dev/null	1 Jan 1970 00:00:00 -0000
> >+++ rbmm.rbmm_goal_info_analysis.m	14 Aug 2007 23:41:11 -0000
> >@@ -0,0 +1,488 @@
> >+%-----------------------------------------------------------------------------%
> >+% vim: ft=mercury ts=4 sw=4 et
> >+%-----------------------------------------------------------------------------%
> >+% Copyright (C) 2007 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 rbmm.rbmm_goal_info_analysis.m.
> >+% Main author: Quan Phan.
> >+%
> >+% This module fills in rbmm_goal_info field in hlds_goal_extra_info data
> >+% structure. The details of this information can be read in hlds_goal.m.
> >+%
> >+% This information is used by the code generator to optimize the runtime
> >+% support for region-based memory management.
> 
> Explain that in more detail.

I tried to add more information.

> 
> 
> >+%
> >+%-----------------------------------------------------------------------------%
> >+
> >+:- module transform_hlds.rbmm.rbmm_goal_info_analysis.
> >+:- interface.
> >+
> >+:- import_module hlds.
> >+:- import_module hlds.hlds_module.
> >+:- import_module transform_hlds.rbmm.actual_region_arguments.
> >+:- import_module transform_hlds.rbmm.points_to_info.
> >+:- import_module transform_hlds.rbmm.region_resurrection_renaming.
> >+:- import_module transform_hlds.rbmm.region_transformation.
> >+
> >+:- pred collect_rbmm_goal_info(rpta_info_table::in,
> >+    proc_pp_actual_region_args_table::in, renaming_table::in,
> >+    renaming_table::in, name_to_prog_var_table::in,
> >+    module_info::in, module_info::out) is det.
> >+
> 
> ...
> 
> >+%-----------------------------------------------------------------------------%
> >+%
> >+% rbmm_goal_info analysis.
> >+%
> 
> Is there any analysis actually going on here?  It looks like you are just 
> annotating the HLDS with information that was derived by analyses that were
> carried out prior to this pass.
> 
> I suggest changing the name of this module to `add_rbmm_goal_infos' or
> something similar.

No, it is not really a full program analysis. It is more like we re-arrange
the existing data (from previous analyses) into the rbmm_goal_info.
I agree to change the name as your suggestion.

> 
> >+    % We need to collect this pieces of information for the procedures 
> >which
> >+    % have been region-analyzed. Therefore we can use one of the resulting
> >+    % tables from previous phases for the PPId. The use of
> >+    % ActualRegionArgumentTable here is convenient because we also need 
> >the
> >+    % information about actual region arguments in this analysis.
> 
> That seem poorly worded.

I explained it in other words.

> 
> ...
> 
> >+collect_rbmm_goal_info_goal_expr(ModuleInfo, ProcInfo, Graph,
> >+        ActualRegionsArgsProc, ResurRenamingProc, IteRenamingProc,
> >+        NameToRegionVarProc, !Expr, !Info) :-
> >+    !.Expr = if_then_else(A, Cond0, Then0, Else0),
> >+    collect_rbmm_goal_info_goal(ModuleInfo, ProcInfo, Graph,
> >+        ActualRegionsArgsProc, ResurRenamingProc, IteRenamingProc,
> >+        NameToRegionVarProc, Cond0, Cond),
> >+    collect_rbmm_goal_info_goal(ModuleInfo, ProcInfo, Graph,
> >+        ActualRegionsArgsProc, ResurRenamingProc, IteRenamingProc,
> >+        NameToRegionVarProc, Then0, Then),
> >+    collect_rbmm_goal_info_goal(ModuleInfo, ProcInfo, Graph,
> >+        ActualRegionsArgsProc, ResurRenamingProc, IteRenamingProc,
> >+        NameToRegionVarProc, Else0, Else),
> >+    !:Expr = if_then_else(A, Cond, Then, Else),
> >+    Else = hlds_goal(_, ElseInfo),
> >+    RbmmInfo = goal_info_get_rbmm(ElseInfo),
> >+    goal_info_set_maybe_rbmm(yes(RbmmInfo), !Info).
> 
> Why is the RbmmInfo for the entire if-then-else goal taken from that of
> the else branch?

This is a bug. Thanks for pointing it out. I fixed it.

> 
> >+    % The regions that are allocated into inside this disjunction are 
> >those
> >+    % allocated into by any disjuncts AND EXIST ...
> >+    % The regions that are read from inside this disjunction are those 
> >that +    % are read from by any disjuncts AND EXIST ... 
> >+    %
> >+:- pred compute_rbmm_info_disjunction(list(hlds_goal)::in,
> >+    rbmm_goal_info::in, rbmm_goal_info::out) is det.
> >+
> >+compute_rbmm_info_disjunction([], !RbmmInfo).
> >+compute_rbmm_info_disjunction([Disj | Disjs], !RbmmInfo) :-
> >+    Disj = hlds_goal(_, DInfo),
> >+    DRbmmInfo = goal_info_get_rbmm(DInfo),
> >+    DRbmmInfo = rbmm_goal_info(_, _, _, DAllocatedInto, DUsed),
> >+    !.RbmmInfo = rbmm_goal_info(Created, Removed, Carried, AllocatedInto0,
> >+        Used0),
> >+    set.difference(set.union(DAllocatedInto, AllocatedInto0), Created,
> >+        AllocatedInto),
> >+    set.difference(set.union(DUsed, Used0), Created, Used),
> >+    !:RbmmInfo = rbmm_goal_info(Created, Removed, Carried, AllocatedInto,
> >+        Used),
> >+    compute_rbmm_info_disjunction(Disjs, !RbmmInfo).
> >+
> >+    % The process here is similar to that for nondet disjunction.
> >+    %
> 
> Similar?  To the above code?  Presumably the above code is also intended
> to work for all disjunctions not just nondet ones.
I changed the comment.

> 
> >+:- pred compute_rbmm_info_switch(list(case)::in, rbmm_goal_info::in,
> >+    rbmm_goal_info::out) is det.
> >+
> >+compute_rbmm_info_switch([], !SwitchRbmmInfo).
> >+compute_rbmm_info_switch([Case | Cases], !SwitchRbmmInfo) :-
> >+    Case = case(_, Goal),
> >+    Goal = hlds_goal(_, Info),
> >+    CaseRbmmInfo = goal_info_get_rbmm(Info),
> >+    CaseRbmmInfo = rbmm_goal_info(_, _, _, CaseAllocatedInto, CaseUsed),
> >+    !.SwitchRbmmInfo = rbmm_goal_info(Created, Removed, Carried,
> >+        AllocatedInto0, Used0),
> >+    set.difference(set.union(CaseAllocatedInto, AllocatedInto0), Created,
> >+        AllocatedInto),
> >+    set.difference(set.union(CaseUsed, Used0), Created, Used),
> >+    !:SwitchRbmmInfo = rbmm_goal_info(Created, Removed, Carried,
> >+        AllocatedInto, Used),
> >+    compute_rbmm_info_switch(Cases, !SwitchRbmmInfo).
> >+
> >+:- pred collect_rbmm_goal_info_unification(unification::in, 
> >module_info::in,
> >+    rpt_graph::in, renaming::in, renaming::in, name_to_prog_var::in,
> >+    hlds_goal_info::in, hlds_goal_info::out) is det.
> >+
> >+collect_rbmm_goal_info_unification(Unification, ModuleInfo, Graph,
> >+        ResurRenaming, IteRenaming, RegionNameToVar, !Info) :-
> >+    (
> >+        Unification = construct(_, _, _, _, HowToConstruct, _, _),
> >+        (
> >+            HowToConstruct = construct_in_region(AllocatedIntoRegion),
> >+            RbmmInfo = rbmm_goal_info(set.init, set.init,
> >+                set.make_singleton_set(AllocatedIntoRegion),
> >+                set.make_singleton_set(AllocatedIntoRegion), set.init),
> >+            goal_info_set_maybe_rbmm(yes(RbmmInfo), !Info)
> >+        ;
> >+            ( HowToConstruct = construct_statically(_)
> >+            ; HowToConstruct = construct_dynamically
> >+            ; HowToConstruct = reuse_cell(_)
> >+            ),
> >+            goal_info_set_maybe_rbmm(yes(rbmm_info_init), !Info)
> >+        )
> >+    ;
> >+        Unification = deconstruct(DeconsCellVar, _, _, _, _, _),
> >+        get_node_by_variable(Graph, DeconsCellVar, Node), 
> >+        NodeType = rptg_lookup_node_type(Graph, Node),
> >+        ( if    type_not_stored_in_region(NodeType, ModuleInfo)
> >+          then
> >+                goal_info_set_maybe_rbmm(yes(rbmm_info_init), !Info)
> >+          else
> >+                OriginalName = rptg_lookup_region_name(Graph, Node),
> >+                ( map.search(ResurRenaming, OriginalName, ResurName) ->
> >+                    Name = ResurName
> >+                ; map.search(IteRenaming, OriginalName, IteName) ->
> >+                    Name = IteName
> >+                ;
> >+                    Name = OriginalName
> >+                ),
> >+                map.lookup(RegionNameToVar, Name, RegionVar),
> >+                RbmmInfo = rbmm_goal_info(set.init, set.init,
> >+                    set.make_singleton_set(RegionVar),
> >+                    set.init, set.make_singleton_set(RegionVar)),
> >+                goal_info_set_maybe_rbmm(yes(RbmmInfo), !Info)
> >+        )
> >+    ;
> >+        ( Unification = assign(_, _)
> >+        ; Unification = simple_test(_, _)
> >+        ),
> >+        goal_info_set_maybe_rbmm(yes(rbmm_goal_info(set.init, set.init,
> >+            set.init, set.init, set.init)), !Info)
> >+    ;
> >+        Unification = complicated_unify(_, _, _),
> >+        unexpected(this_file, "collect_rbmm_goal_info_unification:"
> >+            ++ " encounter complicated unification")
> >+    ).
> 
> s/encounter/encountered/

Fixed.

> 
> >Index: type_util.m
> >===================================================================
> >RCS file: /home/mercury/mercury1/repository/mercury/compiler/type_util.m,v
> >retrieving revision 1.179
> >diff -u -r1.179 type_util.m
> >--- type_util.m	9 Aug 2007 05:28:26 -0000	1.179
> >+++ type_util.m	14 Aug 2007 23:41:12 -0000
> >@@ -233,6 +233,11 @@
> >     %
> > :- func cons_id_adjusted_arity(module_info, mer_type, cons_id) = int.
> >
> >+    % Check if (the terms of) the type is NOT allocated in a region in 
> >+    % region-based memory management.
> >+    %
> 
> What do you mean by "the terms of"?

I wanted to say program terms (values) of the type (not the type itself) will
 not be stored in a region. 
I changed the comment like that. Hope it is clear.
> 
> Julien.
> --------------------------------------------------------------------------
> 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
> --------------------------------------------------------------------------
--------------------------------------------------------------------------
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