Skip to content

Commit 1727aa8

Browse files
committed
stdlib: Make vertex and edge ids in digraph unique
Fix #9191
1 parent 9233927 commit 1727aa8

File tree

2 files changed

+13
-20
lines changed

2 files changed

+13
-20
lines changed

lib/stdlib/src/digraph.erl

+11-20
Original file line numberDiff line numberDiff line change
@@ -165,7 +165,6 @@ new(Type) ->
165165
V = ets:new(vertices, [set, Access]),
166166
E = ets:new(edges, [set, Access]),
167167
N = ets:new(neighbours, [bag, Access]),
168-
ets:insert(N, [{'$vid', 0}, {'$eid', 0}]),
169168
set_type(Ts, #digraph{vtab=V, etab=E, ntab=N});
170169
error ->
171170
erlang:error(badarg)
@@ -251,7 +250,7 @@ The created vertex is represented by term `['$v' | N]`, where `N` is an intege
251250
G :: graph().
252251

253252
add_vertex(G) ->
254-
do_add_vertex({new_vertex_id(G), []}, G).
253+
do_add_vertex({new_vertex_id(), []}, G).
255254

256255
-doc(#{equiv => add_vertex(G, V, [])}).
257256
-spec add_vertex(G, V) -> vertex() when
@@ -409,7 +408,7 @@ out_edges(G, V) ->
409408
V2 :: vertex().
410409

411410
add_edge(G, V1, V2) ->
412-
do_add_edge({new_edge_id(G), V1, V2, []}, G).
411+
do_add_edge({new_edge_id(), V1, V2, []}, G).
413412

414413
-doc(#{equiv => add_edge/5}).
415414
-doc """
@@ -426,7 +425,7 @@ See `t:add_edge_err_rsn/0` for details on possible errors.
426425
Label :: label().
427426

428427
add_edge(G, V1, V2, D) ->
429-
do_add_edge({new_edge_id(G), V1, V2, D}, G).
428+
do_add_edge({new_edge_id(), V1, V2, D}, G).
430429

431430
-doc """
432431
Creates (or modifies) an edge with the identifier
@@ -513,30 +512,22 @@ edge(G, E) ->
513512
%%
514513
%% Generate a "unique" edge identifier (relative to this graph)
515514
%%
516-
-spec new_edge_id(graph()) -> edge().
515+
-spec new_edge_id() -> edge().
517516

518-
-dialyzer({no_improper_lists, new_edge_id/1}).
517+
-dialyzer({no_improper_lists, new_edge_id/0}).
519518

520-
new_edge_id(G) ->
521-
NT = G#digraph.ntab,
522-
[{'$eid', K}] = ets:lookup(NT, '$eid'),
523-
true = ets:delete(NT, '$eid'),
524-
true = ets:insert(NT, {'$eid', K+1}),
525-
['$e' | K].
519+
new_edge_id() ->
520+
['$e' | erlang:unique_integer()].
526521

527522
%%
528523
%% Generate a "unique" vertex identifier (relative to this graph)
529524
%%
530-
-spec new_vertex_id(graph()) -> vertex().
525+
-spec new_vertex_id() -> vertex().
531526

532-
-dialyzer({no_improper_lists, new_vertex_id/1}).
527+
-dialyzer({no_improper_lists, new_vertex_id/0}).
533528

534-
new_vertex_id(G) ->
535-
NT = G#digraph.ntab,
536-
[{'$vid', K}] = ets:lookup(NT, '$vid'),
537-
true = ets:delete(NT, '$vid'),
538-
true = ets:insert(NT, {'$vid', K+1}),
539-
['$v' | K].
529+
new_vertex_id() ->
530+
['$v' | erlang:unique_integer()].
540531

541532
%%
542533
%% Collect elements for a index in a tuple

lib/stdlib/test/digraph_utils_SUITE.erl

+2
Original file line numberDiff line numberDiff line change
@@ -153,6 +153,8 @@ subgraph(Config) when is_list(Config) ->
153153
{fg,f,g,fgl} = digraph:edge(SG, fg),
154154
{fg2,f,g,fgl2} = digraph:edge(SG, fg2),
155155
{_, {_, acyclic}} = lists:keysearch(cyclicity, 1, digraph:info(SG)),
156+
digraph:add_edge(SG, f, g),
157+
digraph:add_vertex(SG, b),
156158
true = digraph:delete(SG),
157159

158160
SG1 = digraph_utils:subgraph(G, [f, g, h],

0 commit comments

Comments
 (0)