~clint-fewbar/ubuntu/precise/erlang/merge-15b

« back to all changes in this revision

Viewing changes to erts/preloaded/src/prim_inet.erl

  • Committer: Package Import Robot
  • Author(s): Sergei Golovan
  • Date: 2011-12-15 19:20:10 UTC
  • mfrom: (1.1.18) (3.5.15 sid)
  • mto: (3.5.16 sid)
  • mto: This revision was merged to the branch mainline in revision 33.
  • Revision ID: package-import@ubuntu.com-20111215192010-jnxcfe3tbrpp0big
Tags: 1:15.b-dfsg-1
* New upstream release.
* Upload to experimental because this release breaks external drivers
  API along with ABI, so several applications are to be fixed.
* Removed SSL patch because the old SSL implementation is removed from
  the upstream distribution.
* Removed never used patch which added native code to erlang beam files.
* Removed the erlang-docbuilder binary package because the docbuilder
  application was dropped by upstream.
* Documented dropping ${erlang-docbuilder:Depends} substvar in
  erlang-depends(1) manpage.
* Made erlang-base and erlang-base-hipe provide virtual package
  erlang-abi-15.b (the number means the first erlang version, which
  provides current ABI).

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%%
2
2
%% %CopyrightBegin%
3
3
%% 
4
 
%% Copyright Ericsson AB 2000-2010. All Rights Reserved.
 
4
%% Copyright Ericsson AB 2000-2011. All Rights Reserved.
5
5
%% 
6
6
%% The contents of this file are subject to the Erlang Public License,
7
7
%% Version 1.1, (the "License"); you may not use this file except in
25
25
 
26
26
%% Primitive inet_drv interface
27
27
 
28
 
-export([open/1, open/2, fdopen/2, fdopen/3, close/1]).
29
 
-export([bind/3, listen/1, listen/2]). 
 
28
-export([open/3, fdopen/4, close/1]).
 
29
-export([bind/3, listen/1, listen/2, peeloff/2]).
30
30
-export([connect/3, connect/4, async_connect/4]).
31
31
-export([accept/1, accept/2, async_accept/2]).
32
32
-export([shutdown/2]).
36
36
-export([recvfrom/2, recvfrom/3]).
37
37
-export([setopt/3, setopts/2, getopt/2, getopts/2, is_sockopt_val/2]).
38
38
-export([chgopt/3, chgopts/2]).
39
 
