Skip to content

Commit a12a43a

Browse files
committed
Merge branch 'master' into httpc_fix
2 parents 794133b + 3b9690d commit a12a43a

32 files changed

+783
-143
lines changed

erts/emulator/drivers/common/inet_drv.c

Lines changed: 38 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -767,6 +767,13 @@ static size_t my_strnlen(const char *s, size_t maxlen)
767767
#define INET_TYPE_DGRAM 2
768768
#define INET_TYPE_SEQPACKET 3
769769

770+
/* open protocol */
771+
#define INET_PROTO_DEFAULT 0
772+
#define INET_PROTO_TCP 1
773+
#define INET_PROTO_UDP 2
774+
#define INET_PROTO_SCTP 3
775+
#define INET_PROTO_MPTCP 4
776+
770777
/* INET_LOPT_MODE options */
771778
#define INET_MODE_LIST 0
772779
#define INET_MODE_BINARY 1
@@ -1611,6 +1618,7 @@ static ErlDrvTermData am_sendfile;
16111618
#endif
16121619

16131620
static char str_eafnosupport[] = "eafnosupport";
1621+
static char str_eprotonosupport[] = "eprotonosupport";
16141622
static char str_einval[] = "einval";
16151623

16161624
/* special errors for bad ports and sequences */
@@ -5078,11 +5086,12 @@ static int erl_inet_close(inet_descriptor* desc)
50785086
return 0;
50795087
}
50805088

