~ubuntu-branches/ubuntu/trusty/erlang/trusty

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Clint Byrum
  • Date: 2011-05-05 15:48:43 UTC
  • mfrom: (3.5.13 sid)
  • Revision ID: james.westby@ubuntu.com-20110505154843-0om6ekzg6m7ugj27
Tags: 1:14.b.2-dfsg-3ubuntu1
* Merge from debian unstable.  Remaining changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to.
  - Drop erlang-wx binary.
  - Drop erlang-wx dependency from -megaco, -common-test, and -reltool, they
    do not really need wx. Also drop it from -debugger; the GUI needs wx,
    but it apparently has CLI bits as well, and is also needed by -megaco,
    so let's keep the package for now.
  - debian/patches/series: Do what I meant, and enable build-options.patch
    instead.
* Additional changes:
  - Drop erlang-wx from -et
* Dropped Changes:
  - patches/pcre-crash.patch: CVE-2008-2371: outer level option with
    alternatives caused crash. (Applied Upstream)
  - fix for ssl certificate verification in newSSL: 
    ssl_cacertfile_fix.patch (Applied Upstream)
  - debian/patches/series: Enable native.patch again, to get stripped beam
    files and reduce the package size again. (build-options is what
    actually accomplished this)
  - Remove build-options.patch on advice from upstream and because it caused
    odd build failures.

Show diffs side-by-side

added added

removed removed

Lines of Context:
66
66
%% @equiv dir("")
67
67
 
68
68
-spec dir() -> 'ok'.
 
69
 
69
70
dir() ->
70
71
    dir("").
71
72
 
74
75
%% @equiv dir(Dir, [])
75
76
 
76
77
-spec dir(file:filename()) -> 'ok'.
 
78
 
77
79
dir(Dir) ->
78
80
    dir(Dir, []).
79
81
 
130
132
              options              :: options()}).
131
133
 
132
134
-spec dir(file:filename(), options()) -> 'ok'.
 
135
 
133
136
dir(Dir, Opts) ->
134
137
    Opts1 = Opts ++ dir__defaults(),
135
138
    Env = #dir{follow_links = proplists:get_bool(follow_links, Opts1),
212
215
%% @equiv file(Name, [])
213
216
 
214
217
-spec file(file:filename()) -> 'ok'.
 
218
 
215
219
file(Name) ->
216
220
    file(Name, []).
217
221
 
275
279
%% @see module/2
276
280
 
277
281
-spec file(file:filename(), options()) -> 'ok'.
 
282
 
278
283
file(Name, Opts) ->
279
284
    Parent = self(),
280
285
    Child = spawn_link(fun () -> file_1(Parent, Name, Opts) end),
478
483
            throw(R)
479
484
    end.
480
485
 
481
 
 
482
486
%% =====================================================================
483
487
%% @spec module(Forms) -> syntaxTree()
484
488
%% @equiv module(Forms, [])
485
489
 
 
490
-spec module(erl_syntax:forms()) -> erl_syntax:syntaxTree().
 
491
 
486
492
module(Forms) ->
487
493
    module(Forms, []).
488
494
 
609
615
%%
610
616
%% </dl>
611
617
 
 
618
-spec module(erl_syntax:forms(), [term()]) -> erl_syntax:syntaxTree().
 
619
 
612
620
module(Forms, Opts) when is_list(Forms) ->
613
621
    module(erl_syntax:form_list(Forms), Opts);
614
622
module(Forms, Opts) ->
668
676
            throw(R)
669
677
    end.
670
678
 
671
 
%% XXX: The following should be imported from erl_syntax_lib
672
 
-type key()       :: atom().
673
 
-type info_pair() :: {key(), any()}.
 
679
-spec get_module_name([erl_syntax_lib:info_pair()], string()) -> atom().
674
680
 
675
 
-spec get_module_name([info_pair()], string()) -> atom().
676
681
get_module_name(List, File) ->
677
682
    case lists:keyfind(module, 1, List) of
678
683
        {module, M} ->
691
696
            []
692
697
    end.
693
698
 
694
 
-spec get_module_exports([info_pair()]) -> [{atom(), byte()}].
 
699
-spec get_module_exports([erl_syntax_lib:info_pair()]) -> [{atom(), arity()}].
 
700
 
