File 1771-Improve-ets-dets-table-2-docs.patch of Package erlang
From cb9bd969267b3074e493810ecd536c042a9dcc35 Mon Sep 17 00:00:00 2001
From: Maria Scott <maria-12648430@hnc-agency.org>
Date: Fri, 19 Dec 2025 17:16:26 +0100
Subject: [PATCH 1/2] Improve ets:/dets:table/2 docs
---
lib/stdlib/src/dets.erl | 21 +++++++++++++--------
lib/stdlib/src/dets_v9.erl | 14 +++++++-------
lib/stdlib/src/ets.erl | 16 +++++++++++-----
3 files changed, 31 insertions(+), 20 deletions(-)
diff --git a/lib/stdlib/src/dets.erl b/lib/stdlib/src/dets.erl
index 10456a06cd..84e65833a2 100644
--- a/lib/stdlib/src/dets.erl
+++ b/lib/stdlib/src/dets.erl
@@ -1393,23 +1393,28 @@ The following example uses an explicit match specification to traverse the
table:
```erlang
-1> dets:open_file(t, []),
-ok = dets:insert(t, [{1,a},{2,b},{3,c},{4,d}]),
-MS = ets:fun2ms(fun({X,Y}) when (X > 1) or (X < 5) -> {Y} end),
-QH1 = dets:table(t, [{traverse, {select, MS}}]).
+1> {ok, t} = dets:open_file(t, []).
+...
+2> ok = dets:insert(t, [{1, a}, {2, b}, {3, c}, {4, d}, {5, e}]).
+...
+3> MS = ets:fun2ms(fun({X, Y}) when X > 1 andalso X < 5 -> {Y} end).
+...
+4> QH1 = dets:table(t, [{traverse, {select, MS}}]).
+...
```
An example with implicit match specification:
```erlang
-2> QH2 = qlc:q([{Y} || {X,Y} <- dets:table(t), (X > 1) or (X < 5)]).
+5> QH2 = qlc:q([{Y} || {X, Y} <- dets:table(t), X > 1 andalso X < 5]).
+...
```
The latter example is equivalent to the former, which can be verified using
function `qlc:info/1`:
```erlang
-3> qlc:info(QH1) =:= qlc:info(QH2).
+6> qlc:info(QH1) =:= qlc:info(QH2).
true
```
@@ -3228,8 +3233,8 @@ fopen_existing_file(Tab, OpenArgs) ->
Auto, access = Acc, debug = Debug} =
OpenArgs,
{ok, Fd, FH} = read_file_header(Fname, Acc, Ram),
- MinF = (MinSlots =:= default) or (MinSlots =:= FH#fileheader.min_no_slots),
- MaxF = (MaxSlots =:= default) or (MaxSlots =:= FH#fileheader.max_no_slots),
+ MinF = MinSlots =:= default orelse MinSlots =:= FH#fileheader.min_no_slots,
+ MaxF = MaxSlots =:= default orelse MaxSlots =:= FH#fileheader.max_no_slots,
Wh = case dets_v9:check_file_header(FH, Fd) of
{ok, Head} when Rep =:= force, Acc =:= read_write,
FH#fileheader.no_colls =/= undefined,
diff --git a/lib/stdlib/src/dets_v9.erl b/lib/stdlib/src/dets_v9.erl
index dd0f952cd8..eff94143a4 100644
--- a/lib/stdlib/src/dets_v9.erl
+++ b/lib/stdlib/src/dets_v9.erl
@@ -1098,7 +1098,7 @@ fast_output2(Head, SizeT, Bases, SegAddr, SS, SegEnd) ->
end.
fast_output_end(Head, SizeT) ->
- case ets:foldl(fun({_Sz,_Pos,Cnt,NoC}, Acc) -> (Cnt =:= NoC) and Acc end,
+ case ets:foldl(fun({_Sz,_Pos,Cnt,NoC}, Acc) -> Acc andalso Cnt =:= NoC end,
true, SizeT) of
true -> {ok, Head};
false -> {error, invalid_objects_list}
@@ -1953,10 +1953,10 @@ hash_invars(H) ->
-define(M8(X), (((X) band (?SEGSZP - 1)) =:= 0)).
hash_invars(N, M, Next, Min, Max) ->
- ?M8(N) and ?M8(M) and ?M8(Next) and ?M8(Min) and ?M8(Max)
- and (0 =< N) and (N =< M) and (N =< 2*Next) and (M =< Next)
- and (Next =< 2*M) and (0 =< Min) and (Min =< Next) and (Next =< Max)
- and (Min =< M).
+ ?M8(N) andalso ?M8(M) andalso ?M8(Next) andalso ?M8(Min) andalso ?M8(Max)
+ andalso 0 =< N andalso N =< M andalso N =< 2*Next andalso M =< Next
+ andalso Next =< 2*M andalso 0 =< Min andalso Min =< Next andalso Next =< Max
+ andalso Min =< M.
seg_zero() ->
<<0:(4*?SEGSZ)/unit:8>>.
@@ -2156,8 +2156,8 @@ updated(Head, Pos, OldSize, BSize, SlotPos, Bins, Ch, DeltaNoOs, DeltaNoKs) ->
%% (and collections) as were present
%% when chunking started (the table
%% must have been fixed).
- (Overwrite0 =/= false) and
- (DeltaNoOs =:= 0) and (DeltaNoKs =:= 0);
+ (Overwrite0 =/= false) andalso
+ (DeltaNoOs =:= 0) andalso (DeltaNoKs =:= 0);
true ->
Overwrite0
end,
diff --git a/lib/stdlib/src/ets.erl b/lib/stdlib/src/ets.erl
index 94472e6b82..f0236ca94c 100644
--- a/lib/stdlib/src/ets.erl
+++ b/lib/stdlib/src/ets.erl
@@ -3112,22 +3112,28 @@ _Examples:_
An explicit match specification is here used to traverse the table:
```erlang
-9> true = ets:insert(Table = ets:new(t, []), [{1,a},{2,b},{3,c},{4,d}]),
-MS = ets:fun2ms(fun({X,Y}) when (X > 1) or (X < 5) -> {Y} end),
-QH1 = ets:table(Table, [{traverse, {select, MS}}]).
+1> T = ets:new(t, []).
+...
+2> true = ets:insert(T, [{1, a}, {2, b}, {3, c}, {4, d}, {5, e}]).
+...
+3> MS = ets:fun2ms(fun({X, Y}) when X > 1 andalso X < 5 -> {Y} end).
+...
+4> QH1 = ets:table(T, [{traverse, {select, MS}}]).
+...
```
An example with an implicit match specification:
```erlang
-10> QH2 = qlc:q([{Y} || {X,Y} <- ets:table(Table), (X > 1) or (X < 5)]).
+5> QH2 = qlc:q([{Y} || {X, Y} <- ets:table(T), X > 1 andalso X < 5]).
+...
```
The latter example is equivalent to the former, which can be verified using
function `qlc:info/1`:
```erlang
-11> qlc:info(QH1) =:= qlc:info(QH2).
+6> qlc:info(QH1) =:= qlc:info(QH2).
true
```
--
2.51.0