~ubuntu-branches/ubuntu/trusty/erlang/trusty

« back to all changes in this revision

Viewing changes to lib/dialyzer/src/dialyzer_behaviours.erl

  • Committer: Bazaar Package Importer
  • Author(s): Clint Byrum
  • Date: 2011-05-05 15:48:43 UTC
  • mfrom: (3.5.13 sid)
  • Revision ID: james.westby@ubuntu.com-20110505154843-0om6ekzg6m7ugj27
Tags: 1:14.b.2-dfsg-3ubuntu1
* Merge from debian unstable.  Remaining changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to.
  - Drop erlang-wx binary.
  - Drop erlang-wx dependency from -megaco, -common-test, and -reltool, they
    do not really need wx. Also drop it from -debugger; the GUI needs wx,
    but it apparently has CLI bits as well, and is also needed by -megaco,
    so let's keep the package for now.
  - debian/patches/series: Do what I meant, and enable build-options.patch
    instead.
* Additional changes:
  - Drop erlang-wx from -et
* Dropped Changes:
  - patches/pcre-crash.patch: CVE-2008-2371: outer level option with
    alternatives caused crash. (Applied Upstream)
  - fix for ssl certificate verification in newSSL: 
    ssl_cacertfile_fix.patch (Applied Upstream)
  - debian/patches/series: Enable native.patch again, to get stripped beam
    files and reduce the package size again. (build-options is what
    actually accomplished this)
  - Remove build-options.patch on advice from upstream and because it caused
    odd build failures.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%% -*- erlang-indent-level: 2 -*-
 
2
%%-----------------------------------------------------------------------
 
3
%% %CopyrightBegin%
 
4
%%
 
5
%% Copyright Ericsson AB 2010. All Rights Reserved.
 
6
%%
 
7
%% The contents of this file are subject to the Erlang Public License,
 
8
%% Version 1.1, (the "License"); you may not use this file except in
 
9
%% compliance with the License. You should have received a copy of the
 
10
%% Erlang Public License along with this software. If not, it can be
 
11
%% retrieved online at http://www.erlang.org/.
 
12
%%
 
13
%% Software distributed under the License is distributed on an "AS IS"
 
14
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
15
%% the License for the specific language governing rights and limitations
 
16
%% under the License.
 
17
%%
 
18
%% %CopyrightEnd%
 
19
%%
 
20
 
 
21
%%%-------------------------------------------------------------------
 
22
%%% File        : dialyzer_behaviours.erl
 
23
%%% Authors     : Stavros Aronis <aronisstav@gmail.com>
 
24
%%% Description : Tools for analyzing proper behaviour usage.
 
25
%%%
 
26
%%% Created     : 28 Oct 2009 by Stavros Aronis <aronisstav@gmail.com>
 
27
%%%-------------------------------------------------------------------
 
28
%%% NOTE: This module is currently experimental -- do NOT rely on it!
 
29
%%%-------------------------------------------------------------------
 
30
 
 
31
-module(dialyzer_behaviours).
 
32
 
 
33
-export([check_callbacks/4, get_behaviours/2, get_behaviour_apis/1,
 
34
         translate_behaviour_api_call/5, translatable_behaviours/1,
 
35
         translate_callgraph/3]).
 
36
 
 
37
-export_type([behaviour/0, behaviour_api_dict/0]).
 
38
 
 
39
%%--------------------------------------------------------------------
 
40
 
 
41
-include("dialyzer.hrl").
 
42
 
 
43
%%--------------------------------------------------------------------
 
44
 
 
45
-type behaviour() :: atom().
 
46
 
 
47
-record(state, {plt        :: dialyzer_plt:plt(),
 
48
                codeserver :: dialyzer_codeserver:codeserver(),
 
49
                filename   :: file:filename(),
 
50
                behlines   :: [{behaviour(), non_neg_integer()}]}).
 
51
 
 
52
%%--------------------------------------------------------------------
 
53
 
 
54
-spec get_behaviours([module()], dialyzer_codeserver:codeserver()) ->
 
55
  {[behaviour()], [behaviour()]}.
 
56
 
 
57
get_behaviours(Modules, Codeserver) ->
 
58
  get_behaviours(Modules, Codeserver, [], []).
 
