~clint-fewbar/ubuntu/precise/erlang/merge-15b

« back to all changes in this revision

Viewing changes to lib/sasl/test/release_handler_SUITE_data/target_system.erl

  • Committer: Package Import Robot
  • Author(s): Sergei Golovan
  • Date: 2011-12-15 19:20:10 UTC
  • mfrom: (1.1.18) (3.5.15 sid)
  • mto: (3.5.16 sid)
  • mto: This revision was merged to the branch mainline in revision 33.
  • Revision ID: package-import@ubuntu.com-20111215192010-jnxcfe3tbrpp0big
Tags: 1:15.b-dfsg-1
* New upstream release.
* Upload to experimental because this release breaks external drivers
  API along with ABI, so several applications are to be fixed.
* Removed SSL patch because the old SSL implementation is removed from
  the upstream distribution.
* Removed never used patch which added native code to erlang beam files.
* Removed the erlang-docbuilder binary package because the docbuilder
  application was dropped by upstream.
* Documented dropping ${erlang-docbuilder:Depends} substvar in
  erlang-depends(1) manpage.
* Made erlang-base and erlang-base-hipe provide virtual package
  erlang-abi-15.b (the number means the first erlang version, which
  provides current ABI).

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%%
 
4
%% Copyright Ericsson AB 2011. All Rights Reserved.
 
5
%%
 
6
%% The contents of this file are subject to the Erlang Public License,
 
7
%% Version 1.1, (the "License"); you may not use this file except in
 
8
%% compliance with the License. You should have received a copy of the
 
9
%% Erlang Public License along with this software. If not, it can be
 
10
%% retrieved online at http://www.erlang.org/.
 
11
%%
 
12
%% Software distributed under the License is distributed on an "AS IS"
 
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
14
%% the License for the specific language governing rights and limitations
 
15
%% under the License.
 
16
%%
 
17
%% %CopyrightEnd%
 
18
%%
 
19
%module
 
20
-module(target_system).
 
21
-export([create/1, create/2, install/2]).
 
22
 
 
23
%% Note: RelFileName below is the *stem* without trailing .rel,
 
24
%% .script etc.
 
25
%%
 
26
 
 
27
%% create(RelFileName)
 
28
%%
 
29
create(RelFileName) ->
 
30
    create(RelFileName,[]).
 
31
 
 
32
create(RelFileName,SystoolsOpts) ->
 
33
    RelFile = RelFileName ++ ".rel", 
 
34
    Dir = filename:dirname(RelFileName),
 
35
    PlainRelFileName = filename:join(Dir,"plain"),
 
36
    PlainRelFile = PlainRelFileName ++ ".rel",
 
37
    io:fwrite("Reading file: ~p ...~n", [RelFile]),
 
38
    {ok, [RelSpec]} = file:consult(RelFile),
 
39
    io:fwrite("Creating file: ~p from ~p ...~n", 
 
40
              [PlainRelFile, RelFile]),
 
41
    {release,
 
42
     {RelName, RelVsn},
 
43
     {erts, ErtsVsn},
 
44
     AppVsns} = RelSpec,
 
45
    PlainRelSpec = {release, 
 
46
                    {RelName, RelVsn},
 
47
                    {erts, ErtsVsn},
 
48
                    lists:filter(fun({kernel, _}) -> 
 
49
                                         true;
 
50
                                    ({stdlib, _}) ->
 
51
                                         true;
 
52
                                    (_) ->
 
53
                                         false
 
54
                                 end, AppVsns)
 
55
                   },
 
56
    {ok, Fd} = file:open(PlainRelFile, [write]),
 
57
    io:fwrite(Fd, "~p.~n", [PlainRelSpec]),
 
58
    file:close(Fd),
 
59
 
 
60
    io:fwrite("Making \"~s.script\" and \"~s.boot\" files ...~n",
 
61
              [PlainRelFileName,PlainRelFileName]),
 
62
    make_script(PlainRelFileName,SystoolsOpts),
 
63
 
 
64
    io:fwrite("Making \"~s.script\" and \"~s.boot\" files ...~n", 
 
65
              [RelFileName, RelFileName]),
 
66
    make_script(RelFileName,SystoolsOpts),
 
67
 
 
68
    TarFileName = filename:join(Dir,RelFileName ++ ".tar.gz"),
 
69
    io:fwrite("Creating tar file ~p ...~n", [TarFileName]),
 
70
    make_tar(RelFileName,SystoolsOpts),
 
71
 
 
72
    TmpDir = filename:join(Dir,"tmp"),
 
73
    io:fwrite("Creating directory ~p ...~n",[TmpDir]),
 
74
    file:make_dir(TmpDir), 
 
75
 
 
76
    io:fwrite("Extracting ~p into directory ~p ...~n", [TarFileName,TmpDir]),
 
77
    extract_tar(TarFileName, TmpDir),
 
78
 
 
79
    TmpBinDir = filename:join([TmpDir, "bin"]),
 
80
    ErtsBinDir = filename:join([TmpDir, "erts-" ++ ErtsVsn, "bin"]),
 
