~statik/ubuntu/maverick/erlang/erlang-merge-testing

« back to all changes in this revision

Viewing changes to erts/boot/src/ear.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-05-01 10:14:38 UTC
  • mfrom: (3.1.4 sid)
  • Revision ID: james.westby@ubuntu.com-20090501101438-6qlr6rsdxgyzrg2z
Tags: 1:13.b-dfsg-2
* Cleaned up patches: removed unneeded patch which helped to support
  different SCTP library versions, made sure that changes for m68k
  architecture applied only when building on this architecture.
* Removed duplicated information from binary packages descriptions.
* Don't require libsctp-dev build-dependency on solaris-i386 architecture
  which allows to build Erlang on Nexenta (thanks to Tim Spriggs for
  the suggestion).

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
 
%% ``The contents of this file are subject to the Erlang Public License,
2
 
%% Version 1.1, (the "License"); you may not use this file except in
3
 
%% compliance with the License. You should have received a copy of the
4
 
%% Erlang Public License along with this software. If not, it can be
5
 
%% retrieved via the world wide web at http://www.erlang.org/.
6
 
%% 
7
 
%% Software distributed under the License is distributed on an "AS IS"
8
 
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
9
 
%% the License for the specific language governing rights and limitations
10
 
%% under the License.
11
 
%% 
12
 
%% The Initial Developer of the Original Code is Ericsson Utvecklings AB.
13
 
%% Portions created by Ericsson are Copyright 2002, Ericsson Utvecklings
14
 
%% AB. All Rights Reserved.''
15
 
%% 
16
 
%%     $Id$
17
 
%%
18
 
 
19
 
-module(ear).
20
 
 
21
 
-compile(export_all).
22
 
 
23
 
-export([start/1]).
24
 
-import(lists, [foldl/3, foreach/2, map/2, member/2]).
25
 
 
26
 
%% ear -a Archive Mod Mod Dir
27
 
%% ear -l Archive
28
 
%% ear -d Archive Mod Mod
29
 
%% ear -e Archive 
30
 
 
31
 
%% Note ear *cannot* be used to build the origonal
32
 
%%   erlang.ear (since erlang.ear) is used for the code base for
33
 
%%   ear :-)
34
 
%%   Erlang.ear is build inside boot_tools.erl
35
 
 
36
 
%% examples
37
 
