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

« back to all changes in this revision

Viewing changes to lib/stdlib/src/file_sorter.erl

  • Committer: Bazaar Package Importer
  • Author(s): Soren Hansen
  • Date: 2007-05-01 16:57:10 UTC
  • mfrom: (1.1.9 upstream)
  • Revision ID: james.westby@ubuntu.com-20070501165710-2sapk0hp2gf3o0ip
Tags: 1:11.b.4-2ubuntu1
* Merge with Debian Unstable. Remaining changes:
  - Add -fno-stack-protector to fix broken crypto_drv.
* DebianMaintainerField update.

Show diffs side-by-side

added added

removed removed

Lines of Context:
189
189
    options(L, Opts#opts{format = Format});
190
190
options([{format, binary_term} | L], Opts) ->
191
191
    options(L, Opts#opts{format = binary_term_fun()});
192
 
options([{size, Size} | L], Opts) 
193
 
            when is_integer(Size), Size > 0, Size < ?MAXSIZE ->
194
 
    options(L, Opts#opts{size = Size});
 
192
options([{size, Size} | L], Opts) when is_integer(Size), Size >= 0 ->
 
193
    options(L, Opts#opts{size = max(Size, 1)});
195
194
options([{no_files, NoFiles} | L], Opts) when is_integer(NoFiles), 
196
195
                                              NoFiles > 1 ->
197
196
    options(L, Opts#opts{no_files = NoFiles});
198
197
options([{tmpdir, ""} | L], Opts) ->
199
198
    options(L, Opts#opts{tmpdir = default});
200
199
options([{tmpdir, Dir} | L],  Opts) ->
201
 
    case is_directory(Dir) of
202
 
        {true, Directory} ->
203
 
            options(L, Opts#opts{tmpdir = {dir, Directory}});
204
 
        Error ->
205
 
            Error
 
200
    case catch filename:absname(Dir) of
 
201
        {'EXIT', _} ->
 
202
            {badarg, Dir};
 
203
        FileName -> 
 
204
            options(L, Opts#opts{tmpdir = {dir, FileName}})
206
205
    end;
207
206
options([{order, Fun} | L], Opts) when is_function(Fun), is_function(Fun, 2) ->
208
207
    options(L, Opts#opts{order = Fun});
1271
1270
            {true, FileName}
1272
1271
    end.
1273
1272
 
1274
 
is_directory(File) ->
1275
 
    case read_file_info(File) of
1276
 
        {ok, FileName, #file_info{type=directory}} ->
1277
 
            {true, FileName};
1278
 
        {ok, _FileName, _FileInfo} ->
1279
 
            {error, {not_a_directory, File}};
1280
 
        Error ->
1281
 
            Error
1282
 
    end.
1283
 
 
1284
1273
read_file_info(File) ->
1285
1274
    %% Absolute names in case some process should call file:set_cwd/1.
1286
1275
    case catch filename:absname(File) of
1456
1445
    end.
1457
1446
 
1458
1447
write_terms(Fd, F, [B | Bs], Args) ->
1459
 
    case io:format(Fd, "~p.~n", [binary_to_term(B)]) of
 
1448
    case io:request(Fd, {format, "~p.~n", [binary_to_term(B)]}) of
1460
1449
        ok -> 
1461
1450
            write_terms(Fd, F, Bs, Args);
1462
1451
        {error, Reason} ->