File 7891-Add-lookup_element-4-which-takes-a-default-value.patch of Package erlang

From e528e26bf76267db4ff450d598c9a816d8d4a4ce Mon Sep 17 00:00:00 2001
From: Robin Morisset <rmorisset@fb.com>
Date: Mon, 22 Aug 2022 12:10:26 +0200
Subject: [PATCH] Add lookup_element/4, which takes a default value

Originally proposed in https://erlangforums.com/t/proposal-adding-ets-lookup-element-as-list-3/1743/4.

lookup_element/3 tends to be faster than lookup/2 when the key is always found, and is also a bit more ergonomic.
Unfortunately, when the key is absent, it throws an exception which is both somewhat slow and
less ergonomic to catch than matching the [] returned by lookup.
LeonardB suggested that a simple solution would be to offer an alternate version of lookup_element that takes an
extra argument, and returns that argument if the key is not found. This matches several other functions in the
standard library such as maps:get and proplists:get_value.

I confirmed the theory with some very simple microbenchmark: https://gist.github.com/RobinMorisset/62030c8fcb7376e16291904a9098e342

Code                                                         ||        QPS       Time     Rel
bench_lookup:bench_lookup_element_default_present().          1     133 Ki    7538 ns    100%
bench_lookup:bench_lookup_element_present().                  1     131 Ki    7604 ns     99%
bench_lookup:bench_lookup_present().                          1      89464   11177 ns     67%

bench_lookup:bench_lookup_element_default_absent().          1     140 Ki    7156 ns    100%
bench_lookup:bench_lookup_absent().                          1     134 Ki    7477 ns     95%
bench_lookup:bench_lookup_element_absent().                  1      88187   11339 ns     63%

As expected, lookup_element/4 is as fast as lookup_element/3 when the element is present, and as fast as lookup/2 when it is absent.

I've updated ets_SUITE.erl, and also done some manual testing. Finally there is the microbenchmark above.
---
 erts/emulator/beam/bif.tab           |  1 +
 erts/emulator/beam/erl_db.c          | 40 ++++++++++++++++++++++++--
 lib/stdlib/doc/src/ets.xml           | 26 +++++++++++++++++
 lib/stdlib/src/erl_stdlib_errors.erl |  3 ++
 lib/stdlib/src/ets.erl               | 12 +++++++-
 lib/stdlib/test/ets_SUITE.erl        | 42 ++++++++++++++++++++++++++--
 6 files changed, 119 insertions(+), 5 deletions(-)

diff --git a/erts/emulator/beam/bif.tab b/erts/emulator/beam/bif.tab
index 5f9c8624ec..500eee4735 100644
--- a/erts/emulator/beam/bif.tab
+++ b/erts/emulator/beam/bif.tab
@@ -362,6 +362,7 @@ bif ets:first/1
 bif ets:is_compiled_ms/1
 bif ets:lookup/2
 bif ets:lookup_element/3
+bif ets:lookup_element/4
 bif ets:info/1
 bif ets:info/2
 bif ets:last/1
diff --git a/erts/emulator/beam/erl_db.c b/erts/emulator/beam/erl_db.c
index bdcb136a05..d243e0506e 100644
--- a/erts/emulator/beam/erl_db.c
+++ b/erts/emulator/beam/erl_db.c
@@ -2670,8 +2670,44 @@ BIF_RETTYPE ets_lookup_element_3(BIF_ALIST_3)
     }
 }
 
