~rdoering/ubuntu/karmic/erlang/fix-535090

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-02-15 16:42:52 UTC
  • mfrom: (3.1.2 squeeze)
  • Revision ID: james.westby@ubuntu.com-20090215164252-q5x4rcf8a5pbesb1
Tags: 1:12.b.5-dfsg-2
Upload to unstable after lenny is released.

Show diffs side-by-side

added added

removed removed

Lines of Context:
31
31
%%                         (Optional - default efile)
32
32
%%        -hosts [Node]  : List of hosts from which we can boot.
33
33
%%                         (Mandatory if -loader inet or ose_inet)
34
 
%%        -mode embedded : Load all modules at startup, no automatic
35
 
%%                         loading
36
 
%%        -mode interactive : Auto. load modules (default system behaviour).
 
34
%%        -mode embedded : Load all modules at startup, no automatic loading
 
35
%%        -mode interactive : Auto load modules (default system behaviour).
37
36
%%        -path          : Override path in bootfile.
38
37
%%        -pa Path+      : Add my own paths first.
39
38
%%        -pz Path+      : Add my own paths last.
40
39
%%        -run           : Start own processes.
41
40
%%        -s             : Start own processes.
42
41
%% 
43
 
%%
44
 
%% 
 
42
%% Experimental flags:
 
43
%%        -init_debug      : Activate debug printouts in init
 
44
%%        -loader_debug    : Activate debug printouts in erl_prim_loader
 
45
%%        -code_path_choice : strict | relaxed
45
46
 
46
47
-module(init).
 
48
 
47
49
-export([restart/0,reboot/0,stop/0,stop/1,
48
50
         get_status/0,boot/1,get_arguments/0,get_plain_arguments/0,
49
51
         get_argument/1,script_id/0]).
50
52
 
51
53
% internal exports
52
54
-export([fetch_loaded/0,ensure_loaded/1,make_permanent/2,
53
 
         notify_when_started/1,wait_until_started/0]).
 
55
         notify_when_started/1,wait_until_started/0, 
 
56
         objfile_extension/0, archive_extension/0,code_path_choice/0]).
 
57
 
 
58
%% Internal function. Exported to avoid dialyzer warnings
 
59
-export([join/2]).
 
60
 
 
61
-include_lib("kernel/include/file.hrl").
54
62
 
55
63
-record(state, {flags = [],
56
64
                args = [],
62
70
                loaded = [],
63
71
                subscribed = []}).
64
72
 
 
73
debug(false, _) -> ok;
 
74
debug(_, T)     -> erlang:display(T).
 
75
 
65
76
get_arguments() ->
66
77
    request(get_arguments).
67
78
 
162
173
    F = b2a(F0),
163
174
    [{F}|flags_to_atoms_again(Rest)].
164
175
 
 
176
code_path_choice() ->
 
177
    case get_argument(code_path_choice) of
 
178
        {ok,[["strict"]]} ->
 
179
            strict;
 
180
        {ok,[["relaxed"]]} ->
 
181
            relaxed;
 
182
        _Else ->
 
183
            strict
 
184
    end.
 
185
 
165
186
boot(Start,Flags,Args) ->
166
187
    BootPid = do_boot(Flags,Start),
167
188
    State = #state{flags = Flags,
274
295
    end.
275
296
 
276
297
ensure_loaded(Module, Loaded) ->
277
 
    File = concat([Module,extension()]),
 
298
    File = concat([Module,objfile_extension()]),
278
299
    case catch load_mod(Module,File) of
279
300
        {ok, FullName} ->
280
301
            {{module, Module}, [{Module, FullName}|Loaded]};
671
692
                             bs2ss(Path),PathFls),
672
693
    BootFile = bootfile(Flags,Root),
673
694
    BootList = get_boot(BootFile,Root),
674
 
    Embedded = b2a(get_flag('-mode',Flags,false)),
 
695
    LoadMode = b2a(get_flag('-mode',Flags,false)),
675
696
    Deb = b2a(get_flag('-init_debug',Flags,false)),
676
697
    BootVars = get_flag_args('-boot_var',Flags),
677
698
    ParallelLoad = 
678
699
        (Pgm =:= "efile") and (erlang:system_info(thread_pool_size) > 0),
 
700
 
 
701
    PathChoice = code_path_choice(),
679
702
    eval_script(BootList,Init,PathFls,{Root,BootVars},Path,
680
 
                {true,Embedded,ParallelLoad},Deb),
 
703
                {true,LoadMode,ParallelLoad},Deb,PathChoice),
681
704
 
682
705
    %% To help identifying Purify windows that pop up,
683
706
    %% print the node name into the Purify log.
