File 7711-erts-inet-Fix-udp-multicast_if-option-for-IPv6.patch of Package erlang
From b2e4859a9a4252ffc3aeb28771316bf21c126cf0 Mon Sep 17 00:00:00 2001
From: Micael Karlberg <bmk@erlang.org>
Date: Tue, 10 May 2022 16:39:06 +0200
Subject: [PATCH 01/11] [erts|inet] Fix (udp) multicast_if option for IPv6
OTP-18091
---
erts/emulator/drivers/common/inet_drv.c | 85 +++++++++++++++++-------
erts/preloaded/ebin/prim_inet.beam | Bin 98988 -> 100100 bytes
erts/preloaded/src/prim_inet.erl | 53 ++++++++++-----
3 files changed, 97 insertions(+), 41 deletions(-)
diff --git a/erts/emulator/drivers/common/inet_drv.c b/erts/emulator/drivers/common/inet_drv.c
index 217518f3aa..60baf3378d 100644
--- a/erts/emulator/drivers/common/inet_drv.c
+++ b/erts/emulator/drivers/common/inet_drv.c
@@ -578,6 +578,7 @@ static int (*p_sctp_connectx)
#define DEBUGF(X) printf X
#endif
+
#if !defined(HAVE_STRNCASECMP)
#define STRNCASECMP my_strncasecmp
@@ -4440,10 +4441,6 @@ static char* inet_set_address(int family, inet_address* dst,
{
short port;
- // printf("inet_set_address -> entry with"
- // "\r\n family: %d"
- // "\r\n", family);
-
switch (family) {
case AF_INET: {
if (*len < 2+4) return str_einval;
@@ -4473,12 +4470,8 @@ static char* inet_set_address(int family, inet_address* dst,
sys_memcpy(&dst->sai6.sin6_addr, *src, 16);
*src += 16;
dst->sai6.sin6_flowinfo = get_int32(*src);
- // printf("inet_set_address -> flowinfo: %u"
- // "\r\n", dst->sai6.sin6_flowinfo);
*src += 4;
dst->sai6.sin6_scope_id = get_int32(*src);
- // printf("inet_set_address -> scope_id: %u"
- // "\r\n", dst->sai6.sin6_scope_id);
*src += 4;
*len = sizeof(struct sockaddr_in6);
return NULL;
@@ -4954,6 +4947,7 @@ static ErlDrvSSizeT inet_ctl_open(inet_descriptor* desc, int domain, int type,
desc->state = INET_STATE_OPEN;
desc->stype = type;
desc->sfamily = domain;
+
return ctl_reply(INET_REP_OK, NULL, 0, rbuf, rsize);
}
@@ -7096,9 +7090,28 @@ static int inet_set_opts(inet_descriptor* desc, char* ptr, int len)
"inet_set_opts(multicast-if) -> %d (%d)\r\n",
__LINE__,
desc->s, driver_caller(desc->port), ival, sock_htonl(ival)) );
- proto = IPPROTO_IP;
- type = IP_MULTICAST_IF;
- ival = sock_htonl(ival);
+ if (desc->sfamily == AF_INET) {
+ proto = IPPROTO_IP;
+ type = IP_MULTICAST_IF;
+ DEBUGF(("inet_set_opts(%p): s=%d, IP_MULTICAST_IF = %x\r\n",
+ desc->port, desc->s, ival));
+ ival = sock_htonl(ival);
+ }
+#if defined(HAVE_IN6) && defined(AF_INET6)
+ else if (desc->sfamily == AF_INET6) {
+ proto = IPPROTO_IPV6;
+ type = IPV6_MULTICAST_IF;
+ DEBUGF(("inet_set_opts(%p): s=%d, IPV6_MULTICAST_IF = %x\r\n",
+ desc->port, desc->s, ival));
+ ival = sock_htonl(ival);
+ } else {
+ return -1;
+ }
+#else
+ else {
+ return -1;
+ }
+#endif
break;
case UDP_OPT_ADD_MEMBERSHIP:
@@ -7210,21 +7223,19 @@ static int inet_set_opts(inet_descriptor* desc, char* ptr, int len)
return -1;
}
-
DDBG(desc,
("INET-DRV-DBG[%d][" SOCKET_FSTR ",%T] "
"inet_set_opts -> try set opt (%d) %d\r\n",
__LINE__, desc->s, driver_caller(desc->port), proto, type) );
-#if defined(IP_TOS) && defined(IPPROTO_IP) \
+#if defined(IP_TOS) && defined(IPPROTO_IP) \
&& defined(SO_PRIORITY) && !defined(__WIN32__)
res = setopt_prio_tos_trick (desc->s, proto, type, arg_ptr, arg_sz, propagate);
#else
res = sock_setopt (desc->s, proto, type, arg_ptr, arg_sz);
#endif
-
DDBG(desc,
("INET-DRV-DBG[%d][" SOCKET_FSTR ",%T] "
"inet_set_opts -> set opt result: %d\r\n",
@@ -8553,14 +8564,44 @@ static ErlDrvSSizeT inet_fill_opts(inet_descriptor* desc,
proto = IPPROTO_IP;
type = IP_MULTICAST_TTL;
break;
+
case UDP_OPT_MULTICAST_LOOP:
proto = IPPROTO_IP;
type = IP_MULTICAST_LOOP;
break;
+
case UDP_OPT_MULTICAST_IF:
- proto = IPPROTO_IP;
- type = IP_MULTICAST_IF;
- break;
+ {
+ int mif = 0;
+ unsigned int mifSz = sizeof(mif);
+
+ *ptr++ = opt;
+ /* We use up the 4 (value) places for the domain/family
+ * So we need to allocate 4 more */
+ PLACE_FOR(4,ptr);
+ if (desc->sfamily == AF_INET) {
+ put_int32(INET_AF_INET, ptr);
+ ptr += 4;
+ proto = IPPROTO_IP;
+ type = IP_MULTICAST_IF;
+ } else if (desc->sfamily == AF_INET6) {
+ put_int32(INET_AF_INET6, ptr);
+ ptr += 4;
+ proto = IPPROTO_IPV6;
+ type = IPV6_MULTICAST_IF;
+ } else {
+ RETURN_ERROR();
+ }
+ if (IS_SOCKET_ERROR(sock_getopt(desc->s,
+ proto, type,
+ &mif, &mifSz))) {
+ TRUNCATE_TO(0,ptr);
+ continue;
+ }
+ put_int32(mif, ptr);
+ }
+ continue;
+
case INET_OPT_LINGER:
arg_sz = sizeof(li_val);
sys_memzero((void *) &li_val, sizeof(li_val));
@@ -8764,6 +8805,7 @@ static ErlDrvSSizeT inet_fill_opts(inet_descriptor* desc,
TRUNCATE_TO(0,ptr);
continue;
}
+
*ptr++ = opt;
if (arg_ptr == (char*)&ival) {
put_int32(ival, ptr);
@@ -9972,9 +10014,9 @@ static ErlDrvSSizeT inet_ctl(inet_descriptor* desc, int cmd, char* buf,
return ctl_error(-replen, rbuf, rsize);
} else
#endif
- if ((replen = inet_fill_opts(desc, buf, len, rbuf, rsize)) < 0) {
- return ctl_error(EINVAL, rbuf, rsize);
- }
+ if ((replen = inet_fill_opts(desc, buf, len, rbuf, rsize)) < 0) {
+ return ctl_error(EINVAL, rbuf, rsize);
+ }
return replen;
}
@@ -10338,12 +10380,9 @@ static ErlDrvSSizeT inet_ctl(inet_descriptor* desc, int cmd, char* buf,
(desc->sfamily, &local, &buf, &len)) != NULL)
return ctl_xerror(xerror, rbuf, rsize);
- // printf("inet_ctl(INET_REQ_BIND) -> try bind\r\n");
if (IS_SOCKET_ERROR(sock_bind(desc->s,(struct sockaddr*) &local, len))) {
- // printf("inet_ctl(INET_REQ_BIND) -> bind failed\r\n");
return ctl_error(sock_errno(), rbuf, rsize);
}
- // printf("inet_ctl(INET_REQ_BIND) -> bound\r\n");
desc->state = INET_STATE_OPEN;
diff --git a/erts/preloaded/src/prim_inet.erl b/erts/preloaded/src/prim_inet.erl
index 2650b54248..27a46fee10 100644
--- a/erts/preloaded/src/prim_inet.erl
+++ b/erts/preloaded/src/prim_inet.erl
@@ -1684,7 +1684,7 @@ type_opt_1(ipv6_v6only) -> bool;
%% multicast
type_opt_1(multicast_ttl) -> int;
type_opt_1(multicast_loop) -> bool;
-type_opt_1(multicast_if) -> ip;
+type_opt_1(multicast_if) -> mif;
type_opt_1(add_membership) -> {ip,ip};
type_opt_1(drop_membership) -> {ip,ip};
%% driver options
@@ -1922,6 +1922,8 @@ type_value_2(uint8, X) when X band 16#ff =:= X -> true;
type_value_2(time, infinity) -> true;
type_value_2(time, X) when is_integer(X), X >= 0 -> true;
type_value_2(ip,{A,B,C,D}) when ?ip(A,B,C,D) -> true;
+type_value_2(mif,{A,B,C,D}) when ?ip(A,B,C,D) -> true;
+type_value_2(mif,Idx) when is_integer(Idx) -> true;
%%
type_value_2(addr, {any,Port}) ->
type_value_2(uint16, Port);
@@ -2081,21 +2083,27 @@ enc_value_tuple(_, _, _, _) -> [].
%%
%% Encoding of option VALUES:
%%
-enc_value_2(bool, true) -> [0,0,0,1];
-enc_value_2(bool, false) -> [0,0,0,0];
-enc_value_2(bool8, true) -> [1];
-enc_value_2(bool8, false) -> [0];
-enc_value_2(int, Val) -> ?int32(Val);
-enc_value_2(uint, Val) -> ?int32(Val);
-enc_value_2(uint32, Val) -> ?int32(Val);
-enc_value_2(uint24, Val) -> ?int24(Val);
-enc_value_2(uint16, Val) -> ?int16(Val);
-enc_value_2(uint8, Val) -> ?int8(Val);
-enc_value_2(time, infinity) -> ?int32(-1);
-enc_value_2(time, Val) -> ?int32(Val);
-enc_value_2(ip,{A,B,C,D}) -> [A,B,C,D];
-enc_value_2(ip, any) -> [0,0,0,0];
-enc_value_2(ip, loopback) -> [127,0,0,1];
+enc_value_2(bool, true) -> [0,0,0,1];
+enc_value_2(bool, false) -> [0,0,0,0];
+enc_value_2(bool8, true) -> [1];
+enc_value_2(bool8, false) -> [0];
+enc_value_2(int, Val) -> ?int32(Val);
+enc_value_2(uint, Val) -> ?int32(Val);
+enc_value_2(uint32, Val) -> ?int32(Val);
+enc_value_2(uint24, Val) -> ?int24(Val);
+enc_value_2(uint16, Val) -> ?int16(Val);
+enc_value_2(uint8, Val) -> ?int8(Val);
+enc_value_2(time, infinity) -> ?int32(-1);
+enc_value_2(time, Val) -> ?int32(Val);
+enc_value_2(ip, IP)
+ when (tuple_size(IP) =:= 4) -> ip4_to_bytes(IP);
+enc_value_2(ip, any) -> [0,0,0,0];
+enc_value_2(ip, loopback) -> [127,0,0,1];
+enc_value_2(mif, IP)
+ when (tuple_size(IP) =:= 4) -> ip4_to_bytes(IP);
+enc_value_2(mif, Idx)
+ when is_integer(Idx) -> ?int32(Idx);
+
%%
enc_value_2(addr, {any,Port}) ->
[?INET_AF_ANY|?int16(Port)];
@@ -2195,7 +2203,15 @@ dec_value(time, [X3,X2,X1,X0|T]) ->
-1 -> {infinity, T};
Val -> {Val, T}
end;
-dec_value(ip, [A,B,C,D|T]) -> {{A,B,C,D}, T};
+dec_value(ip, [A,B,C,D|T]) -> {{A,B,C,D}, T};
+dec_value(mif, [A,B,C,D, X3,X2,X1,X0|T]) ->
+ Domain = ?i32(X3, X2, X1, X0),
+ case Domain of
+ ?INET_AF_INET ->
+ {{A,B,C,D}, T};
+ ?INET_AF_INET6 ->
+ {?i32(A,B,C,D), T}
+ end;
%% dec_value(ether, [X1,X2,X3,X4,X5,X6|T]) -> {[X1,X2,X3,X4,X5,X6],T};
dec_value(sockaddr, [X|T]) ->
get_ip(X, T);
@@ -2501,7 +2517,8 @@ decode_ifopts([B | Buf], Acc) ->
undefined ->
{error, einval};
Opt ->
- {Val,T} = dec_value(type_ifopt(Opt), Buf),
+ OptType = type_ifopt(Opt),
+ {Val,T} = dec_value(OptType, Buf),
decode_ifopts(T, [{Opt,Val} | Acc])
end;
decode_ifopts(_,Acc) -> {ok,Acc}.
--
2.35.3