~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): Erlang Packagers, Sergei Golovan
  • Date: 2006-12-03 17:07:44 UTC
  • mfrom: (2.1.11 feisty)
  • Revision ID: james.westby@ubuntu.com-20061203170744-rghjwupacqlzs6kv
Tags: 1:11.b.2-4
[ Sergei Golovan ]
Fixed erlang-base and erlang-base-hipe prerm scripts.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%% ``The contents of this file are subject to the Erlang Public License,
 
2
%% Version 1.1, (the "License"); you may not use this file except in
 
3
%% compliance with the License. You should have received a copy of the
 
4
%% Erlang Public License along with this software. If not, it can be
 
5
%% retrieved via the world wide web at http://www.erlang.org/.
 
6
%% 
 
7
%% Software distributed under the License is distributed on an "AS IS"
 
8
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
9
%% the License for the specific language governing rights and limitations
 
10
%% under the License.
 
11
%% 
 
12
%% Copyright 2006, Tobias Lindahl and Kostis Sagonas
 
13
%% 
 
14
%%     $Id$
 
15
%%
 
16
 
 
17
%%% -*- erlang-indent-level: 2 -*-
 
18
%%%-------------------------------------------------------------------
 
19
%%% File    : dialyzer_options.erl
 
20
%%% Authors : Richard Carlsson <richardc@csd.uu.se>
 
21
%%% Description : Provides a better way to start Dialyzer from a script.
 
22
%%%
 
23
%%% Created : 17 Oct 2004 by Richard Carlsson <richardc@csd.uu.se>
 
24
%%%-------------------------------------------------------------------
 
25
-module(dialyzer_options).
 
26
 
 
27
-export([build/1]).
 
28
 
 
29
-include("dialyzer.hrl").
 
30
-include("hipe_icode_type.hrl").
 
31
 
 
32
build(Opts) ->
 
33
  DefaultWarns = [?WARN_RETURN_NO_RETURN,
 
34
                  ?WARN_NOT_CALLED,
 
35
                  ?WARN_NON_PROPER_LIST,
 
36
                  ?WARN_TUPLE_AS_FUN,
 
37
                  ?WARN_FUN_APP,
 
38
                  ?WARN_MATCHING,
 
39
                  ?WARN_COMP,
 
40
                  ?WARN_GUARDS,
 
41
                  ?WARN_OLD_BEAM,
 
42
                  ?WARN_FAILING_CALL,
 
43
                  ?WARN_CALLGRAPH],
 
44
  build_options(Opts, #options{legal_warnings=ordsets:from_list(DefaultWarns)}).
 
45
 
 
46
build_options([Term={OptionName,Value}|Rest], Options) ->
 
47
  case OptionName of
 
48
    files ->
 
49
      build_options(Rest, Options#options{files=Value});
 
50
    files_rec ->
 
51
      build_options(Rest, Options#options{files_rec=Value});
 
52
    core_transform ->
 
53
      build_options(Rest, Options#options{core_transform=Value});
 
54
    defines ->
 
55
      build_options(Rest, Options#options{defines=ordsets:from_list(Value)});
 
56
    from ->
 
57
      build_options(Rest, Options#options{from=Value});
 
58
    init_plt ->
 
59
      build_options(Rest, Options#options{init_plt=Value});
 
60
    include_dirs ->
 
61
      build_options(Rest, Options#options{include_dirs=Value});
 
62
    output_file ->
 
63
      build_options(Rest, Options#options{output_file=Value});
 
64
    output_plt ->
 
65
      build_options(Rest, Options#options{output_plt=Value});
 
66
    plt_libs ->
 
67
      case Value of
 
68
        [] -> build_options(Rest, Options);
 
69
        _  -> build_options(Rest, Options#options{plt_libs=Value})
 
70
      end;
 
71
    supress_inline ->
 
72
      build_options(Rest, Options#options{supress_inline=Value});
 
73
    warnings ->
 
74
      NewWarnings = build_warnings(Value, Options#options.legal_warnings),
 
75
      build_options(Rest, Options#options{legal_warnings=NewWarnings});
 
76
    _ ->
 
77
      bad_option(Term)
 
78
  end;
 
79
build_options([Term|_Rest], _Options) ->
 
80
  bad_option(Term);
 
81
build_options([], Options) ->
 
82
  Options.
 
83
 
 
84
bad_option(Term) ->
 
85
  report("error building dialyzer options: ~P.\n",[Term,15]),
 
86
  exit(error).
 
87
 
 
88
 
 
89
build_warnings([Opt|Left], Warnings) ->
 
90
  NewWarnings =
 
91
    case Opt of
 
92
      no_return ->
 
93
        ordsets:del_element(?WARN_RETURN_NO_RETURN, Warnings);
 
94
      no_unused ->
 
95
        ordsets:del_element(?WARN_NOT_CALLED, Warnings);
 
96
      no_improper_lists ->
 
97
        ordsets:del_element(?WARN_NON_PROPER_LIST, Warnings);
 
98
      no_tuple_as_fun ->
 
99
        ordsets:del_element(?WARN_TUPLE_AS_FUN, Warnings);
 
100
      no_fun_app ->
 
101
        ordsets:del_element(?WARN_FUN_APP, Warnings);
 
102
      no_match ->
 
103
        ordsets:del_element(?WARN_MATCHING, Warnings);
 
104
      no_comp ->
 
105
        ordsets:del_element(?WARN_COMP, Warnings);
 
106
      no_guards ->
 
107
        ordsets:del_element(?WARN_GUARDS, Warnings);
 
108
      no_unsafe_beam ->
 
109
        ordsets:del_element(?WARN_OLD_BEAM, Warnings);
 
110
      no_fail_call ->
 
111
        ordsets:del_element(?WARN_FAILING_CALL, Warnings);
 
112
      error_handling ->
 
113
        ordsets:add_element(?WARN_RETURN_ONLY_EXIT, Warnings);
 
114
      Other ->
 
115
        bad_option(Other)
 
116
    end,
 
117
  build_warnings(Left, NewWarnings);
 
118
build_warnings([], Warnings) ->
 
119
  Warnings.
 
120
 
 
121
report(S, As) ->
 
122
  io:nl(),
 
123
  io:fwrite(S, As),
 
124
  io:nl().