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

« back to all changes in this revision

Viewing changes to lib/syntax_tools/src/erl_tidy.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
%% =====================================================================
 
2
%% Tidies Erlang source code, removing unused functions, updating
 
3
%% obsolete constructs and function calls, etc.
 
4
%%
 
5
%% Copyright (C) 1999-2002 Richard Carlsson
 
6
%%
 
7
%% This library is free software; you can redistribute it and/or
 
8
%% modify it under the terms of the GNU Lesser General Public License
 
9
%% as published by the Free Software Foundation; either version 2 of
 
10
%% the License, or (at your option) any later version.
 
11
%%
 
12
%% This library is distributed in the hope that it will be useful, but
 
13
%% WITHOUT ANY WARRANTY; without even the implied warranty of
 
14
%% MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
 
15
%% Lesser General Public License for more details.
 
16
%%
 
17
%% You should have received a copy of the GNU Lesser General Public
 
18
%% License along with this library; if not, write to the Free Software
 
19
%% Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307
 
20
%% USA
 
21
%%
 
22
%% Author contact: richardc@csd.uu.se
 
23
%%
 
24
%% $Id: erl_tidy.erl,v 1.39 2004/11/22 07:24:12 richardc Exp $
 
25
%%
 
26
%% =====================================================================
 
27
%%
 
28
%% @doc Tidies and pretty-prints Erlang source code, removing unused
 
29
%% functions, updating obsolete constructs and function calls, etc.
 
30
%%
 
31
%% <p>Caveats: It is possible that in some intricate uses of macros,
 
32
%% the automatic addition or removal of parentheses around uses or
 
33
%% arguments could cause the resulting program to be rejected by the
 
34
%% compiler; however, we have found no such case in existing
 
35
%% code. Programs defining strange macros can usually not be read by
 
36
%% this program, and in those cases, no changes will be made.</p>
 
37
%%
 
38
%% <p>If you really, really want to, you may call it "Inga".</p>
 
39
%%
 
40
%% <p>Disclaimer: The author accepts no responsibility for errors
 
41
%% introduced in code that has been processed by the program. It has
 
42
%% been reasonably well tested, but the possibility of errors remains.
 
43
%% Keep backups of your original code safely stored, until you feel
 
44
%% confident that the new, modified code can be trusted.</p>
 
45
 
 
46
-module(erl_tidy).
 
47
 
 
48
-export([dir/0, dir/1, dir/2, file/1, file/2, module/1, module/2]).
 
49
 
 
50
-include_lib("kernel/include/file.hrl").
 
51
 
 
52
-define(DEFAULT_BACKUP_SUFFIX, ".bak").
 
53
-define(DEFAULT_DIR, "").
 
54
-define(DEFAULT_REGEXP, ".*\\.erl$").
 
55
 
 
56
 
 
57
dir__defaults() ->
 
58
    [{follow_links, false},
 
59
     recursive,
 
60
     {regexp, ?DEFAULT_REGEXP},
 
61
     verbose].
 
62
 
 
63
%% =====================================================================
 
64
%% @spec dir() -> ok
 
65
%% @equiv dir("")
 
66
 
 
67
dir() ->
 
68
    dir("").
 
69
 
 
70
%% =====================================================================
 
71
%% @spec dir(Dir) -> ok
 
72
%% @equiv dir(Dir, [])
 
73
 
 
74
dir(Dir) ->
 
75
    dir(Dir, []).
 
76
 
 
77
%% =====================================================================
 
78
%% @spec dir(Directory::filename(), Options::[term()]) -> ok
 
79
%%           filename() = file:filename()
 
80
%%
 
81
%% @doc Tidies Erlang source files in a directory and its
 
82
%% subdirectories.
 
83
%%
 
84
%% <p>Available options:
 
85
%% <dl>
 
86
%%   <dt>{follow_links, bool()}</dt>
 
87
%%
 
88
%%       <dd>If the value is <code>true</code>, symbolic directory
 
89
%%       links will be followed.  The default value is
 
90
%%       <code>false</code>.</dd>
 
91
%%
 
92
%%   <dt>{recursive, bool()}</dt>
 
93
%%
 
94
%%       <dd>If the value is <code>true</code>, subdirectories will be
 
95
%%       visited recursively.  The default value is
 
96
%%       <code>true</code>.</dd>
 
97
%%
 
98
%%   <dt>{regexp, string()}</dt>
 
99
%%
 
100
%%       <dd>The value denotes a regular expression (see module
 
101
%%       <code>regexp</code>).  Tidying will only be applied to those
 
102
%%       regular files whose names match this pattern. The default
 
103
%%       value is <code>".*\\.erl$"</code>, which matches normal
 
104
%%       Erlang source file names.</dd>
 
105
%%
 
106
%%   <dt>{test, bool()}</dt>
 
107
%%
 
108
%%       <dd>If the value is <code>true</code>, no files will be
 
109
%%       modified. The default value is <code>false</code>.</dd>
 
110
%%
 
111
%%   <dt>{verbose, bool()}</dt>
 
112
%%
 
113
%%       <dd>If the value is <code>true</code>, progress messages will
 
114
%%       be output while the program is running, unless the
 
115
%%       <code>quiet</code> option is <code>true</code>. The default
 
116
%%       value when calling <code>dir/2</code> is
 
117
%%       <code>true</code>.</dd>
 
118
%%
 
119
%% </dl></p>
 
120
%%
 
121
%% <p>See the function <code>file/2</code> for further options.</p>
 
122
%%
 
123
%% @see regexp
 
124
%% @see file/2
 
125
 
 
126
-record(dir, {follow_links = false, recursive = true, options}).
 
127
 
 
128
dir(Dir, Opts) ->
 
129
    Opts1 = Opts ++ dir__defaults(),
 
130
    Env = #dir{follow_links = proplists:get_bool(follow_links, Opts1),
 
131
               recursive = proplists:get_bool(recursive, Opts1),
 
132
               options = Opts1},
 
133
    Regexp = proplists:get_value(regexp, Opts1),
 
134
    case filename(Dir) of
 
135
        "" ->
 
136
            Dir1 = ".";
 
137
        Dir1 ->
 
138
            ok
 
139
    end,
 
140
    dir_1(Dir1, Regexp, Env).
 
141
 
 
142
dir_1(Dir, Regexp, Env) ->
 
143
    case file:list_dir(Dir) of
 
144
        {ok, Files} ->
 
145
            lists:foreach(fun (X) -> dir_2(X, Regexp, Dir, Env) end,
 
146
                          Files);
 
147
        {error, _} ->
 
148
            report_error("error reading directory `~s'",
 
149
                         [filename(Dir)]),
 
150
            exit(error)
 
151
    end.
 
152
 
 
153
dir_2(Name, Regexp, Dir, Env) ->
 
154
    File = if Dir == "" ->
 
155
                   Name;
 
156
              true ->
 
157
                   filename:join(Dir, Name)
 
158
           end,
 
159
    case file_type(File) of
 
160
        {value, regular} ->
 
161
            dir_4(File, Regexp, Env);
 
162
        {value, directory} when Env#dir.recursive == true ->
 
163
            case is_symlink(Name) of
 
164
                false ->
 
165
                    dir_3(Name, Dir, Regexp, Env);
 
166
                true when Env#dir.follow_links == true ->
 
167
                    dir_3(Name, Dir, Regexp, Env);
 
168
                _ ->
 
169
                    ok
 
170
            end;
 
171
        _ ->
 
172
            ok
 
173
    end.
 
174
 
 
175
dir_3(Name, Dir, Regexp, Env) ->
 
176
    Dir1 = filename:join(Dir, Name),
 
