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

« back to all changes in this revision

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

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

Show diffs side-by-side

added added

removed removed

Lines of Context:
49
49
-define(DEFAULT_DIR, "").
50
50
-define(DEFAULT_REGEXP, ".*\\.erl$").
51
51
 
 
52
%% =====================================================================
 
53
 
 
54
-type filename() :: string().
 
55
-type options()  :: [atom() | {atom(), any()}].
 
56
 
 
57
%% =====================================================================
52
58
 
53
59
dir__defaults() ->
54
60
    [{follow_links, false},
60
66
%% @spec dir() -> ok
61
67
%% @equiv dir("")
62
68
 
 
69
-spec dir() -> 'ok'.
63
70
dir() ->
64
71
    dir("").
65
72
 
67
74
%% @spec dir(Dir) -> ok
68
75
%% @equiv dir(Dir, [])
69
76
 
 
77
-spec dir(filename()) -> 'ok'.
70
78
dir(Dir) ->
71
79
    dir(Dir, []).
72
80
 
118
126
%% @see //stdlib/regexp
119
127
%% @see file/2
120
128
 
121
 
-record(dir, {follow_links = false, recursive = true, options}).
 
129
-record(dir, {follow_links = false :: bool(),
 
130
              recursive    = true  :: bool(),
 
131
              options              :: options()}).
122
132
 
 
133
-spec dir(filename(), options()) -> 'ok'.
123
134
dir(Dir, Opts) ->
124
135
    Opts1 = Opts ++ dir__defaults(),
125
136
    Env = #dir{follow_links = proplists:get_bool(follow_links, Opts1),
202
213
%% @spec file(Name) -> ok
203
214
%% @equiv file(Name, [])
204
215
 
 
216
-spec file(filename()) -> 'ok'.
205
217
file(Name) ->
206
218
    file(Name, []).
207
219
 
253
265
%%
254
266
%%   <dt>{test, bool()}</dt>
255
267
%%
256
 
%%       <dd>If the value is `true', no files will be
257
 
%%       modified; this is typically most useful if the
258
 
%%       `verbose' flag is enabled, to generate reports
259
 
%%       about the program files without affecting them. The default
260
 
%%       value is `false'.</dd>
 
268
%%       <dd>If the value is `true', no files will be modified; this
 
269
%%       is typically most useful if the `verbose' flag is enabled, to
 
270
%%       generate reports about the program files without affecting
 
271
%%       them. The default value is `false'.</dd>
261
272
%% </dl>
262
273
%%
263
274
%% See the function `module/2' for further options.
265
276
%% @see erl_prettypr:format/2
266
277
%% @see module/2
267
278
 
 
279
-spec file(filename(), options()) -> 'ok'.
268
280
file(Name, Opts) ->
269
281
    Parent = self(),
270
282
    Child = spawn_link(fun () -> file_1(Parent, Name, Opts) end),
276
288
    end.
277
289
 
278
290
file_1(Parent, Name, Opts) ->
279
 
    case catch file_2(Name, Opts) of
280
 
        {'EXIT', Reason} ->
281
 
            Parent ! {self(), {error, Reason}};
282
 
        _ ->
283
 
            Parent ! {self(), ok}
 
291
    try file_2(Name, Opts) of
 
292
        _ ->
 
293
            Parent ! {self(), ok}
 
294
    catch
 
295
        throw:syntax_error ->       % ignore syntax errors
 
296
            Parent ! {self(), ok};
 
297
        error:Reason ->
 
298
            Parent ! {self(), {error, Reason}}
284
299
    end.
285
300
 
286
301
file_2(Name, Opts) ->
299
314
 
300
315
read_module(Name, Opts) ->
301
316
    verbose("reading module `~s'.", [filename(Name)], Opts),
302
 
    case epp_dodger:parse_file(Name) of
 
317
    case epp_dodger:parse_file(Name, [no_fail]) of
303
318
        {ok, Forms} ->
304
319
            check_forms(Forms, Name),
305
320
            Forms;
483
498
%% definition. The given `Forms' may be either a single
484
499
%% syntax tree of type `form_list', or a list of syntax
485
500
%% trees representing "program forms". In either case,
486
 
%% `Forms' must represents a single complete module
 
501
%% `Forms' must represent a single complete module
487
502
%% definition. The returned syntax tree has type
488
503
%% `form_list' and represents a tidied-up version of the
489
504
%% same source code.
516
531
%%
517
532
%%   <dt>{auto_list_comp, bool()}</dt>
518
533
%%
519
 
%%       <dd>If the value is `true', calls to
520
 
%%       `lists:map/2' and `lists:filter/2' will
521
 
%%       be rewritten using list comprehensions. The default value is
522
 
%%       `true'.</dd>
 
534
%%       <dd>If the value is `true', calls to `lists:map/2' and
 
535
%%       `lists:filter/2' will be rewritten using list comprehensions.
 
536
%%       The default value is `true'.</dd>
523
537
%%
524
538
%%   <dt>{file, string()}</dt>
525
539
%%
529
543
%%
530
544
%%   <dt>{idem, bool()}</dt>
531
545
%%
532
 
%%       <dd>If the value is `true', all options that affect
533
 
%%       how the code is modified are set to "no changes". For example,
534
 
%%       to only update guard tests, and nothing else, use the options
535
 
%%       `[new_guard_tests, idem]'. (Recall that options
536
 
%%       closer to the beginning of the list have higher
537
 
%%       precedence.)</dd>
 
