aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/src/file_sorter.erl
diff options
context:
space:
mode:
authorKostis Sagonas <[email protected]>2010-02-08 10:29:31 +0200
committerBjörn Gustavsson <[email protected]>2010-02-10 08:25:43 +0100
commit48654b06afc07dba4342e02293b9adb9776d99d1 (patch)
tree76c798ef2d949b850833610af6813ab971d0a447 /lib/stdlib/src/file_sorter.erl
parent19fda3d8ddbd8b844024bd15689dbf45fa8e5e1e (diff)
downloadotp-48654b06afc07dba4342e02293b9adb9776d99d1.tar.gz
otp-48654b06afc07dba4342e02293b9adb9776d99d1.tar.bz2
otp-48654b06afc07dba4342e02293b9adb9776d99d1.zip
stdlib: clean up as suggested by tidier
Hans Bolinder (the author/maintainer of qlc) prefers for readability reasons to use length/1 in a guard when it is known that the list is guaranteed to be short, so the change suggested by tidier for line 875 of qlc_pt has not been included.
Diffstat (limited to 'lib/stdlib/src/file_sorter.erl')
-rw-r--r--lib/stdlib/src/file_sorter.erl24
1 files changed, 12 insertions, 12 deletions
diff --git a/lib/stdlib/src/file_sorter.erl b/lib/stdlib/src/file_sorter.erl
index de9e628e22..f253791f80 100644
--- a/lib/stdlib/src/file_sorter.erl
+++ b/lib/stdlib/src/file_sorter.erl
@@ -186,7 +186,7 @@ options(Option) ->
options([{format, Format} | L], Opts) when Format =:= binary;
Format =:= term;
is_function(Format),
- is_function(Format, 1) ->
+ is_function(Format, 1) ->
options(L, Opts#opts{format = Format});
options([{format, binary_term} | L], Opts) ->
options(L, Opts#opts{format = binary_term_fun()});
@@ -419,9 +419,9 @@ culprit_found(IFun, F, FNs, W, L, I, [_Size | BT]) ->
IFun(close),
check_files(FNs, W, [{F,I,binary_to_term(BT)} | L]).
-files(_I, L, _LSz, #w{seq = 1}=W, []) ->
+files(_I, L, _LSz, #w{seq = 1, out = Out}=W, []) ->
%% No temporary files created, everything in L.
- case W#w.out of
+ case Out of
Fun when is_function(Fun) ->
SL = internal_sort(L, W),
W1 = outfun(binterm_objects(SL, []), W),
@@ -462,8 +462,8 @@ fun_run(I, L, LSz, W, []) ->
{cont, NW, Objs} ->
fun_run(I, L, LSz, NW, Objs)
end;
-fun_run(I, L, LSz, W, Objs) when LSz < W#w.runsize ->
- {NI, NObjs, NL, NLSz} = fun_objs(Objs, L, LSz, W#w.runsize, I, W),
+fun_run(I, L, LSz, #w{runsize = Runsize}=W, Objs) when LSz < Runsize ->
+ {NI, NObjs, NL, NLSz} = fun_objs(Objs, L, LSz, Runsize, I, W),
fun_run(NI, NL, NLSz, W, NObjs);
fun_run(I, L, _LSz, W, Objs) ->
NW = write_run(L, W),
@@ -1201,11 +1201,11 @@ infun(W) ->
erlang:raise(Class, Reason, erlang:get_stacktrace())
end.
-outfun(A, W) when W#w.inout_value =/= no_value ->
+outfun(A, #w{inout_value = Val} = W) when Val =/= no_value ->
W1 = W#w{inout_value = no_value},
W2 = if
W1#w.fun_out ->
- outfun(W#w.inout_value, W1);
+ outfun(Val, W1);
true -> W1
end,
outfun(A, W2);
@@ -1372,19 +1372,19 @@ cleanup(W) ->
end,
lists:foreach(F, W1#w.temp).
-close_input(W) when is_function(W#w.in) ->
- catch (W#w.in)(close),
+close_input(#w{in = In}=W) when is_function(In) ->
+ catch In(close),
W#w{in = undefined};
close_input(#w{in = undefined}=W) ->
W.
-close_out(W) when is_function(W#w.out) ->
- catch (W#w.out)(close);
+close_out(#w{out = Out}) when is_function(Out) ->
+ catch Out(close);
close_out(_) ->
ok.
close_file(Fd, W) ->
- {value, {Fd, FileName}} = lists:keysearch(Fd, 1, W#w.temp),
+ {Fd, FileName} = lists:keyfind(Fd, 1, W#w.temp),
?DEBUG("closing ~p~n", [FileName]),
file:close(Fd),
W#w{temp = [FileName | lists:keydelete(Fd, 1, W#w.temp)]}.