File: hipe_rtl_liveness.erl

package info (click to toggle)
erlang 1%3A11.b.2-4
  • links: PTS
  • area: main
  • in suites: etch, etch-m68k
  • size: 54,332 kB
  • ctags: 138,013
  • sloc: erlang: 566,932; ansic: 185,450; makefile: 14,148; java: 7,835; sh: 7,307; lisp: 5,249; pascal: 3,225; perl: 2,290; asm: 1,325; cpp: 306; tcl: 245; csh: 29; python: 21; sed: 9
file content (128 lines) | stat: -rw-r--r-- 2,893 bytes parent folder | download
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
%% $Id$
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%%
%% LIVENESS ANALYSIS
%%
%% Exports:
%% ~~~~~~~
%% analyze(CFG) - returns a livenes analyzis of CFG.
%% liveout(Liveness, Label) - returns a set of variables that are alive at
%%      exit from basic block named Label.
%% livein(Liveness, Label) - returns a set of variables that are alive at
%%      entry to the basic block named Label.
%% list(Instructions, LiveOut) - Given a list of instructions and a liveout
%%      set, returns a set of variables live at the first instruction.
%%

-module(hipe_rtl_liveness).

-define(LIVEOUT_NEEDED,true).	% needed for liveness.inc below.
-define(PRETTY_PRINT,true).
-include("../flow/liveness.inc").

%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%%
%% Interface to CFG and RTL.
%%

cfg_bb(CFG, L) ->
   hipe_rtl_cfg:bb(CFG, L).

cfg_postorder(CFG) ->
   hipe_rtl_cfg:postorder(CFG).

cfg_succ_map(CFG) ->
   hipe_rtl_cfg:succ_map(CFG).

cfg_succ(CFG, L) ->
   hipe_rtl_cfg:succ(CFG, L).

uses(Instr) ->
  hipe_rtl:uses(Instr).

defines(Instr) ->
  hipe_rtl:defines(Instr).

%%
%% This is the list of registers that are live at exit from a function
%%

liveout_no_succ() ->
  hipe_rtl_arch:live_at_return().

%%
%% The following are used only if annotation of the code is requested.
%%

cfg_labels(CFG) ->
   hipe_rtl_cfg:reverse_postorder(CFG).

pp_block(Label, CFG) ->
  BB=hipe_rtl_cfg:bb(CFG, Label),
  Code=hipe_bb:code(BB),
  hipe_rtl:pp_block(Code).

pp_liveness_info(LiveList) ->
  NewList=remove_precoloured(LiveList),
  print_live_list(NewList).

print_live_list([]) ->
  io:format(" none~n", []);
print_live_list([Last]) ->
  io:format(" ", []),
  print_var(Last),
  io:format("~n", []);
print_live_list([Var|Rest]) ->
  io:format(" ", []),
  print_var(Var),
  io:format(",", []), 
  print_live_list(Rest).

print_var(A) ->
  case hipe_rtl:is_var(A) of
    true -> 
      pp_var(A);
    false ->
      case hipe_rtl:is_reg(A) of
	true ->
	  pp_reg(A);
	false ->
	  case hipe_rtl:is_fpreg(A) of
	    true ->
	      io:format("f~w", [hipe_rtl:fpreg_index(A)]);
	    false ->
	      io:format("unknown:~w", [A])
	  end
      end
  end.

pp_hard_reg(N) ->
  io:format("~s", [hipe_rtl_arch:reg_name(N)]).

pp_reg(Arg) ->
  case hipe_rtl_arch:is_precoloured(Arg) of
    true ->
      pp_hard_reg(hipe_rtl:reg_index(Arg));
    false ->
      io:format("r~w", [hipe_rtl:reg_index(Arg)])
  end.

pp_var(Arg) ->
  case hipe_rtl_arch:is_precoloured(Arg) of
    true ->
      pp_hard_reg(hipe_rtl:var_index(Arg));
    false ->
      io:format("v~w", [hipe_rtl:var_index(Arg)])
  end.	      

remove_precoloured(List) ->
  List.  
%lists:filter(fun(X) -> not hipe_rtl_arch:is_precoloured(X) end, List).

-ifdef(DEBUG_LIVENESS).
cfg_bb_add(CFG, L, NewBB) ->
  hipe_rtl_cfg:bb_add(CFG, L, NewBB).

mk_comment(Text) ->
  hipe_rtl:mk_comment(Text).
-endif.