59
 
 
60
-spec check_callbacks(module(), [{cerl:cerl(), cerl:cerl()}],
 
61
                      dialyzer_plt:plt(),
 
62
                      dialyzer_codeserver:codeserver()) -> [dial_warning()].
 
63
 
 
64
check_callbacks(Module, Attrs, Plt, Codeserver) ->
 
65
  {Behaviours, BehLines} = get_behaviours(Attrs),
 
66
  case Behaviours of
 
67
    [] -> [];
 
68
    _ ->
 
69
      MFA = {Module,module_info,0},
 
70
      {_Var,Code} = dialyzer_codeserver:lookup_mfa_code(MFA, Codeserver),
 
71
      File = get_file(cerl:get_ann(Code)),
 
72
      State = #state{plt = Plt, codeserver = Codeserver, filename = File,
 
73
                     behlines = BehLines},
 
74
      Warnings = get_warnings(Module, Behaviours, State),
 
75
      [add_tag_file_line(Module, W, State) || W <- Warnings]
 
76
  end.
 
77
 
 
78
-spec translatable_behaviours(cerl:c_module()) -> behaviour_api_dict().
 
79
 
 
80
translatable_behaviours(Tree) ->
 
81
  Attrs = cerl:module_attrs(Tree),
 
82
  {Behaviours, _BehLines} = get_behaviours(Attrs),
 
83
  [{B, Calls} || B <- Behaviours, (Calls = behaviour_api_calls(B)) =/= []].
 
84
 
 
85
-spec get_behaviour_apis([behaviour()]) -> [mfa()].
 
86
 
 
87
get_behaviour_apis(Behaviours) ->
 
88
  get_behaviour_apis(Behaviours, []).
 
89
 
 
90
-spec translate_behaviour_api_call(dialyzer_races:mfa_or_funlbl(),
 
91
                                   [erl_types:erl_type()],
 
92
                                   [dialyzer_races:core_vars()],
 
93
                                   module(),
 
94
                                   behaviour_api_dict()) ->
 
95
                                      {dialyzer_races:mfa_or_funlbl(),
 
96
                                       [erl_types:erl_type()],
 
97
                                       [dialyzer_races:core_vars()]}
 
98
                                        | 'plain_call'.
 
99
 
 
100
translate_behaviour_api_call(_Fun, _ArgTypes, _Args, _Module, []) ->
 
101
  plain_call;
 
102
translate_behaviour_api_call({Module, Fun, Arity}, ArgTypes, Args,
 
103
                             CallbackModule, BehApiInfo) ->
 
104
  case lists:keyfind(Module, 1, BehApiInfo) of
 
105
    false -> plain_call;
 
106
    {Module, Calls} ->
 
107
      case lists:keyfind({Fun, Arity}, 1, Calls) of
 
108
        false -> plain_call;
 
109
        {{Fun, Arity}, {CFun, CArity, COrder}} ->
 
110
          {{CallbackModule, CFun, CArity},
 
111
           [nth_or_0(N, ArgTypes, erl_types:t_any()) || N <-COrder],
 
112
           [nth_or_0(N, Args, bypassed) || N <-COrder]}
 
113
      end
 
114
  end;
 
115
translate_behaviour_api_call(_Fun, _ArgTypes, _Args, _Module, _BehApiInfo) ->
 
116
  plain_call.
 
117
 
 
118
-spec translate_callgraph(behaviour_api_dict(), atom(),
 
119
                          dialyzer_callgraph:callgraph()) ->
 
120
                             dialyzer_callgraph:callgraph().
 
121
 
 
122
translate_callgraph([{Behaviour,_}|Behaviours], Module, Callgraph) ->
 
123
  UsedCalls = [Call || {_From, {M, _F, _A}} = Call <-
 
124
                         dialyzer_callgraph:get_behaviour_api_calls(Callgraph),
 
125
                       M =:= Behaviour],
 
126
  Calls = [{{Behaviour, API, Arity}, Callback} ||
 
127
            {{API, Arity}, Callback} <- behaviour_api_calls(Behaviour)],
 
128
  DirectCalls = [{From, {Module, Fun, Arity}} ||
 
129
                  {From, To} <- UsedCalls,{API, {Fun, Arity, _Ord}} <- Calls,
 
130
                  To =:= API],
 
