~ubuntu-branches/debian/squeeze/erlang/squeeze

« back to all changes in this revision

Viewing changes to lib/hipe/ssa/hipe_df.erl

  • Committer: Bazaar Package Importer
  • Author(s): Erlang Packagers, Sergei Golovan
  • Date: 2006-12-03 17:07:44 UTC
  • mfrom: (2.1.11 feisty)
  • Revision ID: james.westby@ubuntu.com-20061203170744-rghjwupacqlzs6kv
Tags: 1:11.b.2-4
[ Sergei Golovan ]
Fixed erlang-base and erlang-base-hipe prerm scripts.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
 
%%%----------------------------------------------------------------------
2
 
%%% File    : df.erl
3
 
%%% Author  : 
4
 
%%% Purpose : 
5
 
%%% Created : 18 Mar 2002 by 
6
 
%%%----------------------------------------------------------------------
7
 
 
8
 
-module(hipe_df).
9
 
-export([get/2,
10
 
         make/2]).
11
 
 
12
 
-define(hash,hipe_hash).
13
 
 
14
 
%%>----------------------------------------------------------------------<
15
 
%  Procedure : create
16
 
%  Purpose   : This function creates an empty instance of DF. It is 
17
 
%              represented by a hash table.
18
 
%  Arguments : N - The number of Dominance Frontiers
19
 
%  Notes     : 
20
 
%%>----------------------------------------------------------------------<
21
 
create() ->
22
 
    ?hash:empty().
23
 
 
24
 
%%>----------------------------------------------------------------------<
25
 
%  Procedure : add
26
 
%  Purpose   : This function adds Node to N in DF.
27
 
%  Arguments : N    - The value being inserted
28
 
%              Node - The node getting the value
29
 
%              DF   - The Dominance Frontiers
30
 
%  Return    : DF
31
 
%  Notes     : If Node already exists at position N, it is not added again.
32
 
%%>----------------------------------------------------------------------<
33
 
add(N, Node, DF) ->
34
 
    case ?hash:lookup(N, DF) of
35
 
        not_found ->
36
 
            ?hash:update(N, [Node], DF);
37
 
        {found, DFList} ->
38
 
            case lists:member(Node, DFList) of
39
 
                true ->
40
 
                    DF;
41
 
                false ->
42
 
                    ?hash:update(N, [Node|DFList], DF)
43
 
            end
44
 
    end.
45
 
 
46
 
 
47
 
%%>----------------------------------------------------------------------<
48
 
%  Procedure : get
49
 
%  Purpose   : This function gets the Dominance Frontier for Node
50
 
%  Arguments : Node - The node which Dominance Frontier we request
51
 
%              DF - The Dominance Frontiers
52
 
%  Return    : 
53
 
%  Notes     : 
54
 
%%>----------------------------------------------------------------------<
55
 
get(Node, DF) ->
56
 
    case ?hash:lookup(Node, DF) of
57
 
        not_found ->  [];
58
 
        {found, List} -> List
59
 
    end.
60
 
 
61
 
 
62
 
%%>----------------------------------------------------------------------<
63
 
%  Procedure : make
64
 
%  Purpose   : This function calculates the Dominance Frontiers from
65
 
%              a CFG and a Dominantor Tree.
66
 
%  Arguments : SuccMap - The successor map of the CFG we are working with
67
 
%              DomTree - The dominance tree of the CFG.
68
 
%  Notes     : DomTree must actually be the dominance tree of the CFG.
69
 
%%>----------------------------------------------------------------------<
70
 
make(SuccMap, DomTree) ->
71
 
    make(hipe_domtree:getRoot(DomTree), SuccMap, DomTree, create()).
72
 
 
73
 
make(Node, SuccMap, DomTree, DF) ->
74
 
 
75
 
    Children = hipe_domtree:getChildren(Node, DomTree),
76
 
    Succ = hipe_gen_cfg:succ(SuccMap, Node),
77
 
    DF1 = checkIDomList(Succ, Node, DomTree, DF),
78
 
    makeDFChildren(Children, Node, SuccMap, DomTree, DF1).
79
 
 
80
 
 
81
 
%%>----------------------------------------------------------------------<
82
 
%  Procedure : makeDFChildren
83
 
%  Purpose   : This function calculates the dominance frontiers of the
84
 
%              children of the parent and adds the nodes in these
85
 
%              dominance frontiers who are not immediate dominantors of
86
 
%              the parent to parents dominance frontier.
87
 
%  Arguments : ChildList - The list of children that the function traverses
88
 
%              Parent - The parent of the children
89
 
%              SuccMap - The successor map of the CFG
90
 
%              DomTree - The dominantor tree of the CFG
91
 
%              DF - The dominance frontiers so far
92
 
%  Notes     : 
93
 
%%>----------------------------------------------------------------------<
94
 
makeDFChildren([Child|T], Parent, SuccMap, DomTree, DF) ->
95
 
    DF1 = make(Child, SuccMap, DomTree, DF),
96
 
    DF2 = checkIDomList(get(Child, DF1), Parent, DomTree, DF1),
97
 
    makeDFChildren(T, Parent, SuccMap, DomTree, DF2);
98
 
makeDFChildren([], _, _, _, DF) -> DF.
99
 
 
100
 
 
101
 
%%>----------------------------------------------------------------------<
102
 
%  Procedure : checIDomList
103
 
%  Purpose   : Adds all the nodes in the list to the parents dominance
104
 
%              frontier who do not have parent as immediate dominator.
105
 
%  Arguments : NodeList - The list of nodes that the function traverses
106
 
%              Parent - The parent of the nodes
107
 
%              DomTree - Our dominator tree
108
 
%              DF - The dominance frontiers so far
109
 
%  Notes     : 
110
 
%%>----------------------------------------------------------------------<
111
 
checkIDomList([Node|T], Parent, DomTree, DF) ->
112
 
    DF1 = checkIDom(Node, Parent, DomTree, DF),
113
 
    checkIDomList(T, Parent, DomTree, DF1);
114
 
checkIDomList([], _, _, DF) -> DF.
115
 
 
116
 
                                                     
117
 
%%>----------------------------------------------------------------------<
118
 
%  Procedure : checkIdom
119
 
%  Purpose   : adds Node1 to Node2s dominance frontier if Node2 is not
120
 
%              Node1s immediate dominator.
121
 
%  Arguments : Node1 - a node
122
 
%              Node2 - another node
123
 
%              DomTree - the dominator tree
124
 
%              DF - the dominance frontier so far
125
 
%  Notes     : 
126
 
%%>----------------------------------------------------------------------<
127
 
checkIDom(Node1, Node2, DomTree, DF) ->
128
 
    case hipe_domtree:getIDom(Node1, DomTree) of
129
 
        Node2 ->
130
 
            DF;
131
 
        none ->
132
 
            DF;
133
 
        _ ->
134
 
            add(Node2, Node1, DF)
135
 
    end.
136
 
 
137
 
 
138
 
 
139
 
 
140
 
 
141