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

« back to all changes in this revision

Viewing changes to lib/kernel/src/code.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
1
%%
2
2
%% %CopyrightBegin%
3
 
%% 
4
 
%% Copyright Ericsson AB 1996-2009. All Rights Reserved.
5
 
%% 
 
3
%%
 
4
%% Copyright Ericsson AB 1996-2011. All Rights Reserved.
 
5
%%
6
6
%% The contents of this file are subject to the Erlang Public License,
7
7
%% Version 1.1, (the "License"); you may not use this file except in
8
8
%% compliance with the License. You should have received a copy of the
9
9
%% Erlang Public License along with this software. If not, it can be
10
10
%% retrieved online at http://www.erlang.org/.
11
 
%% 
 
11
%%
12
12
%% Software distributed under the License is distributed on an "AS IS"
13
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
14
14
%% the License for the specific language governing rights and limitations
15
15
%% under the License.
16
 
%% 
 
16
%%
17
17
%% %CopyrightEnd%
18
18
%%
19
19
-module(code).
63
63
         which/1,
64
64
         where_is_file/1,
65
65
         where_is_file/2,
66
 
         set_primary_archive/2,
 
66
         set_primary_archive/3,
67
67
         clash/0]).
68
68
 
 
69
-export_type([load_error_rsn/0, load_ret/0]).
 
70
 
69
71
-include_lib("kernel/include/file.hrl").
70
72
 
71
73
%% User interface.
72
74
%%
73
 
%% objfile_extension()          -> ".beam"
74
 
%% set_path(Dir*)               -> true
75
 
%% get_path()                   -> Dir*
76
 
%% add_path(Dir)                -> true | {error, What}
77
 
%% add_patha(Dir)               -> true | {error, What}
78
 
%% add_pathz(Dir)               -> true | {error, What}
79
 
%% add_paths(DirList)           -> true | {error, What}
80
 
%% add_pathsa(DirList)          -> true | {error, What}
81
 
%% add_pathsz(DirList)          -> true | {error, What}
82
 
%% del_path(Dir)                -> true | {error, What}
83
 
%% replace_path(Name,Dir)       -> true | {error, What}
84
 
%% load_file(File)              -> {error,What} | {module, Mod}
85
 
%% load_abs(File)               -> {error,What} | {module, Mod}
86
 
%% load_abs(File,Mod)           -> {error,What} | {module, Mod}
87
 
%% load_binary(Mod,File,Bin)    -> {error,What} | {module,Mod}
88
 
%% ensure_loaded(Module)        -> {error,What} | {module, Mod}
89
 
%% delete(Module)
90
 
%% purge(Module)  kills all procs running old code
91
 
%% soft_purge(Module)           -> true | false
92
 
%% is_loaded(Module)            -> {file, File} | false
93
 
%% all_loaded()                 -> {Module, File}*
94
 
%% get_object_code(Mod)         -> error | {Mod, Bin, Filename}
95
 
%% stop()                       -> true
96
 
%% root_dir()                   
97
 
%% compiler_dir()
98
 
%% lib_dir()
99
 
%% priv_dir(Name)
100
 
%% stick_dir(Dir)               -> ok | error
101
 
%% unstick_dir(Dir)             -> ok | error
102
 
%% is_sticky(Module)            -> true | false
103
 
%% which(Module)                -> Filename
104
 
