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

« back to all changes in this revision

Viewing changes to lib/kernel/src/code_server.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 1998-2009. All Rights Reserved.
5
 
%% 
 
3
%%
 
4
%% Copyright Ericsson AB 1998-2010. 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_server).
32
32
 
33
33
-import(lists, [foreach/2]).
34
34
 
35
 
-record(state,{supervisor,
36
 
               root,
37
 
               path,
38
 
               moddb,
39
 
               namedb,
40
 
               cache = no_cache,
41
 
               mode=interactive,
42
 
               on_load = []}).
 
35
-record(state, {supervisor,
 
36
                root,
 
37
                path,
 
38
                moddb,
 
39
                namedb,
 
40
                cache = no_cache,
 
41
                mode = interactive,
 
42
                on_load = []}).
 
43
-type state() :: #state{}.
43
44
 
44
45
start_link(Args) ->
45
46
    Ref = make_ref(),
65
66
 
66
67
    Mode = 
67
68
        case Mode0 of
68
 
            minimal    -> interactive;
69
 
            _          -> Mode0
 
69
            minimal -> interactive;
 
70
            _       -> Mode0
70
71
        end,
71
72
 
72
73
    IPath =
74
75
            interactive ->
75
76
                LibDir = filename:append(Root, "lib"),
76
77
                {ok,Dirs} = erl_prim_loader:list_dir(LibDir),
77
 
                {Paths,_Libs} = make_path(LibDir,Dirs),
 
78
                {Paths,_Libs} = make_path(LibDir, Dirs),
78
79
                UserLibPaths = get_user_lib_dirs(),
79
80
                ["."] ++ UserLibPaths ++ Paths;
80
81
            _ ->
97
98
        end,
98
99
 
99
100
    Parent ! {Ref,{ok,self()}},