131
  NewCallgraph = dialyzer_callgraph:add_edges(DirectCalls, Callgraph),
 
132
  translate_callgraph(Behaviours, Module, NewCallgraph);
 
133
translate_callgraph([], _Module, Callgraph) ->
 
134
  Callgraph.
 
135
 
 
136
%%--------------------------------------------------------------------
 
137
 
 
138
get_behaviours(Attrs) ->
 
139
  BehaviourListsAndLine = [{cerl:concrete(L2), hd(cerl:get_ann(L2))} ||
 
140
                  {L1, L2} <- Attrs, cerl:is_literal(L1),
 
141
                  cerl:is_literal(L2), cerl:concrete(L1) =:= 'behaviour'],
 
142
  Behaviours = lists:append([Behs || {Behs,_} <- BehaviourListsAndLine]),
 
143
  BehLines = [{B,L} || {L1,L} <- BehaviourListsAndLine, B <- L1],
 
144
  {Behaviours, BehLines}.
 
145
 
 
146
get_warnings(Module, Behaviours, State) ->
 
147
  get_warnings(Module, Behaviours, State, []).
 
148
 
 
149
get_warnings(_, [], _, Acc) ->
 
150
  Acc;
 
151
get_warnings(Module, [Behaviour|Rest], State, Acc) ->
 
152
  Warnings = check_behaviour(Module, Behaviour, State),
 
153
  get_warnings(Module, Rest, State, Warnings ++ Acc).
 
154
 
 
155
check_behaviour(Module, Behaviour, State) ->
 
156
  try
 
157
    Callbacks = Behaviour:behaviour_info(callbacks),
 
158
    Fun = fun({_,_,_}) -> true;
 
159
             (_)       -> false
 
160
          end,
 
161
    case lists:any(Fun, Callbacks) of
 
162
      true ->  check_all_callbacks(Module, Behaviour, Callbacks, State);
 
163
      false -> []
 
164
    end
 
165
  catch
 
166
    _:_ -> []
 
167
  end.
 
168
 
 
169
check_all_callbacks(Module, Behaviour, Callbacks, State) ->
 
170
  check_all_callbacks(Module, Behaviour, Callbacks, State, []).
 
171
 
 
172
check_all_callbacks(_Module, _Behaviour, [], _State, Acc) ->
 
173
  Acc;
 
