~ubuntu-branches/debian/squeeze/erlang/squeeze

« back to all changes in this revision

Viewing changes to lib/kernel/src/init.erl

  • Committer: Bazaar Package Importer
  • Author(s): Erlang Packagers, Sergei Golovan
  • Date: 2006-12-03 17:07:44 UTC
  • mfrom: (2.1.11 feisty)
  • Revision ID: james.westby@ubuntu.com-20061203170744-rghjwupacqlzs6kv
Tags: 1:11.b.2-4
[ Sergei Golovan ]
Fixed erlang-base and erlang-base-hipe prerm scripts.

Show diffs side-by-side

added added

removed removed

Lines of Context:
52
52
-deprecated([{get_args,0}]).
53
53
 
54
54
% internal exports
55
 
-export([fetch_loaded/0,ensure_loaded/1,make_permanent/2]).
 
55
-export([fetch_loaded/0,ensure_loaded/1,make_permanent/2,
 
56
         notify_when_started/1,wait_until_started/0]).
56
57
 
57
58
% old interface functions kept for backward compability.
58
59
-export([get_flag/1,get_flags/0]).
65
66
                bootpid,
66
67
                status = {starting, starting},
67
68
                script_id = [],
68
 
                loaded = []}).
 
69
                loaded = [],
 
70
                subscribed = []}).
69
71
 
70
72
get_arguments() ->
71
73
    request(get_arguments).
79
81
script_id() ->
80
82
    request(script_id).
81
83
 
82
 
bs2as(L0) when list(L0) ->
 
84
bs2as(L0) when is_list(L0) ->
83
85
    map(fun b2a/1, L0);
84
86
bs2as(L) ->
85
87
    L.
86
88
 
87
 
bs2ss(L0) when list(L0) ->
 
89
bs2ss(L0) when is_list(L0) ->
88
90
    map(fun b2s/1, L0);
89
91
bs2ss(L) ->
90
92
    L.
112
114
make_permanent(Boot,Config) ->
113
115
    request({make_permanent,Boot,Config}).
114
116
 
 
117
notify_when_started(Pid) ->
 
118
    request({notify_when_started,Pid}).
 
119
 
 
120
wait_until_started() ->
 
121
    receive 
 
122
        {init,started} -> ok 
 
123
    end.            
 
124
 
115
125
request(Req) ->
116
126
    init ! {self(),Req},
117
127
    receive 
131
141
    Flags0 = flags_to_atoms_again(Flags),
132
142
    boot(Start,Flags0,Args).
133
143
 
 
144
prepare_run_args({eval, [Expr]}) ->
 
145
    {eval,Expr};
134
146
prepare_run_args({_, L=[]}) ->
135
147
    bs2as(L);
136
148
prepare_run_args({_, L=[_]}) ->
140
152
prepare_run_args({run, [M,F|Args]}) ->
141
153
    [b2a(M), b2a(F) | bs2ss(Args)].
142
154
 
143
 
b2a(Bin) when binary(Bin) ->
 
155
b2a(Bin) when is_binary(Bin) ->
144
156
    list_to_atom(binary_to_list(Bin));
145
 
b2a(A) when atom(A) ->
 
157
b2a(A) when is_atom(A) ->
146
158
    A.
147
159
 
148
 
b2s(Bin) when binary(Bin) ->
 
160
b2s(Bin) when is_binary(Bin) ->
149
161
    binary_to_list(Bin);
150
 
b2s(L) when list(L) ->
 
162
b2s(L) when is_list(L) ->
151
163
    L.
152
164
 
153
165
map(_F, []) ->
182
194
    boot_loop(BootPid,State).
183
195
 
184
196
%%% Convert a term to a printable string, if possible.
185
 
to_string(X) when list(X) ->                    % assume string
 
197
to_string(X) when is_list(X) ->                 % assume string
186
198
    F = flatten(X, []),
187
199
    case printable_list(F) of
188
200
        true ->  F;
189
201
        false -> ""
190
202
    end;
191
 
to_string(X) when atom(X) ->
 
203
to_string(X) when is_atom(X) ->
192
204
    atom_to_list(X);
193
 
to_string(X) when pid(X) ->
 
205
to_string(X) when is_pid(X) ->
194
206
    pid_to_list(X);
195
 
to_string(X) when float(X) ->
 
207
to_string(X) when is_float(X) ->
196
208
    float_to_list(X);
197
 
to_string(X) when integer(X) ->
 
