File 7811-kernel-test-Skip-multiple_raw-test-case-s-on-OpenBSD.patch of Package erlang

From 5d895620553a366be4480d0d311b767c2d495816 Mon Sep 17 00:00:00 2001
From: Micael Karlberg <bmk@erlang.org>
Date: Wed, 28 Jun 2023 17:11:28 +0200
Subject: [PATCH 1/4] [kernel|test] Skip multiple_raw test case(s) on OpenBSD

The test case(s) uses the socket option dontroute, which
is not supported on OpenBSD.
---
 lib/kernel/test/inet_sockopt_SUITE.erl | 50 +++++++++++++++++++++-----
 1 file changed, 42 insertions(+), 8 deletions(-)

diff --git a/lib/kernel/test/inet_sockopt_SUITE.erl b/lib/kernel/test/inet_sockopt_SUITE.erl
index 5c95781066..5437a139cf 100644
--- a/lib/kernel/test/inet_sockopt_SUITE.erl
+++ b/lib/kernel/test/inet_sockopt_SUITE.erl
@@ -196,21 +196,30 @@ nintbin2int(<<>>) -> 0.
 
 %% Test setopt/getopt of multiple raw options.
 multiple_raw(Config) when is_list(Config) ->
-    do_multiple_raw(Config,false).
+    Cond = fun() -> is_not_openbsd() end,
+    Pre  = fun() -> false end,
+    Case = fun(State) -> do_multiple_raw(Config, State) end,
+    Post = fun(_) -> ok end,
+    ?TC_TRY(?FUNCTION_NAME, Cond, Pre, Case, Post).
+    
 
 %% Test setopt/getopt of multiple raw options, with binaries in
 %% getopt.
 multiple_raw_getbin(Config) when is_list(Config) ->
-    do_multiple_raw(Config,true).
+    Cond = fun() -> is_not_openbsd() end,
+    Pre  = fun() -> true end,
+    Case = fun(State) -> do_multiple_raw(Config, State) end,
+    Post = fun(_) -> ok end,
+    ?TC_TRY(?FUNCTION_NAME, Cond, Pre, Case, Post).
 
 do_multiple_raw(Config, Binary) ->
-    Port = start_helper(Config),
-    SolSocket = ask_helper(Port, ?C_GET_SOL_SOCKET),
-    SoKeepalive = ask_helper(Port, ?C_GET_SO_KEEPALIVE),
-    SoKeepaliveTrue = {raw,SolSocket,SoKeepalive,<<1:32/native>>},
+    Port             = start_helper(Config),
+    SolSocket        = ask_helper(Port, ?C_GET_SOL_SOCKET),
+    SoKeepalive      = ask_helper(Port, ?C_GET_SO_KEEPALIVE),
+    SoKeepaliveTrue  = {raw,SolSocket,SoKeepalive,<<1:32/native>>},
     SoKeepaliveFalse = {raw,SolSocket,SoKeepalive,<<0:32/native>>},
-    SoDontroute = ask_helper(Port, ?C_GET_SO_DONTROUTE),
-    SoDontrouteTrue = {raw,SolSocket,SoDontroute,<<1:32/native>>},
+    SoDontroute      = ask_helper(Port, ?C_GET_SO_DONTROUTE),
+    SoDontrouteTrue  = {raw,SolSocket,SoDontroute,<<1:32/native>>},
     SoDontrouteFalse = {raw,SolSocket,SoDontroute,<<0:32/native>>},
     {S1,S2} =
 	create_socketpair(
@@ -1085,3 +1094,28 @@ binarify(Size,Binary) when Binary =:= true ->
     <<0:Size/unit:8>>;
 binarify(Size,Binary) when Binary =:= false ->
     Size.
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+
+%% Here are all the *general* test case condition functions.
+
+is_not_openbsd() ->
+    is_not_platform(openbsd, "OpenBSD").
+
+is_not_platform(Platform, PlatformStr)
+  when is_atom(Platform) andalso is_list(PlatformStr) ->
+      case os:type() of
+          {unix, Platform} ->
+              skip("This does not work on " ++ PlatformStr);
+        _ ->
+            ok
+    end.
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+
+skip(Reason) ->
+    throw({skip, Reason}).
+
+
-- 
2.35.3

openSUSE Build Service is sponsored by