~rdoering/ubuntu/karmic/erlang/fix-535090

« back to all changes in this revision

Viewing changes to lib/hipe/icode/hipe_icode_type.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-02-15 16:42:52 UTC
  • mfrom: (3.1.2 squeeze)
  • Revision ID: james.westby@ubuntu.com-20090215164252-q5x4rcf8a5pbesb1
Tags: 1:12.b.5-dfsg-2
Upload to unstable after lenny is released.

Show diffs side-by-side

added added

removed removed

Lines of Context:
29
29
-include("hipe_icode_type.hrl").
30
30
-include("../flow/cfg.hrl").
31
31
 
32
 
-type(args_fun() :: fun((mfa(), cfg()) -> [erl_type()])).
33
 
-type(call_fun() :: fun((mfa(), [_]) -> erl_type())).
34
 
-type(final_fun() :: fun((mfa(), [_]) -> 'ok')).
35
 
-type(data() :: {mfa(), args_fun(), call_fun(), final_fun()}).
 
32
-type args_fun()  :: fun((mfa(), cfg()) -> [erl_type()]).
 
33
-type call_fun()  :: fun((mfa(), [_]) -> erl_type()).
 
34
-type final_fun() :: fun((mfa(), [_]) -> 'ok').
 
35
-type data()      :: {mfa(), args_fun(), call_fun(), final_fun()}.
36
36
 
37
37
%-define(DO_HIPE_ICODE_TYPE_TEST, false).
38
38
 
97
97
%% The main exported function
98
98
%%-----------------------------------------------------------------------
99
99
 
100
 