209
to_string(X) when is_integer(X) ->
198
210
    integer_to_list(X);
199
211
to_string(_X) ->
200
212
    "".                                         % can't do anything with it
202
214
%% This is an incorrect and narrow definition of printable characters.
203
215
%% The correct one is in io_lib:printable_list/1
204
216
%%
205
 
printable_list([H|T]) when integer(H), H >= 32, H =< 126 ->
 
217
printable_list([H|T]) when is_integer(H), H >= 32, H =< 126 ->
206
218
    printable_list(T);
207
219
printable_list([$\n|T]) -> printable_list(T);
208
220
printable_list([$\r|T]) -> printable_list(T);
210
222
printable_list([]) -> true;
211
223
printable_list(_) ->  false.
212
224
 
213
 
flatten([H|T], Tail) when list(H) ->
 
225
flatten([H|T], Tail) when is_list(H) ->
214
226
    flatten(H, flatten(T, Tail));
215
227
flatten([H|T], Tail) ->
216
228
    [H|flatten(T, Tail)];
217
229
flatten([], Tail) ->
218
230
    Tail.
219
231
 
220
 
    
221
232
things_to_string([X|Rest]) ->
222
233
    " (" ++ to_string(X) ++ ")" ++ things_to_string(Rest);
223
234
things_to_string([]) ->
224
235
    "".
225
236
 
226
 
halt_string(String, List) when list(List) ->
227
 
    String ++ things_to_string(List);
228
 
%% Just in case someone forgot to listify the argument:
229
237
halt_string(String, List) ->
230
 
    String ++ things_to_string([List]).
231
 
 
 
238
    HaltString = String ++ things_to_string(List),
 
239
    if
 
240
        length(HaltString)<199 -> HaltString;
 
241
        true -> first198(HaltString, 198)
 
242
    end.
 
243
 
 
244
first198([H|T], N) when N>0 ->
 
245
    [H|first198(T, N-1)];
 
246
first198(_, 0) ->
 
247
    [].
 
248
 
 
249
%% String = string()
 
250
%% List = [string() | atom() | pid() | number()]
 
251
%% Any other items in List, such as tuples, are ignored when creating
 
252
%% the string used as argument to erlang:halt/1.
232
253
crash(String, List) ->
233
254
    halt(halt_string(String, List)).
234
255
 
