File 0912-digraph-Avoid-false-edges-for-vertices-with-names-co.patch of Package erlang

From c5e3d13f0325f8caa155bb7cb7298e749b594d50 Mon Sep 17 00:00:00 2001
From: Frej Drejhammar <frej@sics.se>
Date: Wed, 6 May 2020 06:34:45 +0200
Subject: [PATCH] digraph: Avoid false edges for vertices with names containing
 a '_'

This patch fixes a bug in the digraph module where in_edges/2 and
out_edges/2 return false edges in the case they are called for a
vertex which has a '_' in its name term. The following example shows
the problem:

    G = new([acyclic]),
    A = add_vertex(G, 'A'),
    B = add_vertex(G, '_'),
    AB = add_edge(G, A, B),
    0 = out_degree(G, B), %% ok
    [] = out_edges(G, B), %% Fails as [AB] is returned

An edge, E, emanating from and incident on a vertex is stored in the
ntab-ets table as a record of the form {{out, V}, E} and {{in, V}, E}
respectively. As out_edges/2 and in_edges/2 use ets:select/2 to look
up the relevant edges, a vertex with a '_' somewhere in the term used
as its name will trigger ets to do a wildcard match. In the example
above, this will return all out-edges in the whole graph. This problem
is fixed by switching from ets:select to ets:lookup.

This patch includes an extended test case which checks the correctness
of the fix described above as well as checking that the other
edge-related functions in digraph do not suffer from the same problem.
---
 lib/stdlib/src/digraph.erl        |  4 +--
 lib/stdlib/test/digraph_SUITE.erl | 51 +++++++++++++++++++++++++++++--
 2 files changed, 50 insertions(+), 5 deletions(-)

diff --git a/lib/stdlib/src/digraph.erl b/lib/stdlib/src/digraph.erl
index 8a4df95027..58d493cf54 100644
--- a/lib/stdlib/src/digraph.erl
+++ b/lib/stdlib/src/digraph.erl
@@ -230,7 +230,7 @@ in_neighbours(G, V) ->
       Edges :: [edge()].
 
 in_edges(G, V) ->
-    ets:select(G#digraph.ntab, [{{{in, V}, '$1'}, [], ['$1']}]).
+    [E || {{in, _}, E} <- ets:lookup(G#digraph.ntab, {in, V})].
 
 -spec out_degree(G, V) -> non_neg_integer() when
       G :: graph(),
@@ -255,7 +255,7 @@ out_neighbours(G, V) ->
       Edges :: [edge()].
 
 out_edges(G, V) ->
-    ets:select(G#digraph.ntab, [{{{out, V}, '$1'}, [], ['$1']}]).
+    [E || {{out, _}, E} <- ets:lookup(G#digraph.ntab, {out, V})].
 
 -spec add_edge(G, V1, V2) -> edge() | {'error', add_edge_err_rsn()} when
       G :: graph(),
diff --git a/lib/stdlib/test/digraph_SUITE.erl b/lib/stdlib/test/digraph_SUITE.erl
index b5d3452616..ce0bc90f1c 100644
--- a/lib/stdlib/test/digraph_SUITE.erl
+++ b/lib/stdlib/test/digraph_SUITE.erl
@@ -31,7 +31,7 @@
 	 init_per_group/2,end_per_group/2]).
 
 -export([opts/1, degree/1, path/1, cycle/1, vertices/1,
-	 edges/1, data/1, otp_3522/1, otp_3630/1, otp_8066/1]).
+	 edges/1, data/1, otp_3522/1, otp_3630/1, otp_8066/1, vertex_names/1]).
 
 -export([spawn_graph/2]).
 
@@ -41,10 +41,10 @@ suite() -> [{ct_hooks,[ts_install_cth]}].
 
 all() -> 
     [opts, degree, path, cycle, {group, misc},
-     {group, tickets}].
+     {group, tickets}, vertex_names].
 
 groups() -> 
-    [{misc, [], [vertices, edges, data]},
+    [{misc, [], [vertices, edges, data, vertex_names]},
      {tickets, [], [otp_3522, otp_3630, otp_8066]}].
 
 init_per_suite(Config) ->
@@ -337,6 +337,51 @@ otp_8066(Config) when is_list(Config) ->
 
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
+vertex_names(Config) when is_list(Config) ->
+    %% Check that a node named '_' does not lead to wildcard matches
+    %% in ets.
+
+    G = digraph:new([acyclic]),
+    A = digraph:add_vertex(G, 'A'),
+    B = digraph:add_vertex(G, '_'),
+    AB = digraph:add_edge(G, A, B),
+
+    %% Link A -> B
+    1 = digraph:out_degree(G, A),
+    1 = digraph:in_degree(G, B),
+    0 = digraph:out_degree(G, B),
+    0 = digraph:in_degree(G, A),
+    [B] = digraph:out_neighbours(G, A),
+    [A] = digraph:in_neighbours(G, B),
+    [] = digraph:out_neighbours(G, B),
+    [] = digraph:in_neighbours(G, A),
+    [AB] = digraph:out_edges(G, A),
+    [AB] = digraph:in_edges(G, B),
+    [] = digraph:out_edges(G, B),
+    [] = digraph:in_edges(G, A),
+
+    %% Reverse the edge
+    digraph:del_edge(G, AB),
+    BA = digraph:add_edge(G, B, A),
+
+    1 = digraph:out_degree(G, B),
+    1 = digraph:in_degree(G, A),
+    0 = digraph:out_degree(G, A),
+    0 = digraph:in_degree(G, B),
+    [A] = digraph:out_neighbours(G, B),
+    [B] = digraph:in_neighbours(G, A),
+    [] = digraph:out_neighbours(G, A),
+    [] = digraph:in_neighbours(G, B),
+    [BA] = digraph:out_edges(G, B),
+    [BA] = digraph:in_edges(G, A),
+    [] = digraph:out_edges(G, A),
+    [] = digraph:in_edges(G, B),
+
+    digraph:delete(G),
+    ok.
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+
 sane(G) ->
     sane1(G),
     erase(sane) =:= undefined.
-- 
2.26.1

openSUSE Build Service is sponsored by