%%   ear -a foo.ear /ldisk/otp_src_P9_2002-05-26/lib/kernel/ebin/*.beam
38
 
%%   ear -l 
39
 
 
40
 
%% we want all these commands to work like a transaction
41
 
%% their every works or nothing.
42
 
%% This means we do all checking *before* manipulating the
43
 
%% archive
44
 
 
45
 
start([_|X]) ->
46
 
    X0 = map(fun(I) -> binary_to_list(I) end, X),
47
 
    %% io:format("EAR:~p~n",[X0]),
48
 
    [_|Args] = X0,
49
 
    ear(Args),
50
 
    erlang:halt().
51
 
 
52
 
ear(["-l", Archive]) ->
53
 
    is_archive(Archive),
54
 
    Pid = boot_pds:open(Archive, read),
55
 
    Keys = lists:sort(boot_pds:keys(Pid)),
56
 
    foreach(fun(I) -> io:format("~s~n", [print_name(I)]) end, Keys),
57
 
    boot_pds:close(Pid);
58
 
ear(["-a", Archive|Objs]) ->
59
 
    is_archive(Archive),
60
 
    Updates = foldl(fun add_object/2, [], Objs),
61
 
    Pid = boot_pds:open(Archive, read_write),
62
 
    map(fun({add,Key,Val}) ->
63
 
                boot_pds:store(Pid, Key, Val)
64
 
        end, Updates),
65
 
    boot_pds:close(Pid);
66
 
ear(["-r", Archive|Objs]) ->
67
 
    is_archive(Archive),
68
 
    Delete = map(fun get_obj_name/1, Objs),
69
 
    %% io:format("delete=~p~n",[Delete]),
70
 
    Pid = boot_pds:open(Archive, read_write),
71
 
    Keys = boot_pds:keys(Pid),
72
 
    foreach(fun(I) ->
73
 
                    case member(I, Keys) of
74
 
                        true ->
75
 
                            true;
76
 
                        false ->
77
 
                            boot_pds:close(Pid),
78
 
                            io:format("*** archive does not have element:~s~n",
79
 
                                      [print_name(I)]),
80
 
                            erlang:halt()
81
 
                    end
82
 
            end, Delete),
83
 
    foreach(fun(I) -> boot_pds:delete(Pid, I) end, Delete),
84
 
    boot_pds:close(Pid);
85
 
ear(["-e", Archive|Objs]) ->
86
 
    is_archive(Archive),
87
 
    Extract = map(fun get_obj_name/1, Objs),
88
 
    %% io:format("extract=~p~n",[Extract]),
89
 
    Pid = boot_pds:open(Archive, read_write),
90
 
    Keys = boot_pds:keys(Pid),
91
 
    %% check the archive has the required element
92
 
    foreach(fun(I) ->
93
 
                    case member(I, Keys) of
94
 
                        true ->
95
 
                            true;
96
 
                        false ->
97
 
                            boot_pds:close(Pid),
98
 
                            io:format("*** archive does not have element:~s~n",
99
 
                                      [print_name(I)]),
100
 
                            erlang:halt()
101
 
                    end
102
 
            end, Extract),
103
 
    %% check we won't clobber the file
104
 
    foreach(fun(I) ->
105
 
                    F = print_name(I),
106
 
                    case exists(F) of
107
 
                        true ->
108
 
                            boot_pds:close(Pid),
109
 
                            io:format("*** ~s exists and will not be "
110
 
                                      " overwritten~n",
111
 
                                      [F]),
112
 
                            erlang:halt();
113
 
                        false ->
114
 
                            true
115
 
                    end
116
 
            end, Extract),
117
 
    %% Finally extract the files
118
 
    foreach(fun(I) ->
119
 
                    F = print_name(I),
120
 
                    {ok, Bin} = boot_pds:fetch(Pid, I),
121
 
                    file:write_file(F, Bin)
122
 
            end, Extract),
123
 
    boot_pds:close(Pid);
124
 
ear(["-h"]) ->
125
 
    usage();
126
 
ear(_) ->
127
 
    usage().
128
 
    
129
 
exists(File) ->
130
 
     case boot_fprim:read_file_info(File) of
131
 
         {ok, _} -> true;
132
 
         _       -> false
133
 
     end.
134
 
 
135
 
is_archive(F) ->
136
 
     case filename:extension(F) of
137
 
        ".ear" ->
138
 
            true;
139
 
         _ ->
140
 
             io:format("*** ~s is not an archive (.ear file)~n", [F]),
141
 
             erlang:halt()
142
 
     end.
143
 
 
144
 
print_name({mod, I})    -> atom_to_list(I) ++ ".beam";
145
 
print_name({include,F}) -> F ++ ".hrl".
146
 
 
147
 
get_obj_name(Obj) ->
148
 
    case filename:extension(Obj) of
149
 
        ".beam" ->
150
 
            F1 = filename:rootname(filename:basename(Obj)),
151
 
            A = list_to_atom(F1),
152
 
            {mod,A};
153
 
        ".hrl" ->
154
 
            F1 = filename:rootname(filename:basename(Obj)),
155
 
            {include, F1};
156
 
        _ ->
157
 
            io:format("*** ~s not .beam or .hrl~n", [Obj]),
158
 
            erlang:halt()
159
 
    end.
160
 
 
161
 
add_object(Obj, L) ->
162
 
    case filename:extension(Obj) of
163
 
        ".beam" ->
164
 
            case get_module_name(Obj) of
165
 
                {ok, Mod} ->
166
 
                    {ok, Bin} = file:read_file(Obj),
167
 
                    [{add, {mod,Mod}, Bin}|L];
168
 
                error -> 
169
 
                    io:format("** bad module :~s~n", [Obj]),
170
 
                    erlang:halt()
171
 
            end;
172
 
        ".hrl" ->
173
 
            F1 = filename:rootname(filename:basename(Obj)),
174
 
            case file:read_file(Obj) of
175
 
                {ok, Bin} ->
176
 
                    [{add, {include, F1}, Bin}|L];
177
 
                _ ->
178
 
                    io:format("** bad include file :~s~n", [Obj]),
179
 
                    erlang:halt()
180
 
            end;
181
 
        _ ->
182
 
            io:format("** bad extension :~s~n", [Obj]),
183
 
            erlang:halt()
184
 
    end.
185
 
 
186
 
get_module_name(F) ->
187
 
    case beam_lib:info(F) of
188
 
        L when list(L) ->
189
 
            case [M || {module, M} <- L] of
190
 
                [Mod] ->
191
 
                    {ok, Mod};
192
 
                _  ->
193
 
                    error
194
 
            end;
195
 
        _ ->
196
 
            error
197
 
    end.
198
 
 
199
 
usage() ->
200
 
    io:format("Usage: ear [-l |-a |-r |-e] archive files\n"
201
 
              "       ear -h\n"
202
 
              "commands:\n"
203
 
              "  h    - help\n"
204
 
              "  l    - list archive\n"
205
 
              "  a    - add file(s) to archive\n"
206
 
              "  r    - remove file(s) from archive\n"
207
 
              "  e    - extract file(s) from archive\n"
208
 
              "notes:\n"
209
 
              "  archive  files must have the extension .ear\n"
210
 
              "  archived files may have extensions .beam or .hrl\n"
211
 
              "examples:\n"
212
 
              "  > ear -a myLib.ear *.beam my_include.hrl\n"
213
 
              "  > ear -a myLib.ear PathToLib/ebin/*.beam\n"
214
 
              "  > ear -a myLib.ear PathToLib/include/*.hrl\n").