177
    verbose("tidying directory `~s'.", [Dir1], Env#dir.options),
 
178
    dir_1(Dir1, Regexp, Env).
 
179
 
 
180
dir_4(File, Regexp, Env) ->
 
181
    case regexp:first_match(File, Regexp) of
 
182
        {match, _, _} ->
 
183
            Opts = [{outfile, File}, {dir, ""} | Env#dir.options],
 
184
            case catch file(File, Opts) of
 
185
                {'EXIT', _} ->
 
186
                    warn("error tidying `~s'.", [File], Opts);
 
187
                _ ->
 
188
                    ok
 
189
            end;
 
190
        _ ->
 
191
            ok
 
192
    end.
 
193
 
 
194
 
 
195
file__defaults() ->
 
196
    [{backup_suffix, ?DEFAULT_BACKUP_SUFFIX},
 
197
     backups, 
 
198
     {dir, ?DEFAULT_DIR},
 
199
     {printer, default_printer()},
 
200
     {quiet, false},
 
201
     {verbose, false}].
 
202
 
 
203
default_printer() ->
 
204
    fun (Tree, Options) -> erl_prettypr:format(Tree, Options) end.
 
205
 
 
206
%% =====================================================================
 
207
%% @spec file(Name) -> ok
 
208
%% @equiv file(Name, [])
 
209
 
 
210
file(Name) ->
 
211
    file(Name, []).
 
212
 
 
213
%% =====================================================================
 
214
%% @spec file(Name::filename(), Options::[term()]) -> ok
 
215
%%
 
216
%% @doc Tidies an Erlang source code file.
 
217
%%
 
218
%% <p>Available options are:
 
219
%% <dl>
 
220
%%   <dt>{backup_suffix, string()}</dt>
 
221
%%
 
222
%%       <dd>Specifies the file name suffix to be used when a backup
 
223
%%       file is created; the default value is <code>".bak"</code>
 
224
%%       (cf. the <code>backups</code> option).</dd>
 
225
%%
 
226
%%   <dt>{backups, bool()}</dt>
 
227
%%
 
228
%%       <dd>If the value is <code>true</code>, existing files will be
 
229
%%       renamed before new files are opened for writing. The new
 
230
%%       names are formed by appending the string given by the
 
231
%%       <code>backup_suffix</code> option to the original name. The
 
232
%%       default value is <code>true</code>.</dd>
 
233
%%
 
234
%%   <dt>{dir, filename()}</dt>
 
235
%%
 
236
%%       <dd>Specifies the name of the directory in which the output
 
237
%%       file is to be written. By default, the current directory is
 
238
%%       used. If the value is an empty string, the current directory
 
239
%%       is used. </dd>
 
240
%%
 
241
%%   <dt>{outfile, filename()}</dt>
 
242
%%
 
243
%%       <dd>Specifies the name of the file (without suffix) to which
 
244
%%       the resulting source code is to be written. If this option is
 
245
%%       not specified, the <code>Name</code> argument is used.</dd>
 
246
%%
 
247
%%   <dt>{printer, Function}</dt>
 
248
%%       <dd><ul>
 
249
%%         <li><code>Function = (syntaxTree()) -> string()</code></li>
 
250
%%       </ul>
 
251
%%
 
252
%%       <p>Specifies a function for prettyprinting Erlang syntax trees.
 
253
%%       This is used for outputting the resulting module definition.
 
254
%%       The function is assumed to return formatted text for the given
 
255
%%       syntax tree, and should raise an exception if an error occurs.
 
256
%%       The default formatting function calls
 
257
%%       <code>erl_prettypr:format/2</code>.</p></dd>
 
258
%%
 
259
%%   <dt>{test, bool()}</dt>
 
260
%%
 
261
%%       <dd>If the value is <code>true</code>, no files will be
 
262
%%       modified; this is typically most useful if the
 
263
%%       <code>verbose</code> flag is enabled, to generate reports
 
264
%%       about the program files without affecting them. The default
 
265
%%       value is <code>false</code>.</dd>
 
266
%% </dl></p>
 
267
%%
 
268
%% <p>See the function <code>module/2</code> for further options.</p>
 
269
%%
 
270
%% @see erl_prettypr:format/2
 
271
%% @see module/2
 
272
 
 
273
file(Name, Opts) ->
 
274
    Parent = self(),
 
275
    Child = spawn_link(fun () -> file_1(Parent, Name, Opts) end),
 
276
    receive
 
277
        {Child, ok} ->
 
278
            ok;
 
279
        {Child, {error, Reason}} ->
 
280
            exit(Reason)
 
281
    end.
 
282
 
 
283
file_1(Parent, Name, Opts) ->
 
284
    case catch file_2(Name, Opts) of
 
285
        {'EXIT', Reason} ->
 
286
            Parent ! {self(), {error, Reason}};
 
287
        _ ->
 
288
            Parent ! {self(), ok}
 
289
    end.
 
290
 
 
291
file_2(Name, Opts) ->
 
292
    Opts1 = Opts ++ file__defaults(),
 
293
    Forms = read_module(Name, Opts1),
 
294
    Comments = erl_comment_scan:file(Name),
 
295
    Forms1 = erl_recomment:recomment_forms(Forms, Comments),
 
296
    Tree = module(Forms1, [{file, Name} | Opts1]),
 
297
    case proplists:get_bool(test, Opts1) of
 
298
        true ->
 
299
            ok;
 
300
        false ->
 
301
            write_module(Tree, Name, Opts1),
 
302
            ok
 
303
    end.
 
304
 
 
305
read_module(Name, Opts) ->
 
306
    verbose("reading module `~s'.", [filename(Name)], Opts),
 
307
    case epp_dodger:parse_file(Name) of
 
308
        {ok, Forms} ->
 
309
            check_forms(Forms, Name),
 
310
            Forms;
 
311
        {error, R} ->
 
312
            error_read_file(Name),
 
313
            exit({error, R})
 
314
    end.
 
315
 
 
316
check_forms(Fs, Name) ->
 
317
    Fun = fun (F) ->
 
318
                  case erl_syntax:type(F) of
 
319
                      error_marker ->
 
320
                          S = case erl_syntax:error_marker_info(F) of
 
321
                                  {_, M, D} ->
 
322
                                      M:format_error(D);
 
323
                                  _ ->
 
324
                                      "unknown error"
 
325
                              end,
 
326
                          report_error({Name, erl_syntax:get_pos(F),
 
327
                                        "\n  ~s"}, [S]),
 
328
                          exit(error);
 
329
                      _ ->
 
330
                          ok
 
331
                  end
 
332
          end,
 
333
    lists:foreach(Fun, Fs).
 
334
 
 
335
%% Create the target directory and make a backup file if necessary,
 
336
%% then open the file, output the text and close the file
 
337
%% safely. Returns the file name.
 
338
 
 
339
write_module(Tree, Name, Opts) ->
 
340
    Name1 = proplists:get_value(outfile, Opts, filename(Name)),
 
341
    Dir = filename(proplists:get_value(dir, Opts, "")),
 
342
    File = if Dir == "" ->
 
343
                   Name1;
 
344
              true ->
 
345
                   case file_type(Dir) of
 
346
                       {value, directory} ->
 
347
                           ok;
 
348
                       {value, _} ->
 
349
                           report_error("`~s' is not a directory.",
 
350
                                        [filename(Dir)]),
 
351
                           exit(error);
 
352
                       none ->
 
353
                           case file:make_dir(Dir) of
 
354
                               ok ->
 
355
                                   verbose("created directory `~s'.",
 
356
                                           [filename(Dir)], Opts),
 
357
                                   ok;
 
358
                               E ->
 
359
                                   report_error("failed to create "
 
360
                                                "directory `~s'.",
 
361
                                                [filename(Dir)]),
 
362
                                   exit({make_dir, E})
 
363
                           end
 
364
                   end,
 
365
                   filename(filename:join(Dir, Name1))
 
366
           end,
 
367
    case proplists:get_bool(backups, Opts) of
 
368
        true ->
 
369
            backup_file(File, Opts);
 
370
        false ->
 
371
            ok
 
372
    end,
 
373
    Printer = proplists:get_value(printer, Opts),
 
374
    FD = open_output_file(File),
 
375
    verbose("writing to file `~s'.", [File], Opts),
 
376
    V = (catch {ok, output(FD, Printer, Tree, Opts)}),
 
377
    file:close(FD),
 
378
    case V of
 
379
        {ok, _} ->
 
380
            File;
 
381
        {'EXIT', R} ->
 
382
            error_write_file(File),
 
383
            exit(R);
 
384
        R ->
 
385
            error_write_file(File),
 
386
            throw(R)
 
387
    end.
 
388
 
 
389
output(FD, Printer, Tree, Opts) ->
 
390
    io:put_chars(FD, Printer(Tree, Opts)),
 
391
    io:nl(FD).
 
392
 
 
393
%% file_type(filename()) -> {value, Type} | none
 
394
 
 
395
file_type(Name) ->
 
396
    file_type(Name, false).
 
397
 
 
398
is_symlink(Name) ->
 
399
    file_type(Name, true) == {value, symlink}.
 
400
 
 
401
file_type(Name, Links) ->
 
402
    V = case Links of
 
403
            true ->
 
404
                catch file:read_link_info(Name);
 
405
            false ->
 
406
                catch file:read_file_info(Name)
 
407
        end,
 
408
    case V of
 
409
        {ok, Env} ->
 
410
            {value, Env#file_info.type};
 
411
        {error, enoent} ->
 
412
            none;
 
413
        {error, R} ->
 
414
            error_read_file(Name),
 
415
            exit({error, R});
 
416
        {'EXIT', R} ->
 
417
            error_read_file(Name),
 
418
            exit(R);
 
419
        R ->
 
420
            error_read_file(Name),
 
421
            throw(R)
 
422
    end.
 
423
 
 
424
open_output_file(FName) ->
 
425
    case catch file:open(FName, [write]) of
 
426
        {ok, FD} ->
 
427
            FD;
 
428
        {error, R} ->
 
429
            error_open_output(FName),
 
430
            exit({error, R});
 
431
        {'EXIT', R} ->
 
432
            error_open_output(FName),
 
433
            exit(R);
 
434
        R ->
 
435
            error_open_output(FName),
 
436
            exit(R)
 
437
    end.
 
438
 
 
439
%% If the file exists, rename it by appending the given suffix to the
 
440
%% file name.
 
441
 
 
442
backup_file(Name, Opts) ->
 
443
    case file_type(Name) of
 
444
        {value, regular} ->
 
445
            backup_file_1(Name, Opts);
 
446
        {value, _} ->
 
447
            error_backup_file(Name),
 
448
            exit(error);
 
449
        none ->
 
450
            ok
 
451
    end.
 
452
 
 
453
%% The file should exist and be a regular file here.
 
454
 
 
455
backup_file_1(Name, Opts) ->
 
456
    Suffix = proplists:get_value(backup_suffix, Opts, ""),
 
457
    Dest = filename:join(filename:dirname(Name),
 
458
                         filename:basename(Name) ++ Suffix),
 
459
    case catch file:rename(Name, Dest) of
 
460
        ok ->
 
461
            verbose("made backup of file `~s'.", [Name], Opts);
 
462
        {error, R} ->
 
463
            error_backup_file(Name),
 
464
            exit({error, R});
 
465
        {'EXIT', R} ->
 
466
            error_backup_file(Name),
 
467
            exit(R);
 
468
        R ->
 
469
            error_backup_file(Name),
 
470
            throw(R)
 
471
    end.
 
472
 
 
473
 
 
474
%% =====================================================================
 
475
%% @spec module(Forms) -> syntaxTree()
 
476
%% @equiv module(Forms, [])
 
477
 
 
478
module(Forms) ->
 
479
    module(Forms, []).
 
480
 
 
481
%% =====================================================================
 
482
%% @spec module(Forms, Options::[term()]) -> syntaxTree()
 
483
%%
 
484
%%          Forms = syntaxTree() | [syntaxTree()]
 
485
%%          syntaxTree() = erl_syntax:syntaxTree()
 
486
%%
 
487
%% @doc Tidies a syntax tree representation of a module
 
488
%% definition. The given <code>Forms</code> may be either a single
 
489
%% syntax tree of type <code>form_list</code>, or a list of syntax
 
490
%% trees representing "program forms". In either case,
 
491
%% <code>Forms</code> must represents a single complete module
 
492
%% definition. The returned syntax tree has type
 
493
%% <code>form_list</code> and represents a tidied-up version of the
 
494
%% same source code.
 
495
%%
 
496
%% <p>Available options are:
 
497
%% <dl>
 
498
%%   <dt>{auto_export_vars, bool()}</dt>
 
499
%%
 
500
%%       <dd>If the value is <code>true</code>, all matches
 
501
%%       "<code>{V1, ..., Vn} = E</code>" where <code>E</code> is a
 
502
%%       case-, if- or receive-expression whose branches all return
 
503
%%       n-tuples (or explicitly throw exceptions) will be rewritten
 
504
%%       to bind and export the variables <code>V1</code>, ...,
 
505
%%       <code>Vn</code> directly. The default value is
 
506
%%       <code>false</code>.
 
507
%%
 
508
%%       <p>For example:
 
509
%%       <pre>
 
510
%%                {X, Y} = case ... of
 
511
%%                             ... -> {17, foo()};
 
512
%%                             ... -> {42, bar()}
 
513
%%                         end
 
514
%%       </pre>
 
515
%%       will be rewritten to:
 
516
%%       <pre>
 
517
%%                case ... of
 
518
%%                    ... -> X = 17, Y = foo(), {X, Y};
 
519
%%                    ... -> X = 42, Y = bar(), {X, Y}
 
520
%%                end
 
521
%%       </pre></p></dd>
 
522
%%
 
523
%%   <dt>{auto_list_comp, bool()}</dt>
 
524
%%
 
525
%%       <dd>If the value is <code>true</code>, calls to
 
526
%%       <code>lists:map/2</code> and <code>lists:filter/2</code> will
 
527
%%       be rewritten using list comprehensions. The default value is
 
528
%%       <code>true</code>.</dd>
 
529
%%
 
530
%%   <dt>{file, string()}</dt>
 
531
%%
 
532
%%       <dd>Specifies the name of the file from which the source code
 
533
%%       was taken. This is only used for generation of error
 
534
%%       reports. The default value is the empty string.</dd>
 
535
%%
 
536
%%   <dt>{idem, bool()}</dt>
 
537
%%
 
538
%%       <dd>If the value is <code>true</code>, all options that affect
 
539
%%       how the code is modified are set to "no changes". For example,
 
540
%%       to only update guard tests, and nothing else, use the options
 
541
%%       <code>[new_guard_tests, idem]</code>. (Recall that options
 
542
%%       closer to the beginning of the list have higher
 
543
%%       precedence.)</dd>
 
544
%%
 
545
%%   <dt>{keep_unused, bool()}</dt>
 
546
%%
 
547
%%       <dd>If the value is <code>true</code>, unused functions will
 
548
%%       not be removed from the code. The default value is
 
549
%%       <code>false</code>.</dd>
 
550
%%
 
551
%%   <dt>{new_guard_tests, bool()}</dt>
 
552
%%
 
553
%%       <dd>If the value is <code>true</code>, guard tests will be
 
554
%%       updated to use the new names, e.g. "<code>is_integer(X)</code>"
 
555
%%       instead of "<code>integer(X)</code>". The default value is
 
556
%%       <code>true</code>. See also <code>old_guard_tests</code>.</dd>
 
557
%%
 
558
%%   <dt>{no_imports, bool()}</dt>
 
559
%%
 
560
%%       <dd>If the value is <code>true</code>, all import statements
 
561
%%       will be removed and calls to imported functions will be
 
562
%%       expanded to explicit remote calls. The default value is
 
563
%%       <code>false</code>.</dd>
 
564
%%
 
565
%%   <dt>{old_guard_tests, bool()}</dt>
 
566
%%
 
567
%%       <dd>If the value is <code>true</code>, guard tests will be
 
568
%%       changed to use the old names instead of the new ones,
 
569
%%       e.g. "<code>integer(X)</code>" instead of
 
570
%%       "<code>is_integer(X)</code>". The default value is
 
571
%%       <code>false</code>. This option overrides the
 
572
%%       <code>new_guard_tests</code> option.</dd>
 
573
%%
 
574
%%   <dt>{quiet, bool()}</dt>
 
575
%%
 
576
%%       <dd>If the value is <code>true</code>, all information
 
577
%%       messages and warning messages will be suppressed. The default
 
578
%%       value is <code>false</code>.</dd>
 
579
%%
 
580
%%   <dt>{rename, [{{atom(), atom(), integer()},
 
581
%%                  {atom(), atom()}}]}</dt>
 
582
%%
 
583
%%       <dd>The value is a list of pairs, associating tuples
 
584
%%       <code>{Module, Name, Arity}</code> with tuples
 
585
%%       <code>{NewModule, NewName}</code>, specifying renamings of
 
586
%%       calls to remote functions. By default, the value is the empty
 
587
%%       list.
 
588
%%
 
589
%%       <p>The renaming affects only remote calls (also when
 
590
%%       disguised by import declarations); local calls within a
 
591
%%       module are not affected, and no function definitions are
 
592
%%       renamed. Since the arity cannot change, the new name is
 
593
%%       represented by <code>{NewModule, NewName}</code> only. Only
 
594
%%       calls matching the specified arity will match; multiple
 
595
%%       entries are necessary for renaming calls to functions that
 
596
%%       have the same module and function name, but different
 
597
%%       arities.</p>
 
598
%%
 
599
%%       <p>This option can also be used to override the default
 
600
%%       renaming of calls which use obsolete function names.</p></dd>
 
601
%%
 
602
%%   <dt>{verbose, bool()}</dt>
 
603
%%
 
604
%%       <dd>If the value is <code>true</code>, progress messages
 
605
%%       will be output while the program is running, unless the
 
606
%%       <code>quiet</code> option is <code>true</code>. The default
 
607
%%       value is <code>false</code>.</dd>
 
608
%%
 
609
%% </dl></p>
 
610
 
 
611
module(Forms, Opts) when list(Forms) ->
 
612
    module(erl_syntax:form_list(Forms), Opts);
 
613
module(Forms, Opts) ->
 
614
    Opts1 = proplists:expand(module__expansions(), Opts)
 
615
            ++ module__defaults(),
 
616
    File = proplists:get_value(file, Opts1, ""),
 
617
    Forms1 = erl_syntax:flatten_form_list(Forms),
 
618
    module_1(Forms1, File, Opts1).
 
619
 
 
620
module__defaults() ->
 
621
    [{auto_export_vars, false},
 
622
     {auto_list_comp, true},
 
623
     {keep_unused, false},
 
624
     {new_guard_tests, true},
 
625
     {no_imports, false},
 
626
     {old_guard_tests, false},
 
627
     {quiet, false},
 
628
     {verbose, false}].
 
629
 
 
630
module__expansions() ->
 
631
    [{idem, [{auto_export_vars, false},
 
632
             {auto_list_comp, false},
 
633
             {keep_unused, true},
 
634
             {new_guard_tests, false},
 
635
             {no_imports, false},
 
636
             {old_guard_tests, false}]}].
 
637
 
 
638
module_1(Forms, File, Opts) ->
 
639
    Info = analyze_forms(Forms, File),
 
640
    Module = get_module_name(Info, File),
 
641
    Attrs = get_module_attributes(Info),
 
642
    Exports = get_module_exports(Info),
 
643
    Imports = get_module_imports(Info),
 
644
    Opts1 = check_imports(Imports, Opts, File),
 
645
    Fs = erl_syntax:form_list_elements(Forms),
 
646
    {Names, Defs} = collect_functions(Fs),
 
647
    Exports1 = check_export_all(Attrs, Names, Exports),
 
648
    Roots = ordsets:union(ordsets:from_list(Exports1),
 
649
                          hidden_uses(Fs, Imports)),
 
650
    {Names1, Used, Imported, Defs1} = visit_used(Names, Defs, Roots,
 
651
                                                 Imports, Module,
 
652
                                                 Opts1),
 
653
    Fs1 = update_forms(Fs, Defs1, Imported, Opts1),
 
654
    Fs2 = filter_forms(Fs1, Names1, Used, Opts1),
 
655
    rewrite(Forms, erl_syntax:form_list(Fs2)).
 
656
 
 
657
analyze_forms(Forms, File) ->
 
658
    case catch {ok, erl_syntax_lib:analyze_forms(Forms)} of
 
659
        {ok, L1} ->
 
660
            L1;
 
661
        syntax_error ->
 
662
            report_error({File, 0, "syntax error."}),
 
663
            erlang:fault(badarg);
 
664
        {'EXIT', R} ->
 
665
            exit(R);
 
666
        R ->
 
667
            throw(R)
 
668
    end.
 
669
 
 
670
get_module_name(List, File) ->
 
671
    case lists:keysearch(module, 1, List) of
 
672
        {value, {module, M}} ->
 
673
            M;
 
674
        _ ->
 
675
            report_error({File, 0,
 
676
                          "cannot determine module name."}),
 
677
            exit(error)
 
678
    end.
 
679
 
 
680
get_module_attributes(List) ->
 
681
    case lists:keysearch(attributes, 1, List) of
 
682
        {value, {attributes, As}} ->
 
683
            As;
 
684
        _ ->
 
685
            []
 
686
    end.
 
687
 
 
688
get_module_exports(List) ->
 
689
    case lists:keysearch(exports, 1, List) of
 
690
        {value, {exports, Es}} ->
 
691
            Es;
 
692
        _ ->
 
693
            []
 
694
    end.
 
695
 
 
696
get_module_imports(List) ->
 
697
    case lists:keysearch(imports, 1, List) of
 
698
        {value, {imports, Is}} ->
 
699
            flatten_imports(Is);
 
700
        _ ->
 
701
            []
 
702
    end.
 
703
 
 
704
compile_attrs(As) ->
 
705
    lists:append([if list(T) -> T; true -> [T] end
 
706
                  || {compile, T} <- As]).
 
707
 
 
708
flatten_imports(Is) ->
 
709
    [{F, M} || {M, Fs} <- Is, F <- Fs].
 
710
 
 
711
check_imports(Is, Opts, File) ->
 
712
    case check_imports_1(lists:sort(Is)) of
 
713
        true ->
 
714
            Opts;
 
715
        false ->
 
716
            case proplists:get_bool(no_imports, Opts) of
 
717
                true ->
 
718
                    warn({File, 0,
 
719
                          "conflicting import declarations - "
 
720
                          "will not expand imports."},
 
721
                         [], Opts),
 
722
                    %% prevent expansion of imports
 
723
                    [{no_imports, false} | Opts];
 
724
                false ->
 
725
                    Opts
 
726
            end
 
727
    end.
 
728
 
 
729
check_imports_1([{F1, M1}, {F2, M2} | _Is]) when F1 == F2, M1 /= M2 ->
 
730
    false;
 
731
check_imports_1([_ | Is]) ->
 
732
    check_imports_1(Is);
 
733
check_imports_1([]) ->
 
734
    true.
 
735
 
 
736
check_export_all(Attrs, Names, Exports) ->
 
737
    case lists:member(export_all, compile_attrs(Attrs)) of
 
738
        true ->
 
739
            Exports ++ sets:to_list(Names);
 
740
        false ->
 
741
            Exports
 
742
    end.
 
743
 
 
744
filter_forms(Fs, Names, Used, Opts) ->
 
745
    Keep = case proplists:get_bool(keep_unused, Opts) of
 
746
               true ->
 
747
                   Names;
 
748
               false ->
 
749
                   Used
 
750
           end,
 
751
    [F || F <- Fs, keep_form(F, Keep, Opts)].
 
752
 
 
753
keep_form(Form, Used, Opts) ->
 
754
    case erl_syntax:type(Form) of
 
755
        function ->
 
756
            N = erl_syntax_lib:analyze_function(Form),
 
757
            case sets:is_element(N, Used) of
 
758
                false ->
 
759
                    report_removed_def("function", N, Form, Opts),
 
760
                    false;
 
761
                true ->
 
762
                    true
 
763
            end;
 
764
        rule ->
 
765
            N = erl_syntax_lib:analyze_rule(Form),
 
766
            case sets:is_element(N, Used) of
 
767
                false ->
 
768
                    report_removed_def("rule", N, Form, Opts),
 
769
                    false;
 
770
                true ->
 
771
                    true
 
772
            end;
 
773
        attribute ->
 
774
            case erl_syntax_lib:analyze_attribute(Form) of
 
775
                {file, _} ->
 
776
                    false;
 
777
                _ ->
 
778
                    true
 
779
            end;
 
780
        error_marker ->
 
781
            false;
 
782
        warning_marker ->
 
783
            false;
 
784
        eof_marker ->
 
785
            false;
 
786
        _ ->
 
787
            true
 
788
    end.
 
789
 
 
790
report_removed_def(Type, {N, A}, Form, Opts) ->
 
791
    File = proplists:get_value(file, Opts, ""),
 
792
    report({File, erl_syntax:get_pos(Form),
 
793
            "removing unused ~s `~w/~w'."},
 
794
           [Type, N, A], Opts).
 
795
 
 
796
collect_functions(Forms) ->
 
797
    lists:foldl(
 
798
      fun (F, {Names, Defs}) ->
 
799
              case erl_syntax:type(F) of
 
800
                  function ->
 
801
                      N = erl_syntax_lib:analyze_function(F),
 
802
                      {sets:add_element(N, Names),
 
803
                       dict:store(N, {F, []}, Defs)};
 
804
                  rule ->
 
805
                      N = erl_syntax_lib:analyze_rule(F),
 
806
                      {sets:add_element(N, Names),
 
807
                       dict:store(N, {F, []}, Defs)};
 
808
                  _ ->
 
809
                      {Names, Defs}
 
810
              end
 
811
      end,
 
812
      {sets:new(), dict:new()},
 
813
      Forms).
 
814
 
 
815
update_forms([F | Fs], Defs, Imports, Opts) ->
 
816
    case erl_syntax:type(F) of
 
817
        function ->
 
818
            N = erl_syntax_lib:analyze_function(F),
 
819
            {F1, Fs1} = dict:fetch(N, Defs),
 
820
            [F1 | lists:reverse(Fs1)] ++ update_forms(Fs, Defs, Imports,
 
821
                                                      Opts);
 
822
        rule ->
 
823
            N = erl_syntax_lib:analyze_rule(F),
 
824
            {F1, Fs1} = dict:fetch(N, Defs),
 
825
            [F1 | lists:reverse(Fs1)] ++ update_forms(Fs, Defs, Imports,
 
826
                                                      Opts);
 
827
        attribute ->
 
828
            [update_attribute(F, Imports, Opts)
 
829
             | update_forms(Fs, Defs, Imports, Opts)];
 
830
        _ ->
 
831
            [F | update_forms(Fs, Defs, Imports, Opts)]
 
832
    end;
 
833
update_forms([], _, _, _) ->
 
834
    [].
 
835
 
 
836
update_attribute(F, Imports, Opts) ->
 
837
    case erl_syntax_lib:analyze_attribute(F) of
 
838
        {import, {M, Ns}} ->
 
839
            Ns1 = ordsets:from_list([N || N <- Ns,
 
840
                                          sets:is_element(N, Imports)]),
 
841
            case ordsets:subtract(ordsets:from_list(Ns), Ns1) of
 
842
                [] ->
 
843
                    ok;
 
844
                Names ->
 
845
                    File = proplists:get_value(file, Opts, ""),
 
846
                    report({File, erl_syntax:get_pos(F),
 
847
                            "removing unused imports:~s"},
 
848
                           [[io_lib:fwrite("\n\t`~w:~w/~w'", [M, N, A])
 
849
                             || {N, A} <- Names]], Opts)
 
850
            end,
 
851
            Is = [make_fname(N) || N <- Ns1],
 
852
            if Is == [] ->
 
853
                    %% This will be filtered out later.
 
854
                    erl_syntax:warning_marker(deleted);
 
855
               true ->
 
856
                    F1 = erl_syntax:attribute(erl_syntax:atom(import),
 
857
                                              [erl_syntax:atom(M),
 
858
                                               erl_syntax:list(Is)]),
 
859
                    rewrite(F, F1)
 
860
            end;
 
861
        {export, Ns} ->
 
862
            Es = [make_fname(N) || N <- ordsets:from_list(Ns)],
 
863
            F1 = erl_syntax:attribute(erl_syntax:atom(export),
 
864
                                      [erl_syntax:list(Es)]),
 
865
            rewrite(F, F1);
 
866
        _ ->
 
867
            F
 
868
    end.
 
869
 
 
870
make_fname({F, A}) ->
 
871
    erl_syntax:arity_qualifier(erl_syntax:atom(F),
 
872
                               erl_syntax:integer(A)).
 
873
 
 
874
hidden_uses(Fs, Imports) ->
 
875
    Used = lists:foldl(fun (F, S) ->
 
876
                               case erl_syntax:type(F) of
 
877
                                   attribute ->
 
878
                                       hidden_uses_1(F, S);
 
879
                                   _ ->
 
880
                                       S
 
881
                               end
 
882
                       end,
 
883
                       [], Fs),
 
884
    ordsets:subtract(Used, ordsets:from_list([F || {F, _M} <- Imports])).
 
885
 
 
886
hidden_uses_1(Tree, Used) ->
 
887
    erl_syntax_lib:fold(fun hidden_uses_2/2, Used, Tree).
 
888
 
 
889
hidden_uses_2(Tree, Used) ->
 
890
    case erl_syntax:type(Tree) of
 
891
        application ->
 
892
            F = erl_syntax:application_operator(Tree),
 
893
            case erl_syntax:type(F) of
 
894
                atom ->
 
895
                    As = erl_syntax:application_arguments(Tree),
 
896
                    N = {erl_syntax:atom_value(F), length(As)},
 
897
                    case is_auto_imported(N) of
 
898
                        true ->
 
899
                            Used;
 
900
                        false ->
 
901
                            ordsets:add_element(N, Used)
 
902
                    end;
 
903
                _ ->
 
904
                    Used
 
905
            end;
 
906
        implicit_fun ->
 
907
            F = erl_syntax:implicit_fun_name(Tree),
 
908
            case catch {ok, erl_syntax_lib:analyze_function_name(F)} of
 
909
                {ok, {Name, Arity} = N}
 
910
                when atom(Name), integer(Arity) ->
 
911
                    ordsets:add_element(N, Used);
 
912
                _ ->
 
913
                    Used
 
914
            end;
 
915
        _ ->
 
916
            Used
 
917
    end.
 
918
 
 
919
-record(env, {file,
 
920
              module,
 
921
              current,
 
922
              imports,
 
923
              context = normal,
 
924
              verbosity = 1,
 
925
              quiet = false,
 
926
              no_imports = false,
 
927
              spawn_funs = false,
 
928
              auto_list_comp = true,
 
929
              auto_export_vars = false,
 
930
              new_guard_tests = true,
 
931
              old_guard_tests = false}).
 
932
 
 
933
-record(st, {varc, used, imported, vars, functions, new_forms, rename}).
 
934
 
 
935
visit_used(Names, Defs, Roots, Imports, Module, Opts) ->
 
936
    File = proplists:get_value(file, Opts, ""),
 
937
    NoImports = proplists:get_bool(no_imports, Opts),
 
938
    Rename = proplists:append_values(rename, Opts),
 
939
    loop(Roots, sets:new(), Defs,
 
940
         #env{file = File,
 
941
              module = Module,
 
942
              imports = dict:from_list(Imports),
 
943
              verbosity = verbosity(Opts),
 
944
              no_imports = NoImports,
 
945
              spawn_funs = proplists:get_bool(spawn_funs, Opts),
 
946
              auto_list_comp = proplists:get_bool(auto_list_comp, Opts),
 
947
              auto_export_vars = proplists:get_bool(auto_export_vars,
 
948
                                                    Opts),
 
949
              new_guard_tests = proplists:get_bool(new_guard_tests,
 
950
                                                   Opts),
 
951
              old_guard_tests = proplists:get_bool(old_guard_tests,
 
952
                                                   Opts)},
 
953
         #st{used = sets:from_list(Roots),
 
954
             imported = sets:new(),
 
955
             functions = Names,
 
956
             rename = dict:from_list([X || {F1, F2} = X <- Rename,
 
957
                                           is_remote_name(F1),
 
958
                                           is_atom_pair(F2)])}).
 
959
 
 
960
loop([F | Work], Seen0, Defs0, Env, St0) ->
 
961
    case sets:is_element(F, Seen0) of
 
962
        true ->
 
963
            loop(Work, Seen0, Defs0, Env, St0);
 
964
        false ->
 
965
            Seen1 = sets:add_element(F, Seen0),
 
966
            case dict:find(F, Defs0) of
 
967
                {ok, {Form, Fs}} ->
 
968
                    Vars = erl_syntax_lib:variables(Form),
 
969
                    Form1 = erl_syntax_lib:annotate_bindings(Form, []),
 
970
                    {Form2, St1} = visit(Form1, Env#env{current = F},
 
971
                                         St0#st{varc = 1,
 
972
                                                used = sets:new(),
 
973
                                                vars = Vars,
 
974
                                                new_forms = []}),
 
