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

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-05-07 15:07:37 UTC
  • mfrom: (1.2.1 upstream) (5.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20090507150737-i4yb5elwinm7r0hc
Tags: 1:13.b-dfsg1-1
* Removed another bunch of non-free RFCs from original tarball
  (closes: #527053).
* Fixed build-dependencies list by adding missing comma. This requires
  libsctp-dev again. Also, added libsctp1 dependency to erlang-base and
  erlang-base-hipe packages because the shared library is loaded via
  dlopen now and cannot be added using dh_slibdeps (closes: #526682).
* Weakened dependency of erlang-webtool on erlang-observer to recommends
  to avoid circular dependencies (closes: #526627).
* Added solaris-i386 to HiPE enabled architectures.
* Made script sources in /usr/lib/erlang/erts-*/bin directory executable,
  which is more convenient if a user wants to create a target Erlang system.
* Shortened extended description line for erlang-dev package to make it
  fit 80x25 terminals.

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, 2007 Tobias Lindahl and Kostis Sagonas
15
 
%% 
16
 
%% $Id$
 
18
%% %CopyrightEnd%
17
19
%%
18
20
 
19
21
%%%----------------------------------------------------------------------
32
34
 
33
35
%%-----------------------------------------------------------------------
34
36
 
35
 
-spec build(dial_options()) -> #options{} | {'error',string()}.
 
37
-spec build(dial_options()) -> #options{} | {'error', string()}.
36
38
 
37
39
build(Opts) ->
38
40
  DefaultWarns = [?WARN_RETURN_NO_RETURN,
40
42
                  ?WARN_NON_PROPER_LIST,
41
43
                  ?WARN_FUN_APP,
42
44
                  ?WARN_MATCHING,
 
45
                  ?WARN_OPAQUE,
43
46
                  ?WARN_CALLGRAPH,
44
47
                  ?WARN_FAILING_CALL,
 
48
                  ?WARN_BIN_CONSTRUCTION,
45
49
                  ?WARN_CALLGRAPH,
46
50
                  ?WARN_CONTRACT_TYPES,
47
51
                  ?WARN_CONTRACT_SYNTAX],
48
52
  DefaultWarns1 = ordsets:from_list(DefaultWarns),
49
53
  InitPlt = dialyzer_plt:get_default_plt(),
50
54
  DefaultOpts = #options{},
51
 
  DefaultOpts1 = DefaultOpts#options{legal_warnings=DefaultWarns1,
52
 
                                      init_plt=InitPlt},
 
55
  DefaultOpts1 = DefaultOpts#options{legal_warnings = DefaultWarns1,
 
56
                                      init_plt = InitPlt},
53
57
  try 
54
58
    NewOpts = build_options(Opts, DefaultOpts1),
55
59
    postprocess_opts(NewOpts)
61
65
  Opts1 = check_output_plt(Opts),
62
66
  adapt_get_warnings(Opts1).
63
67
 
64
 
check_output_plt(Opts = #options{analysis_type=Mode}) ->
 
68
check_output_plt(Opts = #options{analysis_type = Mode, from = From,
 
69
                                 output_plt = OutPLT}) ->
65
70
  case is_plt_mode(Mode) of
66
71
    true ->
67
 
      case Opts#options.from =:= byte_code of
 
72
      case From =:= byte_code of
68
73
        true -> Opts;
69
 
        false -> 
 
74
        false ->
70
75
          Msg = "Byte code compiled with debug_info is needed to build the PLT",
71
76
          throw({dialyzer_error, Msg})
72
77
      end;
73
78
    false ->
74
 
      case Opts#options.output_plt =:= none of
 
79
      case OutPLT =:= none of
75
80
        true -> Opts;
76
 
        false -> 
77
 
          Msg = io_lib:format("Output plt cannot be specified "
 
81
        false ->
 
82
          Msg = io_lib:format("Output PLT cannot be specified "
78
83
                              "in analysis mode ~w", [Mode]),
79
84
          throw({dialyzer_error, lists:flatten(Msg)})
80
85
      end
81
86
  end.
82
87
 
83
 
adapt_get_warnings(Opts = #options{analysis_type=Mode}) ->
 
88
adapt_get_warnings(Opts = #options{analysis_type = Mode,
 
89
                                   get_warnings = Warns}) ->
84
90
  %% Warnings are off by default in plt mode, and on by default in
85
91
  %% success typings mode. User defined warning mode overrides the
86
92
  %% default.
87
93
  case is_plt_mode(Mode) of
88
94
    true ->
89
 
      case Opts#options.get_warnings =:= maybe of
90
 
        true -> Opts#options{get_warnings=false};
 
95
      case Warns =:= maybe of
 
96
        true -> Opts#options{get_warnings = false};
91
97
        false -> Opts
92
98
      end;
93
99
    false ->
94
 
      case Opts#options.get_warnings =:= maybe of
95
 
        true -> Opts#options{get_warnings=true};
 
100
      case Warns =:= maybe of
 
101
        true -> Opts#options{get_warnings = true};
96
102
        false -> Opts
97
103
      end
98
104
  end.
99
105
 
100
 
-spec bad_option(string(), _) -> no_return().
 
106
-spec bad_option(string(), term()) -> no_return().
101
107
 
102
108
bad_option(String, Term) ->
103
 
  Msg = io_lib:format("~s: ~P\n", [String,Term,25]),
 
109
  Msg = io_lib:format("~s: ~P", [String, Term, 25]),
104
110
  throw({dialyzer_options_error, lists:flatten(Msg)}).
105
111
 
106
 
 
107
112
build_options([{OptName, undefined}|Rest], Options) when is_atom(OptName) ->
108
113
  build_options(Rest, Options);
109
 
build_options([Term = {OptionName, Value}|Rest], Options) ->
 
114
build_options([{OptionName, Value} = Term|Rest], Options) ->
110
115
  case OptionName of
111
116
    files ->
112
117
      assert_filenames(Term, Value),
113
 
      build_options(Rest, Options#options{files=Value});
 
118
      build_options(Rest, Options#options{files = Value});
114
119
    files_rec ->
115
120
      assert_filenames(Term, Value),
116
 
      build_options(Rest, Options#options{files_rec=Value});
 
121
      build_options(Rest, Options#options{files_rec = Value});
117
122
    analysis_type ->
118
123
      NewOptions =
119
124
        case Value of
120
 
          succ_typings -> Options#options{analysis_type=Value};
121
 
          plt_add      -> Options#options{analysis_type=Value};
122
 
          plt_build    -> Options#options{analysis_type=Value};
123
 
          plt_check    -> Options#options{analysis_type=Value};
124
 
          plt_remove   -> Options#options{analysis_type=Value};
 
125
          succ_typings -> Options#options{analysis_type = Value};
 
126
          plt_add      -> Options#options{analysis_type = Value};
 
127
          plt_build    -> Options#options{analysis_type = Value};
 
128
          plt_check    -> Options#options{analysis_type = Value};
 
129
          plt_remove   -> Options#options{analysis_type = Value};
125
130
          dataflow  -> bad_option("Analysis type is no longer supported", Term);
126
131
          old_style -> bad_option("Analysis type is no longer supported", Term);
127
132
          Other     -> bad_option("Unknown analysis type", Other)
129
134
      assert_plt_op(Options, NewOptions),
130
135
      build_options(Rest, NewOptions);
131
136
    check_plt when is_boolean(Value) ->
132
 
      build_options(Rest, Options#options{check_plt=Value});
 
137
      build_options(Rest, Options#options{check_plt = Value});
133
138
    defines ->
134
139
      assert_defines(Term, Value),
135
140
      OldVal = Options#options.defines,
136
141
      NewVal = ordsets:union(ordsets:from_list(Value), OldVal),
137
 
      build_options(Rest, Options#options{defines=NewVal});
 
142
      build_options(Rest, Options#options{defines = NewVal});
138
143
    from when Value =:= byte_code; Value =:= src_code ->
139
 
      build_options(Rest, Options#options{from=Value});
 
144
      build_options(Rest, Options#options{from = Value});
140
145
    get_warnings ->
141
 
      build_options(Rest, Options#options{get_warnings=Value});
 
146
      build_options(Rest, Options#options{get_warnings = Value});
142
147
    init_plt ->
143
148
      assert_filenames([Term], [Value]),
144
 
      build_options(Rest, Options#options{init_plt=Value});
 
149
      build_options(Rest, Options#options{init_plt = Value});
145
150
    include_dirs ->
146
151
      assert_filenames(Term, Value),
147
152
      OldVal = Options#options.include_dirs,
148
153
      NewVal = ordsets:union(ordsets:from_list(Value), OldVal),
149
 
      build_options(Rest, Options#options{include_dirs=NewVal});
 
154
      build_options(Rest, Options#options{include_dirs = NewVal});
150
155
    use_spec ->
151
 
      build_options(Rest, Options#options{use_contracts=Value});
 
156
      build_options(Rest, Options#options{use_contracts = Value});
152
157
    old_style ->
153
158
      bad_option("Analysis type is no longer supported", old_style);
154
159
    output_file ->
155
 
      assert_filenames([Term], [Value]),
156
 
      build_options(Rest, Options#options{output_file=Value});
 
160
      assert_filename(Value),
 
161
      build_options(Rest, Options#options{output_file = Value});
157
162
    output_format ->
158
163
      assert_output_format(Value),
159
 
      build_options(Rest, Options#options{output_format=Value});
 
164
      build_options(Rest, Options#options{output_format = Value});
160
165
    output_plt ->
161
 
      assert_filenames([Term], [Value]),
162
 
      build_options(Rest, Options#options{output_plt=Value});
 
166
      assert_filename(Value),
 
167
      build_options(Rest, Options#options{output_plt = Value});
163
168
    report_mode ->
164
 
      build_options(Rest, Options#options{report_mode=Value});
 
169
      build_options(Rest, Options#options{report_mode = Value});
165
170
    erlang_mode ->
166
 
      build_options(Rest, Options#options{erlang_mode=true});
 
171
      build_options(Rest, Options#options{erlang_mode = true});
167
172
    warnings ->
168
173
      NewWarnings = build_warnings(Value, Options#options.legal_warnings),
169
 
      build_options(Rest, Options#options{legal_warnings=NewWarnings});
 
174
      build_options(Rest, Options#options{legal_warnings = NewWarnings});
 
175
    callgraph_file ->
 
176
      assert_filename(Value),
 
177
      build_options(Rest, Options#options{callgraph_file = Value});
170
178
    _ ->
171
179
      bad_option("Unknown dialyzer command line option", Term)
172
180
  end;
174
182
  Options.
175
183
 
176
184
assert_filenames(Term, [FileName|Left]) when length(FileName) >= 0 ->
 
185
  case filelib:is_file(FileName) orelse filelib:is_dir(FileName) of
 
186
    true -> ok;
 
187
    false -> bad_option("No such file or directory", FileName)
 
188
  end,
177
189
  assert_filenames(Term, Left);
178
190
assert_filenames(_Term, []) ->
179
191
  ok;
180
192
assert_filenames(Term, [_|_]) ->
181
193
  bad_option("Malformed or non-existing filename", Term).
182
194
 
183
 
assert_defines(Term, [{Macro, _Value}|Left]) when is_atom(Macro) ->
184
 
  assert_defines(Term, Left);
 
195
assert_filename(FileName) when length(FileName) >= 0 ->
 
196
  ok;
 
197
assert_filename(FileName) ->
 
198
  bad_option("Malformed or non-existing filename", FileName).
 
199
 
 
200
assert_defines(Term, [{Macro, _Value}|Defs]) when is_atom(Macro) ->
 
201
  assert_defines(Term, Defs);
185
202
assert_defines(_Term, []) ->
186
203
  ok;
187
204
assert_defines(Term, [_|_]) ->
194
211
assert_output_format(Term) ->
195
212
  bad_option("Illegal value for output_format", Term).
196
213
 
197
 
assert_plt_op(#options{analysis_type=OldVal}, 
198
 
              #options{analysis_type=NewVal}) ->
 
214
assert_plt_op(#options{analysis_type = OldVal}, 
 
215
              #options{analysis_type = NewVal}) ->
199
216
  case is_plt_mode(OldVal) andalso is_plt_mode(NewVal) of
200
217
    true -> bad_option("Options cannot be combined", [OldVal, NewVal]);
201
218
    false -> ok
207
224
is_plt_mode(plt_check)    -> true;
208
225
is_plt_mode(succ_typings) -> false.
209
226
 
210
 
%%-spec build_warnings([atom()], ordset(warning())) -> ordset(warning()).
 
227
-spec build_warnings([atom()], [dial_warning()]) -> [dial_warning()].
 
228
 
211
229
build_warnings([Opt|Left], Warnings) ->
212
230
  NewWarnings =
213
231
    case Opt of
221
239
        ordsets:del_element(?WARN_FUN_APP, Warnings);
222
240
      no_match ->
223
241
        ordsets:del_element(?WARN_MATCHING, Warnings);
 
242
      no_opaque ->
 
243
        ordsets:del_element(?WARN_OPAQUE, Warnings);
224
244
      no_fail_call ->
225
245
        ordsets:del_element(?WARN_FAILING_CALL, Warnings);
226
246
      no_contracts ->
230
250
        ordsets:add_element(?WARN_UNMATCHED_RETURN, Warnings);
231
251
      error_handling ->
232
252
        ordsets:add_element(?WARN_RETURN_ONLY_EXIT, Warnings);
233
 
      kostis ->
234
 
        ordsets:add_element(?WARN_TERM_COMP, Warnings);
 
253
      possible_races ->
 
254
        ordsets:add_element(?WARN_POSSIBLE_RACE, Warnings);
235
255
      specdiffs ->
236
256
        S = ordsets:from_list([?WARN_CONTRACT_SUBTYPE, 
237
257
                               ?WARN_CONTRACT_SUPERTYPE,