5081-
static ErlDrvSSizeT inet_ctl_open(inet_descriptor* desc, int domain, int type,
5082-
char** rbuf, ErlDrvSizeT rsize)
5089+
static
5090+
ErlDrvSSizeT inet_ctl_open(inet_descriptor* desc,
5091+
int domain, int type, int protocol,
5092+
char** rbuf, ErlDrvSizeT rsize)
50835093
{
50845094
int save_errno;
5085-
int protocol;
50865095
#ifdef HAVE_SETNS
50875096
int current_ns, new_ns;
50885097
current_ns = new_ns = 0;
@@ -5125,7 +5134,6 @@ static ErlDrvSSizeT inet_ctl_open(inet_descriptor* desc, int domain, int type,
51255134
}
51265135
}
51275136
#endif
5128-
protocol = desc->sprotocol;
51295137
#ifdef HAVE_SYS_UN_H
51305138
if (domain == AF_UNIX) protocol = 0;
51315139
#endif
@@ -11843,13 +11851,13 @@ static ErlDrvSSizeT tcp_inet_ctl(ErlDrvData e, unsigned int cmd,
1184311851
switch(cmd) {
1184411852

1184511853
case INET_REQ_OPEN: { /* open socket and return internal index */
11846-
int domain;
11854+
int domain, protocol;
1184711855

1184811856
DDBG(INETP(desc),
1184911857
("INET-DRV-DBG[%d][%T] tcp_inet_ctl -> OPEN\r\n",
1185011858
__LINE__, driver_caller(desc->inet.port)) );
1185111859

11852-
if (len != 2) return ctl_error(EINVAL, rbuf, rsize);
11860+
if (len != 3) return ctl_error(EINVAL, rbuf, rsize);
1185311861
switch(buf[0]) {
1185411862
case INET_AF_INET:
1185511863
domain = AF_INET;
@@ -11868,7 +11876,18 @@ static ErlDrvSSizeT tcp_inet_ctl(ErlDrvData e, unsigned int cmd,
1186811876
return ctl_xerror(str_eafnosupport, rbuf, rsize);
1186911877
}
1187011878
if (buf[1] != INET_TYPE_STREAM) return ctl_error(EINVAL, rbuf, rsize);
11871-
return inet_ctl_open(INETP(desc), domain, SOCK_STREAM, rbuf, rsize);
11879+
switch(buf[2]) {
11880+
case INET_PROTO_DEFAULT: protocol = 0; break;
11881+
case INET_PROTO_TCP: protocol = IPPROTO_TCP; break;
11882+
#ifdef IPPROTO_MPTCP
11883+
case INET_PROTO_MPTCP: protocol = IPPROTO_MPTCP; break;
11884+
#endif
11885+
default:
11886+
return ctl_xerror(str_eprotonosupport, rbuf, rsize);
11887+
}
11888+
return
11889+
inet_ctl_open(INETP(desc),
11890+
domain, SOCK_STREAM, protocol, rbuf, rsize);
1187211891
break;
1187311892
}
1187411893

@@ -14360,8 +14379,9 @@ static ErlDrvSSizeT packet_inet_ctl(ErlDrvData e, unsigned int cmd, char* buf,
1436014379
ErlDrvSSizeT replen;
1436114380
udp_descriptor * udesc = (udp_descriptor *) e;
1436214381
inet_descriptor* desc = INETP(udesc);
14363-
int type = SOCK_DGRAM;
1436414382
int af = AF_INET;
14383+
int type = SOCK_DGRAM;
14384+
int protocol;
1436514385

1436614386
cmd -= ERTS_INET_DRV_CONTROL_MAGIC_NUMBER;
1436714387

@@ -14370,7 +14390,7 @@ static ErlDrvSSizeT packet_inet_ctl(ErlDrvData e, unsigned int cmd, char* buf,
1437014390
DDBG(desc,
1437114391
("INET-DRV-DBG[%d][%T] packet_inet_ctl -> OPEN\r\n",
1437214392
__LINE__, driver_caller(desc->port)) );
14373-
if (len != 2) {
14393+
if (len != 3) {
1437414394
return ctl_error(EINVAL, rbuf, rsize);
1437514395
}
1437614396

@@ -14396,7 +14416,15 @@ static ErlDrvSSizeT packet_inet_ctl(ErlDrvData e, unsigned int cmd, char* buf,
1439614416
return ctl_error(EINVAL, rbuf, rsize);
1439714417
}
1439814418

14399-
replen = inet_ctl_open(desc, af, type, rbuf, rsize);
14419+
switch(buf[2]) {
14420+
case INET_PROTO_DEFAULT: protocol = 0; break;
14421+
case INET_PROTO_UDP: protocol = IPPROTO_UDP; break;
14422+
case INET_PROTO_SCTP: protocol = IPPROTO_SCTP; break;
14423+
default:
14424+
return ctl_xerror(str_eprotonosupport, rbuf, rsize);
14425+
}
14426+
14427+
replen = inet_ctl_open(desc, af, type, protocol, rbuf, rsize);
1440014428

1440114429
if ((*rbuf)[0] != INET_REP_ERROR) {
1440214430
if (desc->active)

erts/emulator/nifs/common/prim_socket_nif.c

Lines changed: 18 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -2155,6 +2155,7 @@ static const struct in6_addr in6addr_loopback =
21552155
GLOBAL_ATOM_DECL(min_rtt); \
21562156
GLOBAL_ATOM_DECL(monitor); \
21572157
GLOBAL_ATOM_DECL(more); \
2158+
GLOBAL_ATOM_DECL(mptcp); \
21582159
GLOBAL_ATOM_DECL(msfilter); \
21592160
GLOBAL_ATOM_DECL(mss); \
21602161
GLOBAL_ATOM_DECL(mtu); \
@@ -4912,6 +4913,13 @@ ERL_NIF_TERM esock_supports_protocols(ErlNifEnv* env)
49124913
MKT2(env, MKL1(env, esock_atom_igmp), MKI(env, IPPROTO_IGMP)),
49134914
protocols);
49144915

4916+
#ifdef IPPROTO_MPTCP
4917+
protocols =
4918+
MKC(env,
4919+
MKT2(env, MKL1(env, esock_atom_mptcp), MKI(env, IPPROTO_MPTCP)),
4920+
protocols);
4921+
#endif
4922+
49154923
return protocols;
49164924
}
49174925

@@ -12143,7 +12151,11 @@ void esock_dec_socket(int domain, int type, int protocol)
1214312151
/* *** Protocol counter *** */
1214412152
if (protocol == IPPROTO_IP)
1214512153
esock_cnt_dec(&data.numProtoIP, 1);
12146-
else if (protocol == IPPROTO_TCP)
12154+
else if (protocol == IPPROTO_TCP
12155+
#ifdef IPPROTO_MPTCP
12156+
|| protocol == IPPROTO_MPTCP
12157+
#endif
12158+
)
1214712159
esock_cnt_dec(&data.numProtoTCP, 1);
1214812160
else if (protocol == IPPROTO_UDP)
1214912161
esock_cnt_dec(&data.numProtoUDP, 1);
@@ -12188,7 +12200,11 @@ void esock_inc_socket(int domain, int type, int protocol)
1218812200
/* *** Protocol counter *** */
1218912201
if (protocol == IPPROTO_IP)
1219012202
esock_cnt_inc(&data.numProtoIP, 1);
12191-
else if (protocol == IPPROTO_TCP)
12203+
else if (protocol == IPPROTO_TCP
12204+
#ifdef IPPROTO_MPTCP
12205+
|| protocol == IPPROTO_MPTCP
12206+
#endif
12207+
)
1219212208
esock_cnt_inc(&data.numProtoTCP, 1);
1219312209
else if (protocol == IPPROTO_UDP)
1219412210
esock_cnt_inc(&data.numProtoUDP, 1);

erts/emulator/nifs/common/socket_int.h

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -431,6 +431,7 @@ typedef long ssize_t;
431431
GLOBAL_ATOM_DEF(min_rtt); \
432432
GLOBAL_ATOM_DEF(monitor); \
433433
GLOBAL_ATOM_DEF(more); \
434+
GLOBAL_ATOM_DEF(mptcp); \
434435
GLOBAL_ATOM_DEF(msfilter); \
435436
GLOBAL_ATOM_DEF(mss); \
436437
GLOBAL_ATOM_DEF(mtu); \

erts/preloaded/ebin/prim_inet.beam

184 Bytes
Binary file not shown.

erts/preloaded/src/prim_inet.erl

Lines changed: 14 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -77,10 +77,12 @@
7777
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
7878

7979
open(Protocol, Family, Type) ->
80-
open(Protocol, Family, Type, [], ?INET_REQ_OPEN, []).
80+
P = enc_proto(Protocol),
81+
open(Protocol, Family, Type, [], ?INET_REQ_OPEN, [P]).
8182

8283
open(Protocol, Family, Type, Opts) ->
83-
open(Protocol, Family, Type, Opts, ?INET_REQ_OPEN, []).
84+
P = enc_proto(Protocol),
85+
open(Protocol, Family, Type, Opts, ?INET_REQ_OPEN, [P]).
8486

8587
%% FDOPEN(tcp|udp|sctp, inet|inet6|local, stream|dgram|seqpacket, integer())
8688

@@ -126,15 +128,22 @@ enc_type(stream) -> ?INET_TYPE_STREAM;
126128
enc_type(dgram) -> ?INET_TYPE_DGRAM;
127129
enc_type(seqpacket) -> ?INET_TYPE_SEQPACKET.
128130

129-
protocol2drv(tcp) -> "tcp_inet";
130-
protocol2drv(udp) -> "udp_inet";
131-
protocol2drv(sctp) -> "sctp_inet".
131+
protocol2drv(tcp) -> "tcp_inet";
132+
protocol2drv(udp) -> "udp_inet";
133+
protocol2drv(sctp) -> "sctp_inet";
134+
protocol2drv(mptcp) -> "tcp_inet".
132135

133136
drv2protocol("tcp_inet") -> tcp;
134137
drv2protocol("udp_inet") -> udp;
135138
drv2protocol("sctp_inet") -> sctp;
136139
drv2protocol(_) -> undefined.
137140

141+
enc_proto(default) -> ?INET_PROTO_DEFAULT;
142+
enc_proto(tcp) -> ?INET_PROTO_TCP;
143+
enc_proto(udp) -> ?INET_PROTO_UDP;
144+
enc_proto(sctp) -> ?INET_PROTO_SCTP;
145+
enc_proto(mptcp) -> ?INET_PROTO_MPTCP.
146+
138147
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
139148
%%
140149
%% Shutdown(insock(), atom()) -> ok

lib/kernel/src/gen_tcp.erl

Lines changed: 12 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -514,6 +514,12 @@ on the host with IP address `Address`, that may also be a hostname.
514514
- **`{tcp_module, module()}`** - Overrides which callback module is used.
515515
Defaults to `inet_tcp` for IPv4 and `inet6_tcp` for IPv6.
516516

517+
- **`{protocol, tcp|mptcp}`** - With `mptcp` creates the socket
518+
with protocol IPPROTO_MPTCP, if that is defined on the system.
519+
Other than that the socket is regarded as a `tcp` socket.
520+
If IPPROTO_MPTCP is not defined, `{error, eprotonosupport}`
521+
is returned. `tcp` is the default value.
522+
517523
- **`t:option/0`** - See `inet:setopts/2`.
518524

519525
### Socket Data
@@ -661,6 +667,12 @@ The following options are available:
661667
- **`{tcp_module, module()}`** - Overrides which callback module is used.
662668
Defaults to `inet_tcp` for IPv4 and `inet6_tcp` for IPv6.
663669

670+
- **`{protocol, tcp|mptcp}`** - With `mptcp` creates the socket
671+
with protocol IPPROTO_MPTCP, if that is defined on the system.
672+
Other than that the socket is regarded as a `tcp` socket.
673+
If IPPROTO_MPTCP is not defined, `{error, eprotonosupport}`
674+
is returned. `tcp` is the default value.
675+
664676
- **`t:option/0`** - See `inet:setopts/2`.
665677

666678
The returned socket `ListenSocket` should be used when calling

lib/kernel/src/inet.erl

Lines changed: 11 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -3168,6 +3168,11 @@ con_opt([Opt | Opts], #connect_opts{ifaddr = IfAddr} = R, As) ->
31683168
{line_delimiter,C} when is_integer(C), C >= 0, C =< 255 ->
31693169
con_add(line_delimiter, C, R, Opts, As);
31703170

3171+
{protocol, Proto}
3172+
when Proto =:= tcp;
3173+
Proto =:= mptcp ->
3174+
con_opt(Opts, R#connect_opts { protocol = Proto }, As);
3175+
31713176
{Name,Val} when is_atom(Name) -> con_add(Name, Val, R, Opts, As);
31723177

31733178
_ -> {error, badarg}
@@ -3257,6 +3262,10 @@ list_opt([Opt | Opts], #listen_opts{ifaddr = IfAddr} = R, As) ->
32573262
{active,N} when is_integer(N), N < 32768, N >= -32768 ->
32583263
NOpts = lists:keydelete(active, 1, R#listen_opts.opts),
32593264
list_opt(Opts, R#listen_opts { opts = [{active,N}|NOpts] }, As);
3265+
{protocol, Proto}
3266+
when Proto =:= tcp;
3267+
Proto =:= mptcp ->
3268+
list_opt(Opts, R#listen_opts { protocol = Proto }, As);
32603269
{Name,Val} when is_atom(Name) -> list_add(Name, Val, R, Opts, As);
32613270
_ -> {error, badarg}
32623271
end;
@@ -3961,7 +3970,7 @@ gethostbyaddr_tm_native(Addr, Timer, Opts) ->
39613970
undefined, % Internal - no bind()
39623971
BPort :: port_number(),
39633972
Opts :: [socket_setopt()],
3964-
Protocol :: socket_protocol(),
3973+
Protocol :: socket_protocol() | 'mptcp',
39653974
Family :: address_family(),
39663975
Type :: socket_type(),
39673976
Module :: atom()) ->
@@ -4016,7 +4025,7 @@ open(Fd_or_OpenOpts, BAddr, BPort, Opts, Protocol, Family, Type, Module) ->
40164025
undefined, % Internal - translated to 'any'
40174026
BPort :: port_number(),
40184027
Opts :: [socket_setopt()],
4019-
Protocol :: socket_protocol(),
4028+
Protocol :: socket_protocol() | 'mptcp',
40204029
Family :: address_family(),
40214030
Type :: socket_type(),
40224031
Module :: atom()) ->

lib/kernel/src/inet6_tcp.erl

Lines changed: 14 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -40,6 +40,8 @@
4040

4141
%% -define(DBG(T), erlang:display({{self(), ?MODULE, ?LINE, ?FUNCTION_NAME}, T})).
4242

43+
proto(undefined) -> ?PROTO;
44+
proto(Proto) -> Proto.
4345

4446
%% my address family
4547
family() -> ?FAMILY.
@@ -134,17 +136,18 @@ do_connect2(SockAddr, Opts, Time) ->
134136
case inet:connect_options(Opts, ?MODULE) of
135137
{error, Reason} -> exit(Reason);
136138
{ok,
137-
#connect_opts{fd = Fd,
138-
ifaddr = BAddr,
139-
port = BPort,
140-
opts = SockOpts}}
139+
#connect_opts{fd = Fd,
140+
ifaddr = BAddr,
141+
port = BPort,
142+
opts = SockOpts,
143+
protocol = Protocol}}
141144
when is_map(BAddr); % sockaddr_in6()
142145
?port(BPort), ?ip6(BAddr);
143146
?port(BPort), BAddr =:= undefined ->
144147
case
145148
inet:open(
146149
Fd, BAddr, BPort, SockOpts,
147-
?PROTO, ?FAMILY, ?TYPE, ?MODULE)
150+
proto(Protocol), ?FAMILY, ?TYPE, ?MODULE)
148151
of
149152
{ok, S} ->
150153
case prim_inet:connect(S, SockAddr, Time) of
@@ -165,13 +168,14 @@ do_connect(Addr = {A,B,C,D,E,F,G,H}, Port, Opts, Time)
165168
fd = Fd,
166169
ifaddr = BAddr,
167170
port = BPort,
168-
opts = SockOpts}}
171+
opts = SockOpts,
172+
protocol = Protocol}}
169173
when ?port(BPort), ?ip6(BAddr);
170174
?port(BPort), BAddr =:= undefined ->
171175
case
172176
inet:open(
173177
Fd, BAddr, BPort, SockOpts,
174-
?PROTO, ?FAMILY, ?TYPE, ?MODULE)
178+
proto(Protocol), ?FAMILY, ?TYPE, ?MODULE)
175179
of
176180
{ok, S} ->
177181
case prim_inet:connect(S, Addr, Port, Time) of
@@ -198,7 +202,8 @@ listen(Port, Opts) ->
198202
fd = Fd,
199203
ifaddr = BAddr,
200204
port = BPort,
201-
opts = SockOpts} = R}
205+
opts = SockOpts,
206+
protocol = Protocol} = R}
202207
when is_map(BAddr); % sockaddr_in6()
203208
?ip6(BAddr), ?port(BPort);
204209
BAddr =:= undefined, ?port(BPort) ->
@@ -209,7 +214,7 @@ listen(Port, Opts) ->
209214
case
210215
inet:open_bind(
211216
Fd, BAddr, BPort, SockOpts,
212-
?PROTO, ?FAMILY, ?TYPE, ?MODULE)
217+
proto(Protocol), ?FAMILY, ?TYPE, ?MODULE)
213218
of
214219
{ok, S} ->
215220
case prim_inet:listen(S, R#listen_opts.backlog) of

lib/kernel/src/inet_int.hrl

Lines changed: 15 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -41,6 +41,13 @@
4141
-define(INET_TYPE_DGRAM, 2).
4242
-define(INET_TYPE_SEQPACKET, 3).
4343

44+
%% protocols
45+
-define(INET_PROTO_DEFAULT, 0).
46+
-define(INET_PROTO_TCP, 1).
47+
-define(INET_PROTO_UDP, 2).
48+
-define(INET_PROTO_SCTP, 3).
49+
-define(INET_PROTO_MPTCP, 4).
50+
4451
%% socket modes, INET_LOPT_MODE
4552
-define(INET_MODE_LIST, 0).
4653
-define(INET_MODE_BINARY, 1).
@@ -415,22 +422,24 @@
415422
%% deliver = term
416423
%% active = false
417424
%%
418-
-record(connect_opts,
419-
{
425+
-record(connect_opts,
426+
{
420427
ifaddr, %% don't bind explicitly, let connect decide
421428
port = 0, %% bind to port (default is dynamic port)
422429
fd = -1, %% fd >= 0 => already bound
423-
opts = [] %% [{active,true}] added in inet:connect_options
430+
opts = [], %% [{active,true}] added in inet:connect_options
431+
protocol = undefined
424432
}).
425433

426-
-record(listen_opts,
427-
{
434+
-record(listen_opts,
435+
{
428436
ifaddr, %% interpreted as 'any' in *_tcp.erl
429437
port = 0, %% bind to port (default is dynamic port)
430438
backlog = ?LISTEN_BACKLOG, %% backlog
431439
fd = -1, %% %% fd >= 0 => already bound
432-
opts = [] %% [{active,true}] added in
440+
opts = [], %% [{active,true}] added in
433441
%% inet:listen_options
442+
protocol = undefined
434443
}).
435444

436445
-record(udp_opts,

0 commit comments

Comments
 (0)