975
                    Fs1 = St1#st.new_forms ++ Fs,
 
976
                    Defs1 = dict:store(F, {Form2, Fs1}, Defs0),
 
977
                    Used = St1#st.used,
 
978
                    Work1 = sets:to_list(Used) ++ Work,
 
979
                    St2 = St1#st{used = sets:union(Used, St0#st.used)},
 
980
                    loop(Work1, Seen1, Defs1, Env, St2);
 
981
                error ->
 
982
                    %% Quietly ignore any names that have no definition.
 
983
                    loop(Work, Seen1, Defs0, Env, St0)
 
984
            end
 
985
    end;
 
986
loop([], _, Defs, _, St) ->
 
987
    {St#st.functions, St#st.used, St#st.imported, Defs}.
 
988
 
 
989
visit(Tree, Env, St0) ->
 
990
    case erl_syntax:type(Tree) of
 
991
        application ->
 
992
            visit_application(Tree, Env, St0);
 
993
        infix_expr ->
 
994
            visit_infix_expr(Tree, Env, St0);
 
995
        prefix_expr ->
 
996
            visit_prefix_expr(Tree, Env, St0);
 
997
        implicit_fun ->
 
998
            visit_implicit_fun(Tree, Env, St0);
 
999
        clause ->
 
1000
            visit_clause(Tree, Env, St0);
 
1001
        list_comp ->
 
1002
            visit_list_comp(Tree, Env, St0);
 
1003
        match_expr ->
 
1004
            visit_match_expr(Tree, Env, St0);
 
1005
        _ ->
 
1006
            visit_other(Tree, Env, St0)
 
1007
    end.
 
1008
 
 
1009
visit_other(Tree, Env, St) ->
 
1010
    F = fun (T, S) -> visit(T, Env, S) end,
 
1011
    erl_syntax_lib:mapfold_subtrees(F, St, Tree).
 
1012
 
 
1013
visit_list(Ts, Env, St0) ->
 
1014
    lists:mapfoldl(fun (T, S) -> visit(T, Env, S) end, St0, Ts).
 
1015
 
 
1016
visit_implicit_fun(Tree, _Env, St0) ->
 
1017
    F = erl_syntax:implicit_fun_name(Tree),
 
1018
    case catch {ok, erl_syntax_lib:analyze_function_name(F)} of
 
1019
        {ok, {Name, Arity} = N}
 
1020
        when atom(Name), integer(Arity) ->
 
1021
            Used = sets:add_element(N, St0#st.used),
 
1022
            {Tree, St0#st{used = Used}};
 
1023
        _ ->
 
1024
            Tree
 
1025
    end.
 
1026
 
 
1027
visit_clause(Tree, Env, St0) ->
 
1028
    %% We do not visit the patterns (for now, anyway).
 
1029
    Ps = erl_syntax:clause_patterns(Tree),
 
1030
    {G, St1} = case erl_syntax:clause_guard(Tree) of
 
1031
                   none ->
 
1032
                       {none, St0};
 
1033
                   G0 ->
 
1034
                       visit(G0, Env#env{context = guard_test}, St0)
 
1035
               end,
 
1036
    {B, St2} = visit_list(erl_syntax:clause_body(Tree), Env, St1),
 
1037
    {rewrite(Tree, erl_syntax:clause(Ps, G, B)), St2}.
 
1038
 
 
1039
visit_infix_expr(Tree, #env{context = guard_test}, St0) ->
 
1040
    %% Detect transition from guard test to guard expression.
 
1041
    visit_other(Tree, #env{context = guard_expr}, St0);
 
1042
visit_infix_expr(Tree, Env, St0) ->
 
1043
    visit_other(Tree, Env, St0).
 
1044
 
 
1045
visit_prefix_expr(Tree, #env{context = guard_test}, St0) ->
 
1046
    %% Detect transition from guard test to guard expression.
 
1047
    visit_other(Tree, #env{context = guard_expr}, St0);
 
1048
visit_prefix_expr(Tree, Env, St0) ->
 
1049
    visit_other(Tree, Env, St0).
 
1050
 
 
1051
visit_application(Tree, Env, St0) ->
 
1052
    Env1 = case Env of
 
1053
               #env{context = guard_test} ->
 
1054
                   Env#env{context = guard_expr};
 
1055
               _ ->
 
1056
                   Env
 
1057
           end,
 
1058
    {F, St1} = visit(erl_syntax:application_operator(Tree), Env1, St0),
 
1059
    {As, St2} = visit_list(erl_syntax:application_arguments(Tree), Env1,
 
1060
                           St1),
 
1061
    case erl_syntax:type(F) of
 
1062
        atom ->
 
1063
            visit_atom_application(F, As, Tree, Env, St2);
 
1064
        implicit_fun ->
 
1065
            visit_named_fun_application(F, As, Tree, Env, St2);
 
1066
        fun_expr ->
 
1067
            visit_lambda_application(F, As, Tree, Env, St2);
 
1068
        _ ->
 
1069
            visit_nonlocal_application(F, As, Tree, Env, St2)
 
1070
    end.
 
1071
 
 
1072
visit_application_final(F, As, Tree, St0) ->
 
1073
    {rewrite(Tree, erl_syntax:application(F, As)), St0}.
 
1074
 
 
1075
revisit_application(F, As, Tree, Env, St0) ->
 
1076
    visit(rewrite(Tree, erl_syntax:application(F, As)), Env, St0).
 
1077
 
 
1078
visit_atom_application(F, As, Tree, #env{context = guard_test} = Env,
 
1079
                       St0) ->
 
1080
    N = erl_syntax:atom_value(F),
 
1081
    A = length(As),
 
1082
    N1 = case Env#env.old_guard_tests of
 
1083
             true ->
 
1084
                 reverse_guard_test(N, A);
 
1085
             false ->
 
1086
                 case Env#env.new_guard_tests of
 
1087
                     true ->
 
1088
                         rewrite_guard_test(N, A);
 
1089
                     false ->
 
1090
                         N
 
1091
                 end
 
1092
         end,
 
1093
    if N1 /= N ->
 
1094
            report({Env#env.file, erl_syntax:get_pos(F),
 
1095
                    "changing guard test `~w' to `~w'."},
 
1096
                   [N, N1], Env#env.verbosity);
 
1097
       true ->
 
1098
            ok
 
1099
    end,
 
1100
    %% No need to revisit here.
 
1101
    F1 = rewrite(F, erl_syntax:atom(N1)),
 
1102
    visit_application_final(F1, As, Tree, St0);
 
1103
visit_atom_application(F, As, Tree, #env{context = guard_expr}, St0) ->
 
1104
    %% Atom applications in guard expressions are never local calls.
 
1105
    visit_application_final(F, As, Tree, St0);
 
1106
visit_atom_application(F, As, Tree, Env, St0) ->
 
1107
    N = {erl_syntax:atom_value(F), length(As)},
 
1108
    case is_auto_imported(N) of
 
1109
        true ->
 
1110
            visit_bif_call(N, F, As, Tree, Env, St0);
 
1111
        false ->
 
1112
            case is_imported(N, Env) of
 
1113
                true ->
 
1114
                    visit_import_application(N, F, As, Tree, Env, St0);
 
1115
                false ->
 
1116
                    Used = sets:add_element(N, St0#st.used),
 
1117
                    visit_application_final(F, As, Tree,
 
1118
                                            St0#st{used = Used})
 
1119
            end
 
1120
    end.
 
1121
 
 
1122
visit_import_application({N, A} = Name, F, As, Tree, Env, St0) ->
 
1123
    M = dict:fetch(Name, Env#env.imports),
 
1124
    Expand = case Env#env.no_imports of
 
1125
                 true ->
 
1126
                     true;
 
1127
                 false ->
 
1128
                     auto_expand_import({M, N, A}, St0)
 
1129
             end,
 
1130
    case Expand of
 
1131
        true ->
 
1132
            report({Env#env.file, erl_syntax:get_pos(F),
 
1133
                    "expanding call to imported function `~w:~w/~w'."},
 
1134
                   [M, N, A], Env#env.verbosity),
 
1135
            F1 = erl_syntax:module_qualifier(erl_syntax:atom(M),
 
1136
                                             erl_syntax:atom(N)),
 
1137
            revisit_application(rewrite(F, F1), As, Tree, Env, St0);
 
1138
        false ->
 
1139
            Is = sets:add_element(Name, St0#st.imported),
 
1140
            visit_application_final(F, As, Tree, St0#st{imported = Is})
 
1141
    end.
 
1142
 
 
1143
visit_bif_call({apply, 2}, F, [E, Args] = As, Tree, Env, St0) ->
 
1144
    case erl_syntax:is_proper_list(Args) of
 
1145
        true ->
 
1146
            report({Env#env.file, erl_syntax:get_pos(F),
 
1147
                    "changing use of `apply/2' "
 
1148
                    "to direct function call."},
 
1149
                   [], Env#env.verbosity),
 
1150
            As1 = erl_syntax:list_elements(Args),
 
1151
            revisit_application(E, As1, Tree, Env, St0);
 
1152
        false ->
 
1153
            visit_application_final(F, As, Tree, St0)
 
1154
    end;
 
1155
visit_bif_call({apply, 3}, F, [M, N, Args] = As, Tree, Env, St0) ->
 
1156
    case erl_syntax:is_proper_list(Args) of
 
1157
        true ->
 
1158
            report({Env#env.file, erl_syntax:get_pos(F),
 
1159
                    "changing use of `apply/3' "
 
1160
                    "to direct remote call."},
 
1161
                   [], Env#env.verbosity),
 
1162
            F1 = rewrite(F, erl_syntax:module_qualifier(M, N)),
 
1163
            As1 = erl_syntax:list_elements(Args),
 
1164
            visit_nonlocal_application(F1, As1, Tree, Env, St0);
 
1165
        false ->
 
1166
            visit_application_final(F, As, Tree, St0)
 
1167
    end;
 
1168
visit_bif_call({spawn, 3} = N, F, [_, _, _] = As, Tree, Env, St0) ->
 
1169
    visit_spawn_call(N, F, [], As, Tree, Env, St0);
 
1170
visit_bif_call({spawn_link, 3} = N, F, [_, _, _] = As, Tree, Env,
 
1171
               St0) ->
 
1172
    visit_spawn_call(N, F, [], As, Tree, Env, St0);
 
1173
visit_bif_call({spawn, 4} = N, F, [A | [_, _, _] = As], Tree, Env,
 
1174
               St0) ->
 
1175
    visit_spawn_call(N, F, [A], As, Tree, Env, St0);
 
1176
visit_bif_call({spawn_link, 4} = N, F, [A | [_, _, _] = As], Tree, Env,
 
1177
               St0) ->
 
1178
    visit_spawn_call(N, F, [A], As, Tree, Env, St0);
 
1179
visit_bif_call(_, F, As, Tree, _Env, St0) ->
 
1180
    visit_application_final(F, As, Tree, St0).
 
1181
 
 
1182
visit_spawn_call({N, A}, F, Ps, [A1, A2, A3] = As, Tree,
 
1183
                 #env{spawn_funs = true} = Env, St0) ->
 
1184
    case erl_syntax:is_proper_list(A3) of
 
1185
        true ->
 
1186
            report({Env#env.file, erl_syntax:get_pos(F),
 
1187
                    "changing use of `~w/~w' to `~w/~w' with a fun."},
 
1188
                   [N, A, N, 1 + length(Ps)], Env#env.verbosity),
 
1189
            F1 = case erl_syntax:is_atom(A1, Env#env.module) of
 
1190
                     true ->
 
1191
                         A2;    % calling self
 
1192
                     false ->
 
1193
                         clone(A1,
 
1194
                               erl_syntax:module_qualifier(A1, A2))
 
1195
                 end,
 
1196
            %% Need to do some scoping tricks here to make sure the
 
1197
            %% arguments are evaluated by the parent, not by the spawned
 
1198
            %% process.
 
1199
            As1 = erl_syntax:list_elements(A3),
 
1200
            {Vs, St1} = new_variables(length(As1), St0),
 
1201
            E1 = clone(F1, erl_syntax:application(F1, Vs)),
 
1202
            C1 = clone(E1, erl_syntax:clause([], [E1])),
 
1203
            E2 = clone(C1, erl_syntax:fun_expr([C1])),
 
1204
            C2 = clone(E2, erl_syntax:clause(Vs, [], [E2])),
 
1205
            E3 = clone(C2, erl_syntax:fun_expr([C2])),
 
1206
            E4 = clone(E3, erl_syntax:application(E3, As1)),
 
1207
            E5 = erl_syntax_lib:annotate_bindings(E4, get_env(A1)),
 
1208
            {E6, St2} = visit(E5, Env, St1),
 
1209
            F2 = rewrite(F, erl_syntax:atom(N)),
 
1210
            visit_nonlocal_application(F2, Ps ++ [E6], Tree, Env, St2);
 
1211
        false ->
 
1212
            visit_application_final(F, Ps ++ As, Tree, St0)
 
1213
    end;
 
1214
visit_spawn_call(_, F, Ps, As, Tree, _Env, St0) ->
 
1215
    visit_application_final(F, Ps ++ As, Tree, St0).
 
1216
 
 
1217
visit_named_fun_application(F, As, Tree, Env, St0) ->
 
1218
    Name = erl_syntax:implicit_fun_name(F),
 
1219
    case catch {ok, erl_syntax_lib:analyze_function_name(Name)} of
 
1220
        {ok, {A, N}} when atom(A), integer(N), N == length(As) ->
 
1221
            case is_nonlocal({A, N}, Env) of
 
1222
                true ->
 
1223
                    %% Making this a direct call would be an error.
 
1224
                    visit_application_final(F, As, Tree, St0);
 
1225
                false ->
 
1226
                    report({Env#env.file, erl_syntax:get_pos(F),
 
1227
                            "changing application of implicit fun "
 
1228
                            "to direct local call."},
 
1229
                           [], Env#env.verbosity),
 
1230
                    Used = sets:add_element({A, N}, St0#st.used),
 
1231
                    F1 = rewrite(F, erl_syntax:atom(A)),
 
1232
                    revisit_application(F1, As, Tree, Env,
 
1233
                                        St0#st{used = Used})
 
1234
            end;
 
1235
        _  ->
 
1236
            visit_application_final(F, As, Tree, St0)
 
1237
    end.
 
1238
 
 
1239
visit_lambda_application(F, As, Tree, Env, St0) ->
 
1240
    A = erl_syntax:fun_expr_arity(F),
 
1241
    case A == length(As) of
 
1242
        true ->
 
1243
            report({Env#env.file, erl_syntax:get_pos(F),
 
1244
                    "changing application of fun-expression "
 
1245
                    "to local function call."},
 
1246
                   [], Env#env.verbosity),
 
1247
            {Base, _} = Env#env.current,
 
1248
            Free = [erl_syntax:variable(V) || V <- get_free_vars(F)],
 
1249
            N = length(Free),
 
1250
            A1 = A + N,
 
1251
            {Name, St1} = new_fname({Base, A1}, St0),
 
1252
            Cs = augment_clauses(erl_syntax:fun_expr_clauses(F), Free),
 
1253
            F1 = erl_syntax:atom(Name),
 
1254
            New = rewrite(F, erl_syntax:function(F1, Cs)),
 
1255
            Used = sets:add_element({Name, A1}, St1#st.used),
 
1256
            Forms = [New | St1#st.new_forms],
 
1257
            St2 = St1#st{new_forms = Forms, used = Used},
 
1258
            visit_application_final(F1, As ++ Free, Tree, St2);
 
1259
        false ->
 
1260
            warn({Env#env.file, erl_syntax:get_pos(F),
 
1261
                  "arity mismatch in fun-expression application."},
 
1262
                 [], Env#env.verbosity),
 
1263
            visit_application_final(F, As, Tree, St0)
 
1264
    end.
 
1265
 
 
1266
augment_clauses(Cs, Vs) ->
 
1267
    [begin
 
1268
         Ps = erl_syntax:clause_patterns(C),
 
1269
         G = erl_syntax:clause_guard(C),
 
1270
         Es = erl_syntax:clause_body(C),
 
1271
         rewrite(C, erl_syntax:clause(Ps ++ Vs, G, Es))
 
1272
     end
 
1273
     || C <- Cs].
 
1274
 
 
1275
visit_nonlocal_application(F, As, Tree, Env, St0) ->
 
1276
    case erl_syntax:type(F) of
 
1277
        tuple ->
 
1278
            case erl_syntax:tuple_elements(F) of
 
1279
                [X1, X2] ->
 
1280
                    report({Env#env.file, erl_syntax:get_pos(F),
 
1281
                            "changing application of 2-tuple "
 
1282
                            "to direct remote call."},
 
1283
                           [], Env#env.verbosity),
 
1284
                    F1 = erl_syntax:module_qualifier(X1, X2),
 
1285
                    revisit_application(rewrite(F, F1), As, Tree, Env,
 
1286
                                        St0);
 
1287
                _ ->
 
1288
                    visit_application_final(F, As, Tree, St0)
 
1289
            end;
 
1290
        module_qualifier ->
 
1291
            case catch {ok, erl_syntax_lib:analyze_function_name(F)} of
 
1292
                {ok, {M, N}} when atom(M), atom(N) ->
 
1293
                    visit_remote_application({M, N, length(As)}, F, As,
 
1294
                                             Tree, Env, St0);
 
1295
                _ ->
 
1296
                    visit_application_final(F, As, Tree, St0)
 
1297
            end;
 
1298
        _ ->
 
1299
            visit_application_final(F, As, Tree, St0)
 
1300
    end.
 
1301
 
 
1302
visit_remote_application({lists, append, 2}, F, [A1, A2], Tree, Env,
 
1303
                         St0) ->
 
1304
    report({Env#env.file, erl_syntax:get_pos(F),
 
1305
            "replacing call to `lists:append/2' "
 
1306
            "with the `++' operator."},
 
1307
           [], Env#env.verbosity),
 
1308
    Tree1 = erl_syntax:infix_expr(A1, erl_syntax:operator('++'), A2),
 
1309
    visit(rewrite(Tree, Tree1), Env, St0);
 
1310
visit_remote_application({lists, subtract, 2}, F, [A1, A2], Tree, Env,
 
1311
                         St0) ->
 
1312
    report({Env#env.file, erl_syntax:get_pos(F),
 
1313
            "replacing call to `lists:subtract/2' "
 
1314
            "with the `--' operator."},
 
1315
           [], Env#env.verbosity),
 
1316
    Tree1 = erl_syntax:infix_expr(A1, erl_syntax:operator('--'), A2),
 
1317
    visit(rewrite(Tree, Tree1), Env, St0);
 
1318
 
 
1319
visit_remote_application({lists, filter, 2}, F, [A1, A2] = As, Tree,
 
1320
                         Env, St0) ->
 
1321
    case Env#env.auto_list_comp
 
1322
        and (get_var_exports(A1) == [])
 
1323
        and (get_var_exports(A2) == []) of
 
1324
        true ->
 
1325
            report({Env#env.file, erl_syntax:get_pos(F),
 
1326
                    "replacing call to `lists:filter/2' "
 
1327
                    "with a list comprehension."},
 
1328
                   [], Env#env.verbosity),
 
1329
            {V, St1} = new_variable(St0),
 
1330
            G = clone(A2, erl_syntax:generator(V, A2)),
 
1331
            T = clone(A1, erl_syntax:application(A1, [V])),
 
1332
            L = erl_syntax:list_comp(V, [G, T]),
 
1333
            L1 = erl_syntax_lib:annotate_bindings(L, get_env(Tree)),
 
1334
            visit(rewrite(Tree, L1), Env, St1);
 
1335
        false ->
 
1336
            visit_application_final(F, As, Tree, St0)
 
1337
    end;
 
1338
visit_remote_application({lists, map, 2}, F, [A1, A2] = As, Tree, Env,
 
1339
                         St0) ->
 
1340
    case Env#env.auto_list_comp
 
1341
        and (get_var_exports(A1) == [])
 
1342
        and (get_var_exports(A2) == []) of
 
1343
        true ->
 
1344
            report({Env#env.file, erl_syntax:get_pos(F),
 
1345
                    "replacing call to `lists:map/2' "
 
1346
                    "with a list comprehension."},
 
1347
                   [], Env#env.verbosity),
 
1348
            {V, St1} = new_variable(St0),
 
1349
            T = clone(A1, erl_syntax:application(A1, [V])),
 
1350
            G = clone(A2, erl_syntax:generator(V, A2)),
 
1351
            L = erl_syntax:list_comp(T, [G]),
 
1352
            L1 = erl_syntax_lib:annotate_bindings(L, get_env(Tree)),
 
1353
            visit(rewrite(Tree, L1), Env, St1);
 
1354
        false ->
 
1355
            visit_application_final(F, As, Tree, St0)
 
1356
    end;
 
1357
visit_remote_application({M, N, A} = Name, F, As, Tree, Env, St) ->
 
1358
    case is_auto_imported(Name) of
 
1359
        true ->
 
1360
            %% We don't remove the qualifier - it might be there for the
 
1361
            %% sake of clarity.
 
1362
            visit_bif_call({N, A}, F, As, Tree, Env, St);
 
1363
        false ->
 
1364
            case rename_remote_call(Name, St) of
 
1365
                {M1, N1} ->
 
1366
                    report({Env#env.file, erl_syntax:get_pos(F),
 
1367
                            "updating obsolete call to `~w:~w/~w' "
 
1368
                            "to use `~w:~w/~w' instead."},
 
1369
                           [M, N, A, M1, N1, A], Env#env.verbosity),
 
1370
                    M2 = erl_syntax:atom(M1),
 
1371
                    N2 = erl_syntax:atom(N1),
 
1372
                    F1 = erl_syntax:module_qualifier(M2, N2),
 
1373
                    revisit_application(rewrite(F, F1), As, Tree, Env,
 
1374
                                        St);
 
1375
                false ->
 
1376
                    visit_application_final(F, As, Tree, St)
 
1377
            end
 
1378
    end.
 
1379
 
 
1380
auto_expand_import({lists, append, 2}, _St) -> true;
 
1381
auto_expand_import({lists, filter, 2}, _St) -> true;
 
1382
auto_expand_import({lists, map, 2}, _St) -> true;
 
1383
auto_expand_import(Name, St) ->
 
1384
    case is_auto_imported(Name) of
 
1385
        true ->
 
1386
            true;
 
1387
        false ->
 
1388
            case rename_remote_call(Name, St) of
 
1389
                false ->
 
1390
                    false;
 
1391
                _ ->
 
1392
                    true
 
1393
            end
 
1394
    end.
 
1395
 
 
1396
visit_list_comp(Tree, Env, St0) ->
 
1397
    Es = erl_syntax:list_comp_body(Tree),
 
1398
    {Es1, St1} = visit_list_comp_body(Es, Env, St0),
 
1399
    {T, St2} = visit(erl_syntax:list_comp_template(Tree), Env, St1),
 
1400
    {rewrite(Tree, erl_syntax:list_comp(T, Es1)), St2}.
 
1401
 
 
1402
visit_list_comp_body_join(Env) ->
 
1403
    fun (E, St0) ->
 
1404
            case is_generator(E) of
 
1405
                true ->
 
1406
                    visit_generator(E, Env, St0);
 
1407
                false ->
 
1408
                    visit_filter(E, Env, St0)
 
1409
            end
 
1410
    end.
 
1411
 
 
1412
visit_list_comp_body(Es, Env, St0) ->
 
1413
    lists:mapfoldl(visit_list_comp_body_join(Env), St0, Es).
 
1414
 
 
1415
%% 'visit_filter' also handles uninteresting generators.
 
1416
 
 
1417
visit_filter(E, Env, St0) ->
 
1418
    visit(E, Env, St0).
 
1419
 
 
1420
%% "interesting" generators have the form V <- [V || ...]; this can be
 
1421
%% unfolded as long as no bindings become erroneously shadowed.
 
1422
 
 
1423
visit_generator(G, Env, St0) ->
 
1424
    P = erl_syntax:generator_pattern(G),
 
1425
    case erl_syntax:type(P) of
 
1426
        variable ->
 
1427
            B = erl_syntax:generator_body(G),
 
1428
            case erl_syntax:type(B) of
 
1429
                list_comp ->
 
1430
                    T = erl_syntax:list_comp_template(B),
 
1431
                    case erl_syntax:type(T) of
 
1432
                        variable ->
 
1433
                            visit_generator_1(G, Env, St0);
 
1434
                        _ ->
 
1435
                            visit_filter(G, Env, St0)
 
1436
                    end;
 
1437
                _ ->
 
1438
                    visit_filter(G, Env, St0)
 
1439
            end;
 
1440
        _ ->
 
1441
            visit_filter(G, Env, St0)
 
1442
    end.
 
1443
 
 
1444
visit_generator_1(G, Env, St0) ->
 
1445
    recommend({Env#env.file, erl_syntax:get_pos(G),
 
1446
               "unfold that this nested list comprehension can be unfolded "
 
1447
               "by hand to get better efficiency."},
 
1448
              [], Env#env.verbosity),
 
1449
    visit_filter(G, Env, St0).
 
1450
 
 
1451
visit_match_expr(Tree, Env, St0) ->
 
1452
    %% We do not visit the pattern (for now, anyway).
 
1453
    P = erl_syntax:match_expr_pattern(Tree),
 
1454
    {B, St1} = visit(erl_syntax:match_expr_body(Tree), Env, St0),
 
1455
    case erl_syntax:type(P) of
 
1456
        tuple ->
 
1457
            Ps = erl_syntax:tuple_elements(P),
 
1458
            case lists:all(fun is_variable/1, Ps) of
 
1459
                true ->
 
1460
                    Vs = lists:sort([erl_syntax:variable_name(X)
 
1461
                                     || X <- Ps]),
 
1462
                    case ordsets:is_set(Vs) of
 
1463
                        true ->
 
1464
                            Xs = get_var_exports(B),
 
1465
                            case ordsets:intersection(Vs, Xs) of
 
1466
                                [] ->
 
1467
                                    visit_match_body(Ps, P, B, Tree,
 
1468
                                                     Env, St1);
 
1469
                                _ ->
 
1470
                                    visit_match_expr_final(P, B, Tree,
 
1471
                                                           Env, St1)
 
1472
                            end;
 
1473
                        false ->
 
1474
                            visit_match_expr_final(P, B, Tree, Env, St1)
 
1475
                    end;
 
1476
                false ->
 
1477
                    visit_match_expr_final(P, B, Tree, Env, St1)
 
1478
            end;
 
1479
        _  ->
 
1480
            visit_match_expr_final(P, B, Tree, Env, St1)
 
1481
    end.
 
1482
 
 
1483
visit_match_expr_final(P, B, Tree, _Env, St0) ->
 
1484
    {rewrite(Tree, erl_syntax:match_expr(P, B)), St0}.
 
1485
 
 
1486
visit_match_body(_Ps, P, B, Tree, #env{auto_export_vars = false} = Env,
 
1487
                 St0) ->
 
1488
    visit_match_expr_final(P, B, Tree, Env, St0);
 
1489
visit_match_body(Ps, P, B, Tree, Env, St0) ->
 
1490
    case erl_syntax:type(B) of
 
1491
        case_expr ->
 
1492
            Cs = erl_syntax:case_expr_clauses(B),
 
1493
            case multival_clauses(Cs, length(Ps), Ps) of
 
1494
                {true, Cs1} ->
 
1495
                    report_export_vars(Env#env.file,
 
1496
                                       erl_syntax:get_pos(B),
 
1497
                                       "case", Env#env.verbosity),
 
1498
                    A = erl_syntax:case_expr_argument(B),
 
1499
                    Tree1 = erl_syntax:case_expr(A, Cs1),
 
1500
                    {rewrite(Tree, Tree1), St0};
 
1501
                false ->
 
1502
                    visit_match_expr_final(P, B, Tree, Env, St0)
 
1503
            end;
 
1504
        if_expr ->
 
1505
            Cs = erl_syntax:if_expr_clauses(B),
 
1506
            case multival_clauses(Cs, length(Ps), Ps) of
 
1507
                {true, Cs1} ->
 
1508
                    report_export_vars(Env#env.file,
 
1509
                                       erl_syntax:get_pos(B),
 
1510
                                       "if", Env#env.verbosity),
 
1511
                    Tree1 = erl_syntax:if_expr(Cs1),
 
1512
                    {rewrite(Tree, Tree1), St0};
 
1513
                false ->
 
1514
                    visit_match_expr_final(P, B, Tree, Env, St0)
 
1515
            end;
 
1516
        cond_expr ->
 
1517
            Cs = erl_syntax:cond_expr_clauses(B),
 
1518
            case multival_clauses(Cs, length(Ps), Ps) of
 
1519
                {true, Cs1} ->
 
1520
                    report_export_vars(Env#env.file,
 
1521
                                       erl_syntax:get_pos(B),
 
1522
                                       "cond", Env#env.verbosity),
 
1523
                    Tree1 = erl_syntax:cond_expr(Cs1),
 
1524
                    {rewrite(Tree, Tree1), St0};
 
1525
                false ->
 
1526
                    visit_match_expr_final(P, B, Tree, Env, St0)
 
1527
            end;
 
1528
        receive_expr ->
 
1529
            %% Handle the timeout case as an extra clause.
 
1530
            As = erl_syntax:receive_expr_action(B),
 
1531
            C = erl_syntax:clause([], As),
 
1532
            Cs = erl_syntax:receive_expr_clauses(B),
 
1533
            case multival_clauses([C | Cs], length(Ps), Ps) of
 
1534
                {true, [C1 | Cs1]} ->
 
1535
                    report_export_vars(Env#env.file,
 
1536
                                       erl_syntax:get_pos(B),
 
1537
                                       "receive", Env#env.verbosity),
 
1538
                    T = erl_syntax:receive_expr_timeout(B),
 
1539
                    As1 = erl_syntax:clause_body(C1),
 
1540
                    Tree1 = erl_syntax:receive_expr(Cs1, T, As1),
 
1541
                    {rewrite(Tree, Tree1), St0};
 
1542
                false ->
 
1543
                    visit_match_expr_final(P, B, Tree, Env, St0)
 
1544
            end;
 
1545
        _ ->
 
1546
            visit_match_expr_final(P, B, Tree, Env, St0)
 
1547
    end.
 
1548
 
 
1549
multival_clauses(Cs, N, Vs) ->
 
1550
    multival_clauses(Cs, N, Vs, []).
 
1551
 
 
1552
multival_clauses([C | Cs], N, Vs, Cs1) ->
 
1553
    case erl_syntax:clause_body(C) of
 
1554
        [] ->
 
1555
            false;
 
1556
        Es ->
 
1557
            E = lists:last(Es),
 
1558
            case erl_syntax:type(E) of
 
1559
                tuple ->
 
1560
                    Ts = erl_syntax:tuple_elements(E),
 
1561
                    if length(Ts) == N ->
 
1562
                            Bs = make_matches(E, Vs, Ts),
 
1563
                            Es1 = replace_last(Es, Bs),
 
1564
                            Ps = erl_syntax:clause_patterns(C),
 
1565
                            G = erl_syntax:clause_guard(C),
 
1566
                            C1 = erl_syntax:clause(Ps, G, Es1),
 
1567
                            multival_clauses(Cs, N, Vs,
 
1568
                                             [rewrite(C, C1) | Cs1]);
 
1569
                       true ->
 
1570
                            false
 
1571
                    end;
 
1572
                _ ->
 
1573
                    case erl_syntax_lib:is_fail_expr(E) of
 
1574
                        true ->
 
1575
                            %% We must add dummy bindings here so we
 
1576
                            %% don't introduce compilation errors due to
 
1577
                            %% "unsafe" variable exports.
 
1578
                            Bs = make_matches(Vs,
 
1579
                                              erl_syntax:atom(false)),
 
1580
                            Es1 = replace_last(Es, Bs ++ [E]),
 
1581
                            Ps = erl_syntax:clause_patterns(C),
 
1582
                            G = erl_syntax:clause_guard(C),
 
1583
                            C1 = erl_syntax:clause(Ps, G, Es1),
 
1584
                            multival_clauses(Cs, N, Vs,
 
1585
                                             [rewrite(C, C1) | Cs1]);
 
1586
                        false ->
 
1587
                            false
 
1588
                    end
 
1589
            end
 
1590
    end;
 
1591
multival_clauses([], _N, _Vs, Cs) ->
 
1592
    {true, lists:reverse(Cs)}.
 
1593
 
 
1594
make_matches(E, Vs, Ts) ->
 
1595
    case make_matches(Vs, Ts) of
 
1596
        [] ->
 
1597
            [];
 
1598
        [B | Bs] ->
 
1599
            [rewrite(E, B) | Bs]    % preserve comments on E (but not B)
 
1600
    end.
 
1601
 
 
1602
make_matches([V | Vs], [T | Ts]) ->
 
1603
    [erl_syntax:match_expr(V, T) | make_matches(Vs, Ts)];
 
1604
make_matches([V | Vs], T) when T /= [] ->
 
1605
    [erl_syntax:match_expr(V, T) | make_matches(Vs, T)];
 
1606
make_matches([], _) ->
 
1607
    [].
 
1608
 
 
1609
rename_remote_call(F, St) ->
 
1610
    case dict:find(F, St#st.rename) of
 
1611
        error ->
 
1612
            rename_remote_call_1(F);
 
1613
        {ok, F1} -> F1
 
1614
    end.
 
1615
 
 
1616
rename_remote_call_1({dict, dict_to_list, 1}) -> {dict, to_list};
 
1617
rename_remote_call_1({dict, list_to_dict, 1}) -> {dict, from_list};
 
1618
rename_remote_call_1({erl_eval, arg_list, 2}) -> {erl_eval, expr_list};
 
1619
rename_remote_call_1({erl_eval, arg_list, 3}) -> {erl_eval, expr_list};
 
1620
rename_remote_call_1({erl_eval, seq, 2}) -> {erl_eval, exprs};
 
1621
rename_remote_call_1({erl_eval, seq, 3}) -> {erl_eval, exprs};
 
1622
rename_remote_call_1({erl_pp, seq, 1}) -> {erl_eval, seq};
 
1623
rename_remote_call_1({erl_pp, seq, 2}) -> {erl_eval, seq};
 
1624
rename_remote_call_1({erlang, info, 1}) -> {erlang, system_info};
 
1625
rename_remote_call_1({io, parse_erl_seq, 1}) -> {io, parse_erl_exprs};
 
1626
rename_remote_call_1({io, parse_erl_seq, 2}) -> {io, parse_erl_exprs};
 
1627
rename_remote_call_1({io, parse_erl_seq, 3}) -> {io, parse_erl_exprs};
 
1628
rename_remote_call_1({io, scan_erl_seq, 1}) -> {io, scan_erl_exprs};
 
1629
rename_remote_call_1({io, scan_erl_seq, 2}) -> {io, scan_erl_exprs};
 
1630
rename_remote_call_1({io, scan_erl_seq, 3}) -> {io, scan_erl_exprs};
 
1631
rename_remote_call_1({io_lib, reserved_word, 1}) -> {erl_scan, reserved_word};
 
1632
rename_remote_call_1({io_lib, scan, 1}) -> {erl_scan, string};
 
1633
rename_remote_call_1({io_lib, scan, 2}) -> {erl_scan, string};
 
1634
rename_remote_call_1({io_lib, scan, 3}) -> {erl_scan, tokens};
 
1635
rename_remote_call_1({orddict, dict_to_list, 1}) -> {orddict, to_list};
 
1636
rename_remote_call_1({orddict, list_to_dict, 1}) -> {orddict, from_list};
 
1637
rename_remote_call_1({ordsets, list_to_set, 1}) -> {ordsets, from_list};
 
1638
rename_remote_call_1({ordsets, new_set, 0}) -> {ordsets, new};
 
1639
rename_remote_call_1({ordsets, set_to_list, 1}) -> {ordsets, to_list};
 
1640
rename_remote_call_1({ordsets, subset, 2}) -> {ordsets, is_subset};
 
1641
rename_remote_call_1({sets, list_to_set, 1}) -> {sets, from_list};
 
1642
rename_remote_call_1({sets, new_set, 0}) -> {sets, new};
 
1643
rename_remote_call_1({sets, set_to_list, 1}) -> {sets, to_list};
 
1644
rename_remote_call_1({sets, subset, 2}) -> {sets, is_subset};
 
1645
rename_remote_call_1({string, index, 2}) -> {string, str};
 
1646
rename_remote_call_1({unix, cmd, 1}) -> {os, cmd};
 
1647
rename_remote_call_1(_) -> false.
 
1648
 
 
1649
rewrite_guard_test(atom, 1) -> is_atom;
 
1650
rewrite_guard_test(binary, 1) -> is_binary;
 
1651
rewrite_guard_test(constant, 1) -> is_constant;
 
1652
rewrite_guard_test(float, 1) -> is_float;
 
1653
rewrite_guard_test(function, 1) -> is_function;
 
1654
rewrite_guard_test(integer, 1) -> is_integer;
 
1655
rewrite_guard_test(list, 1) -> is_list;
 
1656
rewrite_guard_test(number, 1) -> is_number;
 
1657
rewrite_guard_test(pid, 1) -> is_pid;
 
1658
rewrite_guard_test(port, 1) -> is_port;
 
1659
rewrite_guard_test(reference, 1) -> is_reference;
 
1660
rewrite_guard_test(tuple, 1) -> is_tuple;
 
1661
rewrite_guard_test(record, 2) -> is_record;
 
1662
rewrite_guard_test(N, _A) -> N.
 
1663
 
 
1664
reverse_guard_test(is_atom, 1) -> atom;
 
1665
reverse_guard_test(is_binary, 1) -> binary;
 
1666
reverse_guard_test(is_constant, 1) -> constant;
 
1667
reverse_guard_test(is_float, 1) -> float;
 
1668
reverse_guard_test(is_function, 1) -> function;
 
1669
reverse_guard_test(is_integer, 1) -> integer;
 
1670
reverse_guard_test(is_list, 1) -> list;
 
1671
reverse_guard_test(is_number, 1) -> number;
 
1672
reverse_guard_test(is_pid, 1) -> pid;
 
1673
reverse_guard_test(is_port, 1) -> port;
 
1674
reverse_guard_test(is_reference, 1) -> reference;
 
1675
reverse_guard_test(is_tuple, 1) -> tuple;
 
1676
reverse_guard_test(is_record, 2) -> record;
 
1677
reverse_guard_test(N, _A) -> N.
 
1678
 
 
1679
 
 
1680
%% =====================================================================
 
1681
%% Utility functions
 
1682
 
 
1683
is_remote_name({M,F,A}) when atom(M), atom(F), integer(A) -> true;
 
1684
is_remote_name(_) -> false.
 
1685
 
 
1686
is_atom_pair({M,F}) when atom(M), atom(F) -> true;
 
1687
is_atom_pair(_) -> false.
 
1688
 
 
1689
replace_last([_E], Xs) ->
 
1690
    Xs;
 
1691
replace_last([E | Es], Xs) ->
 
1692
    [E | replace_last(Es, Xs)].
 
1693
 
 
1694
is_generator(E) ->
 
1695
    erl_syntax:type(E) == generator.
 
1696
 
 
1697
is_variable(E) ->
 
1698
    erl_syntax:type(E) == variable.
 
1699
 
 
1700
new_variables(N, St0) when N > 0 ->
 
1701
    {V, St1} = new_variable(St0),
 
1702
    {Vs, St2} = new_variables(N - 1, St1),
 
1703
    {[V | Vs], St2};
 
1704
new_variables(0, St) ->
 
1705
    {[], St}.
 
1706
 
 
1707
new_variable(St0) ->
 
1708
    Fun = fun (N) ->
 
1709
                  list_to_atom("V" ++ integer_to_list(N))
 
1710
          end,
 
1711
    Vs = St0#st.vars,
 
1712
    {Name, N} = new_name(St0#st.varc, Fun, Vs),
 
1713
    St1 = St0#st{varc = N + 1, vars = sets:add_element(Name, Vs)},
 
1714
    {erl_syntax:variable(Name), St1}.
 
1715
 
 
1716
new_fname({F, A}, St0) ->
 
1717
    Base = atom_to_list(F),
 
1718
    Fun = fun (N) ->
 
1719
                  {list_to_atom(Base ++ "_" ++ integer_to_list(N)), A}
 
1720
          end,
 
1721
    Fs = St0#st.functions,
 
1722
    {{F1, _A} = Name, _N} = new_name(1, Fun, Fs),
 
1723
    {F1, St0#st{functions = sets:add_element(Name, Fs)}}.
 
1724
 
 
1725
new_name(N, F, Set) ->
 
1726
    Name = F(N),
 
1727
    case sets:is_element(Name, Set) of
 
1728
        true ->
 
1729
            new_name(N + 1, F, Set);
 
1730
        false ->
 
1731
            {Name, N}
 
1732
    end.
 
1733
 
 
1734
is_imported(F, Env) ->
 
1735
    dict:is_key(F, Env#env.imports).
 
1736
 
 
1737
is_auto_imported({erlang, N, A}) ->
 
1738
    is_auto_imported({N, A});
 
1739
is_auto_imported({_, _N, _A}) ->
 
1740
    false;
 
1741
is_auto_imported({N, A}) ->
 
1742
    erl_internal:bif(N, A).
 
1743
 
 
1744
is_nonlocal(N, Env) ->
 
1745
    case is_imported(N, Env) of
 
1746
        true ->
 
1747
            true;
 
1748
        false ->
 
1749
            is_auto_imported(N)
 
1750
    end.
 
1751
 
 
1752
get_var_exports(Node) ->
 
1753
    get_var_exports_1(erl_syntax:get_ann(Node)).
 
1754
 
 
1755
get_var_exports_1([{bound, B} | _Bs]) -> B;
 
1756
get_var_exports_1([_ | Bs]) -> get_var_exports_1(Bs);
 
1757
get_var_exports_1([]) -> [].
 
1758
 
 
1759
get_free_vars(Node) ->
 
1760
    get_free_vars_1(erl_syntax:get_ann(Node)).
 
1761
 
 
1762
get_free_vars_1([{free, B} | _Bs]) -> B;
 
1763
get_free_vars_1([_ | Bs]) -> get_free_vars_1(Bs);
 
1764
get_free_vars_1([]) -> [].
 
1765
 
 
1766
filename([C | T]) when integer(C), C > 0, C =< 255 ->
 
1767
    [C | filename(T)];
 
1768
filename([H|T]) ->
 
1769
    filename(H) ++ filename(T);
 
1770
filename([]) ->
 
1771
    [];
 
1772
filename(N) when atom(N) ->
 
1773
    atom_to_list(N);
 
1774
filename(N) ->
 
1775
    report_error("bad filename: `~P'.", [N, 25]),
 
1776
    exit(error).
 
1777
 
 
1778
get_env(Tree) ->
 
1779
    case lists:keysearch(env, 1, erl_syntax:get_ann(Tree)) of
 
1780
        {value, {env, Env}} ->
 
1781
            Env;
 
1782
        _ ->
 
1783
            []
 
1784
    end.
 
1785
 
 
1786
rewrite(Source, Target) ->
 
1787
    erl_syntax:copy_attrs(Source, Target).
 
1788
 
 
1789
clone(Source, Target) ->
 
1790
    erl_syntax:copy_pos(Source, Target).
 
1791
 
 
1792
 
 
1793
%% =====================================================================
 
1794
%% Reporting
 
1795
 
 
1796
report_export_vars(F, L, Type, Opts) ->
 
1797
    report({F, L, "rewrote ~s-expression to export variables."},
 
1798
           [Type], Opts).
 
1799
 
 
1800
error_read_file(Name) ->
 
1801
    report_error("error reading file `~s'.", [filename(Name)]).
 
1802
 
 
1803
error_write_file(Name) ->
 
1804
    report_error("error writing to file `~s'.", [filename(Name)]).
 
1805
 
 
1806
error_backup_file(Name) ->
 
1807
    report_error("could not create backup of file `~s'.",
 
1808
                 [filename(Name)]).
 
1809
 
 
1810
error_open_output(Name) ->
 
1811
    report_error("cannot open file `~s' for output.", [filename(Name)]).
 
1812
 
 
1813
verbosity(Opts) ->
 
1814
    case proplists:get_bool(quiet, Opts) of 
 
1815
        true -> 0;
 
1816
        false ->
 
1817
            case proplists:get_value(verbose, Opts) of
 
1818
                true -> 2;
 
1819
                N when integer(N) -> N; 
 
1820
                _ -> 1
 
1821
            end
 
1822
    end.
 
1823
 
 
1824
report_error(D) ->
 
1825
    report_error(D, []).
 
1826
    
 
1827
report_error({F, L, D}, Vs) ->
 
1828
    report({F, L, {error, D}}, Vs);
 
1829
report_error(D, Vs) ->
 
1830
    report({error, D}, Vs).
 
1831
 
 
1832
% warn(D, N) ->
 
1833
%     warn(D, [], N).
 
1834
 
 
1835
warn({F, L, D}, Vs, N) ->
 
1836
    report({F, L, {warning, D}}, Vs, N);
 
1837
warn(D, Vs, N) ->
 
1838
    report({warning, D}, Vs, N).
 
1839
 
 
1840
recommend(D, Vs, N) ->
 
1841
    report({recommend, D}, Vs, N).
 
1842
 
 
1843
verbose(D, Vs, N) ->
 
1844
    report(2, D, Vs, N).
 
1845
 
 
1846
report(D, Vs) ->
 
1847
    report(D, Vs, 1).
 
1848
 
 
1849
report(D, Vs, N) ->
 
1850
    report(1, D, Vs, N).
 
1851
 
 
1852
report(Level, _D, _Vs, N) when integer(N), N < Level ->
 
1853
    ok;
 
1854
report(_Level, D, Vs, N) when integer(N) ->
 
1855
    io:put_chars(format(D, Vs));
 
1856
report(Level, D, Vs, Options) when list(Options) ->
 
1857
    report(Level, D, Vs, verbosity(Options)).
 
1858
 
 
1859
format({error, D}, Vs) ->
 
1860
    ["error: ", format(D, Vs)];
 
1861
format({warning, D}, Vs) ->
 
1862
    ["warning: ", format(D, Vs)];
 
1863
format({recommend, D}, Vs) ->
 
1864
    ["recommendation: ", format(D, Vs)];
 
1865
format({"", L, D}, Vs) when integer(L), L > 0 ->
 
1866
    [io_lib:fwrite("~w: ", [L]), format(D, Vs)];
 
1867
format({"", _L, D}, Vs) ->
 
1868
    format(D, Vs);
 
1869
format({F, L, D}, Vs) when integer(L), L > 0 ->
 
1870
    [io_lib:fwrite("~s:~w: ", [filename(F), L]), format(D, Vs)];
 
1871
format({F, _L, D}, Vs) ->
 
1872
    [io_lib:fwrite("~s: ", [filename(F)]), format(D, Vs)];
 
1873
format(S, Vs) when list(S) ->
 
1874
    [io_lib:fwrite(S, Vs), $\n].
 
1875
 
 
1876
 
 
1877
%% =====================================================================