-export([getstat/2, getfd/1, getindex/1, getstatus/1, gettype/1, 
 
39
-export([getstat/2, getfd/1, ignorefd/2,
 
40
         getindex/1, getstatus/1, gettype/1,
40
41
         getifaddrs/1, getiflist/1, ifget/3, ifset/3,
41
42
         gethostname/1]).
42
43
-export([getservbyname/3, getservbyport/3]).
56
57
 
57
58
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
58
59
%%
59
 
%% OPEN(tcp | udp | sctp, inet | inet6)  ->
 
60
%% OPEN(tcp | udp | sctp, inet | inet6, stream | dgram | seqpacket)  ->
60
61
%%       {ok, insock()} |
61
62
%%       {error, Reason}
62
63
%%
63
64
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
64
65
 
65
 
open(Protocol)          -> open1(Protocol, ?INET_AF_INET).
66
 
 
67
 
open(Protocol,   inet)  -> open1(Protocol, ?INET_AF_INET);
68
 
open(Protocol,  inet6)  -> open1(Protocol, ?INET_AF_INET6);
69
 
open(_, _)              -> {error, einval}.
70
 
 
71
 
fdopen(Protocol, Fd)        -> fdopen1(Protocol, ?INET_AF_INET, Fd).
72
 
 
73
 
fdopen(Protocol, Fd, inet)  -> fdopen1(Protocol, ?INET_AF_INET, Fd);
74
 
fdopen(Protocol, Fd, inet6) -> fdopen1(Protocol, ?INET_AF_INET6, Fd);
75
 
fdopen(_, _, _)             -> {error, einval}.
76
 
 
77
 
open1(Protocol, Family) ->
78
 
    case open0(Protocol) of
79
 
        {ok, S} ->
80
 
            case ctl_cmd(S, ?INET_REQ_OPEN, [Family]) of
81
 
                {ok, _} ->
82
 
                    {ok,S};
83
 
                Error ->
84
 
                    close(S), Error
85
 
            end;
86
 
        Error -> Error
87
 
    end.
88
 
 
89
 
fdopen1(Protocol, Family, Fd) when is_integer(Fd) ->
90
 
    case open0(Protocol) of
91
 
        {ok, S} ->
92
 
            case ctl_cmd(S,?INET_REQ_FDOPEN,[Family,?int32(Fd)]) of
93
 
                {ok, _} -> {ok,S};
94
 
                Error -> close(S), Error
95
 
            end;
96
 
        Error -> Error
97
 
    end.
98
 
 
99
 
open0(Protocol) ->
100
 
    try erlang:open_port({spawn_driver,protocol2drv(Protocol)}, [binary]) of
101
 
        Port -> {ok,Port}
 
66
open(Protocol, Family, Type) ->
 
67
    open(Protocol, Family, Type, ?INET_REQ_OPEN, []).
 
68
 
 
69
fdopen(Protocol, Family, Type, Fd) when is_integer(Fd) ->
 
70
    open(Protocol, Family, Type, ?INET_REQ_FDOPEN, ?int32(Fd)).
 
71
 
 
72
open(Protocol, Family, Type, Req, Data) ->
 
73
    Drv = protocol2drv(Protocol),
 
74
    AF = enc_family(Family),
 
75
    T = enc_type(Type),
 
76
    try erlang:open_port({spawn_driver,Drv}, [binary]) of
 
77
        S ->
 
78
            case ctl_cmd(S, Req, [AF,T,Data]) of
 
79
                {ok,_} -> {ok,S};
 
80
                {error,_}=Error ->
 
81
                    close(S),
 
82
                    Error
 
83
            end
102
84
    catch
103
 
        error:Reason -> {error,Reason}
 
85
        %% The only (?) way to get here is to try to open
 
86
        %% the sctp driver when it does not exist
 
87
        error:badarg -> {error,eprotonosupport}
104
88
    end.
105
89
 
 
90
enc_family(inet) -> ?INET_AF_INET;
 
91
enc_family(inet6) -> ?INET_AF_INET6.
 
92
 
 
93
enc_type(stream) -> ?INET_TYPE_STREAM;
 
94
enc_type(dgram) -> ?INET_TYPE_DGRAM;
 
95
enc_type(seqpacket) -> ?INET_TYPE_SEQPACKET.
 
96
 
106
97
protocol2drv(tcp)  -> "tcp_inet";
107
98
protocol2drv(udp)  -> "udp_inet";
108
 
protocol2drv(sctp) -> "sctp_inet";
109
 
protocol2drv(_) ->
110
 
    erlang:error(eprotonosupport).
 
99
protocol2drv(sctp) -> "sctp_inet".
111
100
 
112
101
drv2protocol("tcp_inet")  -> tcp;
113
102
drv2protocol("udp_inet")  -> udp;
139
128
shutdown_2(S, How) ->
140
129
    case ctl_cmd(S, ?TCP_REQ_SHUTDOWN, [How]) of
141
130
        {ok, []} -> ok;
142
 
        Error -> Error
 
131
        {error,_}=Error -> Error
143
132
    end.
144
133
 
145
134
shutdown_pend_loop(S, N0) ->
195
184
bind(S,IP,Port) when is_port(S), is_integer(Port), Port >= 0, Port =< 65535 ->
196
185
    case ctl_cmd(S,?INET_REQ_BIND,[?int16(Port),ip_to_bytes(IP)]) of
197
186
        {ok, [P1,P0]} -> {ok, ?u16(P1, P0)};
198
 
        Error -> Error
 
187
        {error,_}=Error -> Error
199
188
    end;
200
189
 
201
190
%% Multi-homed "bind": sctp_bindx(). The Op is 'add' or 'remove'.
222
211
                     {IP, Port} <- Addrs]],
223
212
            case ctl_cmd(S, ?SCTP_REQ_BINDX, Args) of
224
213
                {ok,_} -> {ok, S};
225
 
                Error  -> Error
 
214
                {error,_}=Error  -> Error
226
215
            end;
227
216
        _ -> {error, einval}
228
217
    end.
265
254
    case ctl_cmd(S, ?INET_REQ_CONNECT,
266
255
                 [enc_time(Time),?int16(Port),ip_to_bytes(IP)]) of
267
256
        {ok, [R1,R0]} -> {ok, S, ?u16(R1,R0)};