174
check_all_callbacks(Module, Behaviour, [{Fun, Arity, Spec}|Rest],
 
175
                    #state{codeserver = CServer} = State, Acc) ->
 
176
  Records = dialyzer_codeserver:get_records(CServer),
 
177
  ExpTypes = dialyzer_codeserver:get_exported_types(CServer),
 
178
  case parse_spec(Spec, ExpTypes, Records) of
 
179
    {ok, Fun, Type} ->
 
180
      RetType = erl_types:t_fun_range(Type),
 
181
      ArgTypes = erl_types:t_fun_args(Type),
 
182
      Warns = check_callback(Module, Behaviour, Fun, Arity, RetType,
 
183
                             ArgTypes, State#state.plt);
 
184
    Else ->
 
185
      Warns = [{invalid_spec, [Behaviour, Fun, Arity, reason_spec_error(Else)]}]
 
186
  end,
 
187
  check_all_callbacks(Module, Behaviour, Rest, State, Warns ++ Acc);
 
188
check_all_callbacks(Module, Behaviour, [{Fun, Arity}|Rest], State, Acc) ->
 
189
  Warns = {spec_missing, [Behaviour, Fun, Arity]},
 
190
  check_all_callbacks(Module, Behaviour, Rest, State, [Warns|Acc]).
 
191
 
 
192
parse_spec(String, ExpTypes, Records) ->
 
193
  case erl_scan:string(String) of
 
194
    {ok, Tokens, _} ->
 
195
      case erl_parse:parse(Tokens) of
 
196
        {ok, Form} ->
 
197
          case Form of
 
198
            {attribute, _, 'spec', {{Fun, _}, [TypeForm|_Constraint]}} ->
 
199
              MaybeRemoteType = erl_types:t_from_form(TypeForm),
 
200
              try
 
201
                Type = erl_types:t_solve_remote(MaybeRemoteType, ExpTypes,
 
202
                                                Records),
 
203
                {ok, Fun, Type}
 
204
              catch
 
205
                throw:{error,Msg} -> {spec_remote_error, Msg}
 
206
              end;
 
207
            _Other -> not_a_spec
 
208
          end;
 
209
        {error, {Line, _, Msg}} -> {spec_parser_error, Line, Msg}
 
210
      end;
 
211
    _Other ->
 
212
      lexer_error
 
213
  end.
 
214
 
 
215
reason_spec_error({spec_remote_error, Msg}) ->
 
216
  io_lib:format("Remote type solver error: ~s. Make sure the behaviour source is included in the analysis or the plt",[Msg]);
 
217
reason_spec_error(not_a_spec) ->
 
218
  "This is not a spec";
 
219
reason_spec_error({spec_parser_error, Line, Msg}) ->
 
220
  io_lib:format("~s line of the spec: ~s", [ordinal(Line),Msg]);
 
221
reason_spec_error(lexer_error) ->
 
222
  "Lexical error".
 
223
 
 
224
ordinal(1) -> "1st";
 
225
ordinal(2) -> "2nd";
 
226
ordinal(3) -> "3rd";
 
227
ordinal(N) when is_integer(N) -> io_lib:format("~wth",[N]).
 
228
 
 
229
check_callback(Module, Behaviour, Fun, Arity, XRetType, XArgTypes, Plt) ->
 
230
  LookupType = dialyzer_plt:lookup(Plt, {Module, Fun, Arity}),
 
231
  case LookupType of
 
232
    {value, {Type,Args}} ->
 
233
      Warn1 = case unifiable(Type, XRetType) of
 
234
                [] -> [];
 
235
                Offenders ->
 
236
                  [{callback_type_mismatch,
 
237
                   [Behaviour, Fun, Arity, erl_types:t_sup(Offenders)]}]
 
238
              end,
 
239
      ZipArgs = lists:zip3(lists:seq(1, Arity), Args, XArgTypes),
 
240
      Warn2 = [{callback_arg_type_mismatch,
 
241
                [Behaviour, Fun, Arity, N,
 
242
                 erl_types:t_sup(Offenders)]} ||
 
243
                {Offenders, N} <- [check_callback_1(V) || V <- ZipArgs],
 
244
                Offenders =/= []],
 
245
      Warn1 ++ Warn2;
 
246
    _ -> [{callback_missing, [Behaviour, Fun, Arity]}]
 
247
  end.
 
248
 
 
249
check_callback_1({N, T1, T2}) ->
 
250
  {unifiable(T1, T2), N}.
 
251
 
 
252
unifiable(Type1, Type2) ->
 
253
  List1 = erl_types:t_elements(Type1),
 
254
  List2 = erl_types:t_elements(Type2),
 
255
  [T || T <- List1,
 
256
        lists:all(fun(T1) ->
 
257
                      erl_types:t_is_none(erl_types:t_inf(T, T1, opaque))
 
258
                  end, List2)].
 
259
 
 
260
add_tag_file_line(_Module, {Tag, [B|_R]} = Warn, State)
 
261
  when Tag =:= spec_missing;
 
262
       Tag =:= invalid_spec;
 
263
       Tag =:= callback_missing ->
 
264
  {B, Line} = lists:keyfind(B, 1, State#state.behlines),
 
265
  {?WARN_BEHAVIOUR, {State#state.filename, Line}, Warn};
 
266
add_tag_file_line(Module, {_Tag, [_B, Fun, Arity|_R]} = Warn, State) ->
 
267
  {_A, FunCode} =
 
268
    dialyzer_codeserver:lookup_mfa_code({Module, Fun, Arity},
 
269
                                        State#state.codeserver),
 
270
  Anns = cerl:get_ann(FunCode),
 
271
  FileLine = {get_file(Anns), get_line(Anns)},
 
272
  {?WARN_BEHAVIOUR, FileLine, Warn}.
 
273
 
 
274
get_line([Line|_]) when is_integer(Line) -> Line;
 
275
get_line([_|Tail]) -> get_line(Tail);
 
276
get_line([]) -> -1.
 
277
 
 
278
get_file([{file, File}|_]) -> File;
 
279
get_file([_|Tail]) -> get_file(Tail).
 
280
 
 
281
%%-----------------------------------------------------------------------------
 
282
 
 
283
get_behaviours([], _Codeserver, KnownAcc, UnknownAcc) ->
 
284
  {KnownAcc, UnknownAcc};
 
285
get_behaviours([M|Rest], Codeserver, KnownAcc, UnknownAcc) ->
 
286
  Tree = dialyzer_codeserver:lookup_mod_code(M, Codeserver),
 
287
  Attrs = cerl:module_attrs(Tree),
 
288
  {Behaviours, _BehLines} = get_behaviours(Attrs),
 
289
  {Known, Unknown} = call_behaviours(Behaviours),
 
290
  get_behaviours(Rest, Codeserver, Known ++ KnownAcc, Unknown ++ UnknownAcc).
 
291
 
 
292
call_behaviours(Behaviours) ->
 
293
  call_behaviours(Behaviours, [], []).
 
294
call_behaviours([], KnownAcc, UnknownAcc) ->
 
295
  {lists:reverse(KnownAcc), lists:reverse(UnknownAcc)};
 
296
call_behaviours([Behaviour|Rest], KnownAcc, UnknownAcc) ->
 
297
  try
 
298
    Callbacks = Behaviour:behaviour_info(callbacks),
 
299
    Fun = fun({_,_,_}) -> true;
 
300
             (_)       -> false
 
301
          end,
 
302
    case lists:any(Fun, Callbacks) of
 
303
      false -> call_behaviours(Rest, KnownAcc, [Behaviour | UnknownAcc]);
 
304
      true  -> call_behaviours(Rest, [Behaviour | KnownAcc], UnknownAcc)
 
305
    end
 
306
  catch
 
307
    _:_ -> call_behaviours(Rest, KnownAcc, [Behaviour | UnknownAcc])
 
308
  end.
 
309
 
 
310
%------------------------------------------------------------------------------
 
311
 
 
312
get_behaviour_apis([], Acc) ->
 
313
  Acc;
 
314
get_behaviour_apis([Behaviour | Rest], Acc) ->
 
315
  MFAs = [{Behaviour, Fun, Arity} ||
 
316
           {{Fun, Arity}, _} <- behaviour_api_calls(Behaviour)],
 
317
  get_behaviour_apis(Rest, MFAs ++ Acc).
 
318
 
 
319
%------------------------------------------------------------------------------
 
320
 
 
321
nth_or_0(0, _List, Zero) ->
 
322
  Zero;
 
323
nth_or_0(N, List, _Zero) ->
 
324
  lists:nth(N, List).
 
325
 
 
326
%------------------------------------------------------------------------------
 
327
 
 
328
-type behaviour_api_dict()::[{behaviour(), behaviour_api_info()}].
 
329
-type behaviour_api_info()::[{original_fun(), replacement_fun()}].
 
330
-type original_fun()::{atom(), arity()}.
 
331
-type replacement_fun()::{atom(), arity(), arg_list()}.
 
332
-type arg_list()::[byte()].
 
333
 
 
334
-spec behaviour_api_calls(behaviour()) -> behaviour_api_info().
 
335
 
 
336
behaviour_api_calls(gen_server) ->
 
337
  [{{start_link, 3}, {init, 1, [2]}},
 
338
   {{start_link, 4}, {init, 1, [3]}},
 
339
   {{start, 3}, {init, 1, [2]}},
 
340
   {{start, 4}, {init, 1, [3]}},
 
341
   {{call, 2}, {handle_call, 3, [2, 0, 0]}},
 
342
   {{call, 3}, {handle_call, 3, [2, 0, 0]}},
 
343
   {{multi_call, 2}, {handle_call, 3, [2, 0, 0]}},
 
344
   {{multi_call, 3}, {handle_call, 3, [3, 0, 0]}},
 
345
   {{multi_call, 4}, {handle_call, 3, [3, 0, 0]}},
 
346
   {{cast, 2}, {handle_cast, 2, [2, 0]}},
 
347
   {{abcast, 2}, {handle_cast, 2, [2, 0]}},
 
348
   {{abcast, 3}, {handle_cast, 2, [3, 0]}}];
 
349
behaviour_api_calls(_Other) ->
 
350
  [].