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

« back to all changes in this revision

Viewing changes to lib/hipe/main/hipe.hrl

  • 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
 
%% -*- erlang-indent-level: 2 -*-
3
 
%% ====================================================================
4
 
%%  Filename :  hipe.hrl
5
 
%%  Purpose  :  To define some usefull macros for debugging
6
 
%%               and error reports. 
7
 
%%  Notes    :  
8
 
%%              
9
 
%%              
10
 
%%              
11
 
%%  History  :  * 2000-11-03 Erik Johansson (happi@csd.uu.se): 
12
 
%%               Created.
13
 
%%  CVS      :
14
 
%%              $Author: happi $
15
 
%%              $Date: 2002/10/17 11:55:55 $
16
 
%%              $Revision: 1.35 $
17
 
%% ====================================================================
18
 
%%
19
 
%%
20
 
%% Defines:
21
 
%%  version/0          - returns the version number of HiPE as a tuple.
22
 
%%  msg/2              - Works like io:format but prepends 
23
 
%%                       ?MSGTAG to the message.
24
 
%%                       If LOGGING is defined then error_logger is used.
25
 
%%  untagged_msg/2     - Like msg/2 but without the tag.
26
 
%%  warning_msg/2      - Prints a tagged warning.
27
 
%%  error_msg/2        - Logs a tagged error.
28
 
%%  debug_msg/2        - Prints a tagged msg if DEBUG is defined.
29
 
%%  IF_DEBUG(A,B)      - Excutes A if DEBUG is defined B otherwise.    
30
 
%%  IF_DEBUG(Lvl, A,B) - Excutes A if DEBUG is defined to a value >= Lvl 
31
 
%%                       otherwise B is executed.    
32
 
%%  EXIT               - Exits with added module and line info.
33
 
%%  ASSERT             - Exits if the expresion does not evaluate to true.
34
 
%%  VERBOSE_ASSSERT    - A message is printed even when an asertion is true.
35
 
%%  TIME_STMNT(Stmnt, String, FreeVar) 
36
 
%%                     - Times the statemnet Stmnt if TIMING is on. 
37
 
%%                       The execution time is bound to FreeVar. 
38
 
%%                       String is printed after the execution
39
 
%%                       followed by the excution time in s and a newline.
40
 
%%
41
 
%%
42
 
%% Flags:
43
 
%%  DEBUG           - Turns on debugging. (Can be defined to a integer
44
 
%%                    value to determine the level of debugging)
45
 
%%  VERBOSE         - More info is printed...
46
 
%%  HIPE_LOGGING    - Turn on logging of messages with erl_logger.
47
 
%%  DO_ASSERT       - Turn on Assertions.
48
 
%%  TIMING          - Turn on timing.
49
 
%%  HIPE_INSTRUMENT_COMPILER - Turn on instrumentation of the compiler
50
 
%%
51
 
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
52
 
 
53
 
-define(version(),{2,0,2}).
54
 
-define(majorvnr,element(1,?version())).
55
 
-define(minorvnr,element(2,?version())).
56
 
-define(incrementvnr,element(3,?version())).
57
 
-define(msgtagmap(M), 
58
 
        case M of 
59
 
          hipe -> "";
60
 
          hipe_main -> "";
61
 
          hipe_update_catches -> "";
62
 
          hipe_sparc_loader -> "Loader   ";
63
 
          hipe_beam_to_icode -> "";
64
 
          hipe_sparc_ra -> ""; 
65
 
          hipe_sparc_caller_saves -> ""; 
66
 
          hipe_icode_cfg -> ""; 
67
 
          hipe_rtl_cfg -> ""; 
68
 
          hipe_sparc_cfg -> ""; 
69
 
          hipe_x86_cfg -> ""; 
70
 
          _ ->  atom_to_list(M)
71
 
        end).
72
 
 
73
 
 
74
 
-define(MMSGTAG(Mod), 
75
 
        "<HiPE " ++ ?msgtagmap(Mod) ++
76
 
        "(v " ++ integer_to_list(?majorvnr) ++ "."
77
 
        ++ integer_to_list(?minorvnr) ++ "."
78
 
        ++ integer_to_list(?incrementvnr) ++ ")> ").
