File 4401-ets-improve-ets-new-2-already_exists-named_table-err.patch of Package erlang
From 53900d65ce8e7c246ed419ecbfc42ee4fe5956e9 Mon Sep 17 00:00:00 2001
From: Gonzalo Bella <gonzalobfmp@gmail.com>
Date: Thu, 29 Sep 2022 16:40:13 +0100
Subject: [PATCH] ets: improve ets:new/2 already_exists named_table error
Adds extra information in `erl_db.c` before returning the error for already
used table name. The error is only returned if the option `named_table`
is give and the name is already in use.
The extra information is used later to format the error message.
```
1> ets:new(ac_tab,[named_table]).
** exception error: bad argument
in function ets:new/2
called as ets:new(ac_tab,[named_table])
*** argument 1: table name already exists
```
---
erts/emulator/beam/atom.names | 1 +
erts/emulator/beam/erl_db.c | 4 +++-
lib/stdlib/src/erl_stdlib_errors.erl | 14 ++++++++------
lib/stdlib/test/ets_SUITE.erl | 6 +++++-
4 files changed, 17 insertions(+), 8 deletions(-)
diff --git a/erts/emulator/beam/atom.names b/erts/emulator/beam/atom.names
index 223603543f..c201268d03 100644
--- a/erts/emulator/beam/atom.names
+++ b/erts/emulator/beam/atom.names
@@ -90,6 +90,7 @@ atom allocator
atom allocator_sizes
atom alloc_util_allocators
atom allow_passive_connect
+atom already_exists
atom already_loaded
atom amd64
atom anchored
diff --git a/erts/emulator/beam/erl_db.c b/erts/emulator/beam/erl_db.c
index 3708019529..aa49291baa 100644
--- a/erts/emulator/beam/erl_db.c
+++ b/erts/emulator/beam/erl_db.c
@@ -57,6 +57,7 @@
#define EXI_POSITION am_position /* The position is out of range. */
#define EXI_OWNER am_owner /* The receiving process is already the owner. */
#define EXI_NOT_OWNER am_not_owner /* The current process is not the owner. */
+#define EXI_ALREADY_EXISTS am_already_exists /* The table identifier already exists. */
#define DB_WRITE_CONCURRENCY_MIN_LOCKS 1
#define DB_WRITE_CONCURRENCY_MAX_LOCKS 32768
@@ -2532,7 +2533,8 @@ BIF_RETTYPE ets_new_2(BIF_ALIST_2)
tb->common.meth->db_free_empty_table(tb);
db_unlock(tb,LCK_WRITE);
table_dec_refc(tb, 0);
- BIF_ERROR(BIF_P, BADARG);
+ BIF_P->fvalue = EXI_ALREADY_EXISTS;
+ BIF_ERROR(BIF_P, BADARG | EXF_HAS_EXT_INFO);
}
BIF_P->flags |= F_USING_DB; /* So we can remove tb if p dies */
diff --git a/lib/stdlib/src/erl_stdlib_errors.erl b/lib/stdlib/src/erl_stdlib_errors.erl
index 3298ee0f95..eeccb77db1 100644
--- a/lib/stdlib/src/erl_stdlib_errors.erl
+++ b/lib/stdlib/src/erl_stdlib_errors.erl
@@ -653,17 +653,19 @@ format_ets_error(match_spec_compile, [_], _Cause) ->
[bad_matchspec];
format_ets_error(next, Args, Cause) ->
format_default(bad_key, Args, Cause);
-format_ets_error(new, [Name,Options], _Cause) ->
+format_ets_error(new, [Name,Options], Cause) ->
NameError = if
is_atom(Name) -> [];
true -> not_atom
end,
OptsError = must_be_list(Options),
- case {NameError,OptsError} of
- {[],[]} ->
- [[],bad_options];
- {_,_} ->
- [NameError,OptsError]
+ case {NameError, OptsError, Cause} of
+ {[], [], already_exists} ->
+ [name_already_exists, []];
+ {[], [], _} ->
+ [[], bad_options];
+ {_, _, _} ->
+ [NameError, OptsError]
end;
format_ets_error(prev, Args, Cause) ->
format_default(bad_key, Args, Cause);
diff --git a/lib/stdlib/test/ets_SUITE.erl b/lib/stdlib/test/ets_SUITE.erl
index 249a27bd02..99fe33dbff 100644
--- a/lib/stdlib/test/ets_SUITE.erl
+++ b/lib/stdlib/test/ets_SUITE.erl
@@ -8802,6 +8802,7 @@ error_info(_Config) ->
end),
receive T -> T end
end,
+ _ = ets:new(name_already_exists, [named_table]),
L = [{delete, ['$Tab']},
{delete, ['$Tab', no_key], [no_fail]},
@@ -8886,6 +8887,8 @@ error_info(_Config) ->
{new, [name, [a|b]], [no_table]},
{new, [name, [a,b]], [no_table]},
{new, [{bad,name}, [a,b]], [no_table]},
+ {new, [name_already_exists, [named_table]], [no_table,
+ {error_term,already_exists}]},
%% For a set, ets:next/2 and ets:prev/2 fails if the key does
%% not exist.
@@ -9058,8 +9061,9 @@ ets_eval_bif_errors_once(F, Args, Opts) ->
io:format("\n\n*** ets:~p/~p", [F,length(Args)]),
NoFail = lists:member(no_fail, Opts),
+ ErrorTerm = proplists:get_value(error_term, Opts, none),
case ets_apply(F, Args, Opts) of
- {error,none} ->
+ {error,ErrorTerm} when not NoFail ->
ok;
{error,Info} ->
store_error(wrong_failure_reason, MFA, Info);
--
2.35.3