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

« back to all changes in this revision

Viewing changes to lib/dialyzer/src/dialyzer.hrl

  • 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
%%% This is an -*- Erlang -*- file.
 
2
%%%
 
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,
 
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
%%%
2
20
%%%-------------------------------------------------------------------
3
21
%%% File    : dialyzer.hrl
4
22
%%% Author  : Tobias Lindahl <tobiasl@it.uu.se>
30
48
-define(WARN_NON_PROPER_LIST, warn_non_proper_list).
31
49
-define(WARN_FUN_APP, warn_fun_app).
32
50
-define(WARN_MATCHING, warn_matching).
 
51
-define(WARN_OPAQUE, warn_opaque).
33
52
-define(WARN_FAILING_CALL, warn_failing_call).
 
53
-define(WARN_BIN_CONSTRUCTION, warn_bin_construction).
34
54
-define(WARN_CONTRACT_TYPES, warn_contract_types).
35
55
-define(WARN_CONTRACT_SYNTAX, warn_contract_syntax).
36
56
-define(WARN_CONTRACT_NOT_EQUAL, warn_contract_not_equal).
38
58
-define(WARN_CONTRACT_SUPERTYPE, warn_contract_supertype).
39
59
-define(WARN_CALLGRAPH, warn_callgraph).
40
60
-define(WARN_UNMATCHED_RETURN, warn_umatched_return).
41
 
%% Mostly for debugging
42
 
-define(WARN_TERM_COMP, warn_term_comp).
 
61
-define(WARN_POSSIBLE_RACE, warn_possible_race).
43
62
 
44
63
%%
45
64
%% The following type has double role:
48
67
%%
49
68
-type dial_warn_tag() :: ?WARN_RETURN_NO_RETURN | ?WARN_RETURN_ONLY_EXIT
50
69
                       | ?WARN_NOT_CALLED | ?WARN_NON_PROPER_LIST
51
 
                       | ?WARN_MATCHING | ?WARN_FUN_APP
52
 
                       | ?WARN_FAILING_CALL | ?WARN_CALLGRAPH
 
70
                       | ?WARN_MATCHING | ?WARN_OPAQUE | ?WARN_FUN_APP
 
71
                       | ?WARN_FAILING_CALL | ?WARN_BIN_CONSTRUCTION
53
72
                       | ?WARN_CONTRACT_TYPES | ?WARN_CONTRACT_SYNTAX
54
73
                       | ?WARN_CONTRACT_NOT_EQUAL | ?WARN_CONTRACT_SUBTYPE
55
 
                       | ?WARN_CONTRACT_SUPERTYPE | ?WARN_TERM_COMP
56
 
                       | ?WARN_UNMATCHED_RETURN.
 
74
                       | ?WARN_CONTRACT_SUPERTYPE | ?WARN_CALLGRAPH
 
75
                       | ?WARN_UNMATCHED_RETURN | ?WARN_POSSIBLE_RACE.
57
76
 
58
77
%%
59
78
%% This is the representation of each warning as they will be returned
60
79
%% to dialyzer's callers
61
80
%%
62
 
-type file_line()    :: {string(), non_neg_integer()}.
63
 
-type dial_warning() :: {dial_warn_tag(), file_line(), {atom(),[_]}}.
 
81
-type filename()     :: string().
 
82
-type file_line()    :: {filename(), non_neg_integer()}.
 
83
-type dial_warning() :: {dial_warn_tag(), file_line(), {atom(), [term()]}}.
64
84
 
65
85
%%
66
86
%% This is the representation of dialyzer's internal errors
71
91
%% THESE TYPES SHOULD ONE DAY DISAPPEAR -- THEY DO NOT BELONG HERE
72
92
%%--------------------------------------------------------------------
73
93
 
74
 
-type dict()         :: tuple() .  %% XXX: temporarily
75
 
-type orddict()      :: [{_, _}] . %% XXX: temporarily
76
 
-type set()          :: tuple() .  %% XXX: temporarily
77
94
-type ordset(T)      :: [T] .      %% XXX: temporarily
78
 
-type core_module()  :: {'module',_,_,_,_,_} . % XXX: belongs in 'cerl*'
79
 
-type core_tree()    :: tuple() .  %% XXX: belongs in 'cerl*'
80
 
-type core_records() :: tuple() .  %% XXX: belongs in 'cerl*'
81
 
-type erl_type()     :: any() .    %% XXX: belongs to 'erl_types'
 
95
-type core_fun()     :: {'c_fun',_,_,_}.        %% XXX: belongs in 'cerl*'
 
96
-type core_module()  :: {'c_module',_,_,_,_,_}. %% XXX: belongs in 'cerl*'
 
97
-type core_tree()    :: tuple().                %% XXX: belongs in 'cerl*'
 
98
-type core_records() :: tuple().                %% XXX: belongs in 'cerl*'
 
99
-type core_var()     :: {'c_var',_,_}.          %% XXX: belongs in 'cerl*'
 
100
-type core_literal() :: {'c_literal',_,_}.      %% XXX: belongs in 'cerl*'
 
101
-type core_cons()    :: {'c_cons',_,_,_}.         %% XXX: belongs in 'cerl*'
 