733
756
%% boot process hangs (we want to ensure syncronicity).
734
757
%%
735
758
 
736
 
eval_script([{progress,Info}|CfgL],Init,PathFs,Vars,P,Ph,Deb) ->
 
759
eval_script([{progress,Info}|CfgL],Init,PathFs,Vars,P,Ph,Deb,PathChoice) ->
737
760
    debug(Deb,{progress,Info}),
738
761
    init ! {self(),progress,Info},
739
 
    eval_script(CfgL,Init,PathFs,Vars,P,Ph,Deb);
740
 
eval_script([{preLoaded,_}|CfgL],Init,PathFs,Vars,P,Ph,Deb) ->
741
 
    eval_script(CfgL,Init,PathFs,Vars,P,Ph,Deb);
742
 
eval_script([{path,Path}|CfgL],Init,{Pa,Pz},Vars,false,Ph,Deb) ->
743
 
    RealPath = make_path(Pa, Pz, Path, Vars),
 
762
    eval_script(CfgL,Init,PathFs,Vars,P,Ph,Deb,PathChoice);
 
763
eval_script([{preLoaded,_}|CfgL],Init,PathFs,Vars,P,Ph,Deb,PathChoice) ->
 
764
    eval_script(CfgL,Init,PathFs,Vars,P,Ph,Deb,PathChoice);
 
765
eval_script([{path,Path}|CfgL],Init,{Pa,Pz},Vars,false,Ph,Deb,PathChoice) ->
 
766
    RealPath0 = make_path(Pa, Pz, Path, Vars),
 
767
    RealPath = patch_path(RealPath0, PathChoice),
744
768
    erl_prim_loader:set_path(RealPath),
745
 
    eval_script(CfgL,Init,{Pa,Pz},Vars,false,Ph,Deb);
746
 
eval_script([{path,_}|CfgL],Init,PathFs,Vars,P,Ph,Deb) ->
 
769
    eval_script(CfgL,Init,{Pa,Pz},Vars,false,Ph,Deb,PathChoice);
 
770
eval_script([{path,_}|CfgL],Init,PathFs,Vars,P,Ph,Deb,PathChoice) ->
747
771
    %% Ignore, use the command line -path flag.
748
 
    eval_script(CfgL,Init,PathFs,Vars,P,Ph,Deb);
749
 
eval_script([{kernel_load_completed}|CfgL],Init,PathFs,Vars,P,{_,embedded,Par},Deb) ->
750
 
 
751
 
    eval_script(CfgL,Init,PathFs,Vars,P,{true,embedded,Par},Deb);
752
 
eval_script([{kernel_load_completed}|CfgL],Init,PathFs,Vars,P,{_,E,Par},Deb) ->
753
 
    eval_script(CfgL,Init,PathFs,Vars,P,{false,E,Par},Deb);
754
 
eval_script([{primLoad,Mods}|CfgL],Init,PathFs,Vars,P,{true,E,Par},Deb)
 
772
    eval_script(CfgL,Init,PathFs,Vars,P,Ph,Deb,PathChoice);
 
773
eval_script([{kernel_load_completed}|CfgL],Init,PathFs,Vars,P,{_,embedded,Par},Deb,PathChoice) ->
 
774
    eval_script(CfgL,Init,PathFs,Vars,P,{true,embedded,Par},Deb,PathChoice);
 
775
eval_script([{kernel_load_completed}|CfgL],Init,PathFs,Vars,P,{_,E,Par},Deb,PathChoice) ->
 
776
    eval_script(CfgL,Init,PathFs,Vars,P,{false,E,Par},Deb,PathChoice);
 
777
eval_script([{primLoad,Mods}|CfgL],Init,PathFs,Vars,P,{true,E,Par},Deb,PathChoice)
755
778
  when is_list(Mods) ->
756
779
    if 
757
780
        Par =:= true ->
759
782
        true ->
760
783
            load_modules(Mods)
761
784
    end,
762
 
    eval_script(CfgL,Init,PathFs,Vars,P,{true,E,Par},Deb);
763
 
eval_script([{primLoad,_Mods}|CfgL],Init,PathFs,Vars,P,{false,E,Par},Deb) ->
 
785
    eval_script(CfgL,Init,PathFs,Vars,P,{true,E,Par},Deb,PathChoice);
 
786
eval_script([{primLoad,_Mods}|CfgL],Init,PathFs,Vars,P,{false,E,Par},Deb,PathChoice) ->
764
787
    %% Do not load now, code_server does that dynamically!
765
 
    eval_script(CfgL,Init,PathFs,Vars,P,{false,E,Par},Deb);
 
788
    eval_script(CfgL,Init,PathFs,Vars,P,{false,E,Par},Deb,PathChoice);
