~rdoering/ubuntu/karmic/erlang/fix-535090

« back to all changes in this revision

Viewing changes to lib/typer/src/typer_options.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-02-15 16:42:52 UTC
  • mfrom: (3.1.2 squeeze)
  • Revision ID: james.westby@ubuntu.com-20090215164252-q5x4rcf8a5pbesb1
Tags: 1:12.b.5-dfsg-2
Upload to unstable after lenny is released.

Show diffs side-by-side

added added

removed removed

Lines of Context:
7
7
 
8
8
-module(typer_options).
9
9
 
10
 
-export([process/0, option_type/1]).
 
10
-export([process/0]).
11
11
 
12
12
%%---------------------------------------------------------------------------
13
13
 
14
14
-include("typer.hrl").
15
 
-include("typer_options.hrl").
16
15
 
17
16
%%---------------------------------------------------------------------------
18
17
%% Exported functions
19
18
%%---------------------------------------------------------------------------
20
19
 
21
 
-spec(process/0 :: () -> {#args{}, #typer_analysis{}}).
 
20
-spec process() -> {#args{}, #typer_analysis{}}.
22
21
 
23
22
process() ->
24
23
  ArgList = init:get_plain_arguments(),
30
29
           Mode when is_atom(Mode) -> Analysis
31
30
         end}.
32
31
 
33
 
-spec(option_type/1 :: (typer_option()) -> 'for_annotation' | 'for_show').
34
 
 
35
 
option_type(?SHOW) -> for_show;
36
 
option_type(?SHOW_EXPORTED) -> for_show;
37
 
option_type(?ANNOTATE) -> for_annotation;
38
 
option_type(?ANNOTATE_INC_FILES) -> for_annotation.
39
 
 
40
32
%%---------------------------------------------------------------------------
41
33
%% Internal functions
42
34
%%---------------------------------------------------------------------------
53
45
cl(["-v"|_])        -> version_message();
54
46
cl(["--version"|_]) -> version_message();
55
47
cl(["--comments"|Opts]) -> {comments, Opts};
56
 
cl(["--show"|Opts]) -> {{mode,?SHOW}, Opts};
57
 
cl(["--show-exported"|Opts]) -> {{mode,?SHOW_EXPORTED}, Opts};
58
 
cl(["--annotate"|Opts]) -> {{mode,?ANNOTATE}, Opts};
59
 
cl(["--annotate-inc-files"|Opts]) -> {{mode,?ANNOTATE_INC_FILES}, Opts};
 
48
cl(["--show"|Opts]) -> {{mode, ?SHOW}, Opts};
 
49
cl(["--show_exported"|Opts]) -> {{mode, ?SHOW_EXPORTED}, Opts};
 
50
cl(["--show-exported"|Opts]) -> {{mode, ?SHOW_EXPORTED}, Opts};
 
51
cl(["--annotate"|Opts]) -> {{mode, ?ANNOTATE}, Opts};
 
52
cl(["--annotate-inc-files"|Opts]) -> {{mode, ?ANNOTATE_INC_FILES}, Opts};
60
53
cl(["--plt",Plt|Opts]) -> {{plt, Plt}, Opts};
61
54
cl(["-D"++Defines|Opts]) ->
62
55
  case Defines of
63
56
    "" -> typer:error("no defines specified after -D");
64
57
    _ ->
65
 
      {ok,Result} = regexp:split(Defines, "="),
 
58
      {ok, Result} = regexp:split(Defines, "="),
66
59
      Elem = collect_defines(Result),
67
 
      {{macros,Elem}, Opts}
 
60
      {{macros, Elem}, Opts}
68
61
  end;
69
62
cl(["-I",Dir|Opts]) -> {{inc,Dir}, Opts};
70
63
cl(["-I"++Dir|Opts]) ->
71
64
  case Dir of
72
65
    "" -> typer:error("no include directory specified after -I");
73
 
    _ -> {{inc,Dir}, Opts}
 
66
    _ -> {{inc, Dir}, Opts}
74
67
  end;
75
68
cl(["-T"|Opts]) ->
76
69
  {Files, RestOpts} = dialyzer_cl_parse:collect_args(Opts),
77
70
  case Files of
78
71
    [] -> typer:error("no file or directory specified after -T");
79
 
    [_|_] -> {{trust,Files}, RestOpts}
 
72
    [_|_] -> {{trust, Files}, RestOpts}
80
73
  end;
81
74
cl(["-r"|Opts]) ->
82
75
  {Files, RestOpts} = dialyzer_cl_parse:collect_args(Opts),
83
 
  {{a_dir_r,Files}, RestOpts};
 
76
  {{a_dir_r, Files}, RestOpts};
84
77
cl(["-"++H|_]) -> typer:error("unknown option -"++H);
85
78
cl(Opts) -> 
86
79
  {Args, RestOpts} = dialyzer_cl_parse:collect_args(Opts),
87
 
  {{analyze,Args}, RestOpts}.
 
80
  {{analyze, Args}, RestOpts}.
88
81
 
89
82
collect_defines(Result) ->
90
83
  case Result of
91
 
    [Def,Val] ->
92
 
      {ok,Tokens,_} = erl_scan:string(Val++"."),
93
 
      {ok,ErlVal} = erl_parse:parse_term(Tokens),
 
84
    [Def, Val] ->
 
85
      {ok, Tokens, _} = erl_scan:string(Val++"."),
 
86
      {ok, ErlVal} = erl_parse:parse_term(Tokens),
94
87
      {list_to_atom(Def), ErlVal};
95
88
    [Def] ->
96
89
      {list_to_atom(Def), true}
97
90
  end.
98
91
 
99
92
%% Get information about files that the user trusts and wants to analyze
100
 
analyze_result({analyze,Val}, Args, Analysis) -> 
 
93
analyze_result({analyze, Val}, Args, Analysis) -> 
101
94
  NewVal = Args#args.analyze ++ Val,
102
95
  {Args#args{analyze=NewVal}, Analysis};
103
 
analyze_result({a_dir_r,Val}, Args, Analysis) -> 
 
96
analyze_result({a_dir_r, Val}, Args, Analysis) -> 
104
97
  NewVal = Args#args.analyzed_dir_r ++ Val,
105
98
  {Args#args{analyzed_dir_r=NewVal}, Analysis};
106
 
analyze_result({trust,Val}, Args, Analysis) -> 
 
99
analyze_result({trust, Val}, Args, Analysis) -> 
107
100
  NewVal = Args#args.trust ++ Val,
108
101
  {Args#args{trust=NewVal}, Analysis};
109
102
analyze_result(comments, Args, Analysis) ->
114
107
    undefined -> {Args, Analysis#typer_analysis{mode=Val}};
115
108
    _ -> mode_error()
116
109
  end;
117
 
analyze_result({macros,Val}, Args, Analysis) ->
 
110
analyze_result({macros, Val}, Args, Analysis) ->
118
111
  NewVal = Analysis#typer_analysis.macros ++ [Val],
119
112
  {Args, Analysis#typer_analysis{macros=NewVal}};
120
 
analyze_result({inc,Val}, Args, Analysis) -> 
 
113
analyze_result({inc, Val}, Args, Analysis) -> 
121
114
  NewVal = Analysis#typer_analysis.includes ++ [Val],
122
115
  {Args, Analysis#typer_analysis{includes=NewVal}};
123
116
analyze_result({plt, Plt}, Args, Analysis) ->
125
118
 
126
119
%%--------------------------------------------------------------------
127
120
 
128
 
-spec(mode_error/0 :: () -> no_return()).
 
121
-spec mode_error() -> no_return().
129
122
mode_error() ->
130
123
  typer:error("can not do \"show\", \"show-exported\", \"annotate\", and \"annotate-inc-files\" at the same time").
131
124
 
132
 
-spec(version_message/0 :: () -> no_return()).
 
125
-spec version_message() -> no_return().
133
126
version_message() ->
134
127
  io:format("TypEr version "++?VSN++"\n"),
135
128
  erlang:halt(0).
136
129
 
137
 
-spec(help_message/0 :: () -> no_return()).
 
130
-spec help_message() -> no_return().
138
131
help_message() ->
139
 
  S = " Usage: typer [--help] [--version] [--comments] [--plt PltFile]
 
132
  S = " Usage: typer [--help] [--version] [--comments] [--plt PLT]
140
133
              [--show | --show-exported | --annotate | --annotate-inc-files]
141
134
              [-Ddefine]* [-I include_dir]* [-T application]* [-r] file*
142
135
 
144
137
   -r dir*
145
138
       search directories recursively for .erl files below them
146
139
   --show
147
 
       Prints type contracts for all functions on stdout.
 
140
       Prints type specifications for all functions on stdout.
148
141
       (this is the default behaviour; this option is not really needed)
149
 
   --show-exported
150
 
       Same as --show, but prints contracts for exported functions only
 
142
   --show-exported (or --show_exported)
 
143
       Same as --show, but prints specifications for exported functions only
 
144
       Specs are displayed sorted alphabetically on the function's name
151
145
   --annotate
152
 
       Annotates the specified files with type contracts
 
146
       Annotates the specified files with type specifications
153
147
   --annotate-inc-files
154
148
       Same as --annotate but annotates all -include() files as well as
155
 
       all .erl files (use this option with caution)
 
149
       all .erl files (use this option with caution - has not been tested much)
156
150
   --comments
157
 
       Print type information using comments, not type contracts
158
 
   --plt PltFile
159
 
       Use the specified dialyzer plt file rather than the default one
 
151
       Prints type information using Edoc comments, not type specs
 
152
   --plt PLT
 
153
       Use the specified dialyzer PLT file rather than the default one
160
154
   -T file*
161
 
       The file(s) already contain type annotations and these annotations
162
 
       are to be trusted in order to print contracts for the rest of the files
 
155
       The specified file(s) already contain type specifications and these
 
156
       are to be trusted in order to print specs for the rest of the files
163
157
       (Multiple files or dirs, separated by spaces, can be specified.)
164
158
   -Dname (or -Dname=value)
165
159
       pass the defined name(s) to TypEr