~ubuntu-branches/debian/squeeze/erlang/squeeze

« back to all changes in this revision

Viewing changes to lib/kernel/src/prim_inet.erl

  • Committer: Bazaar Package Importer
  • Author(s): Erlang Packagers, Sergei Golovan
  • Date: 2006-12-03 17:07:44 UTC
  • mfrom: (2.1.11 feisty)
  • Revision ID: james.westby@ubuntu.com-20061203170744-rghjwupacqlzs6kv
Tags: 1:11.b.2-4
[ Sergei Golovan ]
Fixed erlang-base and erlang-base-hipe prerm scripts.

Show diffs side-by-side

added added

removed removed

Lines of Context:
19
19
 
20
20
%% Primitive inet_drv interface
21
21
 
22
 
 
23
22
-export([open/1, open/2, fdopen/2, fdopen/3, close/1]).
24
23
-export([bind/3, listen/1, listen/2]). 
25
24
-export([connect/3, connect/4, async_connect/4]).
214
213
        Error -> Error
215
214
    end.
216
215
 
217
 
 
218
216
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
219
217
%%
220
218
%% ACCEPT(insock() [,Timeout] ) -> {ok,insock()} | {error, Reason}
241
239
 
242
240
accept0(L, Time) when port(L), integer(Time) ->
243
241
    case async_accept(L, Time) of
244
 
        {ok, S, Ref} ->
 
242
        {ok, Ref} ->
245
243
            receive 
246
 
                {inet_async, S, Ref, Status} ->
247
 
                    case Status of
248
 
                        ok -> accept_opts(L, S);
249
 
                        Error -> close(S), Error
250
 
                    end
 
244
                {inet_async, L, Ref, {ok,S}} ->
 
245
                    accept_opts(L, S);
 
246
                {inet_async, L, Ref, Error} ->
 
247
                    Error
251
248
            end;
252
249
        Error -> Error
253
250
    end.
254
251
 
255
252
%% setup options from listen socket on the connected socket
256
253
accept_opts(L, S) ->
257
 
    case getopts(L, [active, nodelay, keepalive, delay_send]) of
 
254
    case getopts(L, [active, nodelay, keepalive, delay_send, priority, tos]) of
258
255
        {ok, Opts} ->
259
256
            case setopts(S, Opts) of
260
257
                ok -> {ok, S};
265
262
    end.
266
263
 
267
264
async_accept(L, Time) ->
268
 
    case getindex(L) of
269
 
        {ok, IX} ->
270
 
            case gettype(L) of
271
 
                {ok, {_, Type}} ->
272
 
                    case open0(Type) of
273
 
                        {ok,S} ->
274
 
                            case ctl_cmd(S,?TCP_REQ_ACCEPT,
275
 
                                         [enc_time(Time),?int16(IX)]) of
276
 
                                {ok, [R1,R0]} -> {ok, S, ?u16(R1,R0)};
277
 
                                Error -> close(S), Error
278
 
                            end;
279
 
                        Error -> Error
280
 
                    end;
281
 
                Error -> Error
282
 
            end;
 
265
    case ctl_cmd(L,?TCP_REQ_ACCEPT, [enc_time(Time)]) of
 
266
        {ok, [R1,R0]} -> {ok, ?u16(R1,R0)};
283
267
        Error -> Error
284
268
    end.
285
269
 
290
274
%% set listen mode on socket
291
275
%%
292
276
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
277
 
293
278
listen(S) -> listen(S, ?LISTEN_BACKLOG).
294
279
    
295
280
listen(S, BackLog) when port(S), integer(BackLog) ->
312
297
            receive
313
298
                {inet_reply, S, Status} -> Status
314
299
            end;
315
 
        {'EXIT', _Reason} -> {error, einval}
 
300
        {'EXIT', _Reason} -> 
 
301
            {error, einval}
316
302
    end.
317
303
 
318
304
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
324
310
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
325
311
 
326
312
sendto(S,IP,Port,Data) when port(S), Port >= 0, Port =< 65535 ->
327
 
    case catch erlang:port_command(S, [?int16(Port), ip_to_bytes(IP),Data]) of
 
313
    case catch erlang:port_command(S, [?int16(Port), ip_to_bytes(IP), Data]) of
328
314
        true -> 
329
315
            receive
330
316
                {inet_reply, S, Reply} -> Reply
331
317
            end;
332
 
        {'EXIT', _Reason} -> {error, einval}
 
318
        {'EXIT', _Reason} -> 
 
319
            {error, einval}
333
320
    end.
334
321
 
335
322
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
341
328
%%    N read N bytes
342
329
%%
343
330
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
331
 
344
332
recv(S, Length) -> recv0(S, Length, -1).
345
333
 
