~statik/ubuntu/maverick/erlang/erlang-merge-testing

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-05-01 10:14:38 UTC
  • mfrom: (3.1.4 sid)
  • Revision ID: james.westby@ubuntu.com-20090501101438-6qlr6rsdxgyzrg2z
Tags: 1:13.b-dfsg-2
* Cleaned up patches: removed unneeded patch which helped to support
  different SCTP library versions, made sure that changes for m68k
  architecture applied only when building on this architecture.
* Removed duplicated information from binary packages descriptions.
* Don't require libsctp-dev build-dependency on solaris-i386 architecture
  which allows to build Erlang on Nexenta (thanks to Tim Spriggs for
  the suggestion).

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%% -*- erlang-indent-level: 2 -*-
2
2
%%-----------------------------------------------------------------------
3
 
%% ``The contents of this file are subject to the Erlang Public License,
 
3
%% %CopyrightBegin%
 
4
%% 
 
5
%% Copyright Ericsson AB 2006-2009. All Rights Reserved.
 
6
%% 
 
7
%% The contents of this file are subject to the Erlang Public License,
4
8
%% Version 1.1, (the "License"); you may not use this file except in
5
9
%% compliance with the License. You should have received a copy of the
6
10
%% Erlang Public License along with this software. If not, it can be
7
 
%% retrieved via the world wide web at http://www.erlang.org/.
 
11
%% retrieved online at http://www.erlang.org/.
8
12
%% 
9
13
%% Software distributed under the License is distributed on an "AS IS"
10
14
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
11
15
%% the License for the specific language governing rights and limitations
12
16
%% under the License.
13
17
%% 
14
 
%% Copyright 2006-2008, Tobias Lindahl and Kostis Sagonas
15
 
%% 
16
 
%% $Id$
 
18
%% %CopyrightEnd%
17
19
%%
18
20
 
19
21
%%%-------------------------------------------------------------------
45
47
%%--------------------------------------------------------------------
46
48
 
47
49
-spec new() -> #dialyzer_codeserver{}.
 
50
 
48
51
new() ->
49
 
  Table = table__new(),
50
 
  Exports = sets:new(),
51
 
  #dialyzer_codeserver{table=Table, exports=Exports, next_core_label=0,
52
 
                       records=dict:new(), contracts=dict:new()}.
 
52
  #dialyzer_codeserver{table_pid = table__new()}.
53
53
 