81
    io:fwrite("Deleting \"erl\" and \"start\" in directory ~p ...~n", 
 
82
              [ErtsBinDir]),
 
83
    file:delete(filename:join([ErtsBinDir, "erl"])),
 
84
    file:delete(filename:join([ErtsBinDir, "start"])),
 
85
 
 
86
    io:fwrite("Creating temporary directory ~p ...~n", [TmpBinDir]),
 
87
    file:make_dir(TmpBinDir),
 
88
 
 
89
    io:fwrite("Copying file \"~s.boot\" to ~p ...~n", 
 
90
              [PlainRelFileName, filename:join([TmpBinDir, "start.boot"])]),
 
91
    copy_file(PlainRelFileName++".boot",filename:join([TmpBinDir, "start.boot"])),
 
92
 
 
93
    io:fwrite("Copying files \"epmd\", \"run_erl\" and \"to_erl\" from \n"
 
94
              "~p to ~p ...~n", 
 
95
              [ErtsBinDir, TmpBinDir]),
 
96
    copy_file(filename:join([ErtsBinDir, "epmd"]), 
 
97
              filename:join([TmpBinDir, "epmd"]), [preserve]),
 
98
    copy_file(filename:join([ErtsBinDir, "run_erl"]), 
 
99
              filename:join([TmpBinDir, "run_erl"]), [preserve]),
 
100
    copy_file(filename:join([ErtsBinDir, "to_erl"]), 
 
101
              filename:join([TmpBinDir, "to_erl"]), [preserve]),
 
102
 
 
103
    StartErlDataFile = filename:join([TmpDir, "releases", "start_erl.data"]),
 
104
    io:fwrite("Creating ~p ...~n", [StartErlDataFile]),
 
105
    StartErlData = io_lib:fwrite("~s ~s~n", [ErtsVsn, RelVsn]),
 
106
    write_file(StartErlDataFile, StartErlData),
 
107
    
 
108
    io:fwrite("Recreating tar file ~p from contents in directory ~p ...~n", 
 
109
              [TarFileName,TmpDir]),
 
110
    {ok, Tar} = erl_tar:open(TarFileName, [write, compressed]),
 
111
    %% {ok, Cwd} = file:get_cwd(),
 
112
    %% file:set_cwd("tmp"),
 
113
    ErtsDir = "erts-"++ErtsVsn,
 
114
    erl_tar:add(Tar, filename:join(TmpDir,"bin"), "bin", []),
 
115
    erl_tar:add(Tar, filename:join(TmpDir,ErtsDir), ErtsDir, []),
 
116
    erl_tar:add(Tar, filename:join(TmpDir,"releases"), "releases", []),
 
117
    erl_tar:add(Tar, filename:join(TmpDir,"lib"), "lib", []),
 
118
    erl_tar:close(Tar),
 
119
    %% file:set_cwd(Cwd),
 
120
    io:fwrite("Removing directory ~p ...~n",[TmpDir]),
 
121
    remove_dir_tree(TmpDir),
 
122
    ok.
 
123
 
 
124
 
 
125
install(RelFileName, RootDir) ->
 
126
    TarFile = RelFileName ++ ".tar.gz", 
 
127
    io:fwrite("Extracting ~p ...~n", [TarFile]),
 
128
    extract_tar(TarFile, RootDir),
 
129
    StartErlDataFile = filename:join([RootDir, "releases", "start_erl.data"]),
 
130
    {ok, StartErlData} = read_txt_file(StartErlDataFile),
 
131
    [ErlVsn, _RelVsn| _] = string:tokens(StartErlData, " \n"),
 
132
    ErtsBinDir = filename:join([RootDir, "erts-" ++ ErlVsn, "bin"]),
 
133
    BinDir = filename:join([RootDir, "bin"]),
 
134
    io:fwrite("Substituting in erl.src, start.src and start_erl.src to "
 
135
              "form erl, start and start_erl ...\n"),
 
136
    subst_src_scripts(["erl", "start", "start_erl"], ErtsBinDir, BinDir, 
 
137
                      [{"FINAL_ROOTDIR", RootDir}, {"EMU", "beam"}],
 
138
                      [preserve]),
 
139
    io:fwrite("Creating the RELEASES file ...\n"),
 
140
    create_RELEASES(RootDir, filename:join([RootDir, "releases",
 
141
                                            filename:basename(RelFileName)])).
 
142
 
 
143
%% LOCALS 
 
144
 
 
145
%% make_script(RelFileName,Opts)
 
146
%%
 
147
make_script(RelFileName,Opts) ->
 
148
    systools:make_script(RelFileName, [no_module_tests,
 
149
                                       {outdir,filename:dirname(RelFileName)}
 
150
                                       |Opts]).
 
151
 
 
152
%% make_tar(RelFileName,Opts)
 
153
%%
 
154
make_tar(RelFileName,Opts) ->
 
155
    RootDir = code:root_dir(),
 
156
    systools:make_tar(RelFileName, [{erts, RootDir},
 
157
                                    {outdir,filename:dirname(RelFileName)}
 
158
                                    |Opts]).
 