79
 
-define(MSGTAG,?MMSGTAG(?MODULE)).
80
 
 
81
 
 
82
 
%%
83
 
%% Define the message macros with or without logging,
84
 
 
85
 
-define(msg(Msg, Args),
86
 
        code_server:info_msg(?MSGTAG ++ Msg, Args)).
87
 
-define(mmsg(Msg, Args, Mod),
88
 
        code_server:info_msg(?MMSGTAG(Mod) ++ Msg, Args)).
89
 
-define(untagged_msg(Msg, Args),
90
 
        code_server:info_msg(Msg, Args)).
91
 
 
92
 
%%
93
 
%% Define error and warning messages.
94
 
-define(error_msg(Msg, Args),
95
 
        code_server:error_msg(
96
 
          ?MSGTAG ++
97
 
          "ERROR:~s:~w: " ++ Msg,
98
 
          [?FILE,?LINE|Args])).
99
 
 
100
 
-define(warning_msg(Msg, Args),
101
 
        ?msg("WARNING:~s:~w: " ++ Msg, [?FILE,?LINE|Args])).
102
 
 
103
 
 
104
 
 
105
 
%%
106
 
%% Define the macros that are dependent on the debug flag.
107
 
%%
108
 
 
109
 
-ifdef(DEBUG).
110
 
-define(debug_msg(Msg,Data), ?msg(Msg,Data)).
111
 
-define(debug_untagged_msg(Msg,Data), ?untagged_msg(Msg,Data)).
112
 
-define(IF_DEBUG(DebugAction,NoDebugAction),DebugAction).
113
 
-define(IF_DEBUG_LEVEL(Level,DebugAction,NoDebugAction),
114
 
        if(Level =< ?DEBUG) -> DebugAction; true -> NoDebugAction end ).
115
 
 
116
 
-else.
117
 
-define(debug_msg(Msg,Data), no_debug).
118
 
-define(debug_untagged_msg(Msg,Data), no_debug).
119
 
-define(IF_DEBUG(DebugAction,NoDebugAction),NoDebugAction).
120
 
-define(IF_DEBUG_LEVEL(Level,DebugAction,NoDebugAction),NoDebugAction).
121
 
-endif.
122
 
 
123
 
 
124
 
%% Define the exit macro
125
 
%%
126
 
-ifdef(VERBOSE).
127
 
-define(EXIT(Reason),
128
 
        ?msg("EXITED with reason ~w @~w:~w\n",
129
 
            [Reason,?MODULE,?LINE]),
130
 
        erlang:fault({?MODULE,?LINE,Reason})).
131
 
-else.
132
 
-define(EXIT(Reason),erlang:fault({?MODULE,?LINE,Reason})).
133
 
-endif.
134
 
 
135
 
 
136
 
%% Assertions.
137
 
-ifdef(DO_ASSERT).
138
 
-define(VERBOSE_ASSERT(X),
139
 
        case X of 
140
 
          true ->
141
 
            io:format("Assertion ok ~w ~w\n",[?MODULE,?LINE]),
142
 
            true;
143
 
          __ASSVAL_R -> 
144
 
            io:format("Assertion failed ~w ~w: ~p\n",
145
 
                      [?MODULE,?LINE, __ASSVAL_R]),
146
 
            ?EXIT(assertion_failed)
147
 
        end).
148
 
-define(ASSERT(X),
149
 
        case X of 
150
 
          true -> true;
151
 
          _ -> ?EXIT(assertion_failed)
152
 
        end).
153
 
-else.
154
 
-define(ASSERT(X),true).
155
 
-define(VERBOSE_ASSERT(X),true).
156
 
-endif.
157
 
 
158
 
 
159
 
 
160
 
 
161
 
% Use this to display info, save stuff and so on.
162
 
% Vars cannot be exported from Action
163
 
-define(when_option(__Opt,__Opts,__Action),
164
 
        case proplists:get_bool(__Opt,__Opts) of
165
 
            true -> __Action; false -> ok end).