102
-type core_tuple()   :: {'c_tuple',_,_}.        %% XXX: belongs in 'cerl*'
 
103
-type erl_type()     :: 'any' | 'none' | 'unit' | {'c',atom(),_,_}.    %% XXX: belongs to 'erl_types'
82
104
 
83
105
%%--------------------------------------------------------------------
84
106
%% Basic types used either in the record definitions below or in other
87
109
 
88
110
-type anal_type()    :: 'succ_typings' | 'plt_build'.
89
111
-type anal_type1()   :: anal_type() | 'plt_add' | 'plt_check' | 'plt_remove'.
90
 
-type start_from()   :: 'byte_code' | 'src_code'.
91
 
-type define()       :: {atom(), any()}.
92
 
-type md5()          :: [{string(), binary()}].
93
 
-type rep_mode()     :: 'quiet' | 'normal' | 'verbose'.
 
112
-type contr_constr() :: {'subtype', erl_type(), erl_type()}.
 
113
-type contract()     :: {erl_type(), [contr_constr()]}.
 
114
-type dial_define()  :: {atom(), term()}.
94
115
-type dial_option()  :: {atom(), any()}.
95
116
-type dial_options() :: [dial_option()].
 
117
-type label()        :: non_neg_integer().
 
118
-type md5()          :: [{filename(), binary()}].
 
119
-type rep_mode()     :: 'quiet' | 'normal' | 'verbose'.
 
120
-type start_from()   :: 'byte_code' | 'src_code'.
96
121
 
97
122
%%--------------------------------------------------------------------
98
123
%% Record declarations used by various files
101
126
-record(dialyzer_plt, {info       = dict:new()      :: dict(),
102
127
                       contracts  = dict:new()      :: dict()}).
103
128
 
104
 
-record(dialyzer_codeserver, {table           :: pid(),
105
 
                              exports         :: set(), % set(mfa())
106
 
                              next_core_label :: non_neg_integer(),
107
 
                              records         :: dict(),
108
 
                              contracts       :: dict()}).
 
129
-record(dialyzer_codeserver, {table_pid              :: pid(),
 
130
                              exports   = sets:new() :: set(), % set(mfa())
 
131
                              next_core_label = 0    :: label(),
 
132
                              records   = dict:new() :: dict(),
 
133
                              contracts = dict:new() :: dict()}).
109
134
 
110
135
-record(analysis, {analysis_pid                     :: pid(),
111
136
                   type           = succ_typings    :: anal_type(),
112
 
                   defines        = []              :: [define()],
 
137
                   defines        = []              :: [dial_define()],
113
138
                   doc_plt                          :: #dialyzer_plt{},
114
 
                   files          = []              :: [string()],
115
 
                   include_dirs   = []              :: [string()],
 
139
                   files          = []              :: [filename()],
 
140
                   include_dirs   = []              :: [filename()],
116
141
                   start_from     = byte_code       :: start_from(),
117
142
                   plt                              :: #dialyzer_plt{},
118
 
                   use_contracts  = true            :: bool()}).
 
143
                   use_contracts  = true            :: bool(),
 
144
                   race_detection = false           :: bool(),
 
145
                   callgraph_file = ""              :: filename()}).
119
146
 
120
 
-record(options, {files           = []              :: [string()],
121
 
                  files_rec       = []              :: [string()],
 
147
-record(options, {files           = []              :: [filename()],
 
148
                  files_rec       = []              :: [filename()],
122
149
                  analysis_type   = succ_typings    :: anal_type1(),
123
 
                  defines         = []              :: [define()],
 
150
                  defines         = []              :: [dial_define()],
124
151
                  from            = byte_code       :: start_from(),
125
152
                  get_warnings    = maybe           :: bool() | 'maybe',
126
 
                  init_plt        = none            :: 'none' | string(),
127
 
                  include_dirs    = []              :: [string()],
128
 
                  output_plt      = none            :: 'none' | string(),
 
153
                  init_plt        = none            :: 'none' | filename(),
 
154
                  include_dirs    = []              :: [filename()],
 
155
                  output_plt      = none            :: 'none' | filename(),
129
156
                  legal_warnings  = ordsets:new()   :: ordset(dial_warn_tag()),
130
157
                  report_mode     = normal          :: rep_mode(),
131
158
                  erlang_mode     = false           :: bool(),
132
159
                  use_contracts   = true            :: bool(),
133
 
                  output_file     = none            :: 'none' | string(),
 
160
                  output_file     = none            :: 'none' | filename(),
134
161
                  output_format   = formatted       :: 'raw' | 'formatted',
 
162
                  callgraph_file  = ""              :: filename(),
135
163
                  check_plt       = true            :: bool()
136
164
                 }).
137
165
 
138
 
-record(contract, {contracts      = []              :: [_],        % ???
 
166
-record(contract, {contracts      = []              :: [contract()],
139
167
                   args           = []              :: [erl_type()],
140
168
                   forms          = []              :: [{_, _}]}).
141
169
 
142
170
%%--------------------------------------------------------------------
 
171
 
 
172
-type plt_contracts() :: [{mfa(), #contract{}}]. % actually, an orddict()
 
173
 
 
174
%%--------------------------------------------------------------------