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

« back to all changes in this revision

Viewing changes to lib/syntax_tools/src/epp_dodger.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2010-03-09 17:34:57 UTC
  • mfrom: (10.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20100309173457-4yd6hlcb2osfhx31
Tags: 1:13.b.4-dfsg-3
Manpages in section 1 are needed even if only arch-dependent packages are
built. So, re-enabled them.

Show diffs side-by-side

added added

removed removed

Lines of Context:
90
90
%% This is a so-called Erlang I/O ErrorInfo structure; see the {@link
91
91
%% //stdlib/io} module for details.
92
92
 
 
93
-type errorinfo() :: term(). % {integer(), atom(), term()}.
 
94
 
 
95
-type option() :: atom() | {atom(), term()}.
93
96
 
94
97
%% =====================================================================
95
98
%% @spec parse_file(File) -> {ok, Forms} | {error, errorinfo()}
98
101
%% 
99
102
%% @equiv parse_file(File, [])
100
103
 
 
104
-spec parse_file(file:filename()) ->
 
105
        {'ok', erl_syntax:forms()} | {'error', errorinfo()}.
 
106
 
101
107
parse_file(File) ->
102
108
    parse_file(File, []).
103
109
 
109
115
%% @doc Reads and parses a file. If successful, `{ok, Forms}'
110
116
%% is returned, where `Forms' is a list of abstract syntax
111
117
%% trees representing the "program forms" of the file (cf.
112
 
%% `erl_syntax:is_form/1'). Otherwise, `{error,
113
 
%% errorinfo()}' is returned, typically if the file could not be
114
 
%% opened. Note that parse errors show up as error markers in the
115
 
%% returned list of forms; they do not cause this function to fail or
116
 
%% return `{error,errorinfo()}'.
 
118
%% `erl_syntax:is_form/1'). Otherwise, `{error, errorinfo()}' is
 
119
%% returned, typically if the file could not be opened. Note that
 
120
%% parse errors show up as error markers in the returned list of
 
121
%% forms; they do not cause this function to fail or return
 
122
%% `{error, errorinfo()}'.
117
123
%%
118
124
%% Options:
119
125
%% <dl>
135
141
%% @see quick_parse_file/1
136
142
%% @see erl_syntax:is_form/1
137
143
 
 
144
-spec parse_file(file:filename(), [option()]) ->
 
145
        {'ok', erl_syntax:forms()} | {'error', errorinfo()}.
 
146
 
138
147
parse_file(File, Options) ->
139
148
    parse_file(File, fun parse/3, Options).
140
149
 
144
153
%%
145
154
%% @equiv quick_parse_file(File, [])
146
155
 
 
156
-spec quick_parse_file(file:filename()) ->
 
157
        {'ok', erl_syntax:forms()} | {'error', errorinfo()}.
 
158
 
147
159
quick_parse_file(File) ->
148
160
    quick_parse_file(File, []).
149
161
 
167
179
%% @see quick_parse/2
168
180
%% @see parse_file/2
169
181
 
 
182
-spec quick_parse_file(file:filename(), [option()]) ->
 
183
        {'ok', erl_syntax:forms()} | {'error', errorinfo()}.
 
184
 
170
185
quick_parse_file(File, Options) ->
171
186
    parse_file(File, fun quick_parse/3, Options ++ [no_fail]).
172
187
 
185
200
%% @spec parse(IODevice) -> {ok, Forms} | {error, errorinfo()}
186
201
%% @equiv parse(IODevice, 1)
187
202
 
 
203
-spec parse(file:io_device()) -> {'ok', erl_syntax:forms()}.
 
204
 
188
205
parse(Dev) ->
189
206
    parse(Dev, 1).
190
207
 
196
213
%% @equiv parse(IODevice, StartLine, [])
197
214
%% @see parse/1
198
215
 
 
216
-spec parse(file:io_device(), integer()) -> {'ok', erl_syntax:forms()}.
 
217
 
199
218
parse(Dev, L) ->
200
219
    parse(Dev, L, []).
201
220
 
216
235
%% @see parse_form/2
217
236
%% @see quick_parse/3
218
237
 
 
238
-spec parse(file:io_device(), integer(), [option()]) ->
 
239
        {'ok', erl_syntax:forms()}.
 
240
 
219
241
parse(Dev, L0, Options) ->
220
242
    parse(Dev, L0, fun parse_form/3, Options).
221
243
 
222
244
%% @spec quick_parse(IODevice) -> {ok, Forms} | {error, errorinfo()}
223
245
%% @equiv quick_parse(IODevice, 1)
224
246
 
 
247
-spec quick_parse(file:io_device()) ->
 
248
        {'ok', erl_syntax:forms()}.
 
249
 
225
250
quick_parse(Dev) ->
226
251
    quick_parse(Dev, 1).
227
252
 
234
259
%% @equiv quick_parse(IODevice, StartLine, [])
235
260
%% @see quick_parse/1
236
261
 
 
262
-spec quick_parse(file:io_device(), integer()) ->
 
263
        {'ok', erl_syntax:forms()}.
 
264
 
237
265
quick_parse(Dev, L) ->
238
266
    quick_parse(Dev, L, []).
239
267
 
252
280
%% @see quick_parse_form/2
253
281
%% @see parse/3
254
282
 
 
283
-spec quick_parse(file:io_device(), integer(), [option()]) ->
 
284
        {'ok', erl_syntax:forms()}.
 
285
 
255
286
quick_parse(Dev, L0, Options) ->
256
287
    parse(Dev, L0, fun quick_parse_form/3, Options).
257
288
 
284
315
%%
285
316
%% @see quick_parse_form/2
286
317
 
 
318
-spec parse_form(file:io_device(), integer()) ->
 
319
        {'ok', erl_syntax:forms(), integer()}
 
320
      | {'eof', integer()} | {'error', errorinfo(), integer()}.
 
321
 
287
322
parse_form(Dev, L0) ->
288
323
    parse_form(Dev, L0, []).
289
324
 
310
345
%% @see parse_form/2
311
346
%% @see quick_parse_form/3
312
347
 
 
348
-spec parse_form(file:io_device(), integer(), [option()]) ->
 
349
        {'ok', erl_syntax:forms(), integer()}
 
350
      | {'eof', integer()} | {'error', errorinfo(), integer()}.
 
351
 
313
352
parse_form(Dev, L0, Options) ->
314
353
    parse_form(Dev, L0, fun normal_parser/2, Options).
315
354
 
326
365
%%
327
366
%% @see parse_form/2
328
367
 
 
368
-spec quick_parse_form(file:io_device(), integer()) ->
 
369
        {'ok', erl_syntax:forms(), integer()}
 
370
      | {'eof', integer()} | {'error', errorinfo(), integer()}.
 
371
 
329
372
quick_parse_form(Dev, L0) ->
330
373
    quick_parse_form(Dev, L0, []).
331
374
 
347
390
%% @see quick_parse_form/2
348
391
%% @see parse_form/3
349
392
 
 
393
-spec quick_parse_form(file:io_device(), integer(), [option()]) ->
 
394
        {'ok', erl_syntax:forms(), integer()}
 
395
      | {'eof', integer()} | {'error', errorinfo(), integer()}.
 
396
 
350
397
quick_parse_form(Dev, L0, Options) ->
351
398
    parse_form(Dev, L0, fun quick_parser/2, Options).
352
399
 
751
798
fix_define(_Ts) ->
752
799
    error.
753
800
 
754
 
%% @spec (Tokens::[term()]) -> string()
 
801
%% @spec tokens_to_string(Tokens::[term()]) -> string()
755
802
%% 
756
803
%% @doc Generates a string corresponding to the given token sequence.
757
804
%% The string can be re-tokenized to yield the same token list again.
758
805
 
 
806
-spec tokens_to_string([term()]) -> string().
 
807
 
759
808
tokens_to_string([{atom,_,A} | Ts]) ->
760
809
    io_lib:write_atom(A) ++ " " ++ tokens_to_string(Ts);
761
810
tokens_to_string([{string, _, S} | Ts]) ->
764
813
    float_to_list(F) ++ " " ++ tokens_to_string(Ts);
765
814
tokens_to_string([{integer, _, N} | Ts]) ->
766
815
    integer_to_list(N) ++ " " ++ tokens_to_string(Ts);
767
 
tokens_to_string([{var,_,A} | Ts]) ->
 
816
tokens_to_string([{var, _, A} | Ts]) ->
768
817
    atom_to_list(A) ++ " " ++ tokens_to_string(Ts);
769
 
tokens_to_string([{dot,_} | Ts]) ->
 
818
tokens_to_string([{dot, _} | Ts]) ->
770
819
    ".\n" ++ tokens_to_string(Ts);
771
 
tokens_to_string([{A,_} | Ts]) ->
 
820
tokens_to_string([{A, _} | Ts]) ->
772
821
    atom_to_list(A) ++ " " ++ tokens_to_string(Ts);
773
822
tokens_to_string([]) ->
774
823
    "".
775
824
 
776
825
 
777
 
%% @spec (Descriptor::term()) -> string()
 
826
%% @spec format_error(Descriptor::term()) -> string()
778
827
%% @hidden
779
828
%% @doc Callback function for formatting error descriptors. Not for
780
829
%% normal use.
781
830
 
 
831
-spec format_error(term()) -> string().
 
832
 
782
833
format_error(macro_args) ->
783
834
    errormsg("macro call missing end parenthesis");
784
835
format_error({unknown, Reason}) ->