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

« back to all changes in this revision

Viewing changes to lib/typer/src/typer_preprocess.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:
1
 
%% -*- erlang-indent-level: 2 -*-
2
 
%%
3
 
%% %CopyrightBegin%
4
 
%% 
5
 
%% Copyright Ericsson AB 2006-2009. All Rights Reserved.
6
 
%% 
7
 
%% The contents of this file are subject to the Erlang Public License,
8
 
%% Version 1.1, (the "License"); you may not use this file except in
9
 
%% compliance with the License. You should have received a copy of the
10
 
%% Erlang Public License along with this software. If not, it can be
11
 
%% retrieved online at http://www.erlang.org/.
12
 
%% 
13
 
%% Software distributed under the License is distributed on an "AS IS"
14
 
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
15
 
%% the License for the specific language governing rights and limitations
16
 
%% under the License.
17
 
%% 
18
 
%% %CopyrightEnd%
19
 
%%
20
 
 
21
 
-module(typer_preprocess).
22
 
 
23
 
-export([get_all_files/2]).
24
 
 
25
 
-include("typer.hrl").
26
 
 
27
 
%%----------------------------------------------------------------------------
28
 
 
29
 
-spec get_all_files(#args{}, 'analysis' | 'trust') -> [string()].
30
 
 
31
 
get_all_files(Args, analysis) ->
32
 
  case internal_get_all_files(Args#args.analyze,
33
 
                              Args#args.analyzed_dir_r,
34
 
                              fun test_erl_file_exclude_ann/1) of
35
 
    [] -> typer:error("no file(s) to analyze");
36
 
    AllFiles -> AllFiles
37
 
  end;
38
 
get_all_files(Args, trust) -> 
39
 
  internal_get_all_files(Args#args.trust, [], fun test_erl_file/1).
40
 
 
41
 
-spec test_erl_file_exclude_ann(string()) -> boolean().
42
 
 
43
 
test_erl_file_exclude_ann(File) ->
44
 
  case filename:extension(File) of
45
 
    ".erl" -> %% Exclude files ending with ".ann.erl"
46
 
      case re:run(File, "[\.]ann[\.]erl$") of
47
 
        {match, _} -> false;
48
 
        nomatch -> true
49
 
      end;
50
 
    _ -> false
51
 
  end.
52
 
 
53
 
-spec test_erl_file(string()) -> boolean().
54
 
 
55
 
test_erl_file(File) ->
56
 
  filename:extension(File) =:= ".erl".
57
 
 
58
 
-spec internal_get_all_files([string()], [string()],
59
 
                             fun((string()) -> boolean())) -> [string()].
60
 
 
61
 
internal_get_all_files(File_Dir, Dir_R, Fun) ->
62
 
  All_File_1 = process_file_and_dir(File_Dir, Fun),
63
 
  All_File_2 = process_dir_recursively(Dir_R, Fun),
64
 
  remove_dup(All_File_1 ++ All_File_2).
65
 
 
66
 
-spec process_file_and_dir([string()],
67
 
                           fun((string()) -> boolean())) -> [string()].
68
 
 
69
 
process_file_and_dir(File_Dir, TestFun) ->
70
 
  Fun =
71
 
    fun (Elem, Acc) ->
72
 
        case filelib:is_regular(Elem) of
73
 
          true  -> process_file(Elem, TestFun, Acc);
74
 
          false -> check_dir(Elem, non_recursive, Acc, TestFun)
75
 
        end
76
 
    end,
77
 
  lists:foldl(Fun, [], File_Dir).
78
 
 
79
 
-spec process_dir_recursively([string()],
80
 
                              fun((string()) -> boolean())) -> [string()].
81
 
 
82
 
process_dir_recursively(Dirs, TestFun) ->
83
 
  Fun = fun (Dir, Acc) ->
84
 
            check_dir(Dir, recursive, Acc, TestFun)
85
 
        end,
86
 
  lists:foldl(Fun, [], Dirs).
87
 
 
88
 
-spec check_dir(string(),
89
 
                'non_recursive' | 'recursive',
90
 
                [string()],
91
 
                fun((string()) -> boolean())) -> [string()].
92
 
 
93
 
check_dir(Dir, Mode, Acc, Fun) ->
94
 
  case file:list_dir(Dir) of
95
 
    {ok, Files} ->
96
 
      {TmpDirs, TmpFiles} = split_dirs_and_files(Files, Dir),
97
 
      case Mode of
98
 
        non_recursive ->
99
 
          FinalFiles = process_file_and_dir(TmpFiles, Fun),
100
 
          Acc ++ FinalFiles;
101
 
        recursive ->
102
 
          TmpAcc1 = process_file_and_dir(TmpFiles, Fun),
103
 
          TmpAcc2 = process_dir_recursively(TmpDirs, Fun),
104
 
          Acc ++ TmpAcc1 ++ TmpAcc2
105
 
      end;
106
 
    {error, eacces} ->
107
 
      typer:error("no access permission to dir \""++Dir++"\"");
108
 
    {error, enoent} ->
109
 
      typer:error("cannot access "++Dir++": No such file or directory");
110
 
    {error, _Reason} ->
111
 
      typer:error("error involving a use of file:list_dir/1")
112
 
  end.
113
 
 
114
 
%% Same order as the input list
115
 
-spec process_file(string(), fun((string()) -> boolean()), string()) -> [string()].
116
 
 
117
 
process_file(File, TestFun, Acc) ->
118
 
  case TestFun(File) of
119
 
    true  -> Acc ++ [File];
120
 
    false -> Acc
121
 
  end.
122
 
 
123
 
%% Same order as the input list
124
 
-spec split_dirs_and_files([string()], string()) -> {[string()], [string()]}.
125
 
 
126
 
split_dirs_and_files(Elems, Dir) ->
127
 
  Test_Fun =
128
 
    fun (Elem, {DirAcc, FileAcc}) ->
129
 
        File = filename:join(Dir, Elem),
130
 
        case filelib:is_regular(File) of
131
 
          false -> {[File|DirAcc], FileAcc}; 
132
 
          true  -> {DirAcc, [File|FileAcc]}
133
 
        end
134
 
    end,
135
 
  {Dirs, Files} = lists:foldl(Test_Fun, {[], []}, Elems),
136
 
  {lists:reverse(Dirs), lists:reverse(Files)}.  
137
 
 
138
 
%%-----------------------------------------------------------------------
139
 
%% Utilities
140
 
%%-----------------------------------------------------------------------
141
 
 
142
 
%% Removes duplicate filenames but it keeps the order of the input list
143
 
 
144
 
-spec remove_dup([string()]) -> [string()].
145
 
 
146
 
remove_dup(Files) ->
147
 
  Test_Dup = fun (File, Acc) ->
148
 
                 case lists:member(File, Acc) of
149
 
                   true  -> Acc;
150
 
                   false -> [File|Acc]
151
 
                 end
152
 
             end,
153
 
  Reversed_Elems = lists:foldl(Test_Dup, [], Files),
154
 
  lists:reverse(Reversed_Elems).