268
 
        Error -> Error
 
257
        {error,_}=Error -> Error
269
258
    end.
270
259
 
271
260
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
318
307
    end.
319
308
 
320
309
async_accept(L, Time) ->
321
 
    case ctl_cmd(L,?TCP_REQ_ACCEPT, [enc_time(Time)]) of
 
310
    case ctl_cmd(L,?INET_REQ_ACCEPT, [enc_time(Time)]) of
322
311
        {ok, [R1,R0]} -> {ok, ?u16(R1,R0)};
323
 
        Error -> Error
 
312
        {error,_}=Error -> Error
324
313
    end.
325
314
 
326
315
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
334
323
%% listening) is also accepted:
335
324
 
336
325
listen(S) -> listen(S, ?LISTEN_BACKLOG).
337
 
    
 
326
 
 
327
listen(S, true) -> listen(S, ?LISTEN_BACKLOG);
 
328
listen(S, false) -> listen(S, 0);
338
329
listen(S, BackLog) when is_port(S), is_integer(BackLog) ->
339
 
    case ctl_cmd(S, ?TCP_REQ_LISTEN, [?int16(BackLog)]) of
 
330
    case ctl_cmd(S, ?INET_REQ_LISTEN, [?int16(BackLog)]) of
340
331
        {ok, _} -> ok;
341
 
        Error   -> Error
342
 
    end;
343
 
listen(S, Flag)   when is_port(S), is_boolean(Flag) ->
344
 
    case ctl_cmd(S, ?SCTP_REQ_LISTEN, enc_value(set, bool8, Flag)) of
345
 
        {ok,_} -> ok;
346
 
        Error -> Error
 
332
        {error,_}=Error   -> Error
 
333
    end.
 
334
 
 
335
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
336
%%
 
337
%% PEELOFF(insock(), AssocId) -> {ok,outsock()} | {error, Reason}
 
338
%%
 
339
%% SCTP: Peel off one association into a type stream socket
 
340
%%
 
341
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
342
 
 
343
peeloff(S, AssocId) ->
 
344
    case ctl_cmd(S, ?SCTP_REQ_PEELOFF, [?int32(AssocId)]) of
 
345
        inet_reply ->
 
346
            receive
 
347
                {inet_reply,S,Res} -> Res
 
348
            end;
 
349
        {error,_}=Error -> Error
347
350
    end.
348
351
 
349
352
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
395
398
        true -> 
396
399
            receive
397
400
                {inet_reply,S,Reply} ->
398
 
                    ?DBG_FORMAT("prim_inet:send() -> ~p~n", [Reply]),
 
401
                    ?DBG_FORMAT("prim_inet:sendto() -> ~p~n", [Reply]),
399
402
                     Reply
400
403
            end
401
404
    catch
402
405
        error:_ ->
403
 
            ?DBG_FORMAT("prim_inet:send() -> {error,einval}~n", []),
 
406
            ?DBG_FORMAT("prim_inet:sendto() -> {error,einval}~n", []),
404
407
             {error,einval}
405
408
    end.
406
409
 
455
458
async_recv(S, Length, Time) ->
456
459
    case ctl_cmd(S, ?TCP_REQ_RECV, [enc_time(Time), ?int32(Length)]) of
457
460
        {ok,[R1,R0]} -> {ok, ?u16(R1,R0)};
458
 
        Error -> Error
 
461
        {error,_}=Error -> Error
459
462
    end.            
460
463
 
461
464
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
501
504
                {inet_async, S, Ref, Error={error, _}} ->
502
505
                    Error
503
506
            end;
504
 
        Error ->
 
507
        {error,_}=Error ->
505
508
            Error % Front-end error
506
509
    end;
507
510
recvfrom0(_, _, _) -> {error,einval}.
517
520
        {ok, [F, P1,P0 | Addr]} ->
518
521
            {IP, _} = get_ip(F, Addr),
519
522
            {ok, { IP, ?u16(P1, P0) }};
520
 
        Error -> Error
 
523
        {error,_}=Error -> Error
521
524
    end.
522
525
 
523
526
setpeername(S, {IP,Port}) when is_port(S) ->
524
527
    case ctl_cmd(S, ?INET_REQ_SETPEER, [?int16(Port),ip_to_bytes(IP)]) of
525
528
        {ok,[]} -> ok;
526
 
        Error -> Error
 