54
54
-spec delete(#dialyzer_codeserver{}) -> 'ok'.
55
 
delete(#dialyzer_codeserver{table=Table}) ->
56
 
  table__delete(Table).
 
55
 
 
56
delete(#dialyzer_codeserver{table_pid = TablePid}) ->
 
57
  table__delete(TablePid).
57
58
 
58
59
-spec insert([_], #dialyzer_codeserver{}) -> #dialyzer_codeserver{}.
 
60
 
59
61
insert(List, CS) ->
60
 
  NewTable = table__insert(CS#dialyzer_codeserver.table, List),
61
 
  CS#dialyzer_codeserver{table=NewTable}.
 
62
  NewTablePid = table__insert(CS#dialyzer_codeserver.table_pid, List),
 
63
  CS#dialyzer_codeserver{table_pid = NewTablePid}.
62
64
 
63
65
-spec insert_exports([mfa()], #dialyzer_codeserver{}) -> #dialyzer_codeserver{}.
64
 
insert_exports(List, CS = #dialyzer_codeserver{exports=Exports}) ->
 
66
 
 
67
insert_exports(List, #dialyzer_codeserver{exports = Exports} = CS) ->
65
68
  Set = sets:from_list(List),
66
69
  NewExports = sets:union(Exports, Set),
67
 
  CS#dialyzer_codeserver{exports=NewExports}.
 
70
  CS#dialyzer_codeserver{exports = NewExports}.
68
71
 
69
72
-spec is_exported(mfa(), #dialyzer_codeserver{}) -> bool().
70
 
is_exported(MFA, #dialyzer_codeserver{exports=Exports}) ->
 
73
 
 
74
is_exported(MFA, #dialyzer_codeserver{exports = Exports}) ->
71
75
  sets:is_element(MFA, Exports).
72
76
 
73
77
-spec all_exports(#dialyzer_codeserver{}) -> set().
74
 
all_exports(#dialyzer_codeserver{exports=Exports}) ->
 
78
 
 
79
all_exports(#dialyzer_codeserver{exports = Exports}) ->
75
80
  Exports.
76
81
 
77
 
-spec lookup(_, #dialyzer_codeserver{}) -> any().
 
82
-spec lookup(_, #dialyzer_codeserver{}) -> {'ok', any()}.
 
83
 
78
84
lookup(Id, CS) ->
79
 
  table__lookup(CS#dialyzer_codeserver.table, Id).
80
 
 
81
 
-spec next_core_label(#dialyzer_codeserver{}) -> non_neg_integer().
82
 
next_core_label(#dialyzer_codeserver{next_core_label=NCL}) ->
 
85
  table__lookup(CS#dialyzer_codeserver.table_pid, Id).
 
86
 
 
87
-spec next_core_label(#dialyzer_codeserver{}) -> label().
 
88
 
 
89
next_core_label(#dialyzer_codeserver{next_core_label = NCL}) ->
83
90
  NCL.
84
91
 
85
 
-spec update_next_core_label(non_neg_integer(), #dialyzer_codeserver{}) -> #dialyzer_codeserver{}.
86
 
update_next_core_label(NCL, CS = #dialyzer_codeserver{}) ->
87
 
  CS#dialyzer_codeserver{next_core_label=NCL}.
88
 
 
89
 
-spec store_records(atom(), dict(), #dialyzer_codeserver{}) -> #dialyzer_codeserver{}.
90
 
store_records(Module, Dict, 
91
 
              CS=#dialyzer_codeserver{records=RecDict}) when is_atom(Module) ->
 
92
-spec update_next_core_label(label(), #dialyzer_codeserver{}) -> #dialyzer_codeserver{}.
 
93
 
 
94
update_next_core_label(NCL, CS) ->
 
95
  CS#dialyzer_codeserver{next_core_label = NCL}.
 
96
 
 
97
-spec store_records(module(), dict(), #dialyzer_codeserver{}) -> #dialyzer_codeserver{}.
 
98
 
 
99
store_records(Mod, Dict, 
 
100
              CS = #dialyzer_codeserver{records = RecDict}) when is_atom(Mod) ->
92
101
  case dict:size(Dict) =:= 0 of
93
102
    true -> CS;
94
 
    false ->
95
 
      CS#dialyzer_codeserver{records=dict:store(Module, Dict, RecDict)}
 
103
    false -> CS#dialyzer_codeserver{records = dict:store(Mod, Dict, RecDict)}
96
104
  end.
97
105
 
98
 
-spec lookup_records(atom(), #dialyzer_codeserver{}) -> dict(). 
99
 
lookup_records(Module, 
100
 
               #dialyzer_codeserver{records=RecDict}) when is_atom(Module) ->
101
 
  case dict:find(Module, RecDict) of
 
106
-spec lookup_records(module(), #dialyzer_codeserver{}) -> dict(). 
 
107
 
 
108
lookup_records(Mod, 
 
109
               #dialyzer_codeserver{records = RecDict}) when is_atom(Mod) ->
 
110
  case dict:find(Mod, RecDict) of
102
111
    error -> dict:new();
103
112
    {ok, Dict} -> Dict
104
113
  end.
105
114
 
106
 
-spec store_contracts(atom(), dict(), #dialyzer_codeserver{}) -> #dialyzer_codeserver{}. 
107
 
store_contracts(Module, Dict, 
108
 
                CS=#dialyzer_codeserver{contracts=C}) when is_atom(Module) ->
 
115
-spec store_contracts(module(), dict(), #dialyzer_codeserver{}) -> #dialyzer_codeserver{}. 
 
116
 
 
117
store_contracts(Mod, Dict, 
 
118
                CS = #dialyzer_codeserver{contracts = C}) when is_atom(Mod) ->
109
119
  case dict:size(Dict) =:= 0 of
110
120
    true -> CS;
111
 
    false -> CS#dialyzer_codeserver{contracts=dict:store(Module, Dict, C)}
 
121
    false -> CS#dialyzer_codeserver{contracts = dict:store(Mod, Dict, C)}
112
122
  end.
113
123
 
114
 
-spec lookup_contracts(atom(), #dialyzer_codeserver{}) -> dict(). 
 
124
-spec lookup_contracts(module(), #dialyzer_codeserver{}) -> dict(). 
 
125
 
115
126
lookup_contracts(Mod, 
116
 
                 #dialyzer_codeserver{contracts=ContDict}) when is_atom(Mod) ->
 
127
                 #dialyzer_codeserver{contracts = ContDict}) when is_atom(Mod) ->
117
128
  case dict:find(Mod, ContDict) of
118
129
    error -> dict:new();
119
130
    {ok, Dict} -> Dict
120
131
  end.
121
132
 
122
 
-spec lookup_contract(mfa(), #dialyzer_codeserver{}) -> 'error' | {'ok',_}.
123
 
lookup_contract(MFA={M,_F,_A}, #dialyzer_codeserver{contracts=ContDict}) ->
 
133
-spec lookup_contract(mfa(), #dialyzer_codeserver{}) -> 'error' | {'ok', _}.
 
134
 
 
135
lookup_contract({M,_F,_A} = MFA, #dialyzer_codeserver{contracts = ContDict}) ->
124
136
  case dict:find(M, ContDict) of
125
137
    error -> error;
126
138
    {ok, Dict} -> dict:find(MFA, Dict)
139
151
    {TablePid, Key, Ans} -> Ans
140
152
  end.
141
153
 
142
 
table__insert(Table, List) ->
 
154
table__insert(TablePid, List) ->
143
155
  List1 = [{Key, term_to_binary(Val, [compressed])} || {Key, Val} <- List],
144
 
  Table ! {insert, List1},
145
 
  Table.
 
156
  TablePid ! {insert, List1},
 
157
  TablePid.
146
158
 
147
159
table__loop(Cached, Map) ->
148
160
  receive
149
161
    stop -> ok;
150
 
    {Pid, lookup, Key = {M, F, A}} ->
 
162
    {Pid, lookup, {M, F, A} = MFA} ->
151
163
      {NewCached, Ans} =
152
164
        case Cached of
153
165
          {M, Tree} ->
154
 
            [Val] = [{Var, Fun} || {Var, Fun} <- cerl:module_defs(Tree),
155
 
                                   cerl:fname_id(Var) =:= F,
156
 
                                   cerl:fname_arity(Var) =:= A],
 
166
            [Val] = [VarFun || {Var, _Fun} = VarFun <- cerl:module_defs(Tree),
 
167
                               cerl:fname_id(Var) =:= F,
 
168
                               cerl:fname_arity(Var) =:= A],
157
169
            {Cached, Val};
158
170
          _ ->
159
171
            Tree = fetch_and_expand(M, Map),
160
 
            [Val] = [{Var, Fun} || {Var, Fun} <- cerl:module_defs(Tree),
161
 
                                   cerl:fname_id(Var) =:= F,
162
 
                                   cerl:fname_arity(Var) =:= A],
 
172
            [Val] = [VarFun || {Var, _Fun} = VarFun <- cerl:module_defs(Tree),
 
173
                               cerl:fname_id(Var) =:= F,
 
174
                               cerl:fname_arity(Var) =:= A],
163
175
            {{M, Tree}, Val}
164
176
        end,
165
 
      Pid ! {self(), Key, {ok, Ans}},
 
177
      Pid ! {self(), MFA, {ok, Ans}},
166
178
      table__loop(NewCached, Map);
167
 
    {Pid, lookup, Key} ->
 
179
    {Pid, lookup, Mod} when is_atom(Mod) ->
168
180
      Ans = case Cached of
169
 
              {Key, Tree} -> Tree;
170
 
              _ -> fetch_and_expand(Key, Map)
 
181
              {Mod, Tree} -> Tree;
 
182
              _ -> fetch_and_expand(Mod, Map)
171
183
            end,
172
 
      Pid ! {self(), Key, {ok, Ans}},
173
 
      table__loop({Key, Ans}, Map);
 
184
      Pid ! {self(), Mod, {ok, Ans}},
 
185
      table__loop({Mod, Ans}, Map);
174
186
    {insert, List} ->
175
187
      NewMap = lists:foldl(fun({Key, Val}, AccMap) -> 
176
188
                               dict:store(Key, Val, AccMap)
178
190
      table__loop(Cached, NewMap)
179
191
  end.
180
192
 
181
 
fetch_and_expand(Key, Map) ->
182
 
  Bin = dict:fetch(Key, Map),
183
 
  binary_to_term(Bin).
 
193
fetch_and_expand(Mod, Map) ->
 
194
  try
 
195
    Bin = dict:fetch(Mod, Map),
 
196
    binary_to_term(Bin)
 
197
  catch
 
198
    _:_ ->
 
199
      S = atom_to_list(Mod),
 
200
      Msg = "found no module named '" ++ S ++ "' in the analyzed files",
 
201
      exit({error, Msg})
 
202
  end.