546
%%       <dd>If the value is `true', all options that affect how the
 
547
%%       code is modified are set to "no changes". For example, to
 
548
%%       only update guard tests, and nothing else, use the options
 
549
%%       `[new_guard_tests, idem]'. (Recall that options closer to the
 
550
%%       beginning of the list have higher precedence.)</dd>
538
551
%%
539
552
%%   <dt>{keep_unused, bool()}</dt>
540
553
%%
544
557
%%
545
558
%%   <dt>{new_guard_tests, bool()}</dt>
546
559
%%
547
 
%%       <dd>If the value is `true', guard tests will be
548
 
%%       updated to use the new names, e.g. "`is_integer(X)'"
549
 
%%       instead of "`integer(X)'". The default value is
550
 
%%       `true'. See also `old_guard_tests'.</dd>
 
560
%%       <dd>If the value is `true', guard tests will be updated to
 
561
%%       use the new names, e.g. "`is_integer(X)'" instead of
 
562
%%       "`integer(X)'". The default value is `true'. See also
 
563
%%       `old_guard_tests'.</dd>
551
564
%%
552
565
%%   <dt>{no_imports, bool()}</dt>
553
566
%%
554
 
%%       <dd>If the value is `true', all import statements
555
 
%%       will be removed and calls to imported functions will be
556
 
%%       expanded to explicit remote calls. The default value is
557
 
%%       `false'.</dd>
 
567
%%       <dd>If the value is `true', all import statements will be
 
568
%%       removed and calls to imported functions will be expanded to
 
569
%%       explicit remote calls. The default value is `false'.</dd>
558
570
%%
559
571
%%   <dt>{old_guard_tests, bool()}</dt>
560
572
%%
561
 
%%       <dd>If the value is `true', guard tests will be
562
 
%%       changed to use the old names instead of the new ones,
563
 
%%       e.g. "`integer(X)'" instead of
564
 
%%       "`is_integer(X)'". The default value is
565
 
%%       `false'. This option overrides the
566
 
%%       `new_guard_tests' option.</dd>
 
573
%%       <dd>If the value is `true', guard tests will be changed to
 
574
%%       use the old names instead of the new ones, e.g.
 
575
%%       "`integer(X)'" instead of "`is_integer(X)'". The default
 
576
%%       value is `false'. This option overrides the `new_guard_tests'
 