159
 
 
160
%% extract_tar(TarFile, DestDir)
 
161
%%
 
162
extract_tar(TarFile, DestDir) ->
 
163
    erl_tar:extract(TarFile, [{cwd, DestDir}, compressed]).
 
164
 
 
165
create_RELEASES(DestDir, RelFileName) ->
 
166
    release_handler:create_RELEASES(DestDir, RelFileName ++ ".rel").
 
167
 
 
168
subst_src_scripts(Scripts, SrcDir, DestDir, Vars, Opts) -> 
 
169
    lists:foreach(fun(Script) ->
 
170
                          subst_src_script(Script, SrcDir, DestDir, 
 
171
                                           Vars, Opts)
 
172
                  end, Scripts).
 
173
 
 
174
subst_src_script(Script, SrcDir, DestDir, Vars, Opts) -> 
 
175
    subst_file(filename:join([SrcDir, Script ++ ".src"]),
 
176
               filename:join([DestDir, Script]),
 
177
               Vars, Opts).
 
178
 
 
179
subst_file(Src, Dest, Vars, Opts) ->
 
180
    {ok, Conts} = read_txt_file(Src),
 
181
    NConts = subst(Conts, Vars),
 
182
    write_file(Dest, NConts),
 
183
    case lists:member(preserve, Opts) of
 
184
        true ->
 
185
            {ok, FileInfo} = file:read_file_info(Src),
 
186
            file:write_file_info(Dest, FileInfo);
 
187
        false ->
 
188
            ok
 
189
    end.
 
190
 
 
191
%% subst(Str, Vars)
 
192
%% Vars = [{Var, Val}]
 
193
%% Var = Val = string()
 
194
%% Substitute all occurrences of %Var% for Val in Str, using the list
 
195
%% of variables in Vars.
 
196
%%
 
197
subst(Str, Vars) ->
 
198
    subst(Str, Vars, []).
 
199
 
 
200
subst([$%, C| Rest], Vars, Result) when $A =< C, C =< $Z ->
 
201
    subst_var([C| Rest], Vars, Result, []);
 
202
subst([$%, C| Rest], Vars, Result) when $a =< C, C =< $z ->
 
203
    subst_var([C| Rest], Vars, Result, []);
 
204
subst([$%, C| Rest], Vars, Result) when  C == $_ ->
 
205
    subst_var([C| Rest], Vars, Result, []);
 
206
subst([C| Rest], Vars, Result) ->
 
207
    subst(Rest, Vars, [C| Result]);
 
208
subst([], _Vars, Result) ->
 
209
    lists:reverse(Result).
 
210
 
 
211
subst_var([$%| Rest], Vars, Result, VarAcc) ->
 
212
    Key = lists:reverse(VarAcc),
 
213
    case lists:keysearch(Key, 1, Vars) of
 
214
        {value, {Key, Value}} ->
 
215
            subst(Rest, Vars, lists:reverse(Value, Result));
 
216
        false ->
 
217
            subst(Rest, Vars, [$%| VarAcc ++ [$%| Result]])
 
218
    end;
 
219
subst_var([C| Rest], Vars, Result, VarAcc) ->
 
220
    subst_var(Rest, Vars, Result, [C| VarAcc]);
 
221
subst_var([], Vars, Result, VarAcc) ->
 
222
    subst([], Vars, [VarAcc ++ [$%| Result]]).
 
223
 
 
224
copy_file(Src, Dest) ->
 
225
    copy_file(Src, Dest, []).
 
226
 
 
227
copy_file(Src, Dest, Opts) ->
 
228
    {ok,_} = file:copy(Src, Dest),
 
229
    case lists:member(preserve, Opts) of
 
230
        true ->
 
231
            {ok, FileInfo} = file:read_file_info(Src),
 
232
            file:write_file_info(Dest, FileInfo);
 
233
        false ->
 
234
            ok
 
235
    end.
 
236
       
 
237
write_file(FName, Conts) ->
 
238
    {ok, Fd} = file:open(FName, [write]),
 
239
    file:write(Fd, Conts),
 
240
    file:close(Fd).
 
241
 
 
242
read_txt_file(File) ->
 
243
    {ok, Bin} = file:read_file(File),
 
244
    {ok, binary_to_list(Bin)}.
 
245
 
 
246
remove_dir_tree(Dir) ->
 
247
    remove_all_files(".", [Dir]).
 
248
 
 
249
remove_all_files(Dir, Files) ->
 
250
    lists:foreach(fun(File) ->
 
251
                          FilePath = filename:join([Dir, File]),
 
252
                          case filelib:is_dir(FilePath) of
 
253
                              true ->
 
254
                                  {ok, DirFiles} = file:list_dir(FilePath), 
 
255
                                  remove_all_files(FilePath, DirFiles),
 
256
                                  file:del_dir(FilePath);
 
257
                              _ ->
 
258
                                  file:delete(FilePath)
 
259
                          end
 
260
                  end, Files).
 
261
%module