766
789
eval_script([{kernelProcess,Server,{Mod,Fun,Args}}|CfgL],Init,
767
 
            PathFs,Vars,P,Ph,Deb) ->
 
790
            PathFs,Vars,P,Ph,Deb,PathChoice) ->
768
791
    debug(Deb,{start,Server}),
769
792
    start_in_kernel(Server,Mod,Fun,Args,Init),
770
 
    eval_script(CfgL,Init,PathFs,Vars,P,Ph,Deb);
771
 
eval_script([{apply,{Mod,Fun,Args}}|CfgL],Init,PathFs,Vars,P,Ph,Deb) ->
 
793
    eval_script(CfgL,Init,PathFs,Vars,P,Ph,Deb,PathChoice);
 
794
eval_script([{apply,{Mod,Fun,Args}}|CfgL],Init,PathFs,Vars,P,Ph,Deb,PathChoice) ->
772
795
    debug(Deb,{apply,{Mod,Fun,Args}}),
773
796
    apply(Mod,Fun,Args),
774
 
    eval_script(CfgL,Init,PathFs,Vars,P,Ph,Deb);
775
 
eval_script([],_,_,_,_,_,_) ->
 
797
    eval_script(CfgL,Init,PathFs,Vars,P,Ph,Deb,PathChoice);
 
798
eval_script([],_,_,_,_,_,_,_) ->
776
799
    ok;
777
 
eval_script(What,_,_,_,_,_,_) ->
 
800
eval_script(What,_,_,_,_,_,_,_) ->
778
801
    exit({'unexpected command in bootfile',What}).
779
802
 
780
 
debug(false, _) -> ok;
781
 
debug(_, T)     -> erlang:display(T).
782
 
 
783
803
load_modules([Mod|Mods]) ->
784
 
    File = concat([Mod,extension()]),
 
804
    File = concat([Mod,objfile_extension()]),
785
805
    {ok,Full} = load_mod(Mod,File),
786
806
    init ! {self(),loaded,{Mod,Full}},  %% Tell init about loaded module
787
807
    load_modules(Mods);
788
808
load_modules([]) ->
789
809
    ok.
790
 
    
 
810
 
791
811
%%% An optimization: erl_prim_loader gets the chance of loading many
792
812
%%% files in parallel, using threads. This will reduce the seek times,
793
813
%%% and loaded code can be processed while other threads are waiting
803
823
%%% between directories).
804
824
 
805
825
par_load_modules(Mods,Init) ->
806
 
    Ext = extension(),
 
826
    Ext = objfile_extension(),
807
827
    ModFiles = map(fun(Mod) -> {Mod,concat([Mod,Ext])} end, Mods),
808
828
    Self = self(),
809
829
    Fun = fun(Mod, BinCode, FullName) ->
864
884
get_var_val(Var,[_,_|Vars])    -> get_var_val(Var,Vars);
865
885
get_var_val(_,_)               -> false.
866
886
 
 
887
patch_path(Dirs, strict) ->
 
888
    Dirs;
 
889
patch_path(Dirs, relaxed) ->
 
890
    ArchiveExt = archive_extension(),
 
891
    [patch_dir(Dir, ArchiveExt) || Dir <- Dirs].
 
892
 
 
893
patch_dir(Orig, ArchiveExt) ->
 
894
    case funny_split(Orig, $/) of
 
895
        ["nibe", RevApp, RevArchive | RevTop] ->
 
896
            App = reverse(RevApp),
 
897
            case funny_splitwith(RevArchive, $.) of
 
898
                {Ext, Base} when Ext =:= ArchiveExt, Base =:= App ->
 
899
                    %% Orig archive
 
900
                    Top = reverse([reverse(C) || C <- RevTop]),
 
901
                    Dir = join(Top ++ [App, "ebin"], "/"),
 
902
                    Archive = Orig;
 
903
                _ ->
 
904
                    %% Orig directory
 
905
                    Top = reverse([reverse(C) || C <- [RevArchive | RevTop]]),
 
906
                    Archive = join(Top ++ [App ++ ArchiveExt, App, "ebin"], "/"),
 
907
                    Dir = Orig
 
908
            end,
 
909
            %% First try dir, second try archive and at last use orig if both fails
 
910
            case erl_prim_loader:read_file_info(Dir) of
 