695
701
get_module_exports(List) ->
696
702
    case lists:keyfind(exports, 1, List) of
697
703
        {exports, Es} ->
700
706
            []
701
707
    end.
702
708
 
703
 
-spec get_module_imports([info_pair()]) -> [{atom(), atom()}].
 
709
-spec get_module_imports([erl_syntax_lib:info_pair()]) -> [{atom(), atom()}].
 
710
 
704
711
get_module_imports(List) ->
705
712
    case lists:keyfind(imports, 1, List) of
706
713
        {imports, Is} ->
714
721
                  || {compile, T} <- As]).
715
722
 
716
723
-spec flatten_imports([{atom(), [atom()]}]) -> [{atom(), atom()}].
 
724
 
717
725
flatten_imports(Is) ->
718
726
    [{F, M} || {M, Fs} <- Is, F <- Fs].
719
727
 
736
744
    end.
737
745
 
738
746
-spec check_imports_1([{atom(), atom()}]) -> boolean().
739
 
check_imports_1([{F1, M1}, {F2, M2} | _Is]) when F1 =:= F2, M1 =/= M2 ->
 
747
 
 
748
check_imports_1([{F, M1}, {F, M2} | _Is]) when M1 =/= M2 ->
740
749
    false;
741
750
check_imports_1([_ | Is]) ->
742
751
    check_imports_1(Is);
926
935
            Used
927
936
    end.
928
937
 
 
938
-type fa()      :: {atom(), arity()}.
929
939
-type context() :: 'guard_expr' | 'guard_test' | 'normal'.
930
940
 
931
941
-record(env, {file                     :: file:filename(),
932
 
              module,
933
 
              current,
934
 
              imports,
 
942
              module                   :: atom(),
 
943
              current                  :: fa(),
 
944
              imports = dict:new()     :: dict(),
935
945
              context = normal         :: context(),
936
946
              verbosity = 1            :: 0 | 1 | 2,
937
947
              quiet = false            :: boolean(),
942
952
              new_guard_tests = true   :: boolean(),
943
953
              old_guard_tests = false  :: boolean()}).
944
954
 
945
 
-record(st, {varc, used, imported, vars, functions, new_forms, rename}).
 
955
-record(st, {varc              :: non_neg_integer(),
 
956
             used = sets:new() :: set(),
 
957
             imported          :: set(),
 
958
             vars              :: set(),
 
959
             functions         :: set(),
 
960
             new_forms = []    :: [erl_syntax:syntaxTree()],
 
961
             rename            :: dict()}).
946
962
 
947
963
visit_used(Names, Defs, Roots, Imports, Module, Opts) ->
948
964
    File = proplists:get_value(file, Opts, ""),
1629
1645
    end.
1630
1646
 
1631
1647
-spec rename_remote_call_1(mfa()) -> {atom(), atom()} | 'false'.
 
1648
 
1632
1649
rename_remote_call_1({dict, dict_to_list, 1}) -> {dict, to_list};
1633
1650
rename_remote_call_1({dict, list_to_dict, 1}) -> {dict, from_list};
1634
1651
rename_remote_call_1({erl_eval, arg_list, 2}) -> {erl_eval, expr_list};
1662
1679
rename_remote_call_1({unix, cmd, 1}) -> {os, cmd};
1663
1680
rename_remote_call_1(_) -> false.
1664
1681
 
1665
 
-spec rewrite_guard_test(atom(), byte()) -> atom().
 
1682
-spec rewrite_guard_test(atom(), arity()) -> atom().
 
1683
 
1666
1684
rewrite_guard_test(atom, 1) -> is_atom;
1667
1685
rewrite_guard_test(binary, 1) -> is_binary;
1668
1686
rewrite_guard_test(constant, 1) -> is_constant;
1680
1698
rewrite_guard_test(record, 3) -> is_record;
1681
1699
rewrite_guard_test(N, _A) -> N.
1682
1700
 
1683
 
-spec reverse_guard_test(atom(), byte()) -> atom().
 
1701
-spec reverse_guard_test(atom(), arity()) -> atom().
 
1702
 
1684
1703
reverse_guard_test(is_atom, 1) -> atom;
1685
1704
reverse_guard_test(is_binary, 1) -> binary;
1686
1705
reverse_guard_test(is_constant, 1) -> constant;