577
%%       option.</dd>
567
578
%%
568
579
%%   <dt>{quiet, bool()}</dt>
569
580
%%
575
586
%%                  {atom(), atom()}}]}</dt>
576
587
%%
577
588
%%       <dd>The value is a list of pairs, associating tuples
578
 
%%       `{Module, Name, Arity}' with tuples
579
 
%%       `{NewModule, NewName}', specifying renamings of
580
 
%%       calls to remote functions. By default, the value is the empty
581
 
%%       list.
 
589
%%       `{Module, Name, Arity}' with tuples `{NewModule, NewName}',
 
590
%%       specifying renamings of calls to remote functions. By
 
591
%%       default, the value is the empty list.
582
592
%%
583
593
%%       The renaming affects only remote calls (also when
584
594
%%       disguised by import declarations); local calls within a
595
605
%%
596
606
%%   <dt>{verbose, bool()}</dt>
597
607
%%
598
 
%%       <dd>If the value is `true', progress messages
599
 
%%       will be output while the program is running, unless the
600
 
%%       `quiet' option is `true'. The default
601
 
%%       value is `false'.</dd>
 
608
%%       <dd>If the value is `true', progress messages will be output
 
609
%%       while the program is running, unless the `quiet' option is
 
610
%%       `true'. The default value is `false'.</dd>
602
611
%%
603
612
%% </dl>
604
613
 
654
663
            L1;
655
664
        syntax_error ->
656
665
            report_error({File, 0, "syntax error."}),
657
 
            erlang:error(badarg);
 
666
            throw(syntax_error);
658
667
        {'EXIT', R} ->
659
668
            exit(R);
660
669
        R ->
661
670
            throw(R)
662
671
    end.
663
672
 
 
673
%% XXX: The following should be imported from erl_syntax_lib
 
674
-type key()       :: atom().
 
675
-type info_pair() :: {key(), any()}.
 
676
 
 
677
-spec get_module_name([info_pair()], string()) -> atom().
664
678
get_module_name(List, File) ->
665
679
    case lists:keysearch(module, 1, List) of
666
680
        {value, {module, M}} ->
679
693
            []
680
694
    end.
681
695
 
 
696
-spec get_module_exports([info_pair()]) -> [{atom(), byte()}].
682
697
get_module_exports(List) ->
683
698
    case lists:keysearch(exports, 1, List) of
684
699
        {value, {exports, Es}} ->
687
702
            []
688
703
    end.
689
704
 
 
705
-spec get_module_imports([info_pair()]) -> [{atom(), atom()}].
690
706
get_module_imports(List) ->
691
707
    case lists:keysearch(imports, 1, List) of
692
708
        {value, {imports, Is}} ->
699
715
    lists:append([if is_list(T) -> T; true -> [T] end
700
716
                  || {compile, T} <- As]).
701
717
 
 
718
-spec flatten_imports([{atom(), [atom()]}]) -> [{atom(), atom()}].
702
719
flatten_imports(Is) ->
703
720
    [{F, M} || {M, Fs} <- Is, F <- Fs].
704
721
 
720
737
            end
721
738
    end.
722
739
 
 
740
-spec check_imports_1([{atom(), atom()}]) -> bool().
723
741
check_imports_1([{F1, M1}, {F2, M2} | _Is]) when F1 =:= F2, M1 =/= M2 ->
724
742
    false;
725
743
check_imports_1([_ | Is]) ->
910
928
            Used
911
929
    end.
912
930
 
913
 