529
        {error,_}=Error -> Error
527
530
    end;
528
531
setpeername(S, undefined) when is_port(S) ->
529
532
    case ctl_cmd(S, ?INET_REQ_SETPEER, []) of
530
533
        {ok,[]} -> ok;
531
 
        Error -> Error
 
534
        {error,_}=Error -> Error
532
535
    end.
533
536
 
534
537
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
542
545
        {ok, [F, P1, P0 | Addr]} ->
543
546
            {IP, _} = get_ip(F, Addr),
544
547
            {ok, { IP, ?u16(P1, P0) }};
545
 
        Error -> Error
 
548
        {error,_}=Error -> Error
546
549
    end.
547
550
 
548
551
setsockname(S, {IP,Port}) when is_port(S) ->
549
552
    case ctl_cmd(S, ?INET_REQ_SETNAME, [?int16(Port),ip_to_bytes(IP)]) of
550
553
        {ok,[]} -> ok;
551
 
        Error -> Error
 
554
        {error,_}=Error -> Error
552
555
    end;
553
556
setsockname(S, undefined) when is_port(S) ->
554
557
    case ctl_cmd(S, ?INET_REQ_SETNAME, []) of
555
558
        {ok,[]} -> ok;
556
 
        Error -> Error
 
559
        {error,_}=Error -> Error
557
560
    end.
558
561
 
559
562
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
573
576
        {ok, Buf} ->
574
577
            case ctl_cmd(S, ?INET_REQ_SETOPTS, Buf) of
575
578
                {ok, _} -> ok;
576
 
                Error -> Error
 
579
                {error,_}=Error -> Error
577
580
            end;
578
581
        Error  -> Error
579
582
    end.            
599
602
                {ok,Rep} ->
600
603
                    %% Non-SCTP: "Rep" contains the encoded option vals:
601
604
                    decode_opt_val(Rep);
602
 
                {error,sctp_reply} ->
 
605
                inet_reply ->
603
606
                    %% SCTP: Need to receive the full value:
604
607
                    receive
605
608
                        {inet_reply,S,Res} -> Res
606
609
                    end;
607
 
                Error -> Error
 
610
                {error,_}=Error -> Error
608
611
            end;
609
612
        Error -> Error
610
613
    end.
733
736
getiflist(S) when is_port(S) ->
734
737
    case ctl_cmd(S, ?INET_REQ_GETIFLIST, []) of
735
738
        {ok, Data} -> {ok, build_iflist(Data)};
736
 
        Error -> Error
 
739
        {error,_}=Error -> Error
737
740
    end.
738
741
 
739
742
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
751
754
                {ok, Buf2} ->
752
755
                    case ctl_cmd(S, ?INET_REQ_IFGET, [Buf1,Buf2]) of
753
756
                        {ok, Data} -> decode_ifopts(Data,[]);
754
 
                        Error -> Error
 
757
                        {error,_}=Error -> Error
755
758
                    end;
756
759
                Error -> Error
757
760
            end;
773
776
                {ok, Buf2} ->
774
777
                    case ctl_cmd(S, ?INET_REQ_IFSET, [Buf1,Buf2]) of
775
778
                        {ok, _} -> ok;
776
 
                        Error -> Error
 
779
                        {error,_}=Error -> Error
777
780
                    end;
778
781
                Error -> Error
779
782
            end;
801
804
        {ok, Bytes} ->
802
805
            case ctl_cmd(S, ?INET_REQ_SUBSCRIBE, Bytes) of
803
806
                {ok, Data} -> decode_subs(Data);
804
 
                Error -> Error
 
807
                {error,_}=Error -> Error
805
808
            end;
806
809
        Error -> Error
807
810
    end.
819
822
        {ok, Bytes} ->
820
823
            case ctl_cmd(S, ?INET_REQ_GETSTAT, Bytes) of
821
824
                {ok, Data} -> decode_stats(Data);
822
 
                Error -> Error
 
825
                {error,_}=Error -> Error
823
826
            end;
824
827
        Error -> Error
825
828
    end.
835
838
getfd(S) when is_port(S) ->
836
839
    case ctl_cmd(S, ?INET_REQ_GETFD, []) of
837
840
        {ok, [S3,S2,S1,S0]} -> {ok, ?u32(S3,S2,S1,S0)};
838
 
        Error -> Error
 
841
        {error,_}=Error -> Error