346
334
recv(S, Length, infinity) -> recv0(S, Length,-1);
363
351
    case ctl_cmd(S, ?TCP_REQ_RECV, [enc_time(Time), ?int32(Length)]) of
364
352
        {ok,[R1,R0]} -> {ok, ?u16(R1,R0)};
365
353
        Error -> Error
366
 
    end.
367
 
                    
 
354
    end.            
368
355
 
369
356
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
370
357
%%
445
432
        {ok,[]} -> ok;
446
433
        Error -> Error
447
434
    end.
448
 
             
449
435
 
450
436
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
451
437
%%
618
604
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
619
605
 
620
606
getindex(S) when port(S) ->
621
 
    case ctl_cmd(S, ?INET_REQ_GETIX, []) of
622
 
        {ok, [I3,I2,I1,I0]} -> {ok, ?u32(I3,I2,I1,I0)};
623
 
        Error -> Error
624
 
    end.
 
607
    %% NOT USED ANY MORE
 
608
    {error, einval}.
625
609
 
626
610
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
627
611
%%
674
658
gethostname(S) when port(S) ->
675
659
    ctl_cmd(S, ?INET_REQ_GETHOSTNAME, []).
676
660
 
677
 
 
678
661
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
679
662
%%
680
663
%% GETSERVBYNAME(insock(),Name,Proto) -> {ok,Port} | {error, Reason}
748
731
        Error  -> Error
749
732
    end.
750
733
 
751
 
 
752
734
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
753
735
%%
754
736
%% DETACH(insock()) -> ok
771
753
        {'EXIT', Reason} -> {error, Reason}
772
754
    end.
773
755
 
774
 
    
775
756
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
776
757
%%
777
758
%% INTERNAL FUNCTIONS
778
759
%%
779
760
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
780
761
 
781
 
is_sockopt_val(Opt,Val) ->
 
762
is_sockopt_val(Opt, Val) ->
782
763
    case type_opt(Opt) of
783
764
        undefined -> false;
784
765
        Type -> type_value(Type,Val)
785
 
    end;
786
 
is_sockopt_val(_,_) ->
787
 
    false.
 
766
    end.
788
767
 
789
768
%%
790
769
%% Socket options processing
796
775
enc_opt(broadcast)       -> ?INET_OPT_BROADCAST;
797
776
enc_opt(sndbuf)          -> ?INET_OPT_SNDBUF;
798
777
enc_opt(recbuf)          -> ?INET_OPT_RCVBUF;
 
778
enc_opt(priority)        -> ?INET_OPT_PRIORITY;
 
779
enc_opt(tos)             -> ?INET_OPT_TOS;
799
780
enc_opt(nodelay)         -> ?TCP_OPT_NODELAY;
800
781
enc_opt(multicast_if)    -> ?UDP_OPT_MULTICAST_IF;
801
782
enc_opt(multicast_ttl)   -> ?UDP_OPT_MULTICAST_TTL;
814
795
enc_opt(bit8)            -> ?INET_LOPT_BIT8;
815
796
enc_opt(send_timeout)    -> ?INET_LOPT_TCP_SEND_TIMEOUT;
816
797
enc_opt(delay_send)      -> ?INET_LOPT_TCP_DELAY_SEND;
817
 
enc_opt(_) ->          -1.
 
798
enc_opt(packet_size)     -> ?INET_LOPT_PACKET_SIZE;
 
799
enc_opt(read_packets)    -> ?INET_LOPT_UDP_READ_PACKETS;
 
800
enc_opt(O) when is_atom(O) -> -1.
818
801
 
819
802
dec_opt(?INET_OPT_REUSEADDR)      -> reuseaddr;
820
803
dec_opt(?INET_OPT_KEEPALIVE)      -> keepalive;
823
806
dec_opt(?INET_OPT_BROADCAST)      -> broadcast;
824
807
dec_opt(?INET_OPT_SNDBUF)         -> sndbuf;
825
808
dec_opt(?INET_OPT_RCVBUF)         -> recbuf;
 
809
dec_opt(?INET_OPT_PRIORITY)       -> priority;
 
810
dec_opt(?INET_OPT_TOS)            -> tos;
826
811
dec_opt(?TCP_OPT_NODELAY)         -> nodelay;
827
812
dec_opt(?UDP_OPT_MULTICAST_IF)    -> multicast_if;
828
813
dec_opt(?UDP_OPT_MULTICAST_TTL)   -> multicast_ttl;
840
825
dec_opt(?INET_LOPT_TCP_LOWTRMRK)  -> low_watermark;
841
826
dec_opt(?INET_LOPT_BIT8)          -> bit8;
842
827
dec_opt(?INET_LOPT_TCP_SEND_TIMEOUT) -> send_timeout;
843
 