166
 
 
167
 
 
168
 
 
169
 
%% Timing macros
170
 
 
171
 
-ifdef(TIMING).
172
 
-define(TIME_STMNT(STMNT,Msg,Timer),
173
 
        Timer = hipe_timing:start_timer(),
174
 
        STMNT,
175
 
        ?untagged_msg(Msg ++ "~.2f s\n",[hipe_timing:stop_timer(Timer)/1000])).
176
 
-else.
177
 
-define(TIME_STMNT(STMNT,Msg,Timer),STMNT).
178
 
-endif.
179
 
 
180
 
 
181
 
-define(start_timer(Text), hipe_timing:start(Text, ?MODULE)).
182
 
-define(stop_timer(Text), hipe_timing:stop(Text, ?MODULE)).
183
 
-define(start_hipe_timer(Timer), hipe_timing:start_hipe_timer(Timer)).
184
 
-define(stop_hipe_timer(Timer), hipe_timing:stop_hipe_timer(Timer)).
185
 
-define(get_hipe_timer_val(Timer), get(Timer)).
186
 
-define(set_hipe_timer_val(Timer, Val), put(Timer, Val)).
187
 
-define(option_time(Stmnt, Text, Options),
188
 
        ?when_option(time, Options, ?start_timer(Text)),
189
 
        fun(R) ->
190
 
            ?when_option(time, Options, ?stop_timer(Text)),
191
 
            R
192
 
        end(Stmnt)).
193
 
 
194
 
-define(option_start_time(Text,Options),
195
 
        ?when_option(time, Options, ?start_timer(Text))).
196
 
 
197
 
-define(option_stop_time(Text,Options),
198
 
        ?when_option(time, Options, ?stop_timer(Text))).
199
 
 
200
 
-define(opt_start_timer(Text),
201
 
        hipe_timing:start_optional_timer(Text,?MODULE)).
202
 
-define(opt_stop_timer(Text),
203
 
        hipe_timing:stop_optional_timer(Text,?MODULE)).
204
 
                     
205
 
%% Turn on instrumentation of the compiler.
206
 
-ifdef(HIPE_INSTRUMENT_COMPILER).
207
 
-define(count_pre_ra_instructions(Options, NoInstrs),
208
 
        ?when_option(count_instrs, Options,
209
 
                     put(pre_ra_instrs,
210
 
                         get(pre_ra_instrs)+ NoInstrs))).
211
 
-define(count_post_ra_instructions(Options, NoInstrs),
212
 
        ?when_option(count_instrs, Options,
213
 
                     put(post_ra_instrs,
214
 
                         get(post_ra_instrs)+ NoInstrs))).
215
 
 
216
 
-define(start_time_regalloc(Options),
217
 
        ?when_option(timeregalloc, Options, 
218
 
                     put(regalloctime1,erlang:statistics(runtime)))).
219
 
-define(stop_time_regalloc(Options),
220
 
        ?when_option(timeregalloc, Options, 
221
 
                     put(regalloctime,
222
 
                         get(regalloctime) + 
223
 
                         (element(1,erlang:statistics(runtime))
224
 
                          -element(1,get(regalloctime1)))))).
225
 
-define(start_time_caller_saves(Options),
226
 
        ?when_option(timeregalloc, Options, 
227
 
                     put(callersavetime1,erlang:statistics(runtime)))).
228
 
-define(stop_time_caller_saves(Options),
229
 
        ?when_option(timeregalloc, Options, 
230
 
                     put(callersavetime,
231
 
                         get(callersavetime) + 
232
 
                         (element(1,erlang:statistics(runtime))
233
 
                          -element(1,get(callersavetime1)))))).
234
 
 
235
 
-define(count_pre_ra_temps(Options, NoTemps),
236
 
        ?when_option(count_temps, Options,
237
 
                     put(pre_ra_temps,
238
 
                         get(pre_ra_temps)+ NoTemps))).
239
 
-define(count_post_ra_temps(Options, NoTemps),
240
 
        ?when_option(count_temps, Options,
241
 
                     put(post_ra_temps,
242
 
                         get(post_ra_temps)+ NoTemps))).
