1%%
2%% %CopyrightBegin%
3%%
4%% Copyright Ericsson AB 2000-2019. All Rights Reserved.
5%%
6%% Licensed under the Apache License, Version 2.0 (the "License");
7%% you may not use this file except in compliance with the License.
8%% You may obtain a copy of the License at
9%%
10%%     http://www.apache.org/licenses/LICENSE-2.0
11%%
12%% Unless required by applicable law or agreed to in writing, software
13%% distributed under the License is distributed on an "AS IS" BASIS,
14%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
15%% See the License for the specific language governing permissions and
16%% limitations under the License.
17%%
18%% %CopyrightEnd%
19%%
20%% The SCTP protocol was added 2006
21%% by Leonid Timochouk <l.timochouk@gmail.com>
22%% and Serge Aleynikov  <saleyn@gmail.com>
23%% at IDT Corp. Adapted by the OTP team at Ericsson AB.
24%%
25-module(prim_inet).
26
27%% Primitive inet_drv interface
28
29-export([open/3, open/4, fdopen/4, fdopen/5, close/1]).
30-export([bind/3, listen/1, listen/2, peeloff/2]).
31-export([connect/3, connect/4, async_connect/4]).
32-export([accept/1, accept/2, accept/3, async_accept/2]).
33-export([shutdown/2]).
34-export([send/2, send/3, sendto/4, sendmsg/3, sendfile/4]).
35-export([recv/2, recv/3, async_recv/3]).
36-export([unrecv/2]).
37-export([recvfrom/2, recvfrom/3]).
38-export([setopt/3, setopts/2, getopt/2, getopts/2, is_sockopt_val/2]).
39-export([chgopt/3, chgopts/2]).
40-export([getstat/2, getfd/1, ignorefd/2,
41	 getindex/1, getstatus/1, gettype/1,
42	 getifaddrs/1, getiflist/1, ifget/3, ifset/3,
43	 gethostname/1]).
44-export([getservbyname/3, getservbyport/3]).
45-export([peername/1, setpeername/2, peernames/1, peernames/2]).
46-export([sockname/1, setsockname/2, socknames/1, socknames/2]).
47-export([attach/1, detach/1]).
48
49-include("inet_sctp.hrl").
50-include("inet_int.hrl").
51
52%%%-define(DEBUG, 1).
53-ifdef(DEBUG).
54-define(
55   DBG_FORMAT(Format, Args),
56   begin
57       %% io:format((Format), (Args)),
58       erlang:display(lists:flatten(io_lib:format((Format), (Args)))),
59       ok
60   end).
61-else.
62-define(DBG_FORMAT(Format, Args), ok).
63-endif.
64
65%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
66%%
67%% OPEN(tcp | udp | sctp, inet | inet6, stream | dgram | seqpacket)  ->
68%%       {ok, insock()} |
69%%       {error, Reason}
70%%
71%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
72
73open(Protocol, Family, Type) ->
74    open(Protocol, Family, Type, [], ?INET_REQ_OPEN, []).
75
76open(Protocol, Family, Type, Opts) ->
77    open(Protocol, Family, Type, Opts, ?INET_REQ_OPEN, []).
78
79%% FDOPEN(tcp|udp|sctp, inet|inet6|local, stream|dgram|seqpacket, integer())
80
81fdopen(Protocol, Family, Type, Fd) when is_integer(Fd) ->
82    fdopen(Protocol, Family, Type, Fd, true).
83
84fdopen(Protocol, Family, Type, Fd, Bound)
85  when is_integer(Fd), is_boolean(Bound) ->
86    open(Protocol, Family, Type, [], ?INET_REQ_FDOPEN,
87         [?int32(Fd), enc_value_2(bool, Bound)]).
88
89open(Protocol, Family, Type, Opts, Req, Data) ->
90    Drv = protocol2drv(Protocol),
91    AF = enc_family(Family),
92    T = enc_type(Type),
93    try erlang:open_port({spawn_driver,Drv}, [binary]) of
94	S ->
95	    case setopts(S, Opts) of
96		ok ->
97		    case ctl_cmd(S, Req, [AF,T,Data]) of
98			{ok,_} -> {ok,S};
99			{error,_}=E1 ->
100			    close(S),
101			    E1
102		    end;
103		{error,_}=E2 ->
104		    close(S),
105		    E2
106	    end
107    catch
108	%% The only (?) way to get here is to try to open
109	%% the sctp driver when it does not exist (badarg)
110	error:badarg       -> {error, eprotonosupport};
111	%% system_limit if out of port slots
112	error:system_limit -> {error, system_limit}
113    end.
114
115enc_family(inet)  -> ?INET_AF_INET;
116enc_family(inet6) -> ?INET_AF_INET6;
117enc_family(local) -> ?INET_AF_LOCAL.
118
119enc_type(stream) -> ?INET_TYPE_STREAM;
120enc_type(dgram) -> ?INET_TYPE_DGRAM;
121enc_type(seqpacket) -> ?INET_TYPE_SEQPACKET.
122
123protocol2drv(tcp)  -> "tcp_inet";
124protocol2drv(udp)  -> "udp_inet";
125protocol2drv(sctp) -> "sctp_inet".
126
127drv2protocol("tcp_inet")  -> tcp;
128drv2protocol("udp_inet")  -> udp;
129drv2protocol("sctp_inet") -> sctp;
130drv2protocol(_)           -> undefined.
131
132%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
133%%
134%% Shutdown(insock(), atom()) -> ok
135%%
136%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
137%% TODO: shutdown equivalent for SCTP
138%%
139shutdown(S, read) when is_port(S) ->
140    shutdown_1(S, 0);
141shutdown(S, write) when is_port(S) ->
142    shutdown_1(S, 1);
143shutdown(S, read_write) when is_port(S) ->
144    shutdown_1(S, 2).
145
146shutdown_1(S, How) ->
147    case ctl_cmd(S, ?TCP_REQ_SHUTDOWN, [How]) of
148	{ok, []} -> ok;
149	{error,_}=Error -> Error
150    end.
151
152%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
153%%
154%% CLOSE(insock()) -> ok
155%%
156%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
157
158close(S) when is_port(S) ->
159    ?DBG_FORMAT("prim_inet:close(~p)~n", [S]),
160    case getopt(S, linger) of
161    	{ok,{true,0}} ->
162	    close_port(S);
163        {ok,{true,T}} ->
164            %% Wait for T seconds for pending output to be sent
165            %%
166            %% Note that this handling of Linger may look ok,
167            %% but sweeps some problems under the rug since
168            %% there are OS buffers that may have remaining data
169            %% after the inet driver has emptied its buffers.
170            %% But Linger for nonblocking sockets is broken
171            %% anyway on all OS:es, according to hearsay,
172            %% and is a contradiction in itself.
173            %% We have hereby done our best...
174            %%
175            case subscribe(S, [subs_empty_out_q]) of
176                {ok, [{subs_empty_out_q,0}]} ->
177                    close_port(S);
178                {ok, [{subs_empty_out_q,N}]} when N > 0 ->
179                    %% Wait for pending output to be sent
180                    Tref = erlang:start_timer(T * 1000, self(), close_port),
181                    close_pend_loop(S, Tref, N);
182                _ ->
183                    %% Subscribe failed - wait full time
184                    Tref = erlang:start_timer(T * 1000, self(), close_port),
185                    close_pend_loop(S, Tref, undefined)
186            end;
187	_ -> % Regard this as {ok,{false,_}}
188            case subscribe(S, [subs_empty_out_q]) of
189                {ok, [{subs_empty_out_q,N}]} when N > 0 ->
190                    %% Wait for pending output to be sent
191                    DefaultT = 180000, % Arbitrary system timeout 3 min
192                    Tref = erlang:start_timer(DefaultT, self(), close_port),
193                    close_pend_loop(S, Tref, N);
194                _ ->
195                    %% Subscribe failed or empty out q - give up or done
196                    close_port(S)
197            end
198    end.
199
200close_pend_loop(S, Tref, N) ->
201    ?DBG_FORMAT("prim_inet:close_pend_loop(~p, _, ~p)~n", [S,N]),
202    receive
203        {timeout,Tref,_} -> % Linger timeout
204            ?DBG_FORMAT("prim_inet:close_pend_loop(~p, _, _) timeout~n", [S]),
205	    close_port(S);
206	{empty_out_q,S} when N =/= undefined ->
207            ?DBG_FORMAT(
208               "prim_inet:close_pend_loop(~p, _, _) empty_out_q~n", [S]),
209	    close_port(S, Tref)
210    after ?INET_CLOSE_TIMEOUT ->
211	    case getstat(S, [send_pend]) of
212                {ok, [{send_pend,N1}]} ->
213                    ?DBG_FORMAT(
214                       "prim_inet:close_pend_loop(~p, _, _) send_pend ~p~n",
215                       [S,N1]),
216                    if
217                        N1 =:= 0 ->
218                            %% Empty outq - done
219                            close_port(S, Tref);
220                        N =:= undefined ->
221                            %% Within linger time - wait some more
222                            close_pend_loop(S, Tref, N);
223                        N1 =:= N ->
224                            %% Inactivity - give up
225                            close_port(S, Tref);
226                        true ->
227                            %% Still moving - wait some more
228                            close_pend_loop(S, Tref, N)
229                    end;
230                _Stat ->
231                    %% Failed getstat - give up
232                    ?DBG_FORMAT(
233                       "prim_inet:close_pend_loop(~p, _, _) getstat ~p~n",
234                       [S,_Stat]),
235		    close_port(S, Tref)
236            end
237    end.
238
239
240close_port(S, Tref) ->
241    ?DBG_FORMAT("prim_inet:close_port(~p, _)~n", [S]),
242    case erlang:cancel_timer(Tref) of
243        false ->
244            receive
245                {timeout,Tref,_} ->
246                    ok
247            end;
248        _N ->
249            ok
250    end,
251    close_port(S).
252%%
253close_port(S) ->
254    ?DBG_FORMAT("prim_inet:close_port(~p)~n", [S]),
255    _Closed = (catch erlang:port_close(S)),
256    receive {'EXIT',S,_} -> ok after 0 -> ok end,
257    ?DBG_FORMAT("prim_inet:close_port(~p) ~p~n", [S,_Closed]),
258    ok.
259
260%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
261%%
262%% BIND(insock(), IP, Port) -> {ok, integer()} | {error, Reason}
263%%
264%% bind the insock() to the interface address given by IP and Port
265%%
266%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
267
268%% Multi-homed "bind": sctp_bindx(). The Op is 'add' or 'remove'.
269%% If no addrs are specified, it just does nothing.
270%% Function returns {ok, S} on success, unlike TCP/UDP "bind":
271bind(S, add, Addrs) when is_port(S), is_list(Addrs) ->
272    bindx(S, 1, Addrs);
273bind(S, remove, Addrs) when is_port(S), is_list(Addrs) ->
274    bindx(S, 0, Addrs);
275bind(S, Addr, _) when is_port(S), tuple_size(Addr) =:= 2 ->
276    case type_value(set, addr, Addr) of
277	true ->
278	    case ctl_cmd(S,?INET_REQ_BIND,enc_value(set, addr, Addr)) of
279		{ok, [P1,P0]} -> {ok, ?u16(P1, P0)};
280		{error, _} = Error -> Error
281	    end;
282	false ->
283	    {error, einval}
284    end;
285bind(S, IP, Port) ->
286    bind(S, {IP, Port}, 0).
287
288bindx(S, AddFlag, Addrs) ->
289    case getprotocol(S) of
290	sctp ->
291	    case bindx_check_addrs(Addrs) of
292		true ->
293		    %% Really multi-homed "bindx". Stringified args:
294		    %% [AddFlag, (AddrBytes see enc_value_2(addr,X))+]:
295		    Args =
296			[?int8(AddFlag)|
297			 [enc_value(set, addr, Addr) || Addr <- Addrs]],
298		    case ctl_cmd(S, ?SCTP_REQ_BINDX, Args) of
299			{ok, _} -> {ok, S};
300			{error, _}=Error  -> Error
301		    end;
302		false ->
303		    {error, einval}
304	    end;
305	_ ->
306	    {error, einval}
307    end.
308
309bindx_check_addrs([Addr|Addrs]) ->
310    type_value(set, addr, Addr) andalso bindx_check_addrs(Addrs);
311bindx_check_addrs([]) ->
312    true.
313
314%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
315%%
316%% CONNECT(insock(), IP, Port [,Timeout]) -> ok | {error, Reason}
317%%
318%% connect the insock() to the address given by IP and Port
319%% if timeout is given:
320%%       timeout < 0  -> infinity
321%%                 0  -> immediate connect (mostly works for loopback)
322%%               > 0  -> wait for timeout ms if not connected then
323%%                       return {error, timeout}
324%%
325%% ASYNC_CONNECT(insock(), IP, Port, Timeout) -> {ok, S, Ref} | {error, Reason}
326%%
327%%  a {inet_async,S,Ref,Status} will be sent on socket condition
328%%
329%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
330%% For TCP, UDP or SCTP sockets.
331%%
332
333connect(S, IP, Port) ->
334    connect(S, IP, Port, infinity).
335%%
336connect(S, Addr, _, Time) when is_port(S), tuple_size(Addr) =:= 2 ->
337    case type_value(set, addr, Addr) of
338	true when Time =:= infinity ->
339	    connect0(S, Addr, -1);
340	true when is_integer(Time) ->
341	    connect0(S, Addr, Time);
342	false ->
343	    {error, einval}
344    end;
345connect(S, IP, Port, Time) ->
346    connect(S, {IP, Port}, 0, Time).
347
348connect0(S, Addr, Time) ->
349    case async_connect0(S, Addr, Time) of
350	{ok, S, Ref} ->
351	    receive
352		{inet_async, S, Ref, Status} ->
353		    Status
354	    end;
355	Error -> Error
356    end.
357
358
359async_connect(S, Addr, _, Time) when is_port(S), tuple_size(Addr) =:= 2 ->
360    case type_value(set, addr, Addr) of
361	true when Time =:= infinity ->
362	    async_connect0(S, Addr, -1);
363	true when is_integer(Time) ->
364	    async_connect0(S, Addr, Time);
365	false ->
366	    {error, einval}
367    end;
368%%
369async_connect(S, IP, Port, Time) ->
370    async_connect(S, {IP, Port}, 0, Time).
371
372async_connect0(S, Addr, Time) ->
373    case ctl_cmd(
374	   S, ?INET_REQ_CONNECT,
375	   [enc_time(Time),enc_value(set, addr, Addr)])
376    of
377	{ok, [R1,R0]} -> {ok, S, ?u16(R1,R0)};
378	{error, _}=Error -> Error
379    end.
380
381%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
382%%
383%% ACCEPT(insock() [,Timeout][,FamilyOpts] ) -> {ok,insock()} | {error, Reason}
384%%
385%% accept incoming connection on listen socket
386%% if timeout is given:
387%%       timeout < 0  -> infinity
388%%                 0  -> immediate accept (poll)
389%%               > 0  -> wait for timeout ms for accept if no accept then
390%%                       return {error, timeout}
391%% FamilyOpts are address family specific options to copy from
392%% listen socket to accepted socket
393%%
394%% ASYNC_ACCEPT(insock(), Timeout)
395%%
396%%  async accept. return {ok,S,Ref} or {error, Reason}
397%%  the owner of socket S will receive an {inet_async,S,Ref,Status} on
398%%  socket condition
399%%
400%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
401%% For TCP sockets only.
402%%
403accept(L) -> accept0(L, -1, []).
404
405accept(L, infinity) -> accept0(L, -1, []);
406accept(L, FamilyOpts) when is_list(FamilyOpts) -> accept0(L, -1, FamilyOpts);
407accept(L, Time) -> accept0(L, Time, []).
408
409accept(L, infinity, FamilyOpts) -> accept0(L, -1, FamilyOpts);
410accept(L, Time, FamilyOpts) -> accept0(L, Time, FamilyOpts).
411
412accept0(L, Time, FamilyOpts)
413  when is_port(L), is_integer(Time), is_list(FamilyOpts) ->
414    case async_accept(L, Time) of
415	{ok, Ref} ->
416	    receive
417		{inet_async, L, Ref, {ok,S}} ->
418		    accept_opts(L, S, FamilyOpts);
419		{inet_async, L, Ref, Error} ->
420		    Error
421	    end;
422	Error -> Error
423    end.
424
425%% setup options from listen socket on the connected socket
426accept_opts(L, S, FamilyOpts) ->
427    case
428        getopts(
429          L,
430          [active, nodelay, keepalive, delay_send, priority, linger]
431          ++ FamilyOpts)
432    of
433	{ok, Opts} ->
434            case setopts(S, Opts) of
435                ok ->
436                    {ok, S};
437                Error1 ->
438                    close(S), Error1
439            end;
440	Error2 ->
441	    close(S), Error2
442    end.
443
444async_accept(L, Time) ->
445    case ctl_cmd(L,?INET_REQ_ACCEPT, [enc_time(Time)]) of
446	{ok, [R1,R0]} -> {ok, ?u16(R1,R0)};
447	{error,_}=Error -> Error
448    end.
449
450%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
451%%
452%% LISTEN(insock() [,Backlog]) -> ok | {error, Reason}
453%%
454%% set listen mode on socket
455%%
456%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
457%% For TCP or SCTP sockets. For SCTP, Boolean backlog value (enable/disable
458%% listening) is also accepted:
459
460listen(S) -> listen(S, ?LISTEN_BACKLOG).
461
462listen(S, true) -> listen(S, ?LISTEN_BACKLOG);
463listen(S, false) -> listen(S, 0);
464listen(S, BackLog) when is_port(S), is_integer(BackLog) ->
465    case ctl_cmd(S, ?INET_REQ_LISTEN, [?int16(BackLog)]) of
466	{ok, _} -> ok;
467	{error,_}=Error   -> Error
468    end.
469
470%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
471%%
472%% PEELOFF(insock(), AssocId) -> {ok,outsock()} | {error, Reason}
473%%
474%% SCTP: Peel off one association into a type stream socket
475%%
476%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
477
478peeloff(S, AssocId) ->
479    case ctl_cmd(S, ?SCTP_REQ_PEELOFF, [?int32(AssocId)]) of
480	inet_reply ->
481	    receive
482		{inet_reply,S,Res} -> Res
483	    end;
484	{error,_}=Error -> Error
485    end.
486
487%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
488%%
489%% SEND(insock(), Data) -> ok | {error, Reason}
490%%
491%% send Data on the socket (io-list)
492%%
493%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
494%% This is a generic "port_command" interface used by TCP, UDP, SCTP, depending
495%% on the driver it is mapped to, and the "Data". It actually sends out data,--
496%% NOT delegating this task to any back-end.  For SCTP, this function MUST NOT
497%% be called directly -- use "sendmsg" instead:
498%%
499send(S, Data, OptList) when is_port(S), is_list(OptList) ->
500    ?DBG_FORMAT("prim_inet:send(~p, _, ~p)~n", [S,OptList]),
501    try erlang:port_command(S, Data, OptList) of
502	false -> % Port busy and nosuspend option passed
503	    ?DBG_FORMAT("prim_inet:send() -> {error,busy}~n", []),
504	    {error,busy};
505	true ->
506            send_recv_reply(S, undefined)
507    catch
508	error:_Error ->
509	    ?DBG_FORMAT("prim_inet:send() -> {error,einval}~n", []),
510	     {error,einval}
511    end.
512
513send_recv_reply(S, Mref) ->
514    ReplyTimeout =
515        case Mref of
516            undefined ->
517                ?INET_CLOSE_TIMEOUT;
518            _ ->
519                infinity
520        end,
521    receive
522        {inet_reply,S,Status} ->
523            ?DBG_FORMAT(
524               "prim_inet:send_recv_reply(~p, _): inet_reply ~p~n",
525               [S,Status]),
526            case Mref of
527                undefined -> ok;
528                _ ->
529                    demonitor(Mref, [flush]),
530                    ok
531            end,
532            Status;
533        {'DOWN',Mref,_,_,_Reason} when Mref =/= undefined ->
534            ?DBG_FORMAT(
535               "prim_inet:send_recv_reply(~p, _) 'DOWN' ~p~n",
536               [S,_Reason]),
537            {error,closed}
538    after ReplyTimeout ->
539            send_recv_reply(S, monitor(port, S))
540    end.
541
542
543send(S, Data) ->
544    send(S, Data, []).
545
546%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
547%%
548%% SENDTO(insock(), IP, Port, Data) -> ok | {error, Reason}
549%%
550%% send Datagram to the IP at port (Should add sync send!)
551%%
552%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
553%% "sendto" is for UDP. IP and Port are set by the caller to 0 if the socket
554%% is known to be connected.
555
556sendto(S, {_, _} = Address, AncOpts, Data)
557  when is_port(S), is_list(AncOpts) ->
558    case encode_opt_val(AncOpts) of
559        {ok, AncData} ->
560            AncDataLen = iolist_size(AncData),
561            case
562                type_value(set, addr, Address) andalso
563                type_value(set, uint32, AncDataLen)
564            of
565                true ->
566                    ?DBG_FORMAT("prim_inet:sendto(~p, ~p, ~p, ~p)~n",
567                                [S,Address,AncOpts,Data]),
568                    PortCommandData =
569                        [enc_value(set, addr, Address),
570                         enc_value(set, uint32, AncDataLen), AncData,
571                         Data],
572                    try erlang:port_command(S, PortCommandData) of
573                        true ->
574                            receive
575                                {inet_reply,S,Reply} ->
576                                    ?DBG_FORMAT(
577                                       "prim_inet:sendto() -> ~p~n", [Reply]),
578                                    Reply
579                            end
580                    catch
581                        _:_ ->
582                            ?DBG_FORMAT(
583                               "prim_inet:sendto() -> {error,einval}~n", []),
584                            {error,einval}
585                    end;
586                false ->
587                    ?DBG_FORMAT(
588                       "prim_inet:sendto() -> {error,einval}~n", []),
589                    {error,einval}
590            end;
591        {error,_} ->
592            ?DBG_FORMAT(
593               "prim_inet:sendto() -> {error,einval}~n", []),
594            {error,einval}
595    end;
596sendto(S, IP, Port, Data)
597  when is_port(S), is_integer(Port) ->
598    sendto(S, {IP, Port}, [], Data).
599
600%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
601%%
602%% SENDMSG(insock(), IP, Port, InitMsg, Data)   or
603%% SENDMSG(insock(), SndRcvInfo,        Data)   -> ok | {error, Reason}
604%%
605%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
606%% SCTP: Sending data over an existing association: no need for a destination
607%% addr; uses SndRcvInfo:
608%%
609sendmsg(S, #sctp_sndrcvinfo{}=SRI, Data) when is_port(S) ->
610    Type = type_opt(set, sctp_default_send_param),
611    try type_value(set, Type, SRI) of
612	true ->
613	    send(S, [enc_value(set, Type, SRI)|Data]);
614	false -> {error,einval}
615    catch
616	Reason -> {error,Reason}
617    end.
618
619%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
620%%
621%% SENDFILE(outsock(), Fd, Offset, Length) -> {ok,BytesSent} | {error, Reason}
622%%
623%% send Length data bytes from a file handle, to a socket, starting at Offset
624%%
625%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
626%% "sendfile" is for TCP:
627
628sendfile(S, FileHandle, Offset, Length)
629        when not is_port(S);
630             not is_binary(FileHandle);
631             not is_integer(Offset);
632             not is_integer(Length) ->
633    {error, badarg};
634sendfile(S, FileHandle, Offset, Length) ->
635    case erlang:port_info(S, connected) of
636        {connected, Pid} when Pid =:= self() ->
637            Uncork = sendfile_maybe_cork(S),
638            Result = sendfile_1(S, FileHandle, Offset, Length),
639            sendfile_maybe_uncork(S, Uncork),
640            Result;
641        {connected, Pid} when Pid =/= self() ->
642            {error, not_owner};
643        _Other ->
644            {error, einval}
645    end.
646
647sendfile_maybe_cork(S) ->
648    case getprotocol(S) of
649        tcp ->
650            case getopts(S, [nopush]) of
651                {ok, [{nopush,false}]} ->
652                    _ = setopts(S, [{nopush,true}]),
653                    true;
654                _ ->
655                    false
656            end;
657        _ -> false
658    end.
659
660sendfile_maybe_uncork(S, true) ->
661    _ = setopts(S, [{nopush,false}]),
662    ok;
663sendfile_maybe_uncork(_, false) ->
664    ok.
665
666sendfile_1(S, FileHandle, Offset, 0) ->
667    sendfile_1(S, FileHandle, Offset, (1 bsl 63) - 1);
668sendfile_1(_S, _FileHandle, Offset, Length) when
669         Offset < 0; Offset > ((1 bsl 63) - 1);
670         Length < 0; Length > ((1 bsl 63) - 1) ->
671    {error, einval};
672sendfile_1(S, FileHandle, Offset, Length) ->
673    Args = [FileHandle,
674            ?int64(Offset),
675            ?int64(Length)],
676    case ctl_cmd(S, ?TCP_REQ_SENDFILE, Args) of
677        {ok, []} ->
678            receive
679                {sendfile, S, {ok, SentLow, SentHigh}} ->
680                    {ok, SentLow bor (SentHigh bsl 32)};
681                {sendfile, S, {error, Reason}} ->
682                    {error, Reason};
683                {'EXIT', S, _Reason} ->
684                    {error, closed}
685            end;
686        {error, Reason} ->
687            {error, Reason}
688    end.
689
690%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
691%%
692%% RECV(insock(), Length, [Timeout]) -> {ok,Data} | {error, Reason}
693%%
694%% receive Length data bytes from a socket
695%% if 0 is given then a Data packet is requested (see setopt (packet))
696%%    N read N bytes
697%%
698%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
699%% "recv" is for TCP:
700
701recv(S, Length) -> recv0(S, Length, -1).
702
703recv(S, Length, infinity) -> recv0(S, Length,-1);
704
705recv(S, Length, Time) when is_integer(Time) -> recv0(S, Length, Time).
706
707recv0(S, Length, Time) when is_port(S), is_integer(Length), Length >= 0 ->
708    case async_recv(S, Length, Time) of
709	{ok, Ref} ->
710	    receive
711		{inet_async, S, Ref, Status} -> Status;
712		{'EXIT', S, _Reason} ->
713		    {error, closed}
714	    end;
715	Error -> Error
716    end.
717
718
719async_recv(S, Length, Time) ->
720    case ctl_cmd(S, ?TCP_REQ_RECV, [enc_time(Time), ?int32(Length)]) of
721	{ok,[R1,R0]} -> {ok, ?u16(R1,R0)};
722	{error,_}=Error -> Error
723    end.
724
725%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
726%%
727%% RECVFROM(insock(), Lenth [Timeout]) -> {ok,{IP,Port,Data}} | {error, Reason}
728%%                           For SCTP: -> {ok,{IP,Port,[AncData],Data}}
729%%                                                            | {error, Reason}
730%% receive Length data bytes from a datagram socket sent from IP at Port
731%% if 0 is given then a Data packet is requested (see setopt (packet))
732%%    N read N bytes
733%%
734%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
735%% "recvfrom" is for both UDP and SCTP.
736%% NB: "Length" is actually ignored for these protocols, since they are msg-
737%% oriented: preserved here only for API compatibility.
738%%
739recvfrom(S, Length) ->
740    recvfrom(S, Length, infinity).
741
742recvfrom(S, Length, infinity) when is_port(S) ->
743    recvfrom0(S, Length, -1);
744recvfrom(S, Length, Time) when is_port(S) ->
745    if
746	is_integer(Time), 0 =< Time, Time < 16#ffffffff ->
747	    recvfrom0(S, Length, Time);
748	true ->
749	    {error, einval}
750    end.
751
752recvfrom0(S, Length, Time)
753  when is_integer(Length), 0 =< Length, Length =< 16#ffffffff ->
754    case ctl_cmd(S, ?PACKET_REQ_RECV,[enc_time(Time),?int32(Length)]) of
755	{ok,[R1,R0]} ->
756	    Ref = ?u16(R1,R0),
757	    receive
758		% Success, UDP:
759		{inet_async, S, Ref, {ok, {[F | AddrData], AncData}}} ->
760                    %% With ancillary data
761		    case get_addr(F, AddrData) of
762			{{Family, _} = Addr, Data} when is_atom(Family) ->
763			    {ok, {Addr, 0, AncData, Data}};
764			{{IP, Port}, Data} ->
765			    {ok, {IP, Port, AncData, Data}}
766		    end;
767		{inet_async, S, Ref, {ok, [F | AddrData]}} ->
768                    %% Without ancillary data
769		    case get_addr(F, AddrData) of
770			{{Family, _} = Addr, Data} when is_atom(Family) ->
771			    {ok, {Addr, 0, Data}};
772			{{IP, Port}, Data} ->
773			    {ok, {IP, Port, Data}}
774		    end;
775
776		% Success, SCTP:
777		{inet_async, S, Ref, {ok, {[F,P1,P0 | Addr], AncData, DE}}} ->
778		    {IP, _} = get_ip(F, Addr),
779		    {ok, {IP, ?u16(P1, P0), AncData, DE}};
780
781		% Back-end error:
782		{inet_async, S, Ref, Error={error, _}} ->
783		    Error
784	    end;
785	{error,_}=Error ->
786	    Error % Front-end error
787    end;
788recvfrom0(_, _, _) -> {error,einval}.
789
790%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
791%%
792%% PEERNAME(insock()) -> {ok, {IP, Port}} | {error, Reason}
793%%
794%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
795
796peername(S) when is_port(S) ->
797    case ctl_cmd(S, ?INET_REQ_PEER, []) of
798	{ok, [F | Addr]} ->
799	    {A, _} = get_addr(F, Addr),
800	    {ok, A};
801	{error, _} = Error -> Error
802    end.
803
804setpeername(S, undefined) when is_port(S) ->
805    case ctl_cmd(S, ?INET_REQ_SETPEER, []) of
806	{ok, []} -> ok;
807	{error, _} = Error -> Error
808    end;
809setpeername(S, Addr) when is_port(S) ->
810    case type_value(set, addr, Addr) of
811	true ->
812	    case ctl_cmd(S, ?INET_REQ_SETPEER, enc_value(set, addr, Addr)) of
813		{ok, []} -> ok;
814		{error, _} = Error -> Error
815	    end;
816	false ->
817	    {error, einval}
818    end.
819
820%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
821%%
822%% PEERNAMES(insock()) -> {ok, [{IP, Port}, ...]} | {error, Reason}
823%%
824%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
825
826peernames(S) when is_port(S) ->
827    peernames(S, undefined).
828
829peernames(S, #sctp_assoc_change{assoc_id=AssocId}) when is_port(S) ->
830    peernames(S, AssocId);
831peernames(S, AssocId)
832  when is_port(S), is_integer(AssocId);
833       is_port(S), AssocId =:= undefined ->
834    Q = get,
835    Type = [[sctp_assoc_id,0]],
836    case type_value(Q, Type, AssocId) of
837	true ->
838	    case ctl_cmd
839		(S, ?INET_REQ_GETPADDRS,
840		 enc_value(Q, Type, AssocId)) of
841		{ok,Addrs} ->
842		    {ok,get_addrs(Addrs)};
843		Error ->
844		    Error
845	    end;
846	false ->
847	    {error,einval}
848    end.
849
850%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
851%%
852%% SOCKNAME(insock()) -> {ok, {IP, Port}} | {error, Reason}
853%%
854%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
855
856sockname(S) when is_port(S) ->
857    case ctl_cmd(S, ?INET_REQ_NAME, []) of
858	{ok, [F | Addr]} ->
859	    {A, _} = get_addr(F, Addr),
860	    {ok, A};
861	{error, _} = Error -> Error
862    end.
863
864setsockname(S, undefined) when is_port(S) ->
865    case ctl_cmd(S, ?INET_REQ_SETNAME, []) of
866	{ok, []} -> ok;
867	{error, _} = Error -> Error
868    end;
869setsockname(S, Addr) when is_port(S) ->
870    case type_value(set, addr, Addr) of
871	true ->
872	    case
873		ctl_cmd(S, ?INET_REQ_SETNAME, enc_value(set, addr, Addr))
874	    of
875		{ok, []} -> ok;
876		{error, _} = Error -> Error
877	    end;
878	false ->
879	    {error, einval}
880    end.
881
882%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
883%%
884%% SOCKNAMES(insock()) -> {ok, [{IP, Port}, ...]} | {error, Reason}
885%%
886%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
887
888socknames(S) when is_port(S) ->
889    socknames(S, undefined).
890
891socknames(S, #sctp_assoc_change{assoc_id=AssocId}) when is_port(S) ->
892    socknames(S, AssocId);
893socknames(S, AssocId)
894  when is_port(S), is_integer(AssocId);
895       is_port(S), AssocId =:= undefined ->
896    Q = get,
897    Type = [[sctp_assoc_id,0]],
898    case type_value(Q, Type, AssocId) of
899	true ->
900	    case ctl_cmd
901		(S, ?INET_REQ_GETLADDRS,
902		 enc_value(Q, Type, AssocId)) of
903		{ok,Addrs} ->
904		    {ok,get_addrs(Addrs)};
905		Error ->
906		    Error
907	    end;
908	false ->
909	    {error,einval}
910    end.
911
912%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
913%%
914%% SETOPT(insock(), Opt, Value) -> ok | {error, Reason}
915%% SETOPTS(insock(), [{Opt,Value}]) -> ok | {error, Reason}
916%%
917%% set socket, ip and driver option
918%%
919%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
920
921setopt(S, Opt, Value) when is_port(S) ->
922    setopts(S, [{Opt,Value}]).
923
924setopts(S, Opts) when is_port(S) ->
925    case encode_opt_val(Opts) of
926	{ok, Buf} ->
927	    case ctl_cmd(S, ?INET_REQ_SETOPTS, Buf) of
928		{ok, _} -> ok;
929		{error,_}=Error -> Error
930	    end;
931	Error  -> Error
932    end.
933
934%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
935%%
936%% GETOPT(insock(), Opt) -> {ok,Value} | {error, Reason}
937%% GETOPTS(insock(), [Opt]) -> {ok, [{Opt,Value}]} | {error, Reason}
938%% get socket, ip and driver option
939%%
940%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
941
942getopt(S, Opt) when is_port(S), is_atom(Opt) ->
943    case getopts(S, [Opt]) of
944	{ok,[{_,Value}]} -> {ok, Value};
945	Error -> Error
946    end.
947
948getopts(S, Opts) when is_port(S), is_list(Opts) ->
949    case encode_opts(Opts) of
950	{ok,Buf} ->
951	    case ctl_cmd(S, ?INET_REQ_GETOPTS, Buf) of
952		{ok,Rep} ->
953		    %% Non-SCTP: "Rep" contains the encoded option vals:
954		    decode_opt_val(Rep);
955		inet_reply ->
956		    %% SCTP: Need to receive the full value:
957		    receive
958			{inet_reply,S,Res} -> Res
959		    end;
960		{error,_}=Error -> Error
961	    end;
962	Error -> Error
963    end.
964
965%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
966%%
967%% CHGOPT(insock(), Opt) -> {ok,Value} | {error, Reason}
968%% CHGOPTS(insock(), [Opt]) -> {ok, [{Opt,Value}]} | {error, Reason}
969%% change socket, ip and driver option
970%%
971%% Same as setopts except for record value options where undefined
972%% fields are read with getopts before setting.
973%%
974%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
975
976chgopt(S, Opt, Value) when is_port(S) ->
977    chgopts(S, [{Opt,Value}]).
978
979chgopts(S, Opts) when is_port(S), is_list(Opts) ->
980    case getopts(S, need_template(Opts)) of
981	{ok,Templates} ->
982	    try merge_options(Opts, Templates) of
983		NewOpts ->
984		    setopts(S, NewOpts)
985	    catch
986		Reason -> {error,Reason}
987	    end;
988	Error -> Error
989    end.
990
991%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
992%%
993%% getifaddrs(insock()) -> {ok,IfAddrsList} | {error, Reason}
994%%
995%%   IfAddrsList = [{Name,[Opts]}]
996%%   Name = string()
997%%   Opts = {flags,[Flag]} | {addr,Addr} | {netmask,Addr} | {broadaddr,Addr}
998%%        | {dstaddr,Addr} | {hwaddr,HwAddr} | {mtu,integer()}
999%%   Flag = up | broadcast | loopback | running | multicast
1000%%   Addr = ipv4addr() | ipv6addr()
1001%%   HwAddr = ethernet_addr()
1002%%
1003%% get interface name and addresses list
1004%%
1005%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1006
1007getifaddrs(S) when is_port(S) ->
1008    case ctl_cmd(S, ?INET_REQ_GETIFADDRS, []) of
1009        {ok, Data} ->
1010            {ok, comp_ifaddrs(build_ifaddrs(Data))};
1011        {error,enotsup} ->
1012	    case getiflist(S) of
1013		{ok, IFs} ->
1014		    {ok, getifaddrs_ifget(S, IFs)};
1015		Err1 -> Err1
1016	    end;
1017	Err2 -> Err2
1018    end.
1019
1020%% Restructure interface properties per interface
1021
1022comp_ifaddrs(IfOpts) ->
1023    comp_ifaddrs(IfOpts, ktree_empty()).
1024%%
1025comp_ifaddrs([{If,[{flags,Flags}|Opts]}|IfOpts], IfT) ->
1026    case ktree_is_defined(If, IfT) of
1027        true ->
1028            comp_ifaddrs(
1029              IfOpts,
1030              ktree_update(
1031                If,
1032                comp_ifaddrs_flags(Flags, Opts, ktree_get(If, IfT)),
1033                IfT));
1034        false ->
1035            comp_ifaddrs(
1036              IfOpts,
1037              ktree_insert(
1038                If,
1039                comp_ifaddrs_flags(Flags, Opts, ktree_empty()),
1040                IfT))
1041    end;
1042comp_ifaddrs([], IfT) ->
1043    comp_ifaddrs_2(ktree_keys(IfT), IfT).
1044
1045comp_ifaddrs_flags(Flags, Opts, FlagsT) ->
1046    case ktree_is_defined(Flags, FlagsT) of
1047        true ->
1048            ktree_update(
1049              Flags,
1050              rev(Opts, ktree_get(Flags, FlagsT)),
1051              FlagsT);
1052        false ->
1053            ktree_insert(Flags, rev(Opts), FlagsT)
1054    end.
1055
1056comp_ifaddrs_2([If|Ifs], IfT) ->
1057    FlagsT = ktree_get(If, IfT),
1058    [{If,comp_ifaddrs_3(ktree_keys(FlagsT), FlagsT)}
1059     | comp_ifaddrs_2(Ifs, IfT)];
1060comp_ifaddrs_2([], _IfT) ->
1061    [].
1062%%
1063comp_ifaddrs_3([Flags|FlagsL], FlagsT) ->
1064    [{flags,Flags}|hwaddr_last(rev(ktree_get(Flags, FlagsT)))]
1065        ++ hwaddr_last(comp_ifaddrs_3(FlagsL, FlagsT));
1066comp_ifaddrs_3([], _FlagsT) ->
1067    [].
1068
1069%% Place hwaddr last to look more like legacy emulation
1070hwaddr_last(Opts) ->
1071    hwaddr_last(Opts, Opts, []).
1072%%
1073hwaddr_last([{hwaddr,_} = Opt|Opts], L, R) ->
1074    hwaddr_last(Opts, L, [Opt|R]);
1075hwaddr_last([_|Opts], L, R) ->
1076    hwaddr_last(Opts, L, R);
1077hwaddr_last([], L, []) ->
1078    L;
1079hwaddr_last([], L, R) ->
1080    rev(hwaddr_last(L, []), rev(R)).
1081%%
1082hwaddr_last([{hwaddr,_}|Opts], R) ->
1083    hwaddr_last(Opts, R);
1084hwaddr_last([Opt|Opts], R) ->
1085    hwaddr_last(Opts, [Opt|R]);
1086hwaddr_last([], R) ->
1087    R.
1088
1089
1090%% Legacy emulation of getifaddrs
1091
1092getifaddrs_ifget(_, []) -> [];
1093getifaddrs_ifget(S, [IF|IFs]) ->
1094    case ifget(S, IF, [flags]) of
1095	{ok,[{flags,Flags}]=FlagsVals} ->
1096            GetOpts =
1097                case member(pointtopoint, Flags) of
1098                    true ->
1099                        [dstaddr,hwaddr];
1100                    false ->
1101                        case member(broadcast, Flags) of
1102                            true ->
1103                                [broadaddr,hwaddr];
1104                            false ->
1105                                [hwaddr]
1106                        end
1107                end,
1108	    getifaddrs_ifget(S, IFs, IF, FlagsVals, [addr,netmask|GetOpts]);
1109	_ ->
1110	    getifaddrs_ifget(S, IFs, IF, [], [addr,netmask,hwaddr])
1111    end.
1112
1113getifaddrs_ifget(S, IFs, IF, FlagsVals, Opts) ->
1114    OptVals =
1115	case ifget(S, IF, Opts) of
1116	    {ok,OVs} -> OVs;
1117	    _ -> []
1118	end,
1119    [{IF,FlagsVals++OptVals}|getifaddrs_ifget(S, IFs)].
1120
1121%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1122%%
1123%% getiflist(insock()) -> {ok,IfNameList} | {error, Reason}
1124%%
1125%% get interface name list
1126%%
1127%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1128
1129getiflist(S) when is_port(S) ->
1130    case ctl_cmd(S, ?INET_REQ_GETIFLIST, []) of
1131	{ok, Data} -> {ok, build_iflist(Data)};
1132	{error,_}=Error -> Error
1133    end.
1134
1135%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1136%%
1137%% ifget(insock(), IFOpts) -> {ok,IfNameList} | {error, Reason}
1138%%
1139%% get interface name list
1140%%
1141%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1142
1143ifget(S, Name, Opts) ->
1144    case encode_ifname(Name) of
1145	{ok, Buf1} ->
1146	    case encode_ifopts(Opts,[]) of
1147		{ok, Buf2} ->
1148		    case ctl_cmd(S, ?INET_REQ_IFGET, [Buf1,Buf2]) of
1149			{ok, Data} -> decode_ifopts(Data,[]);
1150			{error,_}=Error -> Error
1151		    end;
1152		Error -> Error
1153	    end;
1154	Error -> Error
1155    end.
1156
1157%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1158%%
1159%% ifset(insock(), Name, IFOptVals) -> {ok,IfNameList} | {error, Reason}
1160%%
1161%% set interface parameters
1162%%
1163%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1164
1165ifset(S, Name, Opts) ->
1166    case encode_ifname(Name) of
1167	{ok, Buf1} ->
1168	    case encode_ifopt_val(Opts,[]) of
1169		{ok, Buf2} ->
1170		    case ctl_cmd(S, ?INET_REQ_IFSET, [Buf1,Buf2]) of
1171			{ok, _} -> ok;
1172			{error,_}=Error -> Error
1173		    end;
1174		Error -> Error
1175	    end;
1176	Error -> Error
1177    end.
1178
1179%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1180%%
1181%% subscribe(insock(), SubsList) -> {ok,StatReply} | {error, Reason}
1182%%
1183%% Subscribe on socket events (from driver)
1184%%
1185%% Available event subscriptions:
1186%%   subs_empty_out_q: StatReply = [{subs_empty_out_q, N}], where N
1187%%                     is current queue length. When the queue becomes empty
1188%%                     a {empty_out_q, insock()} message will be sent to
1189%%                     subscribing process and the subscription will be
1190%%                     removed. If N = 0, the queue is empty and no
1191%%                     subscription is made.
1192%%
1193%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1194
1195subscribe(S, Sub) when is_port(S), is_list(Sub) ->
1196    case encode_subs(Sub) of
1197	{ok, Bytes} ->
1198	    case ctl_cmd(S, ?INET_REQ_SUBSCRIBE, Bytes) of
1199		{ok, Data} -> decode_subs(Data);
1200		{error,_}=Error -> Error
1201	    end;
1202	Error -> Error
1203    end.
1204
1205%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1206%%
1207%% GETSTAT(insock(), StatList) -> {ok,StatReply} | {error, Reason}
1208%%
1209%% get socket statistics (from driver)
1210%%
1211%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1212
1213getstat(S, Stats) when is_port(S), is_list(Stats) ->
1214    case encode_stats(Stats) of
1215	{ok, Bytes} ->
1216	    case ctl_cmd(S, ?INET_REQ_GETSTAT, Bytes) of
1217		{ok, Data} -> decode_stats(Data);
1218		{error,_}=Error -> Error
1219	    end;
1220	Error -> Error
1221    end.
1222
1223%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1224%%
1225%% GETFD(insock()) -> {ok,integer()} | {error, Reason}
1226%%
1227%% get internal file descriptor
1228%%
1229%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1230
1231getfd(S) when is_port(S) ->
1232    case ctl_cmd(S, ?INET_REQ_GETFD, []) of
1233	{ok, [S3,S2,S1,S0]} -> {ok, ?u32(S3,S2,S1,S0)};
1234	{error,_}=Error -> Error
1235    end.
1236
1237%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1238%%
1239%% IGNOREFD(insock(),boolean()) -> {ok,integer()} | {error, Reason}
1240%%
1241%% steal internal file descriptor
1242%%
1243%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1244
1245ignorefd(S,Bool) when is_port(S) ->
1246    Val = if Bool -> 1; true -> 0 end,
1247    case ctl_cmd(S, ?INET_REQ_IGNOREFD, [Val]) of
1248	{ok, _} -> ok;
1249	Error -> Error
1250    end.
1251
1252%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1253%%
1254%% GETIX(insock()) -> {ok,integer()} | {error, Reason}
1255%%
1256%% get internal socket index
1257%%
1258%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1259
1260getindex(S) when is_port(S) ->
1261    %% NOT USED ANY MORE
1262    {error, einval}.
1263
1264%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1265%%
1266%% GETTYPE(insock()) -> {ok,{Family,Type}} | {error, Reason}
1267%%
1268%% get family/type of a socket
1269%%
1270%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1271
1272gettype(S) when is_port(S) ->
1273    case ctl_cmd(S, ?INET_REQ_GETTYPE, []) of
1274	{ok, [F3,F2,F1,F0,T3,T2,T1,T0]} ->
1275	    Family = case ?u32(F3,F2,F1,F0) of
1276			 ?INET_AF_INET  ->  inet;
1277			 ?INET_AF_INET6 ->  inet6;
1278			 _ -> undefined
1279		     end,
1280	    Type = case ?u32(T3,T2,T1,T0) of
1281			?INET_TYPE_STREAM    -> stream;
1282			?INET_TYPE_DGRAM     -> dgram;
1283			?INET_TYPE_SEQPACKET -> seqpacket;
1284			_		     -> undefined
1285		   end,
1286	    {ok, {Family, Type}};
1287	{error,_}=Error -> Error
1288    end.
1289
1290getprotocol(S) when is_port(S) ->
1291    {name,Drv} = erlang:port_info(S, name),
1292    drv2protocol(Drv).
1293
1294%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1295%%  IS_SCTP(insock()) -> true | false
1296%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1297%% is_sctp(S) when is_port(S) ->
1298%%     case gettype(S) of
1299%% 	{ok, {_, seqpacket}} -> true;
1300%% 	_		     -> false
1301%%     end.
1302
1303%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1304%%
1305%% GETSTATUS(insock()) -> {ok,Status} | {error, Reason}
1306%%
1307%% get socket status
1308%%
1309%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1310
1311getstatus(S) when is_port(S) ->
1312    case ctl_cmd(S, ?INET_REQ_GETSTATUS, []) of
1313	{ok, [S3,S2,S1,S0]} ->
1314	    {ok, dec_status(?u32(S3,S2,S1,S0))};
1315	{error,_}=Error -> Error
1316    end.
1317
1318%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1319%%
1320%% GETHOSTNAME(insock()) -> {ok,HostName} | {error, Reason}
1321%%
1322%% get host name
1323%%
1324%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1325
1326gethostname(S) when is_port(S) ->
1327    ctl_cmd(S, ?INET_REQ_GETHOSTNAME, []).
1328
1329%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1330%%
1331%% GETSERVBYNAME(insock(),Name,Proto) -> {ok,Port} | {error, Reason}
1332%%
1333%% get service port
1334%%
1335%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1336
1337getservbyname(S,Name,Proto) when is_port(S), is_atom(Name), is_atom(Proto) ->
1338    getservbyname1(S, atom_to_list(Name), atom_to_list(Proto));
1339getservbyname(S,Name,Proto) when is_port(S), is_atom(Name), is_list(Proto) ->
1340    getservbyname1(S, atom_to_list(Name), Proto);
1341getservbyname(S,Name,Proto) when is_port(S), is_list(Name), is_atom(Proto) ->
1342    getservbyname1(S, Name, atom_to_list(Proto));
1343getservbyname(S,Name,Proto) when is_port(S), is_list(Name), is_list(Proto) ->
1344    getservbyname1(S, Name, Proto);
1345getservbyname(_,_, _) ->
1346    {error, einval}.
1347
1348getservbyname1(S,Name,Proto) ->
1349    L1 = length(Name),
1350    L2 = length(Proto),
1351    if L1 > 255 -> {error, einval};
1352       L2 > 255 -> {error, einval};
1353       true ->
1354	    case ctl_cmd(S, ?INET_REQ_GETSERVBYNAME, [L1,Name,L2,Proto]) of
1355		{ok, [P1,P0]} ->
1356		    {ok, ?u16(P1,P0)};
1357		{error,_}=Error ->
1358		    Error
1359	    end
1360    end.
1361
1362%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1363%%
1364%% GETSERVBYPORT(insock(),Port,Proto) -> {ok,Port} | {error, Reason}
1365%%
1366%% get service port from portnumber and protocol
1367%%
1368%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1369
1370getservbyport(S,Port,Proto) when is_port(S), is_atom(Proto) ->
1371    getservbyport1(S, Port, atom_to_list(Proto));
1372getservbyport(S,Port,Proto) when is_port(S), is_list(Proto) ->
1373    getservbyport1(S, Port, Proto);
1374getservbyport(_, _, _) ->
1375    {error, einval}.
1376
1377getservbyport1(S,Port,Proto) ->
1378    L = length(Proto),
1379    if Port < 0 -> {error, einval};
1380       Port > 16#ffff -> {error, einval};
1381       L > 255 -> {error, einval};
1382       true ->
1383	    case ctl_cmd(S, ?INET_REQ_GETSERVBYPORT, [?int16(Port),L,Proto]) of
1384		{ok, Name} -> {ok, Name};
1385		{error,_}=Error -> Error
1386	    end
1387    end.
1388
1389%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1390%%
1391%% UNRECV(insock(), data) -> ok | {error, Reason}
1392%%
1393%%
1394%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1395
1396unrecv(S, Data) ->
1397    case ctl_cmd(S, ?TCP_REQ_UNRECV, Data) of
1398	{ok, _} -> ok;
1399	{error,_}=Error  -> Error
1400    end.
1401
1402%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1403%%
1404%% DETACH(insock()) -> ok
1405%%
1406%%   unlink from a socket
1407%%
1408%% ATTACH(insock()) -> ok | {error, Reason}
1409%%
1410%%   link and connect to a socket
1411%%
1412%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1413
1414detach(S) when is_port(S) ->
1415    unlink(S),
1416    ok.
1417
1418attach(S) when is_port(S) ->
1419    try erlang:port_connect(S, self()) of
1420	true -> link(S), ok
1421    catch
1422	error:Reason -> {error,Reason}
1423    end.
1424
1425%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1426%%
1427%% INTERNAL FUNCTIONS
1428%%
1429%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1430
1431is_sockopt_val(Opt, Val) ->
1432    Type = type_opt(set, Opt),
1433    try type_value(set, Type, Val)
1434    catch
1435	_ -> false
1436    end.
1437
1438%%
1439%% Socket options processing: Encoding option NAMES:
1440%%
1441enc_opt(reuseaddr)       -> ?INET_OPT_REUSEADDR;
1442enc_opt(keepalive)       -> ?INET_OPT_KEEPALIVE;
1443enc_opt(dontroute)       -> ?INET_OPT_DONTROUTE;
1444enc_opt(linger)          -> ?INET_OPT_LINGER;
1445enc_opt(broadcast)       -> ?INET_OPT_BROADCAST;
1446enc_opt(sndbuf)          -> ?INET_OPT_SNDBUF;
1447enc_opt(recbuf)          -> ?INET_OPT_RCVBUF;
1448enc_opt(priority)        -> ?INET_OPT_PRIORITY;
1449enc_opt(tos)             -> ?INET_OPT_TOS;
1450enc_opt(tclass)          -> ?INET_OPT_TCLASS;
1451enc_opt(recvtos)         -> ?INET_OPT_RECVTOS;
1452enc_opt(recvtclass)      -> ?INET_OPT_RECVTCLASS;
1453enc_opt(pktoptions)      -> ?INET_OPT_PKTOPTIONS;
1454enc_opt(ttl)             -> ?INET_OPT_TTL;
1455enc_opt(recvttl)         -> ?INET_OPT_RECVTTL;
1456enc_opt(nodelay)         -> ?TCP_OPT_NODELAY;
1457enc_opt(nopush)          -> ?TCP_OPT_NOPUSH;
1458enc_opt(multicast_if)    -> ?UDP_OPT_MULTICAST_IF;
1459enc_opt(multicast_ttl)   -> ?UDP_OPT_MULTICAST_TTL;
1460enc_opt(multicast_loop)  -> ?UDP_OPT_MULTICAST_LOOP;
1461enc_opt(add_membership)  -> ?UDP_OPT_ADD_MEMBERSHIP;
1462enc_opt(drop_membership) -> ?UDP_OPT_DROP_MEMBERSHIP;
1463enc_opt(ipv6_v6only)     -> ?INET_OPT_IPV6_V6ONLY;
1464enc_opt(buffer)          -> ?INET_LOPT_BUFFER;
1465enc_opt(header)          -> ?INET_LOPT_HEADER;
1466enc_opt(active)          -> ?INET_LOPT_ACTIVE;
1467enc_opt(packet)          -> ?INET_LOPT_PACKET;
1468enc_opt(mode)            -> ?INET_LOPT_MODE;
1469enc_opt(deliver)         -> ?INET_LOPT_DELIVER;
1470enc_opt(exit_on_close)   -> ?INET_LOPT_EXITONCLOSE;
1471enc_opt(high_watermark)  -> ?INET_LOPT_TCP_HIWTRMRK;
1472enc_opt(low_watermark)   -> ?INET_LOPT_TCP_LOWTRMRK;
1473enc_opt(high_msgq_watermark)  -> ?INET_LOPT_MSGQ_HIWTRMRK;
1474enc_opt(low_msgq_watermark)   -> ?INET_LOPT_MSGQ_LOWTRMRK;
1475enc_opt(send_timeout)    -> ?INET_LOPT_TCP_SEND_TIMEOUT;
1476enc_opt(send_timeout_close) -> ?INET_LOPT_TCP_SEND_TIMEOUT_CLOSE;
1477enc_opt(delay_send)      -> ?INET_LOPT_TCP_DELAY_SEND;
1478enc_opt(packet_size)     -> ?INET_LOPT_PACKET_SIZE;
1479enc_opt(read_packets)    -> ?INET_LOPT_READ_PACKETS;
1480enc_opt(netns)           -> ?INET_LOPT_NETNS;
1481enc_opt(show_econnreset) -> ?INET_LOPT_TCP_SHOW_ECONNRESET;
1482enc_opt(line_delimiter)  -> ?INET_LOPT_LINE_DELIM;
1483enc_opt(raw)             -> ?INET_OPT_RAW;
1484enc_opt(bind_to_device)  -> ?INET_OPT_BIND_TO_DEVICE;
1485% Names of SCTP opts:
1486enc_opt(sctp_rtoinfo)	 	   -> ?SCTP_OPT_RTOINFO;
1487enc_opt(sctp_associnfo)	 	   -> ?SCTP_OPT_ASSOCINFO;
1488enc_opt(sctp_initmsg)	 	   -> ?SCTP_OPT_INITMSG;
1489enc_opt(sctp_autoclose)	 	   -> ?SCTP_OPT_AUTOCLOSE;
1490enc_opt(sctp_nodelay)		   -> ?SCTP_OPT_NODELAY;
1491enc_opt(sctp_disable_fragments)	   -> ?SCTP_OPT_DISABLE_FRAGMENTS;
1492enc_opt(sctp_i_want_mapped_v4_addr)-> ?SCTP_OPT_I_WANT_MAPPED_V4_ADDR;
1493enc_opt(sctp_maxseg)		   -> ?SCTP_OPT_MAXSEG;
1494enc_opt(sctp_set_peer_primary_addr)-> ?SCTP_OPT_SET_PEER_PRIMARY_ADDR;
1495enc_opt(sctp_primary_addr)	   -> ?SCTP_OPT_PRIMARY_ADDR;
1496enc_opt(sctp_adaptation_layer)	   -> ?SCTP_OPT_ADAPTATION_LAYER;
1497enc_opt(sctp_peer_addr_params)	   -> ?SCTP_OPT_PEER_ADDR_PARAMS;
1498enc_opt(sctp_default_send_param)   -> ?SCTP_OPT_DEFAULT_SEND_PARAM;
1499enc_opt(sctp_events)		   -> ?SCTP_OPT_EVENTS;
1500enc_opt(sctp_delayed_ack_time)	   -> ?SCTP_OPT_DELAYED_ACK_TIME;
1501enc_opt(sctp_status)		   -> ?SCTP_OPT_STATUS;
1502enc_opt(sctp_get_peer_addr_info)   -> ?SCTP_OPT_GET_PEER_ADDR_INFO.
1503%%
1504
1505%%
1506%% Decoding option NAMES:
1507%%
1508dec_opt(?INET_OPT_REUSEADDR)      -> reuseaddr;
1509dec_opt(?INET_OPT_KEEPALIVE)      -> keepalive;
1510dec_opt(?INET_OPT_DONTROUTE)      -> dontroute;
1511dec_opt(?INET_OPT_LINGER)         -> linger;
1512dec_opt(?INET_OPT_BROADCAST)      -> broadcast;
1513dec_opt(?INET_OPT_SNDBUF)         -> sndbuf;
1514dec_opt(?INET_OPT_RCVBUF)         -> recbuf;
1515dec_opt(?INET_OPT_PRIORITY)       -> priority;
1516dec_opt(?INET_OPT_TOS)            -> tos;
1517dec_opt(?INET_OPT_TCLASS)         -> tclass;
1518dec_opt(?TCP_OPT_NODELAY)         -> nodelay;
1519dec_opt(?TCP_OPT_NOPUSH)          -> nopush;
1520dec_opt(?INET_OPT_RECVTOS)        -> recvtos;
1521dec_opt(?INET_OPT_RECVTCLASS)     -> recvtclass;
1522dec_opt(?INET_OPT_PKTOPTIONS)     -> pktoptions;
1523dec_opt(?INET_OPT_TTL)            -> ttl;
1524dec_opt(?INET_OPT_RECVTTL)        -> recvttl;
1525dec_opt(?UDP_OPT_MULTICAST_IF)    -> multicast_if;
1526dec_opt(?UDP_OPT_MULTICAST_TTL)   -> multicast_ttl;
1527dec_opt(?UDP_OPT_MULTICAST_LOOP)  -> multicast_loop;
1528dec_opt(?UDP_OPT_ADD_MEMBERSHIP)  -> add_membership;
1529dec_opt(?UDP_OPT_DROP_MEMBERSHIP) -> drop_membership;
1530dec_opt(?INET_OPT_IPV6_V6ONLY)    -> ipv6_v6only;
1531dec_opt(?INET_LOPT_BUFFER)        -> buffer;
1532dec_opt(?INET_LOPT_HEADER)        -> header;
1533dec_opt(?INET_LOPT_ACTIVE)        -> active;
1534dec_opt(?INET_LOPT_PACKET)        -> packet;
1535dec_opt(?INET_LOPT_MODE)          -> mode;
1536dec_opt(?INET_LOPT_DELIVER)       -> deliver;
1537dec_opt(?INET_LOPT_EXITONCLOSE)   -> exit_on_close;
1538dec_opt(?INET_LOPT_TCP_HIWTRMRK)  -> high_watermark;
1539dec_opt(?INET_LOPT_TCP_LOWTRMRK)  -> low_watermark;
1540dec_opt(?INET_LOPT_MSGQ_HIWTRMRK)  -> high_msgq_watermark;
1541dec_opt(?INET_LOPT_MSGQ_LOWTRMRK)  -> low_msgq_watermark;
1542dec_opt(?INET_LOPT_TCP_SEND_TIMEOUT) -> send_timeout;
1543dec_opt(?INET_LOPT_TCP_SEND_TIMEOUT_CLOSE) -> send_timeout_close;
1544dec_opt(?INET_LOPT_TCP_DELAY_SEND)   -> delay_send;
1545dec_opt(?INET_LOPT_PACKET_SIZE)      -> packet_size;
1546dec_opt(?INET_LOPT_READ_PACKETS)     -> read_packets;
1547dec_opt(?INET_LOPT_NETNS)           -> netns;
1548dec_opt(?INET_LOPT_TCP_SHOW_ECONNRESET) -> show_econnreset;
1549dec_opt(?INET_LOPT_LINE_DELIM)      -> line_delimiter;
1550dec_opt(?INET_OPT_RAW)              -> raw;
1551dec_opt(?INET_OPT_BIND_TO_DEVICE) -> bind_to_device;
1552dec_opt(I) when is_integer(I)     -> undefined.
1553
1554
1555
1556%% Metatypes:
1557%% []              Value must be 'undefined' or nonexistent
1558%%                 for setopts and getopts.
1559%% [Type]          Value required for setopts and getopts,
1560%%                 will be encoded for both.
1561%% [Type,Default]  Default used if value is 'undefined'.
1562%% [[Type,Default]] A combination of the two above.
1563%% Type            Value must be 'undefined' or nonexistent for getops,
1564%%                 required for setopts.
1565%%
1566%% The use of [] and [[Type,Default]] is commented out in enc_value/2
1567%% and type_value/2 below since they are only used in record fields.
1568%% And record fields does not call enc_value/2 nor type_value/2.
1569%% Anyone introducing these metatypes otherwhere will have to activate
1570%% those clauses in enc_value/2 and type_value/2. You have been warned!
1571
1572type_opt(get, raw) -> [{[int],[int],[binary_or_uint]}];
1573type_opt(_,   raw) -> {int,int,binary};
1574%% NB: "sctp_status" and "sctp_get_peer_addr_info" are read-only options,
1575%% so they should not be NOT encoded for use with "setopt".
1576type_opt(get, sctp_status) ->
1577    [{record,#sctp_status{
1578	assoc_id = [sctp_assoc_id],
1579	_        = []}}];
1580type_opt(get, sctp_get_peer_addr_info) ->
1581    [{record,#sctp_paddrinfo{
1582	assoc_id = [[sctp_assoc_id,0]],
1583	address  = [[addr,{any,0}]],
1584	_        = []}}];
1585type_opt(_,   Opt) ->
1586    type_opt_1(Opt).
1587
1588%% Types of option values, by option name:
1589%%
1590type_opt_1(reuseaddr)       -> bool;
1591type_opt_1(keepalive)       -> bool;
1592type_opt_1(dontroute)       -> bool;
1593type_opt_1(linger)          -> {bool,int};
1594type_opt_1(broadcast)       -> bool;
1595type_opt_1(sndbuf)          -> int;
1596type_opt_1(recbuf)          -> int;
1597type_opt_1(priority)        -> int;
1598type_opt_1(tos)             -> int;
1599type_opt_1(tclass)          -> int;
1600type_opt_1(recvtos)         -> bool;
1601type_opt_1(recvtclass)      -> bool;
1602type_opt_1(pktoptions)      -> opts;
1603type_opt_1(ttl)             -> int;
1604type_opt_1(recvttl)         -> bool;
1605type_opt_1(nodelay)         -> bool;
1606type_opt_1(nopush)          -> bool;
1607type_opt_1(ipv6_v6only)     -> bool;
1608%% multicast
1609type_opt_1(multicast_ttl)   -> int;
1610type_opt_1(multicast_loop)  -> bool;
1611type_opt_1(multicast_if)    -> ip;
1612type_opt_1(add_membership)  -> {ip,ip};
1613type_opt_1(drop_membership) -> {ip,ip};
1614%% driver options
1615type_opt_1(header)          -> uint;
1616type_opt_1(buffer)          -> int;
1617type_opt_1(active) ->
1618    {enum,[{false, ?INET_PASSIVE},
1619	   {true, ?INET_ACTIVE},
1620	   {once, ?INET_ONCE},
1621           {multi, ?INET_MULTI}]};
1622type_opt_1(packet) ->
1623    {enum,[{0, ?TCP_PB_RAW},
1624	   {1, ?TCP_PB_1},
1625	   {2, ?TCP_PB_2},
1626	   {4, ?TCP_PB_4},
1627	   {raw,?TCP_PB_RAW},
1628	   {sunrm, ?TCP_PB_RM},
1629	   {asn1, ?TCP_PB_ASN1},
1630	   {cdr, ?TCP_PB_CDR},
1631	   {fcgi, ?TCP_PB_FCGI},
1632	   {line, ?TCP_PB_LINE_LF},
1633	   {tpkt, ?TCP_PB_TPKT},
1634	   {http, ?TCP_PB_HTTP},
1635	   {httph,?TCP_PB_HTTPH},
1636	   {http_bin, ?TCP_PB_HTTP_BIN},
1637	   {httph_bin,?TCP_PB_HTTPH_BIN},
1638	   {ssl, ?TCP_PB_SSL_TLS}, % obsolete
1639	   {ssl_tls, ?TCP_PB_SSL_TLS}]};
1640type_opt_1(line_delimiter)  -> int;
1641type_opt_1(mode) ->
1642    {enum,[{list, ?INET_MODE_LIST},
1643	   {binary, ?INET_MODE_BINARY}]};
1644type_opt_1(deliver) ->
1645    {enum,[{port, ?INET_DELIVER_PORT},
1646	   {term, ?INET_DELIVER_TERM}]};
1647type_opt_1(exit_on_close)   -> bool;
1648type_opt_1(low_watermark)   -> int;
1649type_opt_1(high_watermark)  -> int;
1650type_opt_1(low_msgq_watermark)   -> int;
1651type_opt_1(high_msgq_watermark)  -> int;
1652type_opt_1(send_timeout)    -> time;
1653type_opt_1(send_timeout_close) -> bool;
1654type_opt_1(delay_send)      -> bool;
1655type_opt_1(packet_size)     -> uint;
1656type_opt_1(read_packets)    -> uint;
1657type_opt_1(netns)           -> binary;
1658type_opt_1(show_econnreset) -> bool;
1659type_opt_1(bind_to_device)  -> binary;
1660%%
1661%% SCTP options (to be set). If the type is a record type, the corresponding
1662%% record signature is returned, otherwise, an "elementary" type tag
1663%% is returned:
1664%%
1665%% for SCTP_OPT_RTOINFO
1666type_opt_1(sctp_rtoinfo) ->
1667    [{record,#sctp_rtoinfo{
1668	assoc_id = [[sctp_assoc_id,0]],
1669	initial  = [uint32,0],
1670	max      = [uint32,0],
1671	min      = [uint32,0]}}];
1672%% for SCTP_OPT_ASSOCINFO
1673type_opt_1(sctp_associnfo) ->
1674    [{record,#sctp_assocparams{
1675	assoc_id                 = [[sctp_assoc_id,0]],
1676	asocmaxrxt               = [uint16,0],
1677	number_peer_destinations = [uint16,0],
1678	peer_rwnd                = [uint32,0],
1679	local_rwnd               = [uint32,0],
1680	cookie_life              = [uint32,0]}}];
1681%% for SCTP_OPT_INITMSG and SCTP_TAG_SEND_ANC_INITMSG (send*)
1682type_opt_1(sctp_initmsg) ->
1683    [{record,#sctp_initmsg{
1684	num_ostreams   = [uint16,0],
1685	max_instreams  = [uint16,0],
1686	max_attempts   = [uint16,0],
1687	max_init_timeo = [uint16,0]}}];
1688%%
1689type_opt_1(sctp_nodelay)	       -> bool;
1690type_opt_1(sctp_autoclose)	       -> uint;
1691type_opt_1(sctp_disable_fragments)     -> bool;
1692type_opt_1(sctp_i_want_mapped_v4_addr) -> bool;
1693type_opt_1(sctp_maxseg)		       -> uint;
1694%% for SCTP_OPT_PRIMARY_ADDR
1695type_opt_1(sctp_primary_addr) ->
1696    [{record,#sctp_prim{
1697	assoc_id = [sctp_assoc_id],
1698	addr     = addr}}];
1699%% for SCTP_OPT_SET_PEER_PRIMARY_ADDR
1700type_opt_1(sctp_set_peer_primary_addr) ->
1701    [{record,#sctp_setpeerprim{
1702	assoc_id = [sctp_assoc_id],
1703	addr     = addr}}];
1704%% for SCTP_OPT_ADAPTATION_LAYER
1705type_opt_1(sctp_adaptation_layer) ->
1706    [{record,#sctp_setadaptation{
1707	adaptation_ind = [uint32,0]}}];
1708%% for SCTP_OPT_PEER_ADDR_PARAMS
1709type_opt_1(sctp_peer_addr_params) ->
1710    [{record,#sctp_paddrparams{
1711	assoc_id          = [[sctp_assoc_id,0]],
1712	address           = [[addr,{any,0}]],
1713	hbinterval        = [uint32,0],
1714	pathmaxrxt        = [uint16,0],
1715	pathmtu           = [uint32,0],
1716	sackdelay         = [uint32,0],
1717	flags             =
1718	[{bitenumlist,
1719	  [{hb_enable,         ?SCTP_FLAG_HB_ENABLE},
1720	   {hb_disable,        ?SCTP_FLAG_HB_DISABLE},
1721	   {hb_demand,         ?SCTP_FLAG_HB_DEMAND},
1722	   {pmtud_enable,      ?SCTP_FLAG_PMTUD_ENABLE},
1723	   {pmtud_disable,     ?SCTP_FLAG_PMTUD_DISABLE},
1724	   {sackdelay_enable,  ?SCTP_FLAG_SACKDELAY_ENABLE},
1725	   {sackdelay_disable, ?SCTP_FLAG_SACKDELAY_DISABLE}],
1726	  uint32},[]]}}];
1727%% for SCTP_OPT_DEFAULT_SEND_PARAM and SCTP_TAG_SEND_ANC_PARAMS (on send*)
1728type_opt_1(sctp_default_send_param) ->
1729    [{record,#sctp_sndrcvinfo{
1730	stream            = [uint16,0],
1731	ssn               = [],
1732	flags             =
1733	[{bitenumlist,
1734	  [{unordered,  ?SCTP_FLAG_UNORDERED},
1735	   {addr_over,  ?SCTP_FLAG_ADDR_OVER},
1736	   {abort,      ?SCTP_FLAG_ABORT},
1737	   {eof,        ?SCTP_FLAG_EOF}],
1738	  uint16},[]],
1739	ppid              = [uint32,0],
1740	context           = [uint32,0],
1741	timetolive        = [uint32,0],
1742	tsn               = [],
1743	cumtsn            = [],
1744	assoc_id          = [[sctp_assoc_id,0]]}}];
1745%% for SCTP_OPT_EVENTS
1746type_opt_1(sctp_events) ->
1747    [{record,#sctp_event_subscribe{
1748	data_io_event          = [bool8,true],
1749        association_event      = [bool8,true],
1750	address_event          = [bool8,true],
1751	send_failure_event     = [bool8,true],
1752	peer_error_event       = [bool8,true],
1753	shutdown_event         = [bool8,true],
1754	partial_delivery_event = [bool8,true],
1755	adaptation_layer_event = [bool8,false],
1756	authentication_event   = [bool8,false]}}];
1757%% for SCTP_OPT_DELAYED_ACK_TIME
1758type_opt_1(sctp_delayed_ack_time) ->
1759    [{record,#sctp_assoc_value{
1760	assoc_id    = [[sctp_assoc_id,0]],
1761	assoc_value = [uint32,0]}}];
1762%%
1763type_opt_1(undefined)         -> undefined;
1764type_opt_1(O) when is_atom(O) -> undefined.
1765
1766
1767
1768%% Get. No supplied value.
1769type_value(get, undefined)        -> false; % Undefined type
1770%% These two clauses cannot happen since they are only used
1771%% in record fields - from record fields they must have a
1772%% value though it might be 'undefined', so record fields
1773%% calls type_value/3, not type_value/2.
1774%% type_value(get, [])               -> true;  % Ignored
1775%% type_value(get, [[Type,Default]]) ->        % Required field, default value
1776%%     type_value(get, Type, Default);
1777type_value(get, [{record,Types}]) ->        % Implied default value for record
1778    type_value_record(get, Types,
1779		      erlang:make_tuple(tuple_size(Types), undefined), 2);
1780type_value(get, [_])              -> false; % Required value missing
1781type_value(get, _)                -> true.  % Field is supposed to be undefined
1782
1783%% Get and set. Value supplied.
1784type_value(_, undefined, _)   -> false;     % Undefined type
1785type_value(_, [], undefined)  -> true;      % Ignored
1786type_value(_, [], _)          -> false;     % Value should not be supplied
1787type_value(Q, [Type], Value)  ->            % Required field, proceed
1788    type_value_default(Q, Type, Value);
1789type_value(set, Type, Value)  ->            % Required for setopts
1790    type_value_default(set, Type, Value);
1791type_value(_, _, undefined) -> true;        % Value should be undefined for
1792type_value(_, _, _)         -> false.       %   other than setopts.
1793
1794type_value_default(Q, [Type,Default], undefined) ->
1795    type_value_1(Q, Type, Default);
1796type_value_default(Q, [Type,_], Value) ->
1797    type_value_1(Q, Type, Value);
1798type_value_default(Q, Type, Value) ->
1799    type_value_1(Q, Type, Value).
1800
1801type_value_1(Q, {record,Types}, undefined) ->
1802    type_value_record(Q, Types,
1803		      erlang:make_tuple(tuple_size(Types), undefined), 2);
1804type_value_1(Q, {record,Types}, Values)
1805  when tuple_size(Types) =:= tuple_size(Values) ->
1806    type_value_record(Q, Types, Values, 2);
1807type_value_1(Q, Types, Values)
1808  when tuple_size(Types) =:= tuple_size(Values) ->
1809    type_value_tuple(Q, Types, Values, 1);
1810type_value_1(_, Type, Value) ->
1811    type_value_2(Type, Value).
1812
1813type_value_tuple(Q, Types, Values, N)
1814  when is_integer(N), N =< tuple_size(Types) ->
1815    type_value(Q, element(N, Types), element(N, Values))
1816	andalso type_value_tuple(Q, Types, Values, N+1);
1817type_value_tuple(_, _, _, _) -> true.
1818
1819type_value_record(Q, Types, Values, N)
1820  when is_integer(N), N =< tuple_size(Types) ->
1821    case type_value(Q, element(N, Types), element(N, Values)) of
1822	true -> type_value_record(Q, Types, Values, N+1);
1823	false ->
1824	    erlang:throw({type,{record,Q,Types,Values,N}})
1825    end;
1826type_value_record(_, _, _, _) -> true.
1827
1828%% Simple run-time type-checking of (option) values: type -vs- value:
1829%% NB: the LHS is the TYPE, not the option name!
1830%%
1831%% Returns true | false | throw(ErrorReason) only for record types
1832%%
1833type_value_2(undefined, _)                            -> false;
1834%%
1835type_value_2(bool, true)                              -> true;
1836type_value_2(bool, false)                             -> true;
1837type_value_2(bool8, true)                             -> true;
1838type_value_2(bool8, false)                            -> true;
1839type_value_2(int, X) when is_integer(X)               -> true;
1840type_value_2(uint, X) when is_integer(X), X >= 0      -> true;
1841type_value_2(uint32, X) when X band 16#ffffffff =:= X -> true;
1842type_value_2(uint24, X) when X band 16#ffffff =:= X   -> true;
1843type_value_2(uint16, X) when X band 16#ffff =:= X     -> true;
1844type_value_2(uint8, X)  when X band 16#ff =:= X       -> true;
1845type_value_2(time, infinity)                          -> true;
1846type_value_2(time, X) when is_integer(X), X >= 0      -> true;
1847type_value_2(ip,{A,B,C,D}) when ?ip(A,B,C,D)          -> true;
1848%%
1849type_value_2(addr, {any,Port}) ->
1850    type_value_2(uint16, Port);
1851type_value_2(addr, {loopback,Port}) ->
1852    type_value_2(uint16, Port);
1853type_value_2(addr, {IP,_} = Addr) when tuple_size(IP) =:= 4 ->
1854    type_value_2(addr, {inet,Addr});
1855type_value_2(addr, {IP,_} = Addr) when tuple_size(IP) =:= 8 ->
1856    type_value_2(addr, {inet6,Addr});
1857type_value_2(addr, {Local,_}) when is_list(Local); is_binary(Local) ->
1858    type_value_2(addr, {local,Local});
1859%%
1860type_value_2(addr, {Family,{Tag,Port}})
1861  when (Family =:= inet orelse Family =:= inet6) andalso
1862       (Tag =:= any orelse Tag =:= loopback) ->
1863    type_value_2(uint16, Port);
1864type_value_2(addr, {inet,{{A,B,C,D},Port}})
1865  when ?ip(A,B,C,D) ->
1866    type_value_2(uint16, Port);
1867type_value_2(addr, {inet6,{{A,B,C,D,E,F,G,H},Port}})
1868  when ?ip6(A,B,C,D,E,F,G,H) ->
1869    type_value_2(uint16, Port);
1870type_value_2(addr, {local,Addr}) ->
1871    if
1872	is_binary(Addr) ->
1873	    byte_size(Addr) =< 255;
1874	true ->
1875	    try
1876		%% We either get a badarg from byte_size
1877		%% or from characters_to_binary
1878		byte_size(
1879		  unicode:characters_to_binary(
1880		    Addr, file:native_name_encoding()))
1881	    of
1882		N when N =< 255 ->
1883		    true;
1884		_ ->
1885		    false
1886	    catch error:badarg ->
1887		    false
1888	    end
1889    end;
1890%%
1891type_value_2(ether,[X1,X2,X3,X4,X5,X6])
1892  when ?ether(X1,X2,X3,X4,X5,X6)                    -> true;
1893type_value_2({enum,List}, Enum) ->
1894    case enum_val(Enum, List) of
1895	{value,_} 				    -> true;
1896	false                                       -> false
1897    end;
1898type_value_2(sockaddr, Addr) ->
1899    case Addr of
1900	any                                         -> true;
1901	loopback                                    -> true;
1902	{A,B,C,D} when ?ip(A,B,C,D)                 -> true;
1903	{A,B,C,D,E,F,G,H} when ?ip6(A,B,C,D,E,F,G,H) -> true;
1904	_                                           -> false
1905    end;
1906type_value_2(linkaddr, Addr) when is_list(Addr) ->
1907    case len(Addr, 32768) of
1908	undefined                                   -> false;
1909	_                                           -> true
1910    end;
1911type_value_2({bitenumlist,List}, EnumList) ->
1912    case enum_vals(EnumList, List) of
1913	Ls when is_list(Ls)                         -> true;
1914	false                                       -> false
1915    end;
1916type_value_2({bitenumlist,List,_}, EnumList) ->
1917    case enum_vals(EnumList, List) of
1918	Ls when is_list(Ls)                         -> true;
1919	false                                       -> false
1920    end;
1921type_value_2(binary,Bin)
1922  when is_binary(Bin), byte_size(Bin) < (1 bsl 32)  -> true;
1923type_value_2(binary_or_uint,Bin)
1924  when is_binary(Bin), byte_size(Bin) < (1 bsl 32)  -> true;
1925type_value_2(binary_or_uint,Int)
1926  when is_integer(Int), Int >= 0                    -> true;
1927%% Type-checking of SCTP options
1928type_value_2(sctp_assoc_id, X)
1929  when X band 16#ffffffff =:= X                     -> true;
1930type_value_2(_, _)         -> false.
1931
1932
1933
1934%% Get. No supplied value.
1935%%
1936%% These two clauses cannot happen since they are only used
1937%% in record fields - from record fields they must have a
1938%% value though it might be 'undefined', so record fields
1939%% calls enc_value/3, not enc_value/2.
1940%% enc_value(get, [])               -> [];  % Ignored
1941%% enc_value(get, [[Type,Default]]) ->      % Required field, default value
1942%%     enc_value(get, Type, Default);
1943enc_value(get, [{record,Types}]) ->      % Implied default value for record
1944    enc_value_tuple(get, Types,
1945		    erlang:make_tuple(tuple_size(Types), undefined), 2);
1946enc_value(get, _)                -> [].
1947
1948%% Get and set
1949enc_value(_,   [], _)         -> [];     % Ignored
1950enc_value(Q,   [Type], Value) ->         % Required field, proceed
1951    enc_value_default(Q, Type, Value);
1952enc_value(set, Type, Value)   ->         % Required for setopts
1953    enc_value_default(set, Type, Value);
1954enc_value(_, _, _)            -> [].     % Not encoded for other than setopts
1955
1956enc_value_default(Q, [Type,Default], undefined) ->
1957    enc_value_1(Q, Type, Default);
1958enc_value_default(Q, [Type,_], Value) ->
1959    enc_value_1(Q, Type, Value);
1960enc_value_default(Q, Type, Value) ->
1961    enc_value_1(Q, Type, Value).
1962
1963enc_value_1(Q, {record,Types}, undefined) ->
1964    enc_value_tuple(Q, Types,
1965		    erlang:make_tuple(tuple_size(Types), undefined), 2);
1966enc_value_1(Q, {record,Types}, Values)
1967  when tuple_size(Types) =:= tuple_size(Values) ->
1968    enc_value_tuple(Q, Types, Values, 2);
1969enc_value_1(Q, Types, Values) when tuple_size(Types) =:= tuple_size(Values) ->
1970    enc_value_tuple(Q, Types, Values, 1);
1971enc_value_1(_, Type, Value) ->
1972    enc_value_2(Type, Value).
1973
1974enc_value_tuple(Q, Types, Values, N)
1975  when is_integer(N), N =< tuple_size(Types) ->
1976    [enc_value(Q, element(N, Types), element(N, Values))
1977     |enc_value_tuple(Q, Types, Values, N+1)];
1978enc_value_tuple(_, _, _, _) -> [].
1979
1980%%
1981%% Encoding of option VALUES:
1982%%
1983enc_value_2(bool, true)     -> [0,0,0,1];
1984enc_value_2(bool, false)    -> [0,0,0,0];
1985enc_value_2(bool8, true)    -> [1];
1986enc_value_2(bool8, false)   -> [0];
1987enc_value_2(int, Val)       -> ?int32(Val);
1988enc_value_2(uint, Val)      -> ?int32(Val);
1989enc_value_2(uint32, Val)    -> ?int32(Val);
1990enc_value_2(uint24, Val)    -> ?int24(Val);
1991enc_value_2(uint16, Val)    -> ?int16(Val);
1992enc_value_2(uint8, Val)     -> ?int8(Val);
1993enc_value_2(time, infinity) -> ?int32(-1);
1994enc_value_2(time, Val)      -> ?int32(Val);
1995enc_value_2(ip,{A,B,C,D})   -> [A,B,C,D];
1996enc_value_2(ip, any)        -> [0,0,0,0];
1997enc_value_2(ip, loopback)   -> [127,0,0,1];
1998%%
1999enc_value_2(addr, {any,Port}) ->
2000    [?INET_AF_ANY|?int16(Port)];
2001enc_value_2(addr, {loopback,Port}) ->
2002    [?INET_AF_LOOPBACK|?int16(Port)];
2003enc_value_2(addr, {IP,Port}) when tuple_size(IP) =:= 4 ->
2004    [?INET_AF_INET,?int16(Port)|ip4_to_bytes(IP)];
2005enc_value_2(addr, {IP,Port}) when tuple_size(IP) =:= 8 ->
2006    [?INET_AF_INET6,?int16(Port)|ip6_to_bytes(IP)];
2007enc_value_2(addr, {File,_}) when is_list(File); is_binary(File) ->
2008    [?INET_AF_LOCAL,iolist_size(File)|File];
2009%%
2010enc_value_2(addr, {inet,{any,Port}}) ->
2011    [?INET_AF_INET,?int16(Port)|ip4_to_bytes({0,0,0,0})];
2012enc_value_2(addr, {inet,{loopback,Port}}) ->
2013    [?INET_AF_INET,?int16(Port)|ip4_to_bytes({127,0,0,1})];
2014enc_value_2(addr, {inet,{IP,Port}}) ->
2015    [?INET_AF_INET,?int16(Port)|ip4_to_bytes(IP)];
2016enc_value_2(addr, {inet6,{any,Port}}) ->
2017    [?INET_AF_INET6,?int16(Port)|ip6_to_bytes({0,0,0,0,0,0,0,0})];
2018enc_value_2(addr, {inet6,{loopback,Port}}) ->
2019    [?INET_AF_INET6,?int16(Port)|ip6_to_bytes({0,0,0,0,0,0,0,1})];
2020enc_value_2(addr, {inet6,{IP,Port}}) ->
2021    [?INET_AF_INET6,?int16(Port)|ip6_to_bytes(IP)];
2022enc_value_2(addr, {local,Addr}) ->
2023    %% A binary is passed as is, but anything else will be
2024    %% regarded as a filename and therefore encoded according to
2025    %% the current system filename encoding mode.
2026    Bin =
2027	if
2028	    is_binary(Addr) ->
2029		Addr;
2030	    true ->
2031		unicode:characters_to_binary(
2032		  Addr, file:native_name_encoding())
2033	end,
2034    [?INET_AF_LOCAL,byte_size(Bin),Bin];
2035%%
2036enc_value_2(ether, [_,_,_,_,_,_]=Xs) -> Xs;
2037enc_value_2(sockaddr, any) ->
2038    [?INET_AF_ANY];
2039enc_value_2(sockaddr, loopback) ->
2040    [?INET_AF_LOOPBACK];
2041enc_value_2(sockaddr, IP) when tuple_size(IP) =:= 4 ->
2042    [?INET_AF_INET|ip4_to_bytes(IP)];
2043enc_value_2(sockaddr, IP) when tuple_size(IP) =:= 8 ->
2044    [?INET_AF_INET6|ip6_to_bytes(IP)];
2045enc_value_2(linkaddr, Linkaddr) ->
2046    [?int16(length(Linkaddr)),Linkaddr];
2047enc_value_2(sctp_assoc_id, Val) -> ?int32(Val);
2048%% enc_value_2(sctp_assoc_id, Bin) -> [byte_size(Bin),Bin];
2049enc_value_2({enum,List}, Enum) ->
2050    {value,Val} = enum_val(Enum, List),
2051    ?int32(Val);
2052enc_value_2({bitenumlist,List}, EnumList) ->
2053    Vs = enum_vals(EnumList, List),
2054    Val = borlist(Vs, 0),
2055    ?int32(Val);
2056enc_value_2({bitenumlist,List,Type}, EnumList) ->
2057    Vs = enum_vals(EnumList, List),
2058    Value = borlist(Vs, 0),
2059    enc_value_2(Type, Value);
2060enc_value_2(binary,Bin) -> [?int32(byte_size(Bin)),Bin];
2061enc_value_2(binary_or_uint,Datum) when is_binary(Datum) ->
2062    [1,enc_value_2(binary, Datum)];
2063enc_value_2(binary_or_uint,Datum) when is_integer(Datum) ->
2064    [0,enc_value_2(uint, Datum)].
2065
2066
2067
2068%%
2069%% Decoding of option VALUES receved from "getopt":
2070%% NOT required for SCTP, as it always returns ready terms, not lists:
2071%%
2072dec_value(bool, [0,0,0,0|T])       -> {false,T};
2073dec_value(bool, [_,_,_,_|T])       -> {true,T};
2074%% Currently not used i.e only used by SCTP that does not dec_value/2
2075%% dec_value(bool8, [0|T])            -> {false,T};
2076%% dec_value(bool8, [_|T])            -> {true,T};
2077dec_value(int,  [X3,X2,X1,X0|T])   -> {?i32(X3,X2,X1,X0),T};
2078dec_value(uint, [X3,X2,X1,X0|T])   -> {?u32(X3,X2,X1,X0),T};
2079%% Currently not used i.e only used by SCTP that does not dec_value/2
2080%% dec_value(uint32, [X3,X2,X1,X0|T]) -> {?u32(X3,X2,X1,X0),T};
2081%% dec_value(uint24, [X2,X1,X0|T])    -> {?u24(X2,X1,X0),T};
2082%% dec_value(uint16, [X1,X0|T])       -> {?u16(X1,X0),T};
2083%% dec_value(uint8,  [X0|T])          -> {?u8(X0),T};
2084dec_value(time, [X3,X2,X1,X0|T]) ->
2085    case ?i32(X3,X2,X1,X0) of
2086	-1 -> {infinity, T};
2087	Val -> {Val, T}
2088    end;
2089dec_value(ip, [A,B,C,D|T])             -> {{A,B,C,D}, T};
2090%% dec_value(ether, [X1,X2,X3,X4,X5,X6|T]) -> {[X1,X2,X3,X4,X5,X6],T};
2091dec_value(sockaddr, [X|T]) ->
2092    get_ip(X, T);
2093dec_value(linkaddr, [X1,X0|T]) ->
2094    split(?i16(X1,X0), T);
2095dec_value({enum,List}, [X3,X2,X1,X0|T]) ->
2096    Val = ?i32(X3,X2,X1,X0),
2097    case enum_name(Val, List) of
2098	{name, Enum} -> {Enum, T};
2099	_ -> {undefined, T}
2100    end;
2101dec_value({bitenumlist,List}, [X3,X2,X1,X0|T]) ->
2102    Val = ?i32(X3,X2,X1,X0),
2103    {enum_names(Val, List), T};
2104%% Currently not used i.e only used by SCTP that does not dec_value/2
2105%% dec_value({bitenumlist,List,Type}, T0) ->
2106%%     {Val,T} = dec_value(Type, T0),
2107%%     {enum_names(Val, List), T};
2108dec_value(binary,[L0,L1,L2,L3|List]) ->
2109    Len = ?i32(L0,L1,L2,L3),
2110    {X,T}=split(Len,List),
2111    {list_to_binary(X),T};
2112dec_value(opts, [L0,L1,L2,L3|List]) ->
2113    Len = ?u32(L0,L1,L2,L3),
2114    {X,T} = split(Len, List),
2115    Opts = dec_opt_val(X),
2116    {Opts,T};
2117dec_value(Types, List) when is_tuple(Types) ->
2118    {L,T} = dec_value_tuple(Types, List, 1, []),
2119    {list_to_tuple(L),T};
2120dec_value(Type, Val) ->
2121    erlang:error({decode,Type,Val}).
2122%% dec_value(_, B) ->
2123%%     {undefined, B}.
2124
2125dec_value_tuple(Types, List, N, Acc)
2126  when is_integer(N), N =< tuple_size(Types) ->
2127    {Term,Tail} = dec_value(element(N, Types), List),
2128    dec_value_tuple(Types, Tail, N+1, [Term|Acc]);
2129dec_value_tuple(_, List, _, Acc) ->
2130    {rev(Acc),List}.
2131
2132borlist([V|Vs], Value) ->
2133    borlist(Vs, V bor Value);
2134borlist([], Value) -> Value.
2135
2136
2137enum_vals([Enum|Es], List) ->
2138    case enum_val(Enum, List) of
2139	false -> false;
2140	{value,Value} -> [Value | enum_vals(Es, List)]
2141    end;
2142enum_vals([], _) -> [].
2143
2144enum_names(Val, [{Enum,BitVal} |List]) ->
2145    if Val band BitVal =:= BitVal ->
2146	    [Enum | enum_names(Val, List)];
2147       true ->
2148	    enum_names(Val, List)
2149    end;
2150enum_names(_, []) -> [].
2151
2152enum_val(Enum, [{Enum,Value}|_]) -> {value,Value};
2153enum_val(Enum, [_|List]) -> enum_val(Enum, List);
2154enum_val(_, []) -> false.
2155
2156enum_name(Val, [{Enum,Val}|_]) -> {name,Enum};
2157enum_name(Val, [_|List]) -> enum_name(Val, List);
2158enum_name(_, []) -> false.
2159
2160
2161
2162%% Encoding for setopts
2163%%
2164%% encode opt/val REVERSED since options are stored in reverse order
2165%% i.e. the recent options first (we must process old -> new)
2166encode_opt_val(Opts) ->
2167    try
2168	{ok, enc_opt_val(Opts, [])}
2169    catch
2170	throw:Reason -> {error,Reason}
2171    end.
2172
2173%% {active, once} and {active, N} are specially optimized because they will
2174%% be used for every packet or every N packets, not only once when
2175%% initializing the socket.  Measurements show that this optimization is
2176%% worthwhile.
2177enc_opt_val([{active,once}|Opts], Acc) ->
2178    enc_opt_val(Opts, [<<?INET_LOPT_ACTIVE:8,?INET_ONCE:32>>|Acc]);
2179enc_opt_val([{active,N}|Opts], Acc) when is_integer(N), N < 32768, N >= -32768 ->
2180    enc_opt_val(Opts, [<<?INET_LOPT_ACTIVE:8,?INET_MULTI:32,N:16>>|Acc]);
2181enc_opt_val([{raw,P,O,B}|Opts], Acc) ->
2182    enc_opt_val(Opts, Acc, raw, {P,O,B});
2183enc_opt_val([{Opt,Val}|Opts], Acc) ->
2184    enc_opt_val(Opts, Acc, Opt, Val);
2185enc_opt_val([binary|Opts], Acc) ->
2186    enc_opt_val(Opts, Acc, mode, binary);
2187enc_opt_val([list|Opts], Acc) ->
2188    enc_opt_val(Opts, Acc, mode, list);
2189enc_opt_val([_|_], _) ->
2190    throw(einval);
2191enc_opt_val([], Acc) ->
2192    Acc.
2193
2194enc_opt_val(Opts, Acc, Opt, Val) when is_atom(Opt) ->
2195    Type = type_opt(set, Opt),
2196    case type_value(set, Type, Val) of
2197	true ->
2198	    enc_opt_val(Opts, [enc_opt(Opt),enc_value(set, Type, Val)|Acc]);
2199	false ->
2200            throw(einval)
2201    end;
2202enc_opt_val(_, _, _, _) ->
2203    throw(einval).
2204
2205
2206
2207%% Encoding for getopts
2208%%
2209%% "encode_opts" is for "getopt" only, not setopt". But it uses "enc_opt" which
2210%% is common for "getopt" and "setopt":
2211encode_opts(Opts) ->
2212    try enc_opts(Opts) of
2213	Buf -> {ok,Buf}
2214    catch
2215	Error -> {error,Error}
2216    end.
2217
2218% Raw options are a special case, they need to be rewritten to be properly
2219% handled and the types need checking even when querying.
2220enc_opts([{raw,P,O,S}|Opts]) ->
2221    enc_opts(Opts, raw, {P,O,S});
2222enc_opts([{Opt,Val}|Opts]) ->
2223    enc_opts(Opts, Opt, Val);
2224enc_opts([Opt|Opts]) ->
2225    enc_opts(Opts, Opt);
2226enc_opts([]) -> [].
2227
2228enc_opts(Opts, Opt) when is_atom(Opt) ->
2229    Type = type_opt(get, Opt),
2230    case type_value(get, Type) of
2231	true ->
2232	    [enc_opt(Opt),enc_value(get, Type)|enc_opts(Opts)];
2233	false ->
2234	    throw(einval)
2235    end;
2236enc_opts(_, _) ->
2237    throw(einval).
2238
2239enc_opts(Opts, Opt, Val) when is_atom(Opt) ->
2240    Type = type_opt(get, Opt),
2241    case type_value(get, Type, Val) of
2242	true ->
2243	    [enc_opt(Opt),enc_value(get, Type, Val)|enc_opts(Opts)];
2244	false ->
2245	    throw(einval)
2246    end;
2247enc_opts(_, _, _) ->
2248    throw(einval).
2249
2250
2251
2252%% Decoding of raw list data options
2253%%
2254decode_opt_val(Buf) ->
2255    try dec_opt_val(Buf) of
2256	Result -> {ok,Result}
2257    catch
2258	Error  -> {error,Error}
2259    end.
2260
2261dec_opt_val([B|Buf]=BBuf) ->
2262    case dec_opt(B) of
2263	undefined ->
2264	    erlang:error({decode,BBuf});
2265	Opt ->
2266	    Type = type_opt(dec, Opt),
2267	    dec_opt_val(Buf, Opt, Type)
2268    end;
2269dec_opt_val([]) -> [].
2270
2271dec_opt_val(Buf, raw, Type) ->
2272    {{P,O,B},T} = dec_value(Type, Buf),
2273    [{raw,P,O,B}|dec_opt_val(T)];
2274dec_opt_val(Buf, active, Type) ->
2275    case dec_value(Type, Buf) of
2276        {multi,[M0,M1|T]} ->
2277            <<N:16>> = list_to_binary([M0,M1]),
2278            [{active,N}|dec_opt_val(T)];
2279        {Val,T} ->
2280            [{active,Val}|dec_opt_val(T)]
2281    end;
2282dec_opt_val(Buf, Opt, Type) ->
2283    {Val,T} = dec_value(Type, Buf),
2284    [{Opt,Val}|dec_opt_val(T)].
2285
2286
2287
2288%% Pre-processing of options for chgopts
2289%%
2290%% Return list of option requests for getopts
2291%% for all options that containing 'undefined' record fields.
2292%%
2293need_template([{Opt,undefined}=OV|Opts]) when is_atom(Opt) ->
2294    [OV|need_template(Opts)];
2295need_template([{Opt,Val}|Opts]) when is_atom(Opt) ->
2296    case need_template(Val, 2) of
2297	true ->
2298	    [{Opt,undefined}|need_template(Opts)];
2299	false ->
2300	    need_template(Opts)
2301    end;
2302need_template([_|Opts]) ->
2303    need_template(Opts);
2304need_template([]) -> [].
2305%%
2306need_template(T, N) when is_integer(N), N =< tuple_size(T) ->
2307    case element(N, T) of
2308	undefined -> true;
2309	_ ->
2310	    need_template(T, N+1)
2311    end;
2312need_template(_, _) -> false.
2313
2314%% Replace 'undefined' record fields in option values with values
2315%% from template records.
2316%%
2317merge_options([{Opt,undefined}|Opts], [{Opt,_}=T|Templates]) ->
2318    [T|merge_options(Opts, Templates)];
2319merge_options([{Opt,Val}|Opts], [{Opt,Template}|Templates])
2320  when is_atom(Opt), tuple_size(Val) >= 2 ->
2321    Key = element(1, Val),
2322    Size = tuple_size(Val),
2323    if Size =:= tuple_size(Template), Key =:= element(1, Template) ->
2324	    %% is_record(Template, Key)
2325	    [{Opt,list_to_tuple([Key|merge_fields(Val, Template, 2)])}
2326	     |merge_options(Opts, Templates)];
2327       true ->
2328	    throw({merge,Val,Template})
2329    end;
2330merge_options([OptVal|Opts], Templates) ->
2331    [OptVal|merge_options(Opts, Templates)];
2332merge_options([], []) -> [];
2333merge_options(Opts, Templates) ->
2334    throw({merge,Opts,Templates}).
2335
2336merge_fields(Opt, Template, N) when is_integer(N), N =< tuple_size(Opt) ->
2337    case element(N, Opt) of
2338	undefined ->
2339	    [element(N, Template)|merge_fields(Opt, Template, N+1)];
2340	Val ->
2341	    [Val|merge_fields(Opt, Template, N+1)]
2342    end;
2343merge_fields(_, _, _) -> [].
2344
2345%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
2346%%
2347%% handle interface options
2348%%
2349%%
2350%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
2351
2352type_ifopt(addr)      -> sockaddr;
2353type_ifopt(broadaddr) -> sockaddr;
2354type_ifopt(dstaddr)   -> sockaddr;
2355type_ifopt(mtu)       -> int;
2356type_ifopt(netmask)   -> sockaddr;
2357type_ifopt(flags)     ->
2358    {bitenumlist,
2359     [{up, ?INET_IFF_UP},
2360      {down, ?INET_IFF_DOWN},
2361      {broadcast, ?INET_IFF_BROADCAST},
2362      {no_broadcast, ?INET_IFF_NBROADCAST},
2363      {loopback,  ?INET_IFF_LOOPBACK},
2364      {pointtopoint, ?INET_IFF_POINTTOPOINT},
2365      {no_pointtopoint, ?INET_IFF_NPOINTTOPOINT},
2366      {running, ?INET_IFF_RUNNING},
2367      {multicast, ?INET_IFF_MULTICAST}]};
2368type_ifopt(hwaddr)    -> linkaddr;
2369type_ifopt(Opt) when is_atom(Opt) -> undefined.
2370
2371enc_ifopt(addr)      -> ?INET_IFOPT_ADDR;
2372enc_ifopt(broadaddr) -> ?INET_IFOPT_BROADADDR;
2373enc_ifopt(dstaddr)   -> ?INET_IFOPT_DSTADDR;
2374enc_ifopt(mtu)       -> ?INET_IFOPT_MTU;
2375enc_ifopt(netmask)   -> ?INET_IFOPT_NETMASK;
2376enc_ifopt(flags)     -> ?INET_IFOPT_FLAGS;
2377enc_ifopt(hwaddr)    -> ?INET_IFOPT_HWADDR;
2378enc_ifopt(Opt) when is_atom(Opt) -> -1.
2379
2380dec_ifopt(?INET_IFOPT_ADDR)      -> addr;
2381dec_ifopt(?INET_IFOPT_BROADADDR) -> broadaddr;
2382dec_ifopt(?INET_IFOPT_DSTADDR)   -> dstaddr;
2383dec_ifopt(?INET_IFOPT_MTU)       -> mtu;
2384dec_ifopt(?INET_IFOPT_NETMASK)   -> netmask;
2385dec_ifopt(?INET_IFOPT_FLAGS)     -> flags;
2386dec_ifopt(?INET_IFOPT_HWADDR)    -> hwaddr;
2387dec_ifopt(I) when is_integer(I)  -> undefined.
2388
2389%% decode if options returns a reversed list
2390decode_ifopts([B | Buf], Acc) ->
2391    case dec_ifopt(B) of
2392	undefined ->
2393	    {error, einval};
2394	Opt ->
2395	    {Val,T} = dec_value(type_ifopt(Opt), Buf),
2396	    decode_ifopts(T, [{Opt,Val} | Acc])
2397    end;
2398decode_ifopts(_,Acc) -> {ok,Acc}.
2399
2400
2401%% encode if options return a reverse list
2402encode_ifopts([Opt|Opts], Acc) ->
2403    case enc_ifopt(Opt) of
2404	-1 -> {error,einval};
2405	B  -> encode_ifopts(Opts,[B|Acc])
2406    end;
2407encode_ifopts([],Acc) -> {ok,Acc}.
2408
2409
2410%% encode if options return a reverse list
2411encode_ifopt_val([{Opt,Val}|Opts], Buf) ->
2412    Type = type_ifopt(Opt),
2413    try type_value(set, Type, Val) of
2414	true ->
2415	    encode_ifopt_val(Opts,
2416			     [Buf,enc_ifopt(Opt),enc_value(set, Type, Val)]);
2417	false -> {error,einval}
2418    catch
2419	Reason -> {error,Reason}
2420    end;
2421encode_ifopt_val([], Buf) -> {ok,Buf}.
2422
2423
2424%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
2425%%
2426%% handle subscribe options
2427%%
2428%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
2429
2430encode_subs(L) ->
2431    try enc_subs(L) of
2432	Result -> {ok,Result}
2433    catch
2434	Error  -> {error,Error}
2435    end.
2436
2437enc_subs([H|T]) ->
2438    case H of
2439	subs_empty_out_q -> [?INET_SUBS_EMPTY_OUT_Q|enc_subs(T)]%;
2440	%%Dialyzer _ -> throw(einval)
2441    end;
2442enc_subs([]) -> [].
2443
2444
2445decode_subs(Bytes) ->
2446    try dec_subs(Bytes) of
2447	Result -> {ok,Result}
2448    catch
2449	Error  -> {error,Error}
2450    end.
2451
2452dec_subs([X,X3,X2,X1,X0|R]) ->
2453    Val = ?u32(X3,X2,X1,X0),
2454    case X of
2455	?INET_SUBS_EMPTY_OUT_Q  -> [{subs_empty_out_q,Val}|dec_subs(R)];
2456	_  -> throw(einval)
2457    end;
2458dec_subs([]) -> [].
2459
2460%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
2461%%
2462%% handle statictics options
2463%%
2464%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
2465
2466encode_stats(L) ->
2467    try enc_stats(L) of
2468	Result -> {ok,Result}
2469    catch
2470	Error  -> {error,Error}
2471    end.
2472
2473enc_stats([H|T]) ->
2474    case H of
2475	recv_cnt  -> [?INET_STAT_RECV_CNT |enc_stats(T)];
2476	recv_max  -> [?INET_STAT_RECV_MAX |enc_stats(T)];
2477	recv_avg  -> [?INET_STAT_RECV_AVG |enc_stats(T)];
2478	recv_dvi  -> [?INET_STAT_RECV_DVI |enc_stats(T)];
2479	send_cnt  -> [?INET_STAT_SEND_CNT |enc_stats(T)];
2480	send_max  -> [?INET_STAT_SEND_MAX |enc_stats(T)];
2481	send_avg  -> [?INET_STAT_SEND_AVG |enc_stats(T)];
2482	send_pend -> [?INET_STAT_SEND_PEND|enc_stats(T)];
2483	send_oct  -> [?INET_STAT_SEND_OCT |enc_stats(T)];
2484	recv_oct  -> [?INET_STAT_RECV_OCT |enc_stats(T)];
2485	_ -> throw(einval)
2486    end;
2487enc_stats([]) -> [].
2488
2489
2490decode_stats(Bytes) ->
2491    try dec_stats(Bytes) of
2492	Result -> {ok,Result}
2493    catch
2494	Error  -> {error,Error}
2495    end.
2496
2497
2498dec_stats([?INET_STAT_SEND_OCT,X7,X6,X5,X4,X3,X2,X1,X0|R]) ->
2499    Val = ?u64(X7,X6,X5,X4,X3,X2,X1,X0),
2500    [{send_oct, Val}|dec_stats(R)];
2501dec_stats([?INET_STAT_RECV_OCT,X7,X6,X5,X4,X3,X2,X1,X0|R]) ->
2502    Val = ?u64(X7,X6,X5,X4,X3,X2,X1,X0),
2503    [{recv_oct, Val}|dec_stats(R)];
2504dec_stats([X,X3,X2,X1,X0|R]) ->
2505    Val = ?u32(X3,X2,X1,X0),
2506    case X of
2507	?INET_STAT_RECV_CNT  -> [{recv_cnt,Val} |dec_stats(R)];
2508	?INET_STAT_RECV_MAX  -> [{recv_max,Val} |dec_stats(R)];
2509	?INET_STAT_RECV_AVG  -> [{recv_avg,Val} |dec_stats(R)];
2510	?INET_STAT_RECV_DVI  -> [{recv_dvi,Val} |dec_stats(R)];
2511	?INET_STAT_SEND_CNT  -> [{send_cnt,Val} |dec_stats(R)];
2512	?INET_STAT_SEND_MAX  -> [{send_max,Val} |dec_stats(R)];
2513	?INET_STAT_SEND_AVG  -> [{send_avg,Val} |dec_stats(R)];
2514	?INET_STAT_SEND_PEND -> [{send_pend,Val}|dec_stats(R)];
2515	_  -> throw(einval)
2516    end;
2517dec_stats([]) -> [].
2518
2519%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
2520%%
2521%% handle status options
2522%%
2523%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
2524
2525dec_status(Flags) ->
2526    enum_names(Flags,
2527	       [
2528		{busy, ?INET_F_BUSY},
2529		%% {listening, ?INET_F_LST}, NOT USED ANY MORE
2530		{accepting, ?INET_F_ACC},
2531		{connecting, ?INET_F_CON},
2532		{listen, ?INET_F_LISTEN},
2533		{connected, ?INET_F_ACTIVE},
2534		{bound, ?INET_F_BOUND},
2535		{open, ?INET_F_OPEN}
2536	       ]).
2537
2538%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
2539%%
2540%% UTILS
2541%%
2542%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
2543
2544enc_time(Time) when Time < 0 -> [255,255,255,255];
2545enc_time(Time) -> ?int32(Time).
2546
2547encode_ifname(Name) when is_atom(Name) -> encode_ifname(atom_to_list(Name));
2548encode_ifname(Name) ->
2549    N = length(Name),
2550    if N > 255 -> {error, einval};
2551       true -> {ok,[N | Name]}
2552    end.
2553
2554build_ifaddrs(Cs) ->
2555    build_ifaddrs(Cs, []).
2556%%
2557build_ifaddrs([], []) ->
2558    [];
2559build_ifaddrs([0|Cs], Acc) ->
2560    Name = utf8_to_characters(rev(Acc)),
2561    {Opts,Rest} = build_ifaddrs_opts(Cs, []),
2562    [{Name,Opts}|build_ifaddrs(Rest)];
2563build_ifaddrs([C|Cs], Acc) ->
2564    build_ifaddrs(Cs, [C|Acc]).
2565
2566build_ifaddrs_opts([0|Cs], Acc) ->
2567    {rev(Acc),Cs};
2568build_ifaddrs_opts([C|Cs]=CCs, Acc) ->
2569    case dec_ifopt(C) of
2570	undefined ->
2571	    erlang:error(badarg, [CCs,Acc]);
2572	Opt ->
2573	    Type = type_ifopt(Opt),
2574	    {Val,Rest} = dec_value(Type, Cs),
2575	    build_ifaddrs_opts(Rest, [{Opt,Val}|Acc])
2576    end.
2577
2578build_iflist(Cs) ->
2579    build_iflist(Cs, [], []).
2580
2581%% Turn a NULL separated list of chars into a list of strings, removing
2582%% duplicates.
2583build_iflist([0|L], Acc, [H|T]) ->
2584    case rev(Acc) of
2585	H -> build_iflist(L, [], [H|T]);
2586	N -> build_iflist(L, [], [N,H|T])
2587    end;
2588build_iflist([0|L], Acc, []) ->
2589    build_iflist(L, [], [rev(Acc)]);
2590build_iflist([C|L], Acc, List) ->
2591    build_iflist(L, [C|Acc], List);
2592build_iflist([], [], List) ->
2593    rev(List);
2594build_iflist([], Acc, List) ->
2595    build_iflist([0], Acc, List).
2596
2597rev(L) -> rev(L,[]).
2598rev([C|L],Acc) -> rev(L,[C|Acc]);
2599rev([],Acc) -> Acc.
2600
2601split(N, L) -> split(N, L, []).
2602split(0, L, R) when is_list(L) -> {rev(R),L};
2603split(N, [H|T], R) when is_integer(N), N > 0 -> split(N-1, T, [H|R]).
2604
2605len(L, N) -> len(L, N, 0).
2606len([], N, C) when is_integer(N), N >= 0 -> C;
2607len(L, 0, _) when is_list(L) -> undefined;
2608len([_|L], N, C) when is_integer(N), N >= 0 -> len(L, N-1, C+1).
2609
2610member(X, [X|_]) -> true;
2611member(X, [_|Xs]) -> member(X, Xs);
2612member(_, []) -> false.
2613
2614
2615
2616%% Lookup tree that keeps key insert order
2617
2618ktree_empty() -> {[],tree()}.
2619ktree_is_defined(Key, {_,T}) -> tree(T, Key, is_defined).
2620ktree_get(Key, {_,T}) -> tree(T, Key, get).
2621ktree_insert(Key, V, {Keys,T}) -> {[Key|Keys],tree(T, Key, {insert,V})}.
2622ktree_update(Key, V, {Keys,T}) -> {Keys,tree(T, Key, {update,V})}.
2623ktree_keys({Keys,_}) -> rev(Keys).
2624
2625%% Simple lookup tree. Hash the key to get statistical balance.
2626%% Key is matched equal, not compared equal.
2627
2628tree() -> nil.
2629tree(T, Key, Op) -> tree(T, Key, Op, erlang:phash2(Key)).
2630
2631tree(nil, _, is_defined, _) -> false;
2632tree(nil, K, {insert,V}, _) -> {K,V,nil,nil};
2633tree({K,_,_,_}, K, is_defined, _) -> true;
2634tree({K,V,_,_}, K, get, _) -> V;
2635tree({K,_,L,R}, K, {update,V}, _) -> {K,V,L,R};
2636tree({K0,V0,L,R}, K, Op, H) ->
2637    H0 = erlang:phash2(K0),
2638    if  H0 < H;  H0 =:= H, K0 < K ->
2639	    if  is_tuple(Op) ->
2640		    {K0,V0,tree(L, K, Op, H),R};
2641		true ->
2642		    tree(L, K, Op, H)
2643	    end;
2644	true ->
2645	    if  is_tuple(Op) ->
2646		    {K0,V0,L,tree(R, K, Op, H)};
2647		true ->
2648		    tree(R, K, Op, H)
2649	    end
2650    end.
2651
2652
2653
2654utf8_to_characters([]) -> [];
2655utf8_to_characters([B|Bs]=Arg) when (B band 16#FF) =:= B ->
2656    if  16#F8 =< B ->
2657	    erlang:error(badarg, [Arg]);
2658	16#F0 =< B ->
2659	    utf8_to_characters(Bs, B band 16#07, 3);
2660	16#E0 =< B ->
2661	    utf8_to_characters(Bs, B band 16#0F, 2);
2662	16#C0 =< B ->
2663	    utf8_to_characters(Bs, B band 16#1F, 1);
2664	16#80 =< B ->
2665	    erlang:error(badarg, [Arg]);
2666	true ->
2667	    [B|utf8_to_characters(Bs)]
2668    end.
2669%%
2670utf8_to_characters(Bs, U, 0) ->
2671    [U|utf8_to_characters(Bs)];
2672utf8_to_characters([B|Bs], U, N) when ((B band 16#3F) bor 16#80) =:= B ->
2673    utf8_to_characters(Bs, (U bsl 6) bor (B band 16#3F), N-1).
2674
2675ip4_to_bytes({A,B,C,D}) ->
2676    [A band 16#ff, B band 16#ff, C band 16#ff, D band 16#ff].
2677
2678ip6_to_bytes({A,B,C,D,E,F,G,H}) ->
2679    [?int16(A), ?int16(B), ?int16(C), ?int16(D),
2680     ?int16(E), ?int16(F), ?int16(G), ?int16(H)].
2681
2682get_addrs([]) ->
2683    [];
2684get_addrs([F|Addrs]) ->
2685    {Addr,Rest} = get_addr(F, Addrs),
2686    [Addr|get_addrs(Rest)].
2687
2688get_addr(?INET_AF_LOCAL, [N|Addr]) ->
2689    {A,Rest} = split(N, Addr),
2690    {{local,iolist_to_binary(A)},Rest};
2691get_addr(?INET_AF_UNSPEC, Rest) ->
2692    {{unspec,<<>>},Rest};
2693get_addr(?INET_AF_UNDEFINED, Rest) ->
2694    {{undefined,<<>>},Rest};
2695get_addr(Family, [P1,P0|Addr]) ->
2696    {IP,Rest} = get_ip(Family, Addr),
2697    {{IP,?u16(P1, P0)},Rest}.
2698
2699get_ip(?INET_AF_INET, Addr) ->
2700    get_ip4(Addr);
2701get_ip(?INET_AF_INET6, Addr) ->
2702    get_ip6(Addr).
2703
2704get_ip4([A,B,C,D | T]) -> {{A,B,C,D},T}.
2705
2706get_ip6([X1,X2,X3,X4,X5,X6,X7,X8,X9,X10,X11,X12,X13,X14,X15,X16 | T]) ->
2707    { { ?u16(X1,X2),?u16(X3,X4),?u16(X5,X6),?u16(X7,X8),
2708	?u16(X9,X10),?u16(X11,X12),?u16(X13,X14),?u16(X15,X16)},
2709      T }.
2710
2711-define(ERTS_INET_DRV_CONTROL_MAGIC_NUMBER, 16#03f1a300).
2712
2713%% Control command
2714ctl_cmd(Port, Cmd, Args) ->
2715    ?DBG_FORMAT("prim_inet:ctl_cmd(~p, ~p, ~p)~n", [Port,Cmd,Args]),
2716    Result =
2717	try erlang:port_control(Port, Cmd+?ERTS_INET_DRV_CONTROL_MAGIC_NUMBER, Args) of
2718	    [?INET_REP_OK|Reply]  -> {ok,Reply};
2719	    [?INET_REP]  -> inet_reply;
2720	    [?INET_REP_ERROR|Err] -> {error,list_to_atom(Err)}
2721	catch
2722	    error:_               -> {error,einval}
2723	end,
2724        ?DBG_FORMAT("prim_inet:ctl_cmd() -> ~p~n", [Result]),
2725    Result.
2726