240
261
            boot_loop(BootPid,State#state{loaded = [ModLoaded|Loaded]});
241
262
        {BootPid,started,KernelPid} ->
242
263
            boot_loop(BootPid, new_kernelpid(KernelPid, BootPid, State));
 
264
        {BootPid,progress,started} ->
 
265
            {InS,_} = State#state.status,
 
266
            notify(State#state.subscribed),
 
267
            boot_loop(BootPid,State#state{status = {InS,started},
 
268
                                          subscribed = []});
243
269
        {BootPid,progress,NewStatus} ->
244
270
            {InS,_} = State#state.status,
245
271
            boot_loop(BootPid,State#state{status = {InS,NewStatus}});
247
273
            boot_loop(BootPid,State#state{script_id = Id});
248
274
        {'EXIT',BootPid,normal} ->
249
275
            {_,PS} = State#state.status,
250
 
            loop(State#state{status = {started,PS}});
 
276
            notify(State#state.subscribed),
 
277
            loop(State#state{status = {started,PS},
 
278
                             subscribed = []});
251
279
        {'EXIT',BootPid,Reason} ->
252
280
            erlang:display({"init terminating in do_boot",Reason}),
253
281
            crash("init terminating in do_boot", [Reason]);
260
288
        {From,fetch_loaded} ->   %% Fetch and reset initially loaded modules.
261
289
            From ! {init,State#state.loaded},
262
290
            garb_boot_loop(BootPid,State#state{loaded = []});
263
 
        {From, {ensure_loaded, Module}} ->
 
291
        {From,{ensure_loaded,Module}} ->
264
292
            {Res, Loaded} = ensure_loaded(Module, State#state.loaded),
265
 
            From ! {init, Res},
 
293
            From ! {init,Res},
266
294
            boot_loop(BootPid,State#state{loaded = Loaded});
267
295
        Msg ->
268
296
            boot_loop(BootPid,handle_msg(Msg,State))
277
305
            {Res, Loaded}
278
306
    end.
279
307
 
 
308
%% Tell subscribed processes the system has started.
 
309
notify(Pids) ->
 
310
    lists:foreach(fun(Pid) -> Pid ! {init,started} end, Pids).                   
 
311
 
280
312
%% Garbage collect all info about initially loaded modules.
281
313
%% This information is temporary stored until the code_server
282
314
%% is started.
289
321
    garbage_collect(),
290
322
    boot_loop(BootPid,State).
291
323
 
292
 
new_kernelpid({Name,{ok,Pid}},BootPid,State) when pid(Pid) ->
 
324
new_kernelpid({Name,{ok,Pid}},BootPid,State) when is_pid(Pid) ->
293
325
    link(Pid),
294
326
    BootPid ! {self(),ok,Pid},
295
327
    Kernel = State#state.kernel,
333
365
    #state{flags = Flags,
334
366
           status = Status,
335
367
           script_id = Sid,
336
 
           args = Args} = State,
 
368
           args = Args,
 
369
           subscribed = Subscribed} = State,
337
370
    case Msg of
338
371
        {From,get_plain_arguments} ->
339
372
            From ! {init,Args};
362
395
            end;
363
396
        {From,get_flags} -> % Old interface 
364
397
            From ! {init,values_to_atoms_again(Flags)};
 
398
        {From,{notify_when_started,Pid}} ->
 
399
            case Status of
 
400
                {InS,PS} when InS == started ; PS == started ->
 
401
                    From ! {init,started};
 
402
                _ ->
 
403
                    From ! {init,ok},
 
404
                    {new_state,State#state{subscribed = [Pid|Subscribed]}}
 
405
            end;
365
406
        X ->
366
407
            case whereis(user) of
367
408
                undefined ->
397
438
 
398
439
set_flag(_Flag,false,Flags) ->
399
440
    {ok,Flags};
400
 
set_flag(Flag,Value,Flags) when list(Value) ->
 
441
set_flag(Flag,Value,Flags) when is_list(Value) ->
401
442
    case catch list_to_binary(Value) of
402
443
        {'EXIT',_} ->
403
444
            {error,badarg};
442
483
            %% As heart survives a restart the Parent of heart is init.
443
484
            BootPid = self(),
444
485
            %% ignore timeout
445
 
            shutdown_kernel_pid(Pid,BootPid,shutdown,self(),State) 
 
486
            shutdown_kernel_pid(Pid, BootPid, self(), State) 
446
487
    end.
447
488
 
448
489
shutdown_pids(Heart,BootPid,State) ->
458
499
 
459
500
 
460
501
shutdown([{heart,_Pid}|Kernel],BootPid,Timer,State) ->
461
 
    shutdown(Kernel,BootPid,Timer,State);
 
502
    shutdown(Kernel, BootPid, Timer, State);
462
503
shutdown([{_Name,Pid}|Kernel],BootPid,Timer,State) ->
463
 
    shutdown_kernel_pid(Pid,BootPid,shutdown,Timer,State),
 
504
    shutdown_kernel_pid(Pid, BootPid, Timer, State),
464
505
    shutdown(Kernel,BootPid,Timer,State);
465
506
shutdown(_,_,_,_) ->
466
507
    true.
469
510
%%
470
511
%% A kernel pid must handle the special case message
471
512
%% {'EXIT',Parent,Reason} and terminate upon it!
472
 
shutdown_kernel_pid(Pid,_BootPid,kill,_,_) ->
473
 
    exit(Pid,kill);
474
 
shutdown_kernel_pid(Pid,BootPid,Reason,Timer,State) ->
475
 
    Pid ! {'EXIT',BootPid,Reason},
476
 
    shutdown_loop(Pid,Timer,State,[]).
 
513
%%
 
514
shutdown_kernel_pid(Pid, BootPid, Timer, State) ->
 
515
    Pid ! {'EXIT',BootPid,shutdown},
 
516
    shutdown_loop(Pid, Timer, State, []).
477
517
 
478
518
%%
479
519
%% We have to handle init requests here in case a process
480
520
%% performs such a request and cannot shutdown (deadlock).
481
 
%% Keep all other exit messages in case it was another
482
 
%% kernel process. Resend this messages and handle later.
 
521
%% Keep all other EXIT messages in case it was another
 
522
%% kernel process. Resend these messages and handle later.
483
523
%%
484
524
shutdown_loop(Pid,Timer,State,Exits) ->
485
525
    receive
542
582
%% Kill all existing ports in the system (except the heart port),
543
583
%% i.e. ports still existing after all processes have been killed.
544
584
%%
545
 
%% If we are running the threaded system with the async driver,
546
 
%% then let the port (created by the system) stays around.
 
585
%% System ports like the async driver port will nowadays be immortal;
 
586
%% therefore, it is ok to send them exit signals...
547
587
%%
548
588
kill_all_ports(Heart) ->
549
589
    kill_all_ports(Heart,erlang:ports()).
553
593
        {connected,Heart} ->
554
594
            kill_all_ports(Heart,Ps);
555
595
        _ ->
556
 
            case erlang:port_info(P, name) of
557
 
                {name, "async"} ->
558
 
                    kill_all_ports(Heart,Ps);
559
 
                _ ->
560
 
                    exit(P,kill),
561
 
                    kill_all_ports(Heart,Ps)
562
 
            end
 
596
            exit(P,kill),
 
597
            kill_all_ports(Heart,Ps)
563
598
    end;
564
599
kill_all_ports(_,_) ->
565
600
    ok.
714
749
    case erl_prim_loader:get_file(BootFile) of
715
750
        {ok,Bin,_} ->
716
751
            case binary_to_term(Bin) of
717
 
                {script,Id,CmdList} when list(CmdList) ->
 
752
                {script,Id,CmdList} when is_list(CmdList) ->
718
753
                    init ! {self(),{script_id,Id}}, % ;-)
719
754
                    {ok, CmdList};
720
755
                _ ->
750
785
eval_script([{kernel_load_completed}|CfgL],Init,PathFs,Vars,P,{_,E,Par},Deb) ->
751
786
    eval_script(CfgL,Init,PathFs,Vars,P,{false,E,Par},Deb);
752
787
eval_script([{primLoad,Mods}|CfgL],Init,PathFs,Vars,P,{true,E,Par},Deb)
753
 
  when list(Mods) ->
 
788
  when is_list(Mods) ->
754
789
    if 
755
790
        Par == true ->
756
791
            par_load_modules(Mods,Init);
827
862
%% starting with $xxx/, expand $xxx to the value supplied with -boot_var!
828
863
%% If $xxx cannot be expanded this process terminates.
829
864
 
830
 
fix_path([Path|Ps], Vars) when atom(Path) ->
 
865
fix_path([Path|Ps], Vars) when is_atom(Path) ->
831
866
    [add_var(atom_to_list(Path), Vars)|fix_path(Ps, Vars)];
832
867
fix_path([Path|Ps], Vars) ->
833
868
    [add_var(Path, Vars)|fix_path(Ps, Vars)];
882
917
%% Disadvantage: anything started with -s that does not
883
918
%% eventually spawn will hang the startup routine.
884
919
 
 
920
%% We also handle -eval here. The argument is an arbitrary
 
921
%% expression that should be parsed and evaluated.
 
922
 
885
923
start_em([S|Tail]) ->
886
924
    case whereis(user) of
887
925
        undefined -> 
888
926
            ok;
889
 
        P when pid(P) ->                        %Let's set the group_leader()
 
927
        P when is_pid(P) ->                     %Let's set the group_leader()
890
928
            erlang:group_leader(P, self())
891
929
    end,
892
930
    start_it(S),
895
933
 
896
934
start_it([]) -> 
897
935
    ok;
 
936
start_it({eval,Bin}) ->
 
937
    Str = binary_to_list(Bin),
 
938
    {ok,Ts,_} = erl_scan:string(Str),
 
939
    Ts1 = case reverse(Ts) of
 
940
              [{dot,_}|_] -> Ts;
 
941
              TsR -> reverse([{dot,1} | TsR])
 
942
          end,
 
943
    {ok,Expr} = erl_parse:parse_exprs(Ts1),
 
944
    erl_eval:exprs(Expr, []),
 
945
    ok;
898
946
start_it([_|_]=MFA) ->
899
947
    Ref = make_ref(),
900
948
    case catch {Ref,case MFA of
946
994
            self();
947
995
        Time ->
948
996
            case catch list_to_integer(binary_to_list(Time)) of
949
 
                T when integer(T) ->
 
997
                T when is_integer(T) ->
950
998
                    Pid = spawn(fun() -> timer(T) end),
951
999
                    receive
952
1000
                        {Pid, started} ->
988
1036
        start_arg2 ->
989
1037
            {S,Rest} = get_args(Bs, []),
990
1038
            parse_boot_args(Rest, [{run, S}|Ss], Fs, As);
 
1039
        eval_arg ->
 
1040
            {Expr,Rest} = get_args(Bs, []),
 
1041
            parse_boot_args(Rest, [{eval, Expr}|Ss], Fs, As);
991
1042
        flag ->
992
1043
            {F,Rest} = get_args(Bs, []),
993
1044
            Fl = case F of
1007
1058
check(<<"-extra">>) -> start_extra_arg;
1008
1059
check(<<"-s">>) -> start_arg;
1009
1060
check(<<"-run">>) -> start_arg2;
 
1061
check(<<"-eval">>) -> eval_arg;
1010
1062
check(<<"--">>) -> end_args;
1011
 
check(X) when binary(X) ->
 
1063
check(X) when is_binary(X) ->
1012
1064
    case binary_to_list(X) of
1013
1065
        [$-|_Rest] -> flag;
1014
1066
        _Chars     -> arg                       %Even empty atoms
1020
1072
        start_extra_arg -> {reverse(As), [B|Bs]};
1021
1073
        start_arg -> {reverse(As), [B|Bs]};
1022
1074
        start_arg2 -> {reverse(As), [B|Bs]};
 
1075
        eval_arg -> {reverse(As), [B|Bs]};
1023
1076
        end_args -> {reverse(As), Bs};
1024
1077
        flag -> {reverse(As), [B|Bs]};
1025
1078
        arg ->
1080
1133
%%
1081
1134
get_flag_args(F,Flags) -> get_flag_args(F,Flags,[]).
1082
1135
 
1083
 
get_flag_args(F,[{F,V}|Flags],Acc) when list(V) ->
 
1136
get_flag_args(F,[{F,V}|Flags],Acc) when is_list(V) ->
1084
1137
    get_flag_args(F,Flags,[V|Acc]);
1085
1138
get_flag_args(F,[{F,V}|Flags],Acc) ->
1086
1139
    get_flag_args(F,Flags,[[V]|Acc]);
1098
1151
get_arguments([]) ->
1099
1152
    [].
1100
1153
 
1101
 
to_strings([H|T]) when atom(H) -> [atom_to_list(H)|to_strings(T)];
1102
 
to_strings([H|T]) when binary(H) -> [binary_to_list(H)|to_strings(T)];
 
1154
to_strings([H|T]) when is_atom(H) -> [atom_to_list(H)|to_strings(T)];
 
1155
to_strings([H|T]) when is_binary(H) -> [binary_to_list(H)|to_strings(T)];
1103
1156
to_strings([])    -> [].
1104
1157
 
1105
1158
get_argument(Arg,Flags) ->
1127
1180
set_argument([],Flag,Value) ->
1128
1181
    [{Flag,[Value]}].
1129
1182
 
1130
 
concat([A|T]) when atom(A) ->                   %Atom
1131
 
    append(atom_to_list(A), concat(T));
1132
 
concat([C|T]) when C >= 0, C =< 255 ->
 
1183
concat([A|T]) when is_atom(A) ->
 
1184
    atom_to_list(A) ++ concat(T);
 
1185
concat([C|T]) when is_integer(C), 0 =< C, C =< 255 ->
1133
1186
    [C|concat(T)];
1134
 
concat([S|T]) ->                                %String
1135
 
    append(S, concat(T));
 
1187
concat([Bin|T]) when is_binary(Bin) ->
 
1188
    binary_to_list(Bin) ++ concat(T);
 
1189
concat([S|T]) ->
 
1190
    S ++ concat(T);
1136
1191
concat([]) ->
1137
1192
    [].
1138
1193
 
1150
1205
    reverse(T, [H|Y]);
1151
1206
reverse([], X) -> X.
1152
1207
                        
1153
 
search(Key, [H|_T]) when tuple(H), element(1, H) == Key ->
 
1208
search(Key, [H|_T]) when is_tuple(H), element(1, H) == Key ->
1154
1209
    {value, H};
1155
1210
search(Key, [_|T]) -> search(Key, T);
1156
1211
search(_Key, []) -> false.
1157
1212
 
1158
 
extension() -> 
1159
 
    case erlang:system_info(machine) of
1160
 
        "JAM" -> ".jam";
1161
 
        "VEE" -> ".vee";
1162
 
        "BEAM" -> ".beam"
1163
 
    end.
 
1213
extension() ->
 
1214
    ".beam".
 
1215
%%    case erlang:system_info(machine) of
 
1216
%%      "JAM" -> ".jam";
 
1217
%%      "VEE" -> ".vee";
 
1218
%%      "BEAM" -> ".beam"
 
1219
%%    end.