-/* 
- * BIF to erase a whole table and release all memory it holds 
+/*
+** Get an element from a term
+** get_element_4(Tab, Key, Index, Default)
+** return the element or a list of elements if bag or Default if the element is not present
+*/
+BIF_RETTYPE ets_lookup_element_4(BIF_ALIST_4)
+{
+    DbTable* tb;
+    Sint index;
+    int cret;
+    Eterm ret;
+
+    CHECK_TABLES();
+
+    DB_BIF_GET_TABLE(tb, DB_READ, LCK_READ, BIF_ets_lookup_element_4);
+
+    if (is_not_small(BIF_ARG_3) || ((index = signed_val(BIF_ARG_3)) < 1)) {
+	    db_unlock(tb, LCK_READ);
+	    BIF_ERROR(BIF_P, BADARG);
+    }
+
+    cret = tb->common.meth->db_get_element(BIF_P, tb,
+					   BIF_ARG_2, index, &ret);
+    db_unlock(tb, LCK_READ);
+    switch (cret) {
+        case DB_ERROR_NONE:
+            BIF_RET(ret);
+        case DB_ERROR_BADKEY:
+            BIF_RET(BIF_ARG_4);
+        case DB_ERROR_SYSRES:
+            BIF_ERROR(BIF_P, SYSTEM_LIMIT);
+        default:
+            BIF_ERROR(BIF_P, BADARG);
+    }
+}
+
+/*
+ * BIF to erase a whole table and release all memory it holds
  */
 BIF_RETTYPE ets_delete_1(BIF_ALIST_1)
 {
diff --git a/lib/stdlib/doc/src/ets.xml b/lib/stdlib/doc/src/ets.xml
index 507d27d8d6..e323713668 100644
--- a/lib/stdlib/doc/src/ets.xml
+++ b/lib/stdlib/doc/src/ets.xml
@@ -955,6 +955,32 @@ Error: fun containing local Erlang function calls
       </desc>
     </func>
 
+    <func>
+      <name name="lookup_element" arity="4" since="OTP 26.0"/>
+      <fsummary>Return the <c>Pos</c>:th element of all objects with a
+        specified key in an ETS table, or <c>Default</c> if there is no such object.</fsummary>
+      <desc>
+        <p>For a table <c><anno>Table</anno></c> of type <c>set</c> or
+          <c>ordered_set</c>, the function returns the
+          <c><anno>Pos</anno></c>:th
+          element of the object with key <c><anno>Key</anno></c>.</p>
+        <p>For tables of type <c>bag</c> or <c>duplicate_bag</c>,
+          the functions returns a list with the <c><anno>Pos</anno></c>:th
+          element of every object with key <c><anno>Key</anno></c>.</p>
+        <p>If no object with key <c><anno>Key</anno></c> exists, the
+          function returns <c><anno>Default</anno></c>.</p>
+        <p>If <c><anno>Pos</anno></c> is larger than the size of
+          any tuple with a matching key, the function exits with
+          reason <c>badarg</c>.</p>
+        <p>The difference between <c>set</c>, <c>bag</c>, and
+          <c>duplicate_bag</c> on one hand, and <c>ordered_set</c> on
+          the other, regarding the fact that <c>ordered_set</c>
+          view keys as equal when they <em>compare equal</em>
+          whereas the other table types regard them equal only when
+          they <em>match</em>, holds for <c>lookup_element/4</c>.</p>
+      </desc>
+    </func>
+
     <func>
       <name name="match" arity="1" since=""/>
       <fsummary>Continues matching objects in an ETS table.</fsummary>
diff --git a/lib/stdlib/src/ets.erl b/lib/stdlib/src/ets.erl
index 979a75b231..3545c8a186 100644
--- a/lib/stdlib/src/ets.erl
+++ b/lib/stdlib/src/ets.erl
@@ -70,7 +70,7 @@
 -export([all/0, delete/1, delete/2, delete_all_objects/1,
          delete_object/2, first/1, give_away/3, info/1, info/2,
          insert/2, insert_new/2, is_compiled_ms/1, last/1, lookup/2,
-         lookup_element/3, match/1, match/2, match/3, match_object/1,
+         lookup_element/3, lookup_element/4, match/1, match/2, match/3, match_object/1,
          match_object/2, match_object/3, match_spec_compile/1,
          match_spec_run_r/3, member/2, new/2, next/2, prev/2,
          rename/2, safe_fixtable/2, select/1, select/2, select/3,
@@ -232,6 +232,16 @@ lookup(_, _) ->
 lookup_element(_, _, _) ->
     erlang:nif_error(undef).
 
+-spec lookup_element(Table, Key, Pos, Default) -> Elem when
+    Table :: table(),
+    Key :: term(),
+    Pos :: pos_integer(),
+    Default :: term(),
+    Elem :: term() | [term()].
+
+lookup_element(_, _, _, _) ->
+  erlang:nif_error(undef).
+
 -spec match(Table, Pattern) -> [Match] when
       Table :: table(),
       Pattern :: match_pattern(),
diff --git a/lib/stdlib/test/ets_SUITE.erl b/lib/stdlib/test/ets_SUITE.erl
index 64009a5273..6a58ff14f0 100644
--- a/lib/stdlib/test/ets_SUITE.erl
+++ b/lib/stdlib/test/ets_SUITE.erl
@@ -39,7 +39,7 @@
 -export([tab2file/1, tab2file2/1, tabfile_ext1/1,
 	 tabfile_ext2/1, tabfile_ext3/1, tabfile_ext4/1, badfile/1]).
 -export([heavy_lookup/1, heavy_lookup_element/1, heavy_concurrent/1]).
--export([lookup_element_mult/1]).
+-export([lookup_element_mult/1, lookup_element_default/1]).
 -export([foldl_ordered/1, foldr_ordered/1, foldl/1, foldr/1, fold_empty/1]).
 -export([t_delete_object/1, t_init_table/1, t_whitebox/1,
          select_bound_chunk/1, t_delete_all_objects/1, t_test_ms/1,
@@ -191,7 +191,7 @@ groups() ->
        privacy]},
      {insert, [], [empty, badinsert]},
      {lookup, [], [badlookup, lookup_order]},
-     {lookup_element, [], [lookup_element_mult]},
+     {lookup_element, [], [lookup_element_mult, lookup_element_default]},
      {delete, [],
       [delete_elem, delete_tab, delete_large_tab,
        delete_large_named_table, evil_delete, table_leak,
@@ -4034,6 +4034,41 @@ fill_tab(Tab,Val) ->
 
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
+lookup_element_default(Config) when is_list(Config) ->
+    EtsMem = etsmem(),
+
+    TabSet = ets_new(foo, [set]),
+    ets:insert(TabSet, {key, 42}),
+    42 = ets:lookup_element(TabSet, key, 2, 13),
+    13 = ets:lookup_element(TabSet, not_key, 2, 13),
+    {'EXIT',{badarg,_}} = catch ets:lookup_element(TabSet, key, 3, 13),
+    true = ets:delete(TabSet),
+
+    TabOrderedSet = ets_new(foo, [ordered_set]),
+    ets:insert(TabOrderedSet, {key, 42}),
+    42 = ets:lookup_element(TabOrderedSet, key, 2, 13),
+    13 = ets:lookup_element(TabOrderedSet, not_key, 2, 13),
+    {'EXIT',{badarg,_}} = catch ets:lookup_element(TabOrderedSet, key, 3, 13),
+    true = ets:delete(TabOrderedSet),
+
+    TabBag = ets_new(foo, [bag]),
+    ets:insert(TabBag, {key, 42}),
+    ets:insert(TabBag, {key, 43, 44}),
+    [42, 43] = ets:lookup_element(TabBag, key, 2, 13),
+    13 = ets:lookup_element(TabBag, not_key, 2, 13),
+    {'EXIT',{badarg,_}} = catch ets:lookup_element(TabBag, key, 3, 13),
+    true = ets:delete(TabBag),
+
+    TabDuplicateBag = ets_new(foo, [duplicate_bag]),
+    ets:insert(TabDuplicateBag, {key, 42}),
+    ets:insert(TabDuplicateBag, {key, 42}),
+    ets:insert(TabDuplicateBag, {key, 43, 44}),
+    [42, 42, 43] = ets:lookup_element(TabDuplicateBag, key, 2, 13),
+    13 = ets:lookup_element(TabDuplicateBag, not_key, 2, 13),
+    {'EXIT',{badarg,_}} = catch ets:lookup_element(TabDuplicateBag, key, 3, 13),
+    true = ets:delete(TabDuplicateBag),
+
+    verify_etsmem(EtsMem).
 
 %% OTP-2386. Multiple return elements.
 lookup_element_mult(Config) when is_list(Config) ->
-- 
2.35.3

openSUSE Build Service is sponsored by