-record(env, {file,
 
931
-type context() :: 'guard_expr' | 'guard_test' | 'normal'.
 
932
 
 
933
-record(env, {file                     :: filename(),
914
934
              module,
915
935
              current,
916
936
              imports,
917
 
              context = normal,
918
 
              verbosity = 1,
919
 
              quiet = false,
920
 
              no_imports = false,
921
 
              spawn_funs = false,
922
 
              auto_list_comp = true,
923
 
              auto_export_vars = false,
924
 
              new_guard_tests = true,
925
 
              old_guard_tests = false}).
 
937
              context = normal         :: context(),
 
938
              verbosity = 1            :: 0 | 1 | 2,
 
939
              quiet = false            :: bool(),
 
940
              no_imports = false       :: bool(),
 
941
              spawn_funs = false       :: bool(),
 
942
              auto_list_comp = true    :: bool(),
 
943
              auto_export_vars = false :: bool(),
 
944
              new_guard_tests = true   :: bool(),
 
945
              old_guard_tests = false  :: bool()}).
926
946
 
927
947
-record(st, {varc, used, imported, vars, functions, new_forms, rename}).
928
948
 
1015
1035
            Used = sets:add_element(N, St0#st.used),
1016
1036
            {Tree, St0#st{used = Used}};
1017
1037
        _ ->
1018
 
            Tree
 
1038
            %% symbolic funs do not count as uses of a function
 
1039
            {Tree, St0}
1019
1040
    end.
1020
1041
 
1021
1042
visit_clause(Tree, Env, St0) ->
1084
1105
                         N
1085
1106
                 end
1086
1107
         end,
1087
 
    if N1 /= N ->
 
1108
    if N1 =/= N ->
1088
1109
            report({Env#env.file, erl_syntax:get_pos(F),
1089
1110
                    "changing guard test `~w' to `~w'."},
1090
1111
                   [N, N1], Env#env.verbosity);
1293
1314
            visit_application_final(F, As, Tree, St0)
1294
1315
    end.
1295
1316
 
 
1317
%% --- lists:append/2 and lists:subtract/2 ---
1296
1318
visit_remote_application({lists, append, 2}, F, [A1, A2], Tree, Env,
1297
1319
                         St0) ->
1298
1320
    report({Env#env.file, erl_syntax:get_pos(F),
1309
1331
           [], Env#env.verbosity),
1310
1332
    Tree1 = erl_syntax:infix_expr(A1, erl_syntax:operator('--'), A2),
1311
1333
    visit(rewrite(Tree, Tree1), Env, St0);
1312
 
 
 
1334
%% --- lists:map/2 and lists:filter/2 ---
1313
1335
visit_remote_application({lists, filter, 2}, F, [A1, A2] = As, Tree,
1314
1336
                         Env, St0) ->
1315
1337
    case Env#env.auto_list_comp
 
1338
        and (erl_syntax:type(A1) =/= variable)
1316
1339
        and (get_var_exports(A1) =:= [])
1317
1340
        and (get_var_exports(A2) =:= []) of
1318
1341
        true ->
1332
1355
visit_remote_application({lists, map, 2}, F, [A1, A2] = As, Tree, Env,
1333
1356
                         St0) ->
1334
1357
    case Env#env.auto_list_comp
 
1358
        and (erl_syntax:type(A1) =/= variable)
1335
1359
        and (get_var_exports(A1) =:= [])
1336
1360
        and (get_var_exports(A2) =:= []) of
1337
1361
        true ->
1348
1372
        false ->
1349
1373
            visit_application_final(F, As, Tree, St0)
1350
1374
    end;
 
1375
%% --- all other functions ---
1351
1376
visit_remote_application({M, N, A} = Name, F, As, Tree, Env, St) ->
1352
1377
    case is_auto_imported(Name) of
1353
1378
        true ->
1371
1396
            end
1372
1397
    end.
1373
1398
 
 
1399
-spec auto_expand_import(mfa(), #st{}) -> bool().
1374
1400
auto_expand_import({lists, append, 2}, _St) -> true;
 
1401
auto_expand_import({lists, subtract, 2}, _St) -> true;
1375
1402
auto_expand_import({lists, filter, 2}, _St) -> true;
1376
1403
auto_expand_import({lists, map, 2}, _St) -> true;
1377
1404
auto_expand_import(Name, St) ->
1595
1622
 
1596
1623
make_matches([V | Vs], [T | Ts]) ->
1597
1624
    [erl_syntax:match_expr(V, T) | make_matches(Vs, Ts)];
1598
 
make_matches([V | Vs], T) when T /= [] ->
 
1625
make_matches([V | Vs], T) when T =/= [] ->
1599
1626
    [erl_syntax:match_expr(V, T) | make_matches(Vs, T)];
1600
1627
make_matches([], _) ->
1601
1628
    [].
1607
1634
        {ok, F1} -> F1
1608
1635
    end.
1609
1636
 
 
1637
-spec rename_remote_call_1(mfa()) -> {atom(), atom()} | 'false'.
1610
1638
rename_remote_call_1({dict, dict_to_list, 1}) -> {dict, to_list};
1611
1639
rename_remote_call_1({dict, list_to_dict, 1}) -> {dict, from_list};
1612
1640
rename_remote_call_1({erl_eval, arg_list, 2}) -> {erl_eval, expr_list};
1640
1668
rename_remote_call_1({unix, cmd, 1}) -> {os, cmd};
1641
1669
rename_remote_call_1(_) -> false.
1642
1670
 
 
1671
-spec rewrite_guard_test(atom(), byte()) -> atom().
1643
1672
rewrite_guard_test(atom, 1) -> is_atom;
1644
1673
rewrite_guard_test(binary, 1) -> is_binary;
1645
1674
rewrite_guard_test(constant, 1) -> is_constant;
1646
1675
rewrite_guard_test(float, 1) -> is_float;
1647
1676
rewrite_guard_test(function, 1) -> is_function;
 
1677
rewrite_guard_test(function, 2) -> is_function;
1648
1678
rewrite_guard_test(integer, 1) -> is_integer;
1649
1679
rewrite_guard_test(list, 1) -> is_list;
1650
1680
rewrite_guard_test(number, 1) -> is_number;
1653
1683
rewrite_guard_test(reference, 1) -> is_reference;
1654
1684
rewrite_guard_test(tuple, 1) -> is_tuple;
1655
1685
rewrite_guard_test(record, 2) -> is_record;
 
1686
rewrite_guard_test(record, 3) -> is_record;
1656
1687
rewrite_guard_test(N, _A) -> N.
1657
1688
 
 
1689
-spec reverse_guard_test(atom(), byte()) -> atom().
1658
1690
reverse_guard_test(is_atom, 1) -> atom;
1659
1691
reverse_guard_test(is_binary, 1) -> binary;
1660
1692
reverse_guard_test(is_constant, 1) -> constant;
1661
1693
reverse_guard_test(is_float, 1) -> float;
1662
1694
reverse_guard_test(is_function, 1) -> function;
 
1695
reverse_guard_test(is_function, 2) -> function;
1663
1696
reverse_guard_test(is_integer, 1) -> integer;
1664
1697
reverse_guard_test(is_list, 1) -> list;
1665
1698
reverse_guard_test(is_number, 1) -> number;
1668
1701
reverse_guard_test(is_reference, 1) -> reference;
1669
1702
reverse_guard_test(is_tuple, 1) -> tuple;
1670
1703
reverse_guard_test(is_record, 2) -> record;
 
1704
reverse_guard_test(is_record, 3) -> record;
1671
1705
reverse_guard_test(N, _A) -> N.
1672
1706
 
1673
1707
 
1823
1857
report_error(D, Vs) ->
1824
1858
    report({error, D}, Vs).
1825
1859
 
1826
 
% warn(D, N) ->
1827
 
%     warn(D, [], N).
 
1860
%% warn(D, N) ->
 
1861
%%     warn(D, [], N).
1828
1862
 
1829
1863
warn({F, L, D}, Vs, N) ->
1830
1864
    report({F, L, {warning, D}}, Vs, N);
1867
1901
format(S, Vs) when is_list(S) ->
1868
1902
    [io_lib:fwrite(S, Vs), $\n].
1869
1903
 
1870
 
 
1871
1904
%% =====================================================================