911
                {ok, #file_info{type = directory}} ->
 
912
                    Dir;
 
913
                _ ->
 
914
                    case erl_prim_loader:read_file_info(Archive) of
 
915
                        {ok, #file_info{type = directory}} ->
 
916
                            Archive;
 
917
                        _ ->
 
918
                            Orig
 
919
                    end
 
920
            end;
 
921
        _ ->
 
922
            Orig
 
923
    end.
 
924
 
 
925
%% Returns all lists in reverse order
 
926
funny_split(List, Sep) ->
 
927
   funny_split(List, Sep, [], []).
 
928
 
 
929
funny_split([Sep | Tail], Sep, Path, Paths) ->
 
930
    funny_split(Tail, Sep, [], [Path | Paths]);
 
931
funny_split([Head | Tail], Sep, Path, Paths) ->
 
932
    funny_split(Tail, Sep, [Head | Path], Paths);
 
933
funny_split([], _Sep, Path, Paths) ->
 
934
    [Path | Paths].
 
935
 
 
936
%% Returns {BeforeSep, AfterSep} where BeforeSep is in reverse order
 
937
funny_splitwith(List, Sep) ->
 
938
    funny_splitwith(List, Sep, [], List).
 
939
 
 
940
funny_splitwith([Sep | Tail], Sep, Acc, _Orig) ->
 
941
    {Acc, Tail};
 
942
funny_splitwith([Head | Tail], Sep, Acc, Orig) ->
 
943
    funny_splitwith(Tail, Sep, [Head | Acc], Orig);
 
944
funny_splitwith([], _Sep, _Acc, Orig) ->
 
945
    {[], Orig}.
 
946
 
 
947
join([H1, H2| T], S) ->
 
948
    H1 ++ S ++ join([H2| T], S);
 
949
join([H], _) ->
 
950
    H;
 
951
join([], _) ->
 
952
    [].
 
953
 
867
954
%% Servers that are located in the init kernel are linked
868
955
%% and supervised by init.
869
956
 
929
1016
%% Fetch a module and load it into the system.
930
1017
%%
931
1018
load_mod(Mod, File) ->
932
 
    case erl_prim_loader:get_file(File) of
933
 
        {ok,BinCode,FullName} ->
934
 
            load_mod_code(Mod, BinCode, FullName);
935
 
        _ ->
936
 
            exit({'cannot load',Mod,get_file})
 
1019
    case erlang:module_loaded(Mod) of
 
1020
        false ->
 
1021
            case erl_prim_loader:get_file(File) of
 
1022
                {ok,BinCode,FullName} ->
 
1023
                    load_mod_code(Mod, BinCode, FullName);
 
1024
                _ ->
 
1025
                    exit({'cannot load',Mod,get_file})
 
1026
            end;
 
1027
        _ -> % Already loaded.
 
1028
            {ok,File}
937
1029
    end.
938
1030
 
939
1031
load_mod_code(Mod, BinCode, FullName) ->
996
1088
parse_boot_args([B|Bs], Ss, Fs, As) ->
997
1089
    case check(B) of
998
1090
        start_extra_arg ->
999
 
            {reverse(Ss),reverse(Fs),reverse(As, Bs)};
 
1091
            {reverse(Ss),reverse(Fs),lists:reverse(As, Bs)}; % BIF
1000
1092
        start_arg ->
1001
1093
            {S,Rest} = get_args(Bs, []),
1002
1094
            parse_boot_args(Rest, [{s, S}|Ss], Fs, As);
1165
1257
    H ++ append(T);
1166
1258
append([]) -> [].
1167
1259
 
1168
 
reverse(X) ->
1169
 
    reverse(X, []).
1170
 
 
1171
 
reverse([H|T], Y) ->
1172
 
    reverse(T, [H|Y]);
1173
 
reverse([], X) -> X.
 
1260
reverse([] = L) ->
 
1261
    L;
 
1262
reverse([_] = L) ->
 
1263
    L;
 
1264
reverse([A, B]) ->
 
1265
    [B, A];
 
1266
reverse([A, B | L]) ->
 
1267
    lists:reverse(L, [B, A]). % BIF
1174
1268
                        
1175
1269
search(Key, [H|_T]) when is_tuple(H), element(1, H) =:= Key ->
1176
1270
    {value, H};
1177
 
search(Key, [_|T]) -> search(Key, T);
1178
 
search(_Key, []) -> false.
 
1271
search(Key, [_|T]) ->
 
1272
    search(Key, T);
 
1273
search(_Key, []) ->
 
1274
    false.
1179
1275
 
1180
 
extension() ->
 
1276
objfile_extension() ->
1181
1277
    ".beam".
1182
1278
%%    case erlang:system_info(machine) of
1183
1279
%%      "JAM" -> ".jam";
1184
1280
%%      "VEE" -> ".vee";
1185
1281
%%      "BEAM" -> ".beam"
1186
1282
%%    end.
 
1283
 
 
1284
archive_extension() ->
 
1285
    ".ez".