243
 
 
244
 
-define(inc_counter(Counter, Val),
245
 
        case get(Counter) of
246
 
          undefined -> true;
247
 
          _ -> put(Counter, Val + get(Counter))
248
 
        end).
249
 
 
250
 
-define(cons_counter(Counter, Val),
251
 
        case get(Counter) of
252
 
          undefined -> true;
253
 
          _ -> put(Counter, [Val|get(Counter)])
254
 
        end).
255
 
 
256
 
 
257
 
-define(update_counter(Counter, Val, Op),
258
 
        case get(Counter) of
259
 
          undefined -> true;
260
 
          _ -> put(Counter, get(Counter) Op Val)
261
 
        end).
262
 
 
263
 
 
264
 
-define(start_ra_instrumentation(Options, NoInstrs, NoTemps),
265
 
        begin
266
 
          ?count_pre_ra_instructions(Options, NoInstrs),
267
 
          ?count_pre_ra_temps(Options, NoTemps),
268
 
          case get(counter_mem_temps) of
269
 
            undefined -> true;
270
 
            _ -> put(counter_mfa_mem_temps,[])
271
 
          end,
272
 
          ?start_time_regalloc(Options)
273
 
        end).
274
 
-define(stop_ra_instrumentation(Options, NoInstrs, NoTemps),
275
 
        begin
276
 
          ?stop_time_regalloc(Options),
277
 
          ?count_post_ra_instructions(Options, NoInstrs),
278
 
          ?cons_counter(counter_mem_temps, get(counter_mfa_mem_temps)),
279
 
          ?cons_counter(ra_all_iterations_counter, get(ra_iteration_counter)),
280
 
          put(ra_iteration_counter,0),
281
 
          ?count_post_ra_temps(Options, NoTemps)
282
 
        end).
283
 
 
284
 
-define(add_spills(Options, NoSpills),
285
 
        ?when_option(count_spills, Options, 
286
 
                     put(spilledtemps, get(spilledtemps) + NoSpills))).
287
 
 
288
 
-define(optional_start_timer(Timer, Options),
289
 
        case lists:member(Timer, proplists:get_value(timers,Options++[{timers,[]}])) of
290
 
          true -> ?start_hipe_timer(Timer);
291
 
          false -> true
292
 
        end).
293
 
-define(optional_stop_timer(Timer, Options),
294
 
        case lists:member(Timer, proplists:get_value(timers,Options++[{timers,[]}])) of
295
 
          true -> ?stop_hipe_timer(Timer);
296
 
          false -> true
297
 
        end).
298
 
        
299
 
                     
300
 
-else.  %% HIPE_INSTRUMENT_COMPILER
301
 
-define(count_pre_ra_instructions(Options, NoInstrs), no_instrumentation).
302
 
-define(count_post_ra_instructions(Options, NoInstrs),no_instrumentation).
303
 
-define(start_time_regalloc(Options),no_instrumentation).
304
 
-define(stop_time_regalloc(Options),no_instrumentation).
305
 
-define(start_time_caller_saves(Options),no_instrumentation).
306
 
-define(stop_time_caller_saves(Options),no_instrumentation).
307
 
-define(count_pre_ra_temps(Options, NoTemps),no_instrumentation).
308
 
-define(count_post_ra_temps(Options, NoTemps),no_instrumentation).
309
 
-define(start_ra_instrumentation(Options, NoInstrs, NoTemps),no_instrumentation).
310
 
-define(stop_ra_instrumentation(Options, NoInstrs, NoTemps),no_instrumentation).
311
 
-define(add_spills(Options, NoSpills), no_instrumentation).
312
 
-define(optional_start_timer(Options,Timer), no_instrumentation).
313
 
-define(optional_stop_timer(Options,Timer), no_instrumentation).
314
 
-define(inc_counter(Counter, Val), no_instrumentation).
315
 
-define(update_counter(Counter, Val, Op), no_instrumentation).
316
 
-define(cons_counter(Counter, Val),no_instrumentation).
317
 
-endif. %% HIPE_INSTRUMENT_COMPILER     
318
 
 
319