Skip to content

Commit

Permalink
Tests for ets:update_element/4
Browse files Browse the repository at this point in the history
  • Loading branch information
juhlig committed Nov 13, 2023
1 parent aa9b84d commit fd4ce7d
Show file tree
Hide file tree
Showing 2 changed files with 39 additions and 2 deletions.
22 changes: 22 additions & 0 deletions lib/stdlib/src/erl_stdlib_errors.erl
Original file line number Diff line number Diff line change
Expand Up @@ -772,6 +772,8 @@ format_ets_error(update_element, [_,_,ElementSpec]=Args, Cause) ->
case Cause of
keypos ->
[same_as_keypos];
position ->
[update_op_range];
_ ->
case is_element_spec_top(ElementSpec) of
true ->
Expand All @@ -785,6 +787,26 @@ format_ets_error(update_element, [_,_,ElementSpec]=Args, Cause) ->
[<<"is not a valid element specification">>]
end
end];
format_ets_error(update_element, [_, _, ElementSpec, Default]=Args, Cause) ->
TabCause = format_cause(Args, Cause),
ArgsCause = case Cause of
keypos ->
[same_as_keypos];
position ->
[update_op_range];
_ ->
case {is_element_spec_top(ElementSpec), format_tuple(Default)} of
{true, [""]} ->
[range];
{true, TupleCause} ->
["" | TupleCause];
{false, [""]} ->
[<<"is not a valid element specification">>];
{false, TupleCause} ->
["" | TupleCause]
end
end,
[TabCause, "" | ArgsCause];
format_ets_error(whereis, _Args, _Cause) ->
[bad_table_name];
format_ets_error(_, Args, Cause) ->
Expand Down
19 changes: 17 additions & 2 deletions lib/stdlib/test/ets_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -2568,6 +2568,8 @@ update_element_do(Tab,Tuple,Key,UpdPos) ->
%%io:format("update_element(~p)~n",[PosValArg]),
ArgHash = erlang:phash2({Tab,Key,PosValArg}),
true = ets:update_element(Tab, Key, PosValArg),
[DefaultObj] = ets:lookup(Tab, Key),
true = ets:update_element(Tab, make_ref(), PosValArg, DefaultObj),
ArgHash = erlang:phash2({Tab,Key,PosValArg}),
NewTuple = update_tuple(PosValArg,Tuple),
[NewTuple] = ets:lookup(Tab,Key),
Expand Down Expand Up @@ -2629,7 +2631,9 @@ update_element_neg(Opts) ->
Bag = ets_new(bag,[bag | Opts]),
DBag = ets_new(duplicate_bag,[duplicate_bag | Opts]),
{'EXIT',{badarg,_}} = (catch ets:update_element(Bag,key,{2,1})),
{'EXIT',{badarg,_}} = (catch ets:update_element(Bag,key,{2,1},{key,0})),
{'EXIT',{badarg,_}} = (catch ets:update_element(DBag,key,{2,1})),
{'EXIT',{badarg,_}} = (catch ets:update_element(DBag,key,{2,1},{key,0})),
true = ets:delete(Bag),
true = ets:delete(DBag),
ok.
Expand Down Expand Up @@ -9515,9 +9519,20 @@ error_info(_Config) ->
{update_element, ['$Tab', no_key, {2, new}], [no_fail]},
{update_element, [BagTab, no_key, {2, bagged}]},
{update_element, [OneKeyTab, one, not_tuple]},
{update_element, [OneKeyTab, one, {0, new}]},
{update_element, [OneKeyTab, one, {0, new}], [{error_term, position}]},
{update_element, [OneKeyTab, one, {1, new}], [{error_term,keypos}]},
{update_element, [OneKeyTab, one, {4, new}]},
{update_element, [OneKeyTab, one, {4, new}], [{error_term, position}]},

{update_element, ['$Tab', no_key, {2, new}, {no_key, old}], [no_fail]},
{update_element, ['$Tab', no_key, {0, new}, {no_key, old}], [{error_term, position}]},
{update_element, ['$Tab', no_key, {1, new}, {no_key, old}], [{error_term, keypos}]},
{update_element, ['$Tab', no_key, {4, new}, {no_key, old}], [{error_term, position}]},
{update_element, ['$Tab', no_key, {4, new}, not_tuple]},
{update_element, [BagTab, no_key, {1, bagged}, {no_key, old}], []},
{update_element, [OneKeyTab, no_key, {0, new}, {no_key, old}], [{error_term, position}]},
{update_element, [OneKeyTab, no_key, {1, new}, {no_key, old}], [{error_term, keypos}]},
{update_element, [OneKeyTab, no_key, {4, new}, {no_key, old}], [{error_term, position}]},
{update_element, [OneKeyTab, no_key, {4, new}, not_tuple]},

{whereis, [{bad,name}], [no_table]}
],
Expand Down

0 comments on commit fd4ce7d

Please sign in to comment.