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

« back to all changes in this revision

Viewing changes to lib/tools/src/make.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:
21
21
%% necessary.
22
22
%% Files to be checked are contained in a file 'Emakefile' 
23
23
%% If Emakefile is missing the current directory is used.
24
 
 
25
24
-module(make).
26
25
 
27
26
-export([all/0,all/1,files/1,files/2]).
36
35
all(Options) ->
37
36
    {MakeOpts,CompileOpts} = sort_options(Options,[],[]),
38
37
    case read_emakefile('Emakefile',CompileOpts) of
39
 
        Files when list(Files) ->
 
38
        Files when is_list(Files) ->
40
39
            do_make_files(Files,MakeOpts);
41
40
        error ->
42
41
            error
46
45
    files(Fs, []).
47
46
 
48
47
files(Fs0, Options) ->
49
 
    Fs = [filename:basename(F,".erl") || F <- Fs0],
 
48
    Fs = [filename:rootname(F,".erl") || F <- Fs0],
50
49
    {MakeOpts,CompileOpts} = sort_options(Options,[],[]),
51
50
    case get_opts_from_emakefile(Fs,'Emakefile',CompileOpts) of
52
 
        Files when list(Files) ->
 
51
        Files when is_list(Files) ->
53
52
            do_make_files(Files,MakeOpts);          
54
53
        error -> error
55
54
    end.
111
110
transform([],_Opts,Files,_Already) ->
112
111
    lists:reverse(Files).
113
112
 
114
 
expand(Mod,Already) when atom(Mod) ->
 
113
expand(Mod,Already) when is_atom(Mod) ->
115
114
    expand(atom_to_list(Mod),Already);
116
 
expand(Mods,Already) when list(Mods), not is_integer(hd(Mods)) ->
 
115
expand(Mods,Already) when is_list(Mods), not is_integer(hd(Mods)) ->
117
116
    lists:concat([expand(Mod,Already) || Mod <- Mods]);
118
117
expand(Mod,Already) ->
119
118
    case lists:member($*,Mod) of
127
126
                  end,
128
127
            lists:foldl(Fun, [], filelib:wildcard(Mod++".erl"));
129
128
        false ->
130
 
            case lists:member(Mod,Already) of
 
129
            Mod2 = filename:rootname(Mod, ".erl"),
 
130
            case lists:member(Mod2,Already) of
131
131
                true -> [];
132
 
                false -> [Mod]
 
132
                false -> [Mod2]
133
133
            end
134
134
    end.
135
135
 
229
229
    end.
230
230
 
231
231
recompilep1(#file_info{mtime=Te},
232
 
            #file_info{mtime=To}, File, NoExec, Load, Opts) when Te > To ->
 
232
            #file_info{mtime=To}, File, NoExec, Load, Opts) when Te>To ->
233
233
    recompile(File, NoExec, Load, Opts);
234
234
recompilep1(_Erl, #file_info{mtime=To}, File, NoExec, Load, Opts) ->
235
235
    recompile2(To, File, NoExec, Load, Opts).
284
284
writable(#file_info{access=write})      -> true;
285
285
writable(_) -> false.
286
286
 
287
 
coerce_2_list(X) when atom(X) ->
 
287
coerce_2_list(X) when is_atom(X) ->
288
288
    atom_to_list(X);
289
289
coerce_2_list(X) ->
290
290
    X.
307
307
            check_includes2(Epp, File, ObjMTime);
308
308
        {ok, {attribute, 1, file, {IncFile, 1}}} ->
309
309
            case file:read_file_info(IncFile) of
310
 
                {ok, #file_info{mtime=MTime}} when MTime > ObjMTime ->
 
310
                {ok, #file_info{mtime=MTime}} when MTime>ObjMTime ->
311
311
                    epp:close(Epp),
312
312
                    true;
313
313
                _ ->