839
842
    end.        
840
843
 
841
844
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
842
845
%%
 
846
%% IGNOREFD(insock(),boolean()) -> {ok,integer()} | {error, Reason}
 
847
%%
 
848
%% steal internal file descriptor
 
849
%%
 
850
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
851
 
 
852
ignorefd(S,Bool) when is_port(S) ->
 
853
    Val = if Bool -> 1; true -> 0 end,
 
854
    case ctl_cmd(S, ?INET_REQ_IGNOREFD, [Val]) of
 
855
        {ok, _} -> ok;
 
856
        Error -> Error
 
857
    end.
 
858
 
 
859
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
860
%%
843
861
%% GETIX(insock()) -> {ok,integer()} | {error, Reason}
844
862
%%
845
863
%% get internal socket index
873
891
                        _                    -> undefined
874
892
                   end,
875
893
            {ok, {Family, Type}};
876
 
        Error -> Error
 
894
        {error,_}=Error -> Error
877
895
    end.
878
896
 
879
897
getprotocol(S) when is_port(S) ->
901
919
    case ctl_cmd(S, ?INET_REQ_GETSTATUS, []) of
902
920
        {ok, [S3,S2,S1,S0]} ->  
903
921
            {ok, dec_status(?u32(S3,S2,S1,S0))};
904
 
        Error -> Error
 
922
        {error,_}=Error -> Error
905
923
    end.
906
924
 
907
925
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
943
961
            case ctl_cmd(S, ?INET_REQ_GETSERVBYNAME, [L1,Name,L2,Proto]) of
944
962
                {ok, [P1,P0]} ->
945
963
                    {ok, ?u16(P1,P0)};
946
 
                Error -> 
 
964
                {error,_}=Error ->
947
965
                    Error
948
966
            end
949
967
    end.
971
989
       true ->
972
990
            case ctl_cmd(S, ?INET_REQ_GETSERVBYPORT, [?int16(Port),L,Proto]) of
973
991
                {ok, Name} -> {ok, Name};
974
 
                Error -> Error
 
992
                {error,_}=Error -> Error
975
993
            end
976
994
    end.
977
995
 
985
1003
unrecv(S, Data) ->
986
1004
    case ctl_cmd(S, ?TCP_REQ_UNRECV, Data) of
987
1005
        {ok, _} -> ok;
988
 
        Error  -> Error
 
1006
        {error,_}=Error  -> Error
989
1007
    end.
990
1008
 
991
1009
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1518
1536
    [?INET_AF_INET,?int16(Port)|ip4_to_bytes(IP)];
1519
1537
enc_value_2(addr, {IP,Port}) when tuple_size(IP) =:= 8 ->
1520
1538
    [?INET_AF_INET6,?int16(Port)|ip6_to_bytes(IP)];
1521
 
enc_value_2(ether, [X1,X2,X3,X4,X5,X6]) -> [X1,X2,X3,X4,X5,X6];
 
1539
enc_value_2(ether, [_,_,_,_,_,_]=Xs) -> Xs;
1522
1540
enc_value_2(sockaddr, any) ->
1523
1541
    [?INET_AF_ANY];
1524
1542
enc_value_2(sockaddr, loopback) ->
1572
1590
        Val -> {Val, T}
1573
1591
    end;
1574
1592
dec_value(ip, [A,B,C,D|T])             -> {{A,B,C,D}, T};
1575
 
dec_value(ether,[X1,X2,X3,X4,X5,X6|T]) -> {[X1,X2,X3,X4,X5,X6],T};
 
1593
%% dec_value(ether, [X1,X2,X3,X4,X5,X6|T]) -> {[X1,X2,X3,X4,X5,X6],T};
1576
1594
dec_value(sockaddr, [X|T]) ->
1577
1595
    get_ip(X, T);
1578
1596
dec_value(linkaddr, [X1,X0|T]) ->
2163
2181
    Result =
2164
2182
        try erlang:port_control(Port, Cmd, Args) of
2165
2183
            [?INET_REP_OK|Reply]  -> {ok,Reply};
2166
 
            [?INET_REP_SCTP]  -> {error,sctp_reply};
 
2184
            [?INET_REP]  -> inet_reply;
2167
2185
            [?INET_REP_ERROR|Err] -> {error,list_to_atom(Err)}
2168
2186
        catch
2169
2187
            error:_               -> {error,einval}