dec_opt(?INET_LOPT_TCP_DELAY_SEND) -> delay_send;
844
 
dec_opt(_)                        -> undefined.
 
828
dec_opt(?INET_LOPT_TCP_DELAY_SEND)   -> delay_send;
 
829
dec_opt(?INET_LOPT_PACKET_SIZE)      -> packet_size;
 
830
dec_opt(?INET_LOPT_UDP_READ_PACKETS) -> read_packets;
 
831
dec_opt(I) when is_integer(I)     -> undefined.
845
832
 
846
833
type_opt(reuseaddr)       -> bool;
847
834
type_opt(keepalive)       -> bool;
850
837
type_opt(broadcast)       -> bool;
851
838
type_opt(sndbuf)          -> int;
852
839
type_opt(recbuf)          -> int;
 
840
type_opt(priority)        -> int;
 
841
type_opt(tos)             -> int;
853
842
type_opt(nodelay)         -> bool;
854
843
%% multicast
855
844
type_opt(multicast_ttl)   -> int;
860
849
%% driver options
861
850
type_opt(header)          -> uint;
862
851
type_opt(buffer)          -> int;
863
 
type_opt(active)          ->
 
852
type_opt(active) ->
864
853
    {enum, [{false, 0}, {true, 1}, {once, 2}]};
865
 
type_opt(packet)        -> 
 