%% set_primary_archive((FileName, Bin)  -> ok | {error, Reason}
105
 
%% clash() ->                   -> print out
 
75
%% objfile_extension()           -> ".beam"
 
76
%% get_path()                    -> [Dir]
 
77
%% set_path([Dir])               -> true | {error, bad_directory | bad_path}
 
78
%% add_path(Dir)                 -> true | {error, bad_directory}
 
79
%% add_patha(Dir)                -> true | {error, bad_directory}
 
80
%% add_pathz(Dir)                -> true | {error, bad_directory}
 
81
%% add_paths([Dir])              -> ok
 
82
%% add_pathsa([Dir])             -> ok
 
83
%% add_pathsz([Dir])             -> ok
 
84
%% del_path(Dir)                 -> boolean() | {error, bad_name}
 
85
%% replace_path(Name, Dir)       -> true | replace_path_error()
 
86
%% load_file(Module)             -> {module, Module} | {error, What :: atom()}
 
87
%% load_abs(File)                -> {module, Module} | {error, What :: atom()}
 
88
%% load_abs(File, Module)        -> {module, Module} | {error, What :: atom()}
 
89
%% load_binary(Module, File, Bin)-> {module, Module} | {error, What :: atom()}
 
90
%% ensure_loaded(Module)         -> {module, Module} | {error, What :: atom()}
 
91
%% delete(Module)                -> boolean()
 
92
%% purge(Module)                 -> boolean()  kills all procs running old code
 
93
%% soft_purge(Module)            -> boolean()
 
94
%% is_loaded(Module)             -> {file, loaded_filename()} | false
 
95
%% all_loaded()                  -> [{Module, loaded_filename()}]
 
96
%% get_object_code(Module)       -> {Module, Bin, Filename} | error
 
97
%% stop()                        -> no_return()
 
98
%% root_dir()                    -> Dir
 
99
%% compiler_dir()                -> Dir
 
100
%% lib_dir()                     -> Dir
 
101
%% lib_dir(Application)          -> Dir | {error, bad_name}
 
102
%% priv_dir(Application)         -> Dir | {error, bad_name}
 
103
%% stick_dir(Dir)                -> ok | error
 
104
%% unstick_dir(Dir)              -> ok | error
 
105
%% stick_mod(Module)             -> true
 
106
%% unstick_mod(Module)           -> true
 
107
%% is_sticky(Module)             -> boolean()
 
108
%% which(Module)                 -> Filename | loaded_ret_atoms() | non_existing
 
109
%% set_primary_archive((FileName, Bin, FileInfo) -> ok | {error, Reason}
 
110
%% clash()                       -> ok         prints out number of clashes
106
111
 
107
112
%%----------------------------------------------------------------------------
108
113
%% Some types for basic exported functions of this module
118
123
%% User interface
119
124
%%----------------------------------------------------------------------------
120
125
 
121
 
-spec objfile_extension() -> file:filename().
 
126
-spec objfile_extension() -> nonempty_string().
122
127
objfile_extension() ->
123
128
    init:objfile_extension().
124
129
 
136
141
 
137
142
%% XXX Filename is also an atom(), e.g. 'cover_compiled'
138
143
-spec load_abs(Filename :: loaded_filename(), Module :: atom()) -> load_ret().
139
 
load_abs(File,M) when (is_list(File) orelse is_atom(File)), is_atom(M) ->
 
144
load_abs(File, M) when (is_list(File) orelse is_atom(File)), is_atom(M) ->
140
145
    call({load_abs,File,M}).
141
146
 
142
147
%% XXX Filename is also an atom(), e.g. 'cover_compiled'
143
148
-spec load_binary(Module :: atom(), Filename :: loaded_filename(), Binary :: binary()) -> load_ret().
144
 
load_binary(Mod,File,Bin)
 
149
load_binary(Mod, File, Bin)
145
150
  when is_atom(Mod), (is_list(File) orelse is_atom(File)), is_binary(Bin) ->
146
151
    call({load_binary,Mod,File,Bin}).
147
152
 
148
153
-spec load_native_partial(Module :: atom(), Binary :: binary()) -> load_ret().
149
 
load_native_partial(Mod,Bin) when is_atom(Mod), is_binary(Bin) ->
 
154
load_native_partial(Mod, Bin) when is_atom(Mod), is_binary(Bin) ->
150
155
    call({load_native_partial,Mod,Bin}).
151
156
 
152
157
-spec load_native_sticky(Module :: atom(), Binary :: binary(), WholeModule :: 'false' | binary()) -> load_ret().
153
 
load_native_sticky(Mod,Bin,WholeModule)
 
158
load_native_sticky(Mod, Bin, WholeModule)
154
159
  when is_atom(Mod), is_binary(Bin),
155
160
       (is_binary(WholeModule) orelse WholeModule =:= false) ->
156
161
    call({load_native_sticky,Mod,Bin,WholeModule}).
158
163
-spec delete(Module :: atom()) -> boolean().
159
164
delete(Mod) when is_atom(Mod) -> call({delete,Mod}).
160
165
 
161
 
-spec purge/1 :: (Module :: atom()) -> boolean().
 
166
-spec purge(Module :: atom()) -> boolean().
162
167
purge(Mod) when is_atom(Mod) -> call({purge,Mod}).
163
168
 
164
169
-spec soft_purge(Module :: atom()) -> boolean().
193
198
compiler_dir() -> call({dir,compiler_dir}).
194
199
 
195
200
%% XXX is_list() is for backwards compatibility -- take out in future version
196
 
-spec priv_dir(Appl :: atom()) -> file:filename() | {'error', 'bad_name'}.
 
201
-spec priv_dir(App :: atom()) -> file:filename() | {'error', 'bad_name'}.
197
202
priv_dir(App) when is_atom(App) ; is_list(App) -> call({dir,{priv_dir,App}}).
198
203
 
199
204
-spec stick_dir(Directory :: file:filename()) -> 'ok' | 'error'.
211
216
-spec is_sticky(Module :: atom()) -> boolean().
212
217
is_sticky(Mod) when is_atom(Mod) -> call({is_sticky,Mod}).
213
218
 
214
 
-spec set_path(Directories :: [file:filename()]) -> 'true' | {'error', term()}.
 
219
-spec set_path(Directories :: [file:filename()]) ->
 
220
        'true' | {'error', 'bad_directory' | 'bad_path'}.
215
221
set_path(PathList) when is_list(PathList) -> call({set_path,PathList}).
216
222
 
217
223
-spec get_path() -> [file:filename()].
218
224
get_path() -> call(get_path).
219
225
 
220
 
-spec add_path(Directory :: file:filename()) -> 'true' | {'error', term()}.
 
226
-type add_path_ret() :: 'true' | {'error', 'bad_directory'}.
 
227
-spec add_path(Directory :: file:filename()) -> add_path_ret().
221
228
add_path(Dir) when is_list(Dir) -> call({add_path,last,Dir}).
222
229
 
223
 
-spec add_pathz(Directory :: file:filename()) -> 'true' | {'error', term()}.
 
230
-spec add_pathz(Directory :: file:filename()) -> add_path_ret().
224
231
add_pathz(Dir) when is_list(Dir) -> call({add_path,last,Dir}).
225
232
 
226
 
-spec add_patha(Directory :: file:filename()) -> 'true' | {'error', term()}.
 
233
-spec add_patha(Directory :: file:filename()) -> add_path_ret().
227
234
add_patha(Dir) when is_list(Dir) -> call({add_path,first,Dir}).
228
235
 
229
236
-spec add_paths(Directories :: [file:filename()]) -> 'ok'.
235
242
-spec add_pathsa(Directories :: [file:filename()]) -> 'ok'.
236
243
add_pathsa(Dirs) when is_list(Dirs) -> call({add_paths,first,Dirs}).
237
244
 
238
 
%% XXX Contract's input argument differs from add_path/1 -- why?
239
245
-spec del_path(Name :: file:filename() | atom()) -> boolean() | {'error', 'bad_name'}.
240
246
del_path(Name) when is_list(Name) ; is_atom(Name) -> call({del_path,Name}).
241
247
 
242
248
-type replace_path_error() :: {'error', 'bad_directory' | 'bad_name' | {'badarg',_}}.
243
249
-spec replace_path(Name:: atom(), Dir :: file:filename()) -> 'true' | replace_path_error().
244
 
replace_path(Name, Dir) when (is_atom(Name) or is_list(Name)) and
245
 
                             (is_atom(Dir) or is_list(Dir)) ->
 
250
replace_path(Name, Dir) when (is_atom(Name) orelse is_list(Name)),
 
251
                             (is_atom(Dir) orelse is_list(Dir)) ->
246
252
    call({replace_path,Name,Dir}).
247
253
 
248
254
-spec rehash() -> 'ok'.
273
279
 
274
280
do_start(Flags) ->
275
281
    %% The following module_info/1 calls are here to ensure
276
 
    %% that the modules are loaded prior to their use elsewhere in 
 
282
    %% that these modules are loaded prior to their use elsewhere in
277
283
    %% the code_server.
278
284
    %% Otherwise a deadlock may occur when the code_server is starting.
279
 
    code_server:module_info(module),
280
 
    packages:module_info(module),
 
285
    code_server = code_server:module_info(module),
 
286
    packages = packages:module_info(module),
281
287
    catch hipe_unified_loader:load_hipe_modules(),
282
 
    gb_sets:module_info(module),
283
 
    gb_trees:module_info(module),
284
 
 
285
 
    ets:module_info(module),
286
 
    os:module_info(module),
287
 
    filename:module_info(module),
288
 
    lists:module_info(module),
 
288
    Modules2 = [gb_sets, gb_trees, ets, os, binary, unicode, filename, lists],
 
289
    lists:foreach(fun (M) -> M = M:module_info(module) end, Modules2),
289
290
 
290
291
    Mode = get_mode(Flags),
291
292
    case init:get_argument(root) of 
293
294
            Root = filename:join([Root0]), % Normalize.  Use filename
294
295
            case code_server:start_link([Root,Mode]) of
295
296
                {ok,_Pid} = Ok2 ->
296
 
                    if 
 
297
                    if
297
298
                        Mode =:= interactive ->
298
299
                            case lists:member(stick, Flags) of
299
300
                                true -> do_stick_dirs();
302
303
                        true ->
303
304
                            ok
304
305
                    end,
 
306
                    %% Quietly load native code for all modules loaded so far
 
307
                    catch load_native_code_for_all_loaded(),
305
308
                    Ok2;
306
309
                Other ->
307
310
                    Other
308
311
            end;
309
312
        Other ->
310
 
            error_logger:error_msg("Can not start code server ~w ~n",[Other]),
 
313
            error_logger:error_msg("Can not start code server ~w ~n", [Other]),
311
314
            {error, crash}
312
315
    end.
313
316
 
324
327
            %% The return value is intentionally ignored. Missing
325
328
            %% directories is not a fatal error. (In embedded systems,
326
329
            %% there is usually no compiler directory.)
327
 
            stick_dir(filename:append(Dir, "ebin")),
 
330
            _ = stick_dir(filename:append(Dir, "ebin")),
328
331
            ok
329
332
    end.
330
333
 
420
423
            which(File, ".", Path)
421
424
    end.
422
425
 
423
 
-spec set_primary_archive(ArchiveFile :: file:filename(), ArchiveBin :: binary()) -> 'ok' | {'error', atom()}.
 
426
-spec set_primary_archive(ArchiveFile :: file:filename(),
 
427
                          ArchiveBin :: binary(),
 
428
                          FileInfo :: file:file_info())
 
429
                         -> 'ok' | {'error', atom()}.
424
430
 
425
 
set_primary_archive(ArchiveFile0, ArchiveBin) when is_list(ArchiveFile0), is_binary(ArchiveBin) ->
 
431
set_primary_archive(ArchiveFile0, ArchiveBin, #file_info{} = FileInfo)
 
432
  when is_list(ArchiveFile0), is_binary(ArchiveBin) ->
426
433
    ArchiveFile = filename:absname(ArchiveFile0),
427
 
    case call({set_primary_archive, ArchiveFile, ArchiveBin}) of
 
434
    case call({set_primary_archive, ArchiveFile, ArchiveBin, FileInfo}) of
428
435
        {ok, []} ->
429
436
            ok;
430
437
        {ok, _Mode, Ebins} ->
461
468
 
462
469
build([]) -> [];
463
470
build([Dir|Tail]) ->
464
 
    Files = filter(objfile_extension(), Dir, file:list_dir(Dir)),
 
471
    Files = filter(objfile_extension(), Dir,
 
472
                   erl_prim_loader:list_dir(Dir)),
465
473
    [decorate(Files, Dir) | build(Tail)].
466
474
 
467
475
decorate([], _) -> [];
468
476
decorate([File|Tail], Dir) ->
469
477
    [{Dir, File} | decorate(Tail, Dir)].
470
478
 
471
 
filter(_Ext, Dir, {error,_}) ->     
 
479
filter(_Ext, Dir, error) ->
472
480
    io:format("** Bad path can't read ~s~n", [Dir]), [];
473
481
filter(Ext, _, {ok,Files}) -> 
474
482
    filter2(Ext, length(Ext), Files).
475
483
 
476
484
filter2(_Ext, _Extlen, []) -> [];
477
 
filter2(Ext, Extlen,[File|Tail]) ->
478
 
    case has_ext(Ext,Extlen, File) of 
 
485
filter2(Ext, Extlen, [File|Tail]) ->
 
486
    case has_ext(Ext, Extlen, File) of
479
487
        true -> [File | filter2(Ext, Extlen, Tail)];
480
488
        false -> filter2(Ext, Extlen, Tail)
481
489
    end.
482
490
 
483
 
has_ext(Ext, Extlen,File) ->
 
491
has_ext(Ext, Extlen, File) ->
484
492
    L = length(File),
485
493
    case catch lists:nthtail(L - Extlen, File) of
486
494
        Ext -> true;
489
497
 
490
498
to_path(X) ->
491
499
    filename:join(packages:split(X)).
 
500
 
 
501
-spec load_native_code_for_all_loaded() -> ok.
 
502
load_native_code_for_all_loaded() ->
 
503
    Architecture = erlang:system_info(hipe_architecture),
 
504
    ChunkName = hipe_unified_loader:chunk_name(Architecture),
 
505
    lists:foreach(fun({Module, BeamFilename}) ->
 
506
        case code:is_module_native(Module) of
 
507
            false ->
 
508
                case beam_lib:chunks(BeamFilename, [ChunkName]) of
 
509
                    {ok,{_,[{_,Bin}]}} when is_binary(Bin) ->
 
510
                        load_native_partial(Module, Bin);
 
511
                    {error, beam_lib, _} -> ok
 
512
                end;
 
513
            true -> ok
 
514
        end
 
515
    end, all_loaded()).