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

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-02-15 16:42:52 UTC
  • mfrom: (1.1.13 upstream)
  • Revision ID: james.westby@ubuntu.com-20090215164252-dxpjjuq108nz4noa
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:
48
48
%%
49
49
%% ============================================================================
50
50
 
51
 
-type(abstract_code() :: [_]).
 
51
-type abstract_code() :: [_].
52
52
 
53
 
-spec(get_abstract_code_from_src/1 :: 
54
 
      (atom() | string()) -> {'ok', abstract_code()} | {'error', [string()]}).
 
53
-spec get_abstract_code_from_src(atom() | string()) ->
 
54
                {'ok', abstract_code()} | {'error', [string()]}.
55
55
 
56
56
get_abstract_code_from_src(File) ->
57
57
  get_abstract_code_from_src(File, ?SRC_COMPILE_OPTS).
58
58
 
59
 
-spec(get_abstract_code_from_src/2 ::
60
 
      (atom() | string(), [_]) ->
61
 
         {'ok', abstract_code()} | {'error', [string()]}).
 
59
-spec get_abstract_code_from_src(atom() | string(), [_]) ->
 
60
                {'ok', abstract_code()} | {'error', [string()]}.
62
61
 
63
62
get_abstract_code_from_src(File, Opts) ->
64
63
  case compile:file(File, [to_pp, binary|Opts]) of
67
66
    {ok, _, AbstrCode} -> {ok, AbstrCode}
68
67
  end.
69
68
 
70
 
-spec(get_core_from_src/1 ::
71
 
      (string()) -> {'ok', core_records()} | {'error', string()}).
 
69
-spec get_core_from_src(string()) -> {'ok', core_records()} | {'error', string()}.
72
70
 
73
71
get_core_from_src(File) ->
74
72
  get_core_from_src(File, []).
75
73
 
76
 
-spec(get_core_from_src/2 ::
77
 
      (string(), [_]) -> {'ok', core_records()} | {'error', string()}).
 
74
-spec get_core_from_src(string(), [_]) -> {'ok', core_records()} | {'error', string()}.
78
75
 
79
76
get_core_from_src(File, Opts) ->
80
77
  case get_abstract_code_from_src(File, Opts) of
86
83
      end
87
84
  end.
88
85
 
89
 
-spec(get_abstract_code_from_beam/1 :: 
90
 
      (string()) -> 'error' | {'ok', abstract_code()}).
 
86
-spec get_abstract_code_from_beam(string()) -> 'error' | {'ok', abstract_code()}.
91
87
 
92
88
get_abstract_code_from_beam(File) ->
93
89
  case beam_lib:chunks(File, [abstract_code]) of
101
97
      error
102
98
  end.
103
99
 
104
 
-spec(get_core_from_abstract_code/1 ::
105
 
      (abstract_code()) -> 'error' | {ok, core_records()}).
 
100
-spec get_core_from_abstract_code(abstract_code()) -> 'error' | {ok, core_records()}.
106
101
 
107
102
get_core_from_abstract_code(AbstrCode) ->
108
103
  get_core_from_abstract_code(AbstrCode, []).
109
104
 
110
 
-spec(get_core_from_abstract_code/2 ::
111
 
      (abstract_code(), [_]) -> 'error' | {ok, core_records()}).
 
105
-spec get_core_from_abstract_code(abstract_code(), [_]) -> 'error' | {ok, core_records()}.
112
106
 
113
107
get_core_from_abstract_code(AbstrCode, Opts) ->
114
108
  %% We do not want the parse_transorms left since we have already
128
122
%%
129
123
%% ============================================================================
130
124
 
 
125
-spec get_record_and_type_info(abstract_code()) ->
 
126
                {'ok', dict()} | {'error', string()}.
131
127
 
132
 
-spec(get_record_and_type_info/1 :: 
133
 
      (abstract_code()) -> {'ok', dict()} | {'error', string()}).
134
 
         
135
128
get_record_and_type_info(AbstractCode) ->
136
129
  get_record_and_type_info(AbstractCode, dict:new()).
137
130
 
138
 
-spec(get_record_and_type_info/2 :: 
139
 
      (abstract_code(), dict()) -> {'ok', dict()} | {'error', string()}).
 
131
-spec get_record_and_type_info(abstract_code(), dict()) ->
 
132
                {'ok', dict()} | {'error', string()}.
140
133
 
141
134
get_record_and_type_info([{attribute, _, record, {Name, Fields0}}|Left], 
142
135
                         RecDict) ->
232
225
%%
233
226
%% ============================================================================
234
227
 
235
 
-spec(get_spec_info/2 :: 
236
 
      (abstract_code(), dict()) -> {'ok', dict()} | {'error', string()}).
 
228
-spec get_spec_info(abstract_code(), dict()) -> {'ok', dict()} | {'error', string()}.
237
229
 
238
230
get_spec_info(AbstractCode, RecordsDict) ->
239
231
  {value, {attribute, _, module, ModName}} =
293
285
cleanup_parse_transforms([]) ->
294
286
  [].
295
287
 
296
 
-spec(format_errors/1 :: ([{atom(), string()}]) -> [string()]).
 
288
-spec format_errors([{atom(), string()}]) -> [string()].
297
289
 
298
290
format_errors([{Mod, Errors}|Left]) ->
299
291
  FormatedError = 
303
295
format_errors([]) ->
304
296
  [].
305
297
 
306
 
-spec(format_sig/1 :: (erl_type()) -> string()).
 
298
-spec format_sig(erl_type()) -> string().
307
299
 
308
300
format_sig(Type) ->
309
301
  format_sig(Type, dict:new()).
310
302
 
311
 
-spec(format_sig/2 :: (erl_type(), dict()) -> string()).
 
303
-spec format_sig(erl_type(), dict()) -> string().
312
304
 
313
305
format_sig(Type, RecDict) ->
314
306
  "fun(" ++ Sig = lists:flatten(erl_types:t_to_string(Type, RecDict)),
321
313
%% Created     : 5 March 2007
322
314
%%-------------------------------------------------------------------
323
315
 
324
 
-spec(pp_hook/0 :: () -> fun((core_tree(), _, _) -> any())).
 
316
-spec pp_hook() -> fun((core_tree(), _, _) -> any()).
325
317
 
326
318
pp_hook() ->
327
319
  fun pp_hook/3.