100
 
    loop(State#state{supervisor=Parent}).
 
101
    loop(State#state{supervisor = Parent}).
101
102
 
102
103
get_user_lib_dirs() ->
103
104
    case os:getenv("ERL_LIBS") of
169
170
%%%%%%%%%%%%%%%%%%%%%%%%%%%
170
171
%% System upgrade
171
172
 
172
 
handle_system_msg(SysState,Msg,From,Parent,Misc) ->
173
 
    case do_sys_cmd(SysState,Msg,Parent, Misc) of
 
173
handle_system_msg(SysState, Msg, From, Parent, Misc) ->
 
174
    case do_sys_cmd(SysState, Msg, Parent, Misc) of
174
175
        {suspended, Reply, NMisc} ->
175
176
            gen_reply(From, Reply),
176
177
            suspend_loop(suspended, Parent, NMisc);
207
208
do_sys_cmd(suspended, {change_code, Module, Vsn, Extra}, _Parent, Misc0) ->
208
209
    {Res, Misc} = 
209
210
        case catch ?MODULE:system_code_change(Misc0, Module, Vsn, Extra)  of
210
 
            {ok, Misc1} -> {ok, Misc1};
 
211
            {ok, _} = Ok -> Ok;
211
212
            Else -> {{error, Else}, Misc0}
212
213
        end,
213
214
    {suspended, Res, Misc};
218
219
    loop(State).
219
220
 
220
221
system_terminate(_Reason, _Parent, _Debug, _State) ->
221
 
%    error_msg("~p terminating: ~p~n ",[?MODULE,Reason]),
 
222
    %% error_msg("~p terminating: ~p~n ", [?MODULE, Reason]),
222
223
    exit(shutdown).
223
224
 
 
225
-spec system_code_change(state(), module(), term(), term()) -> {'ok', state()}.
224
226
system_code_change(State, _Module, _OldVsn, _Extra) ->
225
227
    {ok, State}.
226
228
 
240
242
handle_call({unstick_mod,Mod}, {_From,_Tag}, S) ->
241
243
    {reply,stick_mod(Mod, false, S),S};
242
244
 
243
 
handle_call({dir,Dir},{_From,_Tag}, S) ->
 
245
handle_call({dir,Dir}, {_From,_Tag}, S) ->
244
246
    Root = S#state.root,
245
247
    Resp = do_dir(Root,Dir,S#state.namedb),
246
248
    {reply,Resp,S};
253
255
            load_file(Mod, Caller, St)
254
256
    end;
255
257
 
256
 
handle_call({add_path,Where,Dir0}, {_From,_Tag}, S=#state{cache=Cache0}) ->
 
258
handle_call({add_path,Where,Dir0}, {_From,_Tag},
 
259
            #state{cache=Cache0,namedb=Namedb,path=Path0}=S) ->
257
260
    case Cache0 of
258
261
        no_cache ->
259
 
            {Resp,Path} = add_path(Where, Dir0, S#state.path, S#state.namedb),
 
262
            {Resp,Path} = add_path(Where, Dir0, Path0, Namedb),
260
263
            {reply,Resp,S#state{path=Path}};
261
264
        _ ->
262
265
            Dir = absname(Dir0), %% Cache always expands the path 
263
 
            {Resp,Path} = add_path(Where, Dir, S#state.path, S#state.namedb),
264
 
            Cache=update_cache([Dir],Where,Cache0),
 
266
            {Resp,Path} = add_path(Where, Dir, Path0, Namedb),
 
267
            Cache = update_cache([Dir], Where, Cache0),
265
268
            {reply,Resp,S#state{path=Path,cache=Cache}}
266
269
    end;
267
270
 
268
 
handle_call({add_paths,Where,Dirs0}, {_From,_Tag}, S=#state{cache=Cache0}) ->
 
271
handle_call({add_paths,Where,Dirs0}, {_From,_Tag},
 
272
            #state{cache=Cache0,namedb=Namedb,path=Path0}=S) ->
269
273
    case Cache0 of
270
274
        no_cache ->
271
 
            {Resp,Path} = add_paths(Where,Dirs0,S#state.path,S#state.namedb),
272
 
            {reply,Resp, S#state{path=Path}};
 
275
            {Resp,Path} = add_paths(Where, Dirs0, Path0, Namedb),
 
276
            {reply,Resp,S#state{path=Path}};
273
277
        _ ->
274
278
            %% Cache always expands the path 
275
279
            Dirs = [absname(Dir) || Dir <- Dirs0], 
276
 
            {Resp,Path} = add_paths(Where, Dirs, S#state.path, S#state.namedb),
 
280
            {Resp,Path} = add_paths(Where, Dirs, Path0, Namedb),
277
281
            Cache=update_cache(Dirs,Where,Cache0),
278
282
            {reply,Resp,S#state{cache=Cache,path=Path}}
279
283
    end;
280
284
 
281
 
handle_call({set_path,PathList}, {_From,_Tag}, S) ->
282
 
    Path = S#state.path,
283
 
    {Resp, NewPath,NewDb} = set_path(PathList, Path, S#state.namedb),
284
 
    {reply,Resp,rehash_cache(S#state{path = NewPath, namedb=NewDb})};
285
 
 
286
 
handle_call({del_path,Name}, {_From,_Tag}, S) ->
287
 
    {Resp,Path} = del_path(Name,S#state.path,S#state.namedb),
288
 
    {reply,Resp,rehash_cache(S#state{path = Path})};
289
 
 
290
 
handle_call({replace_path,Name,Dir}, {_From,_Tag}, S) ->
291
 
    {Resp,Path} = replace_path(Name,Dir,S#state.path,S#state.namedb),
292
 
    {reply,Resp,rehash_cache(S#state{path = Path})};
 
285
handle_call({set_path,PathList}, {_From,_Tag},
 
286
            #state{path=Path0,namedb=Namedb}=S) ->
 
287
    {Resp,Path,NewDb} = set_path(PathList, Path0, Namedb),
 
288
    {reply,Resp,rehash_cache(S#state{path=Path,namedb=NewDb})};
 
289
 
 
290
handle_call({del_path,Name}, {_From,_Tag},
 
291
            #state{path=Path0,namedb=Namedb}=S) ->
 
292
    {Resp,Path} = del_path(Name, Path0, Namedb),
 
293
    {reply,Resp,rehash_cache(S#state{path=Path})};
 
294
 
 
295
handle_call({replace_path,Name,Dir}, {_From,_Tag},
 
296
            #state{path=Path0,namedb=Namedb}=S) ->
 
297
    {Resp,Path} = replace_path(Name, Dir, Path0, Namedb),
 
298
    {reply,Resp,rehash_cache(S#state{path=Path})};
293
299
 
294
300
handle_call(rehash, {_From,_Tag}, S0) ->
295
301
    S = create_cache(S0),
311
317
    do_load_binary(Mod, File, Bin, Caller, S);
312
318
 
313
319
handle_call({load_native_partial,Mod,Bin}, {_From,_Tag}, S) ->
314
 
    Result = (catch hipe_unified_loader:load(Mod,Bin)),
 
320
    Result = (catch hipe_unified_loader:load(Mod, Bin)),
315
321
    Status = hipe_result_to_status(Result),
316
322
    {reply,Status,S};
317
323
 
318
324
handle_call({load_native_sticky,Mod,Bin,WholeModule}, {_From,_Tag}, S) ->
319
 
    Result = (catch hipe_unified_loader:load_module(Mod,Bin,WholeModule)),
 
325
    Result = (catch hipe_unified_loader:load_module(Mod, Bin, WholeModule)),
320
326
    Status = hipe_result_to_status(Result),
321
327
    {reply,Status,S};
322
328
 
384
390
handle_call({is_cached,_File}, {_From,_Tag}, S=#state{cache=no_cache}) ->
385
391
    {reply, no, S};
386
392
 
387
 
handle_call({set_primary_archive, File, ArchiveBin}, {_From,_Tag}, S=#state{mode=Mode}) ->
388
 
    case erl_prim_loader:set_primary_archive(File, ArchiveBin) of
 
393
handle_call({set_primary_archive, File, ArchiveBin, FileInfo}, {_From,_Tag}, S=#state{mode=Mode}) ->
 
394
    case erl_prim_loader:set_primary_archive(File, ArchiveBin, FileInfo) of
389
395
        {ok, Files} ->
390
396
            {reply, {ok, Mode, Files}, S};
391
 
        {error, Reason} ->
392
 
            {reply, {error, Reason}, S}
 
397
        {error, _Reason} = Error ->
 
398
            {reply, Error, S}
393
399
    end;
394
400
 
395
401
handle_call({is_cached,File}, {_From,_Tag}, S=#state{cache=Cache}) ->
469
475
filter_mods([File|Rest], Where, Exts, Dir, Cache) ->
470
476
    Ext = filename:extension(File),
471
477
    Root = list_to_atom(filename:rootname(File, Ext)),
472
 
    case lists:keysearch(Ext, 2, Exts) of
473
 
        {value,{Type,_}} ->
 
478
    case lists:keyfind(Ext, 2, Exts) of
 
479
        {Type, _} ->
474
480
            Key = {Type,Root},
475
481
            case Where of
476
482
                first ->
487
493
            ok
488
494
    end,
489
495
    filter_mods(Rest, Where, Exts, Dir, Cache);
490
 
 
491
496
filter_mods([], _, _, _, Cache) ->
492
497
    Cache.
493
498
 
498
503
%%
499
504
%% Create the initial path. 
500
505
%%
501
 
make_path(BundleDir,Bundles0) ->
 
506
make_path(BundleDir, Bundles0) ->
502
507
    Bundles = choose_bundles(Bundles0),
503
 
    make_path(BundleDir,Bundles,[],[]).
 
508
    make_path(BundleDir, Bundles, [], []).
504
509
 
505
510
choose_bundles(Bundles) ->
506
511
    ArchiveExt = archive_extension(),
507
 
    Bs = lists:sort([create_bundle(B,ArchiveExt) || B <- Bundles]),
 
512
    Bs = lists:sort([create_bundle(B, ArchiveExt) || B <- Bundles]),
508
513
    [FullName || {_Name,_NumVsn,FullName} <-
509
514
                     choose(lists:reverse(Bs), [], ArchiveExt)].
510
515
 
511
 
create_bundle(FullName,ArchiveExt) ->
512
 
    BaseName = filename:basename(FullName,ArchiveExt),
 
516
create_bundle(FullName, ArchiveExt) ->
 
517
    BaseName = filename:basename(FullName, ArchiveExt),
513
518
    case split(BaseName, "-") of
514
 
        Toks when length(Toks) > 1 ->
 
519
        [_, _|_] = Toks ->
515
520
            VsnStr = lists:last(Toks),
516
521
            case vsn_to_num(VsnStr) of
517
522
                {ok, VsnNum} ->
518
 
                    Name = join(lists:sublist(Toks,length(Toks)-1),"-"),
 
523
                    Name = join(lists:sublist(Toks, length(Toks)-1),"-"),
519
524
                    {Name,VsnNum,FullName};
520
525
                false ->
521
 
                    {FullName, [0], FullName}
 
526
                    {FullName,[0],FullName}
522
527
            end;
523
528
        _ ->
524
529
            {FullName,[0],FullName}
569
574
    [].
570
575
 
571
576
choose([{Name,NumVsn,NewFullName}=New|Bs], Acc, ArchiveExt) ->
572
 
    case lists:keysearch(Name,1,Acc) of
573
 
        {value, {_, NV, OldFullName}} when NV =:= NumVsn ->
 
577
    case lists:keyfind(Name, 1, Acc) of
 
578
        {_, NV, OldFullName} when NV =:= NumVsn ->
574
579
            case filename:extension(OldFullName) =:= ArchiveExt of
575
580
                false ->
576
581
                    choose(Bs,Acc, ArchiveExt);
578
583
                    Acc2 = lists:keystore(Name, 1, Acc, New),
579
584
                    choose(Bs,Acc2, ArchiveExt)
580
585
            end;
581
 
        {value, {_, _, _}} ->
 
586
        {_, _, _} ->
582
587
            choose(Bs,Acc, ArchiveExt);
583
588
        false ->
584
589
            choose(Bs,[{Name,NumVsn,NewFullName}|Acc], ArchiveExt)
602
607
            Ebin2 = filename:join([filename:dirname(Dir), Base ++ Ext, Base, "ebin"]),
603
608
            Ebins = 
604
609
                case split(Base, "-") of
605
 
                    Toks when length(Toks) > 1 ->
606
 
                        AppName = join(lists:sublist(Toks,length(Toks)-1),"-"),
 
610
                    [_, _|_] = Toks ->
 
611
                        AppName = join(lists:sublist(Toks, length(Toks)-1),"-"),
607
612
                        Ebin3 = filename:join([filename:dirname(Dir), Base ++ Ext, AppName, "ebin"]),
608
613
                        [Ebin3, Ebin2, Dir];
609
614
                    _ ->
835
840
%% then the table is created :-)
836
841
%%
837
842
do_add(first,Dir,Path,NameDb) ->
838
 
    update(Dir,NameDb),
 
843
    update(Dir, NameDb),
839
844
    [Dir|lists:delete(Dir,Path)];
840
845
do_add(last,Dir,Path,NameDb) ->
841
846
    case lists:member(Dir,Path) of
842
847
        true ->
843
848
            Path;
844
849
        false ->
845
 
            maybe_update(Dir,NameDb),
 
850
            maybe_update(Dir, NameDb),
846
851
            Path ++ [Dir]
847
852
    end.
848
853
 
849
854
%% Do not update if the same name already exists !
850
 
maybe_update(Dir,NameDb) ->
851
 
    case lookup_name(get_name(Dir),NameDb) of
852
 
        false -> update(Dir,NameDb);
853
 
        _     -> false
854
 
    end.
 
855
maybe_update(Dir, NameDb) ->
 
856
    (lookup_name(get_name(Dir), NameDb) =:= false) andalso update(Dir, NameDb).
855
857
 
856
858
update(_Dir, false) ->
857
 
    ok;
858
 
update(Dir,NameDb) ->
859
 
    replace_name(Dir,NameDb).
860
 
 
861
 
 
 
859
    true;
 
860
update(Dir, NameDb) ->
 
861
    replace_name(Dir, NameDb).
862
862
 
863
863
%%
864
864
%% Set a completely new path.
946
946
    Base = filename:basename(AppDir),
947
947
    Dirs = 
948
948
        case split(Base, "-") of
949
 
            Toks when length(Toks) > 1 ->
950
 
                Base2 = join(lists:sublist(Toks,length(Toks)-1),"-"),
 
949
            [_, _|_] = Toks ->
 
950
                Base2 = join(lists:sublist(Toks, length(Toks)-1), "-"),
951
951
                [Base2, Base];
952
952
            _ ->
953
953
                [Base]
1060
1060
            {error,bad_name}
1061
1061
    end.
1062
1062
 
1063
 
 
1064
1063
del_ebin(Dir) ->
1065
1064
    case filename:basename(Dir) of
1066
1065
        "ebin" -> 
1079
1078
            Dir
1080
1079
    end.
1081
1080
 
1082
 
 
1083
 
 
1084
1081
replace_name(Dir, Db) ->
1085
1082
    case get_name(Dir) of
1086
1083
        Dir ->
1187
1184
get_mods([], _) -> [].
1188
1185
 
1189
1186
is_sticky(Mod, Db) ->
1190
 
    case erlang:module_loaded(Mod) of
1191
 
        true ->
1192
 
            case ets:lookup(Db, {sticky,Mod}) of
1193
 
                [] -> false;
1194
 
                _  -> true
1195
 
            end;
1196
 
        false ->
1197
 
            false
1198
 
    end.
 
1187
    erlang:module_loaded(Mod) andalso (ets:lookup(Db, {sticky, Mod}) =/= []).
1199
1188
 
1200
1189
add_paths(Where,[Dir|Tail],Path,NameDb) ->
1201
1190
    {_,NPath} = add_path(Where,Dir,Path,NameDb),
1203
1192
add_paths(_,_,Path,_) ->
1204
1193
    {ok,Path}.
1205
1194
 
1206
 
 
1207
1195
do_load_binary(Module, File, Binary, Caller, St) ->
1208
1196
    case modp(Module) andalso modp(File) andalso is_binary(Binary) of
1209
1197
        true ->
1220
1208
modp(List) when is_list(List) -> int_list(List);
1221
1209
modp(_)                       -> false.
1222
1210
 
1223
 
 
1224
1211
load_abs(File, Mod0, Caller, St) ->
1225
1212
    Ext = objfile_extension(),
1226
1213
    FileName0 = lists:concat([File, Ext]),
1263
1250
            {reply,{error,sticky_directory},St};
1264
1251
        false ->
1265
1252
            case catch load_native_code(Mod, Bin) of
1266
 
                {module,Mod} ->
 
1253
                {module,Mod} = Module ->
1267
1254
                    ets:insert(Db, {Mod,File}),
1268
 
                    {reply,{module,Mod},St};
 
1255
                    {reply,Module,St};
1269
1256
                no_native ->
1270
1257
                    case erlang:load_module(Mod, Bin) of
1271
 
                        {module,Mod} ->
 
1258
                        {module,Mod} = Module ->
1272
1259
                            ets:insert(Db, {Mod,File}),
1273
1260
                            post_beam_load(Mod),
1274
 
                            {reply,{module,Mod},St};
 
1261
                            {reply,Module,St};
1275
1262
                        {error,on_load} ->
1276
1263
                            handle_on_load(Mod, File, Caller, St);
1277
 
                        {error,What} ->
 
1264
                        {error,What} = Error ->
1278
1265
                            error_msg("Loading of ~s failed: ~p\n", [File, What]),
1279
 
                            {reply,{error,What},St}
 
1266
                            {reply,Error,St}
1280
1267
                    end;
1281
1268
                Error ->
1282
1269
                    error_msg("Native loading of ~s failed: ~p\n",
1479
1466
    end.
1480
1467
 
1481
1468
finish_on_load_1(Mod, File, OnLoadRes, WaitingPids, Db) ->
1482
 
    Keep = if
1483
 
               is_boolean(OnLoadRes) -> OnLoadRes;
1484
 
               true -> false
1485
 
           end,
 
1469
    Keep = OnLoadRes =:= ok,
1486
1470
    erlang:finish_after_on_load(Mod, Keep),
1487
1471
    Res = case Keep of
1488
 
              false -> {error,on_load_failure};
 
1472
              false ->
 
1473
                  finish_on_load_report(Mod, OnLoadRes),
 
1474
                  {error,on_load_failure};
1489
1475
              true ->
1490
1476
                  ets:insert(Db, {Mod,File}),
1491
1477
                  {module,Mod}
1493
1479
    [reply(Pid, Res) || Pid <- WaitingPids],
1494
1480
    ok.
1495
1481
 
 
1482
finish_on_load_report(_Mod, Atom) when is_atom(Atom) ->
 
1483
    %% No error reports for atoms.
 
1484
    ok;
 
1485
finish_on_load_report(Mod, Term) ->
 
1486
    %% Play it very safe here. The error_logger module and
 
1487
    %% modules it depend on may not be loaded yet and there
 
1488
    %% would be a dead-lock if we called it directly
 
1489
    %% from the code_server process.
 
1490
    spawn(fun() ->
 
1491
                  F = "The on_load function for module "
 
1492
                      "~s returned ~P\n",
 
1493
 
 
1494
                  %% Express the call as an apply to simplify
 
1495
                  %% the ext_mod_dep/1 test case.
 
1496
                  E = error_logger,
 
1497
                  E:warning_msg(F, [Mod,Term,10])
 
1498
          end).
 
1499
 
1496
1500
%% -------------------------------------------------------
1497
1501
%% Internal functions.
1498
1502
%% -------------------------------------------------------