-spec(cfg/4 :: (cfg(), mfa(), comp_options(), #comp_servers{}) -> cfg()).
 
100
-spec cfg(cfg(), mfa(), comp_options(), #comp_servers{}) -> cfg().
101
101
 
102
102
cfg(Cfg, MFA, Options, Servers) ->
103
103
  case proplists:get_bool(concurrent_comp, Options) of
150
150
  FinalFun = fun(_,_) -> ok end,
151
151
  {MFA,ArgsFun,CallFun,FinalFun}.
152
152
 
153
 
%debug_make_data(Cfg, {_M,_F,A}=MFA) ->
154
 
%  NoArgs = 
155
 
%    case hipe_icode_cfg:is_closure(Cfg) of
156
 
%      true -> hipe_icode_cfg:closure_arity(Cfg);
157
 
%      false -> A
158
 
%    end,
159
 
%  Args = lists:duplicate(NoArgs,t_any()), 
160
 
%  ArgsFun = fun(MFA,_Cfg) -> io:format("Start:~p~n",[MFA]),Args end,
161
 
%  CallFun = fun(MFA,Types) -> io:format("Call With:~p~nTo:~p~n",[Types,MFA]), t_any() end,
162
 
%  FinalFun = fun(MFA,Type) -> io:format("ResType:~p~nFor:~p~n",[Type,MFA]),ok end,
163
 
%  {MFA,ArgsFun,CallFun,FinalFun}.
 
153
%%debug_make_data(Cfg, {_M,_F,A}=MFA) ->
 
154
%%  NoArgs = 
 
155
%%    case hipe_icode_cfg:is_closure(Cfg) of
 
156
%%      true -> hipe_icode_cfg:closure_arity(Cfg);
 
157
%%      false -> A
 
158
%%    end,
 
159
%%  Args = lists:duplicate(NoArgs,t_any()), 
 
160
%%  ArgsFun = fun(MFA,_Cfg) -> io:format("Start:~p~n",[MFA]),Args end,
 
161
%%  CallFun = fun(MFA,Types) -> io:format("Call With:~p~nTo:~p~n",[Types,MFA]), t_any() end,
 
162
%%  FinalFun = fun(MFA,Type) -> io:format("ResType:~p~nFor:~p~n",[Type,MFA]),ok end,
 
163
%%  {MFA,ArgsFun,CallFun,FinalFun}.
164
164
 
165
165
 
166
166
%% _________________________________________________________________
174
174
%% information is added to the worklist.
175
175
%%
176
176
 
177
 
-spec(analyse/2 :: (cfg(), data()) -> 'ok').
 
177
-spec analyse(cfg(), data()) -> 'ok'.
178
178
 
179
179
analyse(Cfg, Data) ->
180
180
  try
183
183
  catch throw:no_input -> ok % No need to do anything since we have no input
184
184
  end.
185
185
 
186
 
-spec(safe_analyse/2 :: (cfg(), data()) -> #state{}).
 
186
-spec safe_analyse(cfg(), data()) -> #state{}.
187
187
 
188
188
safe_analyse(Cfg, {MFA,_,_,_}=Data) ->
189
189
  State = new_state(Cfg, Data),
1115
1115
%% out of the block to annotate all variables in it.
1116
1116
%%
1117
1117
 
1118
 
-spec(specialize/1 :: (cfg()) -> cfg()).
 
1118
-spec specialize(cfg()) -> cfg().
1119
1119
 
1120
1120
specialize(Cfg) ->
1121
1121
  Labels = hipe_icode_cfg:reverse_postorder(Cfg),
1884
1884
butlast([H|T]) ->
1885
1885
  [H|butlast(T)].
1886
1886
 
1887
 
-spec(any_is_none/1 :: ([erl_type()]) -> bool()).
 
1887
-spec any_is_none([erl_type()]) -> bool().
1888
1888
any_is_none([H|T]) ->
1889
1889
  case t_is_none(H) of
1890
1890
    true -> true;
2083
2083
make_annotation(X, Info) ->
2084
2084
  {type_anno, safe_lookup(X, Info), fun erl_types:t_to_string/1}. 
2085
2085
 
2086
 
-spec(unannotate_cfg/1 :: (cfg()) -> cfg()).
 
2086
-spec unannotate_cfg(cfg()) -> cfg().
2087
2087
 
2088
2088
unannotate_cfg(Cfg) ->
2089
2089
  NewCfg = unannotate_params(Cfg),
2166
2166
  end.
2167
2167
 
2168
2168
get_primop_arg_types(Primop) ->
2169
 
  case erl_bif_types:arg_types(Primop) of
 
2169
  case hipe_icode_primops:arg_types(Primop) of
2170
2170
    any -> any;
2171
2171
    ArgTypes -> add_tuple_to_args(ArgTypes)
2172
2172
  end.
2209
2209
%% Icode Coordinator Callbacks
2210
2210
%%=====================================================================
2211
2211
 
2212
 
-spec(replace_nones/1 :: ([erl_type()] | erl_type()) -> [erl_type()]).
 
2212
-spec replace_nones([erl_type()] | erl_type()) -> [erl_type()].
2213
2213
 
2214
2214
replace_nones(Types) when is_list(Types) ->
2215
2215
  [replace_none(T) || T <- Types];
2216
2216
replace_nones(Type) ->
2217
2217
  [replace_none(Type)].
2218
2218
 
2219
 
-spec(replace_none/1 :: (erl_type()) -> erl_type()).
 
2219
-spec replace_none(erl_type()) -> erl_type().
2220
2220
 
2221
2221
replace_none(Type) ->
2222
2222
  case erl_types:t_is_none(Type) of
2226
2226
      Type
2227
2227
  end.
2228
2228
 
2229
 
-spec(update__info/2 :: ([erl_type()], [erl_type()]) -> {bool(), [erl_type()]}).
 
2229
-spec update__info([erl_type()], [erl_type()]) -> {bool(), [erl_type()]}.
2230
2230
 
2231
2231
update__info(NewTypes, OldTypes) ->
2232
2232
  SupFun = 
2238
2238
  Change = lists:zipwith(EqFun, ResTypes, OldTypes),
2239
2239
  {lists:all(fun(X) -> X end, Change), ResTypes}.
2240
2240
 
2241
 
-spec(new__info/1 :: ([erl_type()]) -> [erl_type()]).
 
2241
-spec new__info([erl_type()]) -> [erl_type()].
2242
2242
 
2243
2243
new__info(NewTypes) ->
2244
2244
  [erl_types:t_limit(T, ?TYPE_DEPTH) || T <- NewTypes].
2245
2245
 
2246
 
-spec(return__info/1 :: (erl_type()) -> erl_type()).
 
2246
-spec return__info(erl_type()) -> erl_type().
2247
2247
 
2248
2248
return__info(Types) ->  
2249
2249
  Types.
2250
2250
 
2251
 
-spec(return_none/0 :: () -> [erl_type(),...]).
 
2251
-spec return_none() -> [erl_type(),...].
2252
2252
 
2253
2253
return_none() ->
2254
2254
  [erl_types:t_none()].
2255
2255
 
2256
 
-spec(return_none_args/2 :: (cfg(), mfa()) -> [erl_type()]).
 
2256
-spec return_none_args(cfg(), mfa()) -> [erl_type()].
2257
2257
 
2258
2258
return_none_args(Cfg, {_M,_F,A}) ->
2259
2259
  NoArgs = 
2263
2263
    end,
2264
2264
  lists:duplicate(NoArgs, erl_types:t_none()).
2265
2265
 
2266
 
-spec(return_any_args/2 :: (cfg(), mfa()) -> [erl_type()]).
 
2266
-spec return_any_args(cfg(), mfa()) -> [erl_type()].
2267
2267
 
2268
2268
return_any_args(Cfg, {_M,_F,A}) ->
2269
2269
  NoArgs =