854
type_opt(packet) -> 
866
855
    {enum, [{0, ?TCP_PB_RAW},
867
856
            {1, ?TCP_PB_1},
868
857
            {2, ?TCP_PB_2},
882
871
type_opt(deliver) ->
883
872
    {enum, [{port, ?INET_DELIVER_PORT},
884
873
            {term, ?INET_DELIVER_TERM}]};
885
 
 
886
 
type_opt(exit_on_close) -> bool;
887
 
type_opt(low_watermark)  -> int;
888
 
type_opt(high_watermark) -> int;
 
874
type_opt(exit_on_close)   -> bool;
 
875
type_opt(low_watermark)   -> int;
 
876
type_opt(high_watermark)  -> int;
889
877
type_opt(bit8) ->
890
878
    {enum, [{clear, ?INET_BIT8_CLEAR},
891
879
            {set,   ?INET_BIT8_SET},
892
880
            {on,    ?INET_BIT8_ON},
893
881
            {off,   ?INET_BIT8_OFF}]};
894
 
type_opt(send_timeout) -> time;
895
 
type_opt(delay_send) -> bool;
896
 
type_opt(_)         -> undefined.
897
 
 
 
882
type_opt(send_timeout)    -> time;
 
883
type_opt(delay_send)      -> bool;
 
884
type_opt(packet_size)     -> uint;
 
885
type_opt(read_packets)    -> uint;
 
886
type_opt(O) when is_atom(O) -> undefined.
898
887
 
899
888
 
900
889
type_value(bool, true)                     -> true;
904
893
type_value(time, infinity)                 -> true;
905
894
type_value(time, X) when integer(X), X>=0  -> true;
906
895
type_value(ip,{A,B,C,D}) when ?ip(A,B,C,D) -> true;
907
 
type_value(ether,[_X1,_X2,_X3,_X4,_X5,_X6])      -> true;
 
896
type_value(ether,[_X1,_X2,_X3,_X4,_X5,_X6]) -> true;
908
897
type_value({X,Y},{XV,YV}) -> type_value(X,XV) and type_value(Y,YV);
909
898
type_value({enum,List},Enum) -> 
910
899
    case enum_val(Enum, List) of
925
914
enc_value(uint, Val)      -> ?int32(Val);
926
915
enc_value(time, infinity) -> ?int32(-1);
927
916
enc_value(time, Val)      -> ?int32(Val);
928
 
enc_value(ip,{A,B,C,D}) -> [A,B,C,D];
929
 
enc_value(ip,any)       -> [0,0,0,0];
930
 
enc_value(ip,loopback)  -> [127,0,0,1];
 
917
enc_value(ip,{A,B,C,D})   -> [A,B,C,D];
 
918
enc_value(ip,any)         -> [0,0,0,0];
 
919
enc_value(ip,loopback)    -> [127,0,0,1];
931
920
enc_value(ether,[X1,X2,X3,X4,X5,X6]) -> [X1,X2,X3,X4,X5,X6];
932
921
enc_value({enum,List},Enum) ->
933
922
    {value,Val} = enum_val(Enum, List),
984
973
enum_vals([], _) -> [].
985
974
 
986
975
enum_names(Val, [{Enum,BitVal} |List]) ->
987
 
    if Val band BitVal == BitVal ->
 
976
    if Val band BitVal =:= BitVal ->
988
977
            [Enum | enum_names(Val, List)];
989
978
       true ->
990
979
            enum_names(Val, List)
1000
989
enum_name(_, []) -> false.
1001
990
 
1002
991
%% encode opt/val REVERSED since options are stored in reverse order
1003
 
%% i.e the recent options first (we must process old -> new)
 
992
%% i.e. the recent options first (we must process old -> new)
1004
993
encode_opt_val(Opts) -> enc_opt_val(Opts, []).
1005
994
 
1006
995
enc_opt_val([{Opt,Val} | Opts], Acc) ->
1054
1043
type_ifopt(dstaddr)   -> ip;
1055
1044
type_ifopt(mtu)       -> int;
1056
1045
type_ifopt(netmask)   -> ip;
1057
 
type_ifopt(flags) ->
 
1046
type_ifopt(flags)     ->
1058
1047
    {bitenumlist,
1059
1048
     [{up, ?INET_IFF_UP},
1060
1049
      {down, ?INET_IFF_DOWN},
1065
1054
      {no_pointtopoint, ?INET_IFF_NPOINTTOPOINT},
1066
1055
      {running, ?INET_IFF_RUNNING},
1067
1056
      {multicast, ?INET_IFF_MULTICAST}]};
1068
 
type_ifopt(hwaddr)  -> ether;
1069
 
type_ifopt(_)       -> undefined.
 
1057
type_ifopt(hwaddr)    -> ether;
 
1058
type_ifopt(Opt) when is_atom(Opt) -> undefined.
1070
1059
 
1071
1060
enc_ifopt(addr)      -> ?INET_IFOPT_ADDR;
1072
1061
enc_ifopt(broadaddr) -> ?INET_IFOPT_BROADADDR;
1075
1064
enc_ifopt(netmask)   -> ?INET_IFOPT_NETMASK;
1076
1065
enc_ifopt(flags)     -> ?INET_IFOPT_FLAGS;
1077
1066
enc_ifopt(hwaddr)    -> ?INET_IFOPT_HWADDR;
1078
 
enc_ifopt(_) -> -1.
 
1067
enc_ifopt(Opt) when is_atom(Opt) -> -1.
1079
1068
 
1080
1069
dec_ifopt(?INET_IFOPT_ADDR)      -> addr;
1081
1070
dec_ifopt(?INET_IFOPT_BROADADDR) -> broadaddr;
1084
1073
dec_ifopt(?INET_IFOPT_NETMASK)   -> netmask;
1085
1074
dec_ifopt(?INET_IFOPT_FLAGS)     -> flags;
1086
1075
dec_ifopt(?INET_IFOPT_HWADDR)    -> hwaddr;
1087
 
dec_ifopt(_)                     -> undefined.
 
1076
dec_ifopt(I) when is_integer(I)  -> undefined.
1088
1077
 
1089
1078
%% decode if options returns a reversed list
1090
1079
decode_ifopts([B | Buf], Acc) ->
1218
1207
    enum_names(Flags,
1219
1208
               [
1220
1209
                {busy, ?INET_F_BUSY},
1221
 
                {listening, ?INET_F_LST},
 
1210
                %% {listening, ?INET_F_LST}, NOT USED ANY MORE
1222
1211
                {accepting, ?INET_F_ACC},
1223
1212
                {connecting, ?INET_F_CON},
1224
1213
                {listen, ?INET_F_LISTEN},
1266
1255
rev([C|L],Acc) -> rev(L,[C|Acc]);
1267
1256
rev([],Acc) -> Acc.
1268
1257
 
1269
 
ip_to_bytes(IP) when size(IP) == 4 -> ip4_to_bytes(IP);
1270
 
ip_to_bytes(IP) when size(IP) == 8 -> ip6_to_bytes(IP).
1271
 
 
 
1258
ip_to_bytes(IP) when size(IP) =:= 4 -> ip4_to_bytes(IP);
 
1259
ip_to_bytes(IP) when size(IP) =:= 8 -> ip6_to_bytes(IP).
1272
1260
 
1273
1261
ip4_to_bytes({A,B,C,D}) ->
1274
1262
    [A band 16#ff, B band 16#ff, C band 16#ff, D band 16#ff].
1289
1277
 
1290
1278
%% Control command
1291
1279
ctl_cmd(Port, Cmd, Args) ->
1292
 
    case catch port_control(Port, Cmd, Args) of
1293
 
        [?INET_REP_OK | Reply]      -> {ok, Reply};
 
1280
    case catch erlang:port_control(Port, Cmd, Args) of
 
1281
        [?INET_REP_OK | Reply] -> {ok, Reply};
1294
1282
        [?INET_REP_ERROR| Err] -> {error, list_to_atom(Err)};
1295
1283
        {'EXIT', _} -> {error, einval};
1296
1284
        _ -> {error, internal}