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

« back to all changes in this revision

Viewing changes to lib/typer/src/typer_info.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_info).
22
 
 
23
 
-export([collect/1]).
24
 
 
25
 
-type func_info() :: {non_neg_integer(), atom(), arity()}.
26
 
-type inc_file_info() :: {string(), func_info()}.
27
 
 
28
 
-record(tmpAcc, {file           :: string(),
29
 
                 module         :: atom(),
30
 
                 funcAcc=[]     :: [func_info()],
31
 
                 incFuncAcc=[]  :: [inc_file_info()],
32
 
                 dialyzerObj=[] :: [{mfa(), {_, _}}]}).
33
 
 
34
 
-include("typer.hrl").
35
 
 
36
 
-spec collect(#typer_analysis{}) -> #typer_analysis{}.
37
 
 
38
 
collect(Analysis) ->
39
 
  NewPlt =
40
 
    try get_dialyzer_plt(Analysis) of
41
 
        DialyzerPlt ->
42
 
        dialyzer_plt:merge_plts([Analysis#typer_analysis.trust_plt, DialyzerPlt])
43
 
    catch
44
 
      throw:{dialyzer_error,_Reason} ->
45
 
        typer:error("Dialyzer's PLT is missing or is not up-to-date; please (re)create it")
46
 
    end,
47
 
  NewAnalysis = lists:foldl(fun collect_one_file_info/2, 
48
 
                            Analysis#typer_analysis{trust_plt = NewPlt}, 
49
 
                            Analysis#typer_analysis.ana_files),
50
 
  %% Process Remote Types
51
 
  TmpCServer = NewAnalysis#typer_analysis.code_server,
52
 
  NewCServer =
53
 
    try
54
 
      NewRecords = dialyzer_codeserver:get_temp_records(TmpCServer),
55
 
      OldRecords = dialyzer_plt:get_types(NewPlt),
56
 
      MergedRecords = dialyzer_utils:merge_records(NewRecords, OldRecords),
57
 
      %% io:format("Merged Records ~p",[MergedRecords]),
58
 
      TmpCServer1 = dialyzer_codeserver:set_temp_records(MergedRecords, TmpCServer),
59
 
      TmpCServer2 = dialyzer_utils:process_record_remote_types(TmpCServer1),
60
 
      dialyzer_contracts:process_contract_remote_types(TmpCServer2)
61
 
    catch
62
 
      throw:{error, ErrorMsg} ->
63
 
        typer:error(ErrorMsg)
64
 
    end,
65
 
  NewAnalysis#typer_analysis{code_server = NewCServer}.
66
 
 
67
 
collect_one_file_info(File, Analysis) ->
68
 
  Ds = [{d,Name,Val} || {Name,Val} <- Analysis#typer_analysis.macros],
69
 
  %% Current directory should also be included in "Includes".
70
 
  Includes = [filename:dirname(File)|Analysis#typer_analysis.includes],
71
 
  Is = [{i,Dir} || Dir <- Includes],
72
 
  Options = dialyzer_utils:src_compiler_opts() ++ Is ++ Ds,
73
 
  case dialyzer_utils:get_abstract_code_from_src(File, Options) of
74
 
    {error, Reason} ->
75
 
      %% io:format("File=~p\n,Options=~p\n,Error=~p\n", [File,Options,Reason]),
76
 
      typer:compile_error(Reason);
77
 
    {ok, AbstractCode} ->
78
 
      case dialyzer_utils:get_core_from_abstract_code(AbstractCode, Options) of
79
 
        error -> typer:compile_error(["Could not get core erlang for "++File]);
80
 
        {ok, Core} ->
81
 
          case dialyzer_utils:get_record_and_type_info(AbstractCode) of
82
 
            {error, Reason} -> typer:compile_error([Reason]);
83
 
            {ok, Records} -> 
84
 
              Mod = list_to_atom(filename:basename(File, ".erl")),
85
 
              case dialyzer_utils:get_spec_info(Mod, AbstractCode, Records) of
86
 
                {error, Reason} -> typer:compile_error([Reason]);
87
 
                {ok, SpecInfo} -> 
88
 
                  analyze_core_tree(Core, Records, SpecInfo, Analysis, File)
89
 
              end
90
 
          end
91
 
      end
92
 
  end.
93
 
 
94
 
analyze_core_tree(Core, Records, SpecInfo, Analysis, File) ->
95
 
  Module = list_to_atom(filename:basename(File, ".erl")),
96
 
  TmpTree = cerl:from_records(Core),
97
 
  CS1 = Analysis#typer_analysis.code_server,
98
 
  NextLabel = dialyzer_codeserver:get_next_core_label(CS1),
99
 
  {Tree, NewLabel} = cerl_trees:label(TmpTree, NextLabel),
100
 
  CS2 = dialyzer_codeserver:insert(Module, Tree, CS1),
101
 
  CS3 = dialyzer_codeserver:set_next_core_label(NewLabel, CS2),
102
 
  CS4 = dialyzer_codeserver:store_temp_records(Module, Records, CS3),
103
 
  CS5 = dialyzer_codeserver:store_temp_contracts(Module, SpecInfo, CS4),
104
 
  Ex_Funcs = [{0,F,A} || {_,_,{F,A}} <- cerl:module_exports(Tree)],
105
 
  TmpCG = Analysis#typer_analysis.callgraph,
106
 
  CG = dialyzer_callgraph:scan_core_tree(Tree, TmpCG),
107
 
  Fun = fun analyze_one_function/2,
108
 
  All_Defs = cerl:module_defs(Tree),
109
 
  Acc = lists:foldl(Fun, #tmpAcc{file=File, module=Module}, All_Defs),
110
 
  Exported_FuncMap = typer_map:insert({File, Ex_Funcs},
111
 
                                      Analysis#typer_analysis.ex_func),
112
 
  %% NOTE: we must sort all functions in the file which
113
 
  %% originate from this file by *numerical order* of lineNo
114
 
  Sorted_Functions = lists:keysort(1, Acc#tmpAcc.funcAcc),
115
 
  FuncMap = typer_map:insert({File, Sorted_Functions},
116
 
                             Analysis#typer_analysis.func),
117
 
  %% NOTE: However we do not need to sort functions
118
 
  %% which are imported from included files.
119
 
  IncFuncMap = typer_map:insert({File, Acc#tmpAcc.incFuncAcc}, 
120
 
                                Analysis#typer_analysis.inc_func),
121
 
  Final_Files = Analysis#typer_analysis.final_files ++ [{File, Module}],
122
 
  RecordMap = typer_map:insert({File, Records}, Analysis#typer_analysis.record),
123
 
  Analysis#typer_analysis{final_files=Final_Files,
124
 
                          callgraph=CG,
125
 
                          code_server=CS5,
126
 
                          ex_func=Exported_FuncMap,
127
 
                          inc_func=IncFuncMap,
128
 
                          record=RecordMap,
129
 
                          func=FuncMap}.
130
 
 
131
 
analyze_one_function({Var, FunBody} = Function, Acc) ->
132
 
  F = cerl:fname_id(Var),
133
 
  A = cerl:fname_arity(Var),
134
 
  TmpDialyzerObj = {{Acc#tmpAcc.module, F, A}, Function},
135
 
  NewDialyzerObj = Acc#tmpAcc.dialyzerObj ++ [TmpDialyzerObj],  
136
 
  [_, LineNo, {file, FileName}] = cerl:get_ann(FunBody),
137
 
  BaseName = filename:basename(FileName),
138
 
  FuncInfo = {LineNo, F, A},
139
 
  OriginalName = Acc#tmpAcc.file,
140
 
  {FuncAcc, IncFuncAcc} =
141
 
    case (FileName =:= OriginalName) orelse (BaseName =:= OriginalName) of
142
 
      true -> %% Coming from original file
143
 
        %% io:format("Added function ~p\n", [{LineNo, F, A}]),
144
 
        {Acc#tmpAcc.funcAcc ++ [FuncInfo], Acc#tmpAcc.incFuncAcc};
145
 
      false ->
146
 
        %% Coming from other sourses, including:
147
 
        %%     -- .yrl (yecc-generated file)
148
 
        %%     -- yeccpre.hrl (yecc-generated file)
149
 
        %%     -- other cases
150
 
        {Acc#tmpAcc.funcAcc, Acc#tmpAcc.incFuncAcc ++ [{FileName, FuncInfo}]}
151
 
    end,
152
 
  Acc#tmpAcc{funcAcc = FuncAcc,
153
 
             incFuncAcc = IncFuncAcc,
154
 
             dialyzerObj = NewDialyzerObj}.
155
 
 
156
 
get_dialyzer_plt(#typer_analysis{plt = PltFile0}) ->
157
 
  PltFile =
158
 
    case PltFile0 =:= none of
159
 
      true -> dialyzer_plt:get_default_plt();
160
 
      false -> PltFile0
161
 
    end,
162
 
  dialyzer_plt:from_file(PltFile).