~rdoering/ubuntu/karmic/erlang/fix-535090

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-02-15 16:42:52 UTC
  • mfrom: (1.1.13 upstream)
  • mto: (3.3.1 squeeze)
  • mto: This revision was merged to the branch mainline in revision 17.
  • Revision ID: james.westby@ubuntu.com-20090215164252-dxpjjuq108nz4noa
Upload to unstable after lenny is released.

Show diffs side-by-side

added added

removed removed

Lines of Context:
61
61
-export([start_timer/1, timeout/1, timeout/2, stop_timer/1]).
62
62
 
63
63
%% imports
64
 
-import(lists, [append/1, duplicate/2, member/2, filter/2,
65
 
                map/2, foldl/3, foreach/2]).
 
64
-import(lists, [append/1, duplicate/2, filter/2, foldl/3]).
66
65
 
67
66
%% Record Signature
68
67
-define(RS(Record),
69
 
        {Record,record_info(size, Record)}).
 
68
        {Record, record_info(size, Record)}).
70
69
%% Record Signature Check (guard)
71
70
-define(RSC(Record, RS),
72
71
        element(1, Record) =:= element(1, RS),
73
 
        size(Record) =:= element(2, RS)).
 
72
        tuple_size(Record) =:= element(2, RS)).
74
73
 
75
74
%%% ---------------------------------
76
75
%%% Contract type definitions
77
76
 
78
 
-type(socket() :: port()).
79
 
-type(posix() :: atom()).
 
77
-type socket() :: port().
 
78
-type posix() :: atom().
80
79
 
81
 
-type(socket_setopt() ::
 
80
-type socket_setopt() ::
82
81
      {'raw', non_neg_integer(), non_neg_integer(), binary()} |
83
82
      %% TCP/UDP options
84
83
      {'reuseaddr',       bool()} |
127
126
      {'sctp_peer_addr_params',      #sctp_paddrparams{}} |
128
127
      {'sctp_default_send_param',    #sctp_sndrcvinfo{}} |
129
128
      {'sctp_events',                #sctp_event_subscribe{}} |
130
 
      {'sctp_delayed_ack_time',      #sctp_assoc_value{}}).
 
129
      {'sctp_delayed_ack_time',      #sctp_assoc_value{}}.
131
130
 
132
 
-type(socket_getopt() ::
 
131
-type socket_getopt() ::
133
132
      {'raw',
134
133
       non_neg_integer(), non_neg_integer(), binary()|non_neg_integer()} |
135
134
      %% TCP/UDP options
162
161
      'sctp_events' |
163
162
      {'sctp_events',                #sctp_event_subscribe{}} |
164
163
      'sctp_delayed_ack_time' |
165
 
      {'sctp_delayed_ack_time',      #sctp_assoc_value{}}).
166
 
 
167
 
-type(ether_address() :: [0..255]).
168
 
 
169
 
-type(if_setopt() ::
 
164
      {'sctp_delayed_ack_time',      #sctp_assoc_value{}}.
 
165
 
 
166
-type ether_address() :: [0..255].
 
167
 
 
168
-type if_setopt() ::
170
169
      {'addr', ip_address()} |
171
170
      {'broadaddr', ip_address()} |
172
171
      {'dstaddr', ip_address()} |
175
174
      {'flags', ['up' | 'down' | 'broadcast' | 'no_broadcast' |
176
175
                 'pointtopoint' | 'no_pointtopoint' | 
177
176
                 'running' | 'multicast']} |
178
 
      {'hwaddr', ether_address()}).
 
177
      {'hwaddr', ether_address()}.
179
178
 
180
 
-type(if_getopt() ::
 
179
-type if_getopt() ::
181
180
      'addr' | 'broadaddr' | 'dstaddr' | 
182
 
      'mtu' | 'netmask' | 'flags' |'hwaddr'). 
 
181
      'mtu' | 'netmask' | 'flags' |'hwaddr'.
183
182
 
184
 
-type(family_option() :: 'inet' | 'inet6').
185
 
-type(protocol_option() :: 'tcp' | 'udp' | 'sctp').
186
 
-type(stat_option() :: 
 
183
-type family_option() :: 'inet' | 'inet6'.
 
184
-type protocol_option() :: 'tcp' | 'udp' | 'sctp'.
 
185
-type stat_option() :: 
187
186
        'recv_cnt' | 'recv_max' | 'recv_avg' | 'recv_oct' | 'recv_dvi' |
188
 
        'send_cnt' | 'send_max' | 'send_avg' | 'send_oct' | 'send_pend').
 
187
        'send_cnt' | 'send_max' | 'send_avg' | 'send_oct' | 'send_pend'.
 
188
 
189
189
%%% ---------------------------------
190
190
 
191
 
-spec(get_rc/0 :: () -> [{any(),any()}]).
 
191
-spec get_rc() -> [{any(),any()}].
192
192
 
193
193
get_rc() ->
194
194
    inet_db:get_rc().
195
195
 
196
 
-spec(close/1 :: (Socket :: socket()) -> 'ok').
 
196
-spec close(Socket :: socket()) -> 'ok'.
197
197
 
198
198
close(Socket) ->
199
199
    prim_inet:close(Socket),
204
204
            ok
205
205
    end.
206
206
 
207
 
-spec(peername/1 :: (Socket :: socket()) -> 
208
 
        {'ok', {ip_address(), non_neg_integer()}} | {'error', posix()}).
 
207
-spec peername(Socket :: socket()) -> 
 
208
        {'ok', {ip_address(), non_neg_integer()}} | {'error', posix()}.
209
209
 
210
210
peername(Socket) -> 
211
211
    prim_inet:peername(Socket).
212
212
 
213
 
-spec(setpeername/2 :: (
214
 
        Socket :: socket(), 
215
 
        Address :: {ip_address(), ip_port()}) ->
216
 
        'ok' | {'error', any()}).  
 
213
-spec setpeername(Socket :: socket(), Address :: {ip_address(), ip_port()}) ->
 
214
        'ok' | {'error', any()}.
217
215
 
218
216
setpeername(Socket, {IP,Port}) ->
219
217
    prim_inet:setpeername(Socket, {IP,Port});
221
219
    prim_inet:setpeername(Socket, undefined).
222
220
 
223
221
 
224
 
-spec(sockname/1 :: (Socket :: socket()) -> 
225
 
        {'ok', {ip_address(), non_neg_integer()}} | {'error', posix()}).
 
222
-spec sockname(Socket :: socket()) -> 
 
223
        {'ok', {ip_address(), non_neg_integer()}} | {'error', posix()}.
226
224
 
227
225
sockname(Socket) -> 
228
226
    prim_inet:sockname(Socket).
229
227
 
230
 
-spec(setsockname/2 :: (
231
 
        Socket :: socket(),
232
 
        Address :: {ip_address(), ip_port()}) ->
233
 
        'ok' | {'error', any()}).       
 
228
-spec setsockname(Socket :: socket(), Address :: {ip_address(), ip_port()}) ->
 
229
        'ok' | {'error', any()}.
234
230
 
235
231
setsockname(Socket, {IP,Port}) -> 
236
232
    prim_inet:setsockname(Socket, {IP,Port});
237
233
setsockname(Socket, undefined) ->
238
234
    prim_inet:setsockname(Socket, undefined).
239
235
 
240
 
-spec(port/1 :: (Socket :: socket()) -> 
241
 
        {'ok', ip_port()} | {'error', any()}). 
 
236
-spec port(Socket :: socket()) -> {'ok', ip_port()} | {'error', any()}.
242
237
 
243
238
port(Socket) ->
244
239
    case prim_inet:sockname(Socket) of
246
241
        Error -> Error
247
242
    end.
248
243
 
249
 
-spec(send/2 :: (
250
 
        Socket :: socket(),
251
 
        Packet :: iolist()) -> % iolist()?
252
 
        'ok' | {'error', posix()}).
 
244
-spec send(Socket :: socket(), Packet :: iolist()) -> % iolist()?
 
245
        'ok' | {'error', posix()}.
253
246
 
254
247
send(Socket, Packet) -> 
255
248
    prim_inet:send(Socket, Packet).
256
249
    
257
 
-spec(setopts/2 :: (
258
 
        Socket :: socket(),
259
 
        Opts :: [socket_setopt()]) -> 
260
 
        'ok' | {'error', posix()}).
 
250
-spec setopts(Socket :: socket(), Opts :: [socket_setopt()]) -> 
 
251
        'ok' | {'error', posix()}.
261
252
 
262
253
setopts(Socket, Opts) -> 
263
254
    prim_inet:setopts(Socket, Opts).
264
255
 
265
 
-spec(getopts/2 :: (
266
 
        Socket :: socket(),
267
 
        Opts :: [socket_getopt()]) ->   
268
 
        {'ok', [socket_setopt()]} | {'error', posix()}).
 
256
-spec getopts(Socket :: socket(), Opts :: [socket_getopt()]) -> 
 
257
        {'ok', [socket_setopt()]} | {'error', posix()}.
269
258
 
270
259
getopts(Socket, Opts) ->
271
260
    prim_inet:getopts(Socket, Opts).
272
261
 
273
 
-spec(getiflist/1 :: (Socket :: socket()) ->
274
 
        {'ok', [string()]} | {'error', posix()}).        
 
262
-spec getiflist(Socket :: socket()) ->
 
263
        {'ok', [string()]} | {'error', posix()}.
275
264
 
276
265
getiflist(Socket) -> 
277
266
    prim_inet:getiflist(Socket).
278
267
 
279
 
-spec(getiflist/0 :: () ->
280
 
        {'ok', [string()]} | {'error', posix()}).        
 
268
-spec getiflist() -> {'ok', [string()]} | {'error', posix()}.
281
269
 
282
270
getiflist() -> 
283
271
    withsocket(fun(S) -> prim_inet:getiflist(S) end).
284
272
    
285
 
-spec(ifget/3 :: (
286
 
        Socket :: socket(),
287
 
        Name :: string() | atom(),
288
 
        Opts :: [if_getopt()]) ->
289
 
        {'ok', [if_setopt()]} | 
290
 
        {'error', posix()}).    
 
273
-spec ifget(Socket :: socket(),
 
274
            Name :: string() | atom(),
 
275
            Opts :: [if_getopt()]) ->
 
276
        {'ok', [if_setopt()]} | {'error', posix()}.
291
277
 
292
278
ifget(Socket, Name, Opts) -> 
293
279
    prim_inet:ifget(Socket, Name, Opts).
294
280
 
295
 
-spec(ifget/2 :: (
296
 
        Name :: string() | atom(),
297
 
        Opts :: [if_getopt()]) ->
298
 
        {'ok', [if_setopt()]} | 
299
 
        {'error', posix()}).    
 
281
-spec ifget(Name :: string() | atom(), Opts :: [if_getopt()]) ->
 
282
        {'ok', [if_setopt()]} | {'error', posix()}.
300
283
 
301
 
ifget(Name, Opts) -> 
 
284
ifget(Name, Opts) ->
302
285
    withsocket(fun(S) -> prim_inet:ifget(S, Name, Opts) end).
303
286
 
304
 
-spec(ifset/3 :: (
305
 
        Socket :: socket(),
306
 
        Name :: string() | atom(),
307
 
        Opts :: [if_setopt()]) ->
308
 
        'ok' | {'error', posix()}).     
 
287
-spec ifset(Socket :: socket(),
 
288
            Name :: string() | atom(),
 
289
            Opts :: [if_setopt()]) ->
 
290
        'ok' | {'error', posix()}.
309
291
 
310
292
ifset(Socket, Name, Opts) -> 
311
293
    prim_inet:ifset(Socket, Name, Opts).
312
294
 
313
 
-spec(ifset/2 :: (
314
 
        Name :: string() | atom(),
315
 
        Opts :: [if_setopt()]) ->
316
 
        'ok' | {'error', posix()}).     
 
295
-spec ifset(Name :: string() | atom(), Opts :: [if_setopt()]) ->
 
296
        'ok' | {'error', posix()}.
317
297
 
318
 
ifset(Name, Opts) -> 
 
298
ifset(Name, Opts) ->
319
299
    withsocket(fun(S) -> prim_inet:ifset(S, Name, Opts) end).
320
300
 
321
 
-spec(getif/0 :: () ->
 
301
-spec getif() ->
322
302
        {'ok', [{ip_address(), ip_address() | 'undefined', ip_address()}]} | 
323
 
        {'error', posix()}).    
 
303
        {'error', posix()}.
324
304
 
325
305
getif() -> 
326
306
    withsocket(fun(S) -> getif(S) end).
327
307
 
328
308
%% backwards compatible getif
329
 
-spec(getif/1 :: (Socket :: socket()) ->
 
309
-spec getif(Socket :: socket()) ->
330
310
        {'ok', [{ip_address(), ip_address() | 'undefined', ip_address()}]} | 
331
 
        {'error', posix()}).    
 
311
        {'error', posix()}.
332
312
 
333
313
getif(Socket) ->
334
314
    case prim_inet:getiflist(Socket) of
373
353
% use of the DHCP-protocol
374
354
% should never fail
375
355
 
376
 
-spec(gethostname/0 :: () -> {'ok', string()}).
 
356
-spec gethostname() -> {'ok', string()}.
377
357
 
378
358
gethostname() ->
379
359
    case inet_udp:open(0,[]) of
386
366
            {ok, "nohost.nodomain"}
387
367
    end.
388
368
 
389
 
-spec(gethostname/1 :: (Socket :: socket()) ->
390
 
        {'ok', string()} | {'error', posix()}).
 
369
-spec gethostname(Socket :: socket()) ->
 
370
        {'ok', string()} | {'error', posix()}.
391
371
 
392
372
gethostname(Socket) ->
393
373
    prim_inet:gethostname(Socket).
394
374
 
395
 
-spec(getstat/1 :: (Socket :: socket()) ->
396
 
        {'ok', [{stat_option(), integer()}]} | {'error', posix()}).             
 
375
-spec getstat(Socket :: socket()) ->
 
376
        {'ok', [{stat_option(), integer()}]} | {'error', posix()}.
397
377
 
398
378
getstat(Socket) ->
399
379
    prim_inet:getstat(Socket, stats()).
400
380
 
401
 
-spec(getstat/2 :: (
402
 
        Socket :: socket(),
403
 
        Statoptions :: [stat_option()]) ->
404
 
        {'ok', [{stat_option(), integer()}]} | {'error', posix()}).             
 
381
-spec getstat(Socket :: socket(), Statoptions :: [stat_option()]) ->
 
382
        {'ok', [{stat_option(), integer()}]} | {'error', posix()}.
405
383
 
406
384
getstat(Socket,What) ->
407
385
    prim_inet:getstat(Socket, What).
408
386
 
409
 
-spec(gethostbyname/1 :: (Name :: string() | atom()) ->
410
 
        {'ok', #hostent{}} | {'error', posix()}).
 
387
-spec gethostbyname(Name :: string() | atom()) ->
 
388
        {'ok', #hostent{}} | {'error', posix()}.
411
389
 
412
390
gethostbyname(Name) -> 
413
391
    gethostbyname_tm(Name, inet, false).
414
392
 
415
 
-spec(gethostbyname/2 :: (
416
 
        Name :: string() | atom(),
417
 
        Family :: family_option()) ->
418
 
        {'ok', #hostent{}} | {'error', posix()}).
 
393
-spec gethostbyname(Name :: string() | atom(), Family :: family_option()) ->
 
394
        {'ok', #hostent{}} | {'error', posix()}.
419
395
 
420
396
gethostbyname(Name,Family) -> 
421
397
    gethostbyname_tm(Name, Family, false).
422
398
 
423
 
-spec(gethostbyname/3 :: (
424
 
        Name :: string() | atom(),
425
 
        Family :: family_option(),
426
 
        Timeout :: non_neg_integer() | 'infinity') ->
427
 
        {'ok', #hostent{}} | {'error', posix()}).
 
399
-spec gethostbyname(Name :: string() | atom(),
 
400
                    Family :: family_option(),
 
401
                    Timeout :: non_neg_integer() | 'infinity') ->
 
402
        {'ok', #hostent{}} | {'error', posix()}.
428
403
        
429
404
gethostbyname(Name,Family,Timeout) ->
430
405
    Timer = start_timer(Timeout),
436
411
    gethostbyname_tm(Name,Family,Timer,inet_db:res_option(lookup)).
437
412
 
438
413
 
439
 
-spec(gethostbyaddr/1 :: (Address :: string() | ip_address()) ->
440
 
        {'ok', #hostent{}} | {'error', posix()}).
 
414
-spec gethostbyaddr(Address :: string() | ip_address()) ->
 
415
        {'ok', #hostent{}} | {'error', posix()}.
441
416
 
442
417
gethostbyaddr(Address) ->
443
418
    gethostbyaddr_tm(Address, false).
444
419
 
445
 
-spec(gethostbyaddr/2 :: (
446
 
        Address :: string() | ip_address(), 
447
 
        Timeout :: non_neg_integer() | 'infinity') ->
448
 
        {'ok', #hostent{}} | {'error', posix()}).
 
420
-spec gethostbyaddr(Address :: string() | ip_address(), 
 
421
                    Timeout :: non_neg_integer() | 'infinity') ->
 
422
        {'ok', #hostent{}} | {'error', posix()}.
449
423
 
450
424
gethostbyaddr(Address,Timeout) ->
451
425
    Timer = start_timer(Timeout),    
456
430
gethostbyaddr_tm(Address,Timer) ->
457
431
    gethostbyaddr_tm(Address, Timer, inet_db:res_option(lookup)).
458
432
 
459
 
-spec(ip/1 :: (Ip :: ip_address() | string() | atom()) ->
460
 
        {'ok', ip_address()} | {'error', posix()}).
 
433
-spec ip(Ip :: ip_address() | string() | atom()) ->
 
434
        {'ok', ip_address()} | {'error', posix()}.
461
435
 
462
436
ip({A,B,C,D}) when ?ip(A,B,C,D) ->
463
437
    {ok, {A,B,C,D}};
469
443
    end.
470
444
 
471
445
%% This function returns the erlang port used (with inet_drv)
472
 
%% Return values: {ok,#Port} if ok
473
 
%%                {error, einval} if not applicable
474
446
 
475
 
-spec(getll/1 :: (Socket :: socket()) ->
476
 
        {'ok', socket()}).
 
447
-spec getll(Socket :: socket()) -> {'ok', socket()}.
477
448
 
478
449
getll(Socket) when is_port(Socket) ->
479
450
    {ok, Socket}.
482
453
%% Return the internal file descriptor number
483
454
%%
484
455
 
485
 
-spec(getfd/1 :: (Socket :: socket()) ->
486
 
        {'ok', non_neg_integer()} | {'error', posix()}).
 
456
-spec getfd(Socket :: socket()) ->
 
457
        {'ok', non_neg_integer()} | {'error', posix()}.
487
458
 
488
459
getfd(Socket) ->
489
460
    prim_inet:getfd(Socket).
492
463
%% Lookup an ip address
493
464
%%
494
465
 
495
 
-spec(getaddr/2 :: (
496
 
        Host :: ip_address() | string() | atom(),
497
 
        Family :: family_option()) ->
498
 
        {'ok', ip_address()} | {'error', posix()}).     
 
466
-spec getaddr(Host :: ip_address() | string() | atom(),
 
467
              Family :: family_option()) ->
 
468
        {'ok', ip_address()} | {'error', posix()}.
499
469
 
500
470
getaddr(Address, Family) ->
501
471
    getaddr(Address, Family, infinity).
502
472
 
503
 
-spec(getaddr/3 :: (
504
 
        Host :: ip_address() | string() | atom(),
505
 
        Family :: family_option(),
506
 
        Timeout :: non_neg_integer() | 'infinity') ->
507
 
        {'ok', ip_address()} | {'error', posix()}).     
 
473
-spec getaddr(Host :: ip_address() | string() | atom(),
 
474
              Family :: family_option(),
 
475
              Timeout :: non_neg_integer() | 'infinity') ->
 
476
        {'ok', ip_address()} | {'error', posix()}.
508
477
 
509
478
getaddr(Address, Family, Timeout) ->
510
479
    Timer = start_timer(Timeout),
511
480
    Res = getaddr_tm(Address, Family, Timer),
512
481
    stop_timer(Timer),
513
482
    Res.
514
 
    
 
483
 
515
484
getaddr_tm(Address, Family, Timer) ->
516
485
    case getaddrs_tm(Address, Family, Timer) of
517
486
        {ok, [IP|_]} -> {ok, IP};
518
487
        Error -> Error
519
488
    end.
520
489
 
521
 
-spec(getaddrs/2 :: (
522
 
        Host :: ip_address() | string() | atom(),
523
 
        Family :: family_option()) ->
524
 
        {'ok', [ip_address()]} | {'error', posix()}).   
 
490
-spec getaddrs(Host :: ip_address() | string() | atom(),
 
491
               Family :: family_option()) ->
 
492
        {'ok', [ip_address()]} | {'error', posix()}.
525
493
 
526
494
getaddrs(Address, Family) -> 
527
495
    getaddrs(Address, Family, infinity).
528
496
 
529
 
-spec(getaddrs/3 :: (
530
 
        Host :: ip_address() | string() | atom(),
531
 
        Family :: family_option(),
532
 
        Timeout :: non_neg_integer() | 'infinity') ->
533
 
        {'ok', [ip_address()]} | {'error', posix()}).   
 
497
-spec getaddrs(Host :: ip_address() | string() | atom(),
 
498
               Family :: family_option(),
 
499
               Timeout :: non_neg_integer() | 'infinity') ->
 
500
        {'ok', [ip_address()]} | {'error', posix()}.
534
501
 
535
 
getaddrs(Address, Family,Timeout) -> 
536
 
    Timer = start_timer(Timeout),    
 
502
getaddrs(Address, Family, Timeout) ->
 
503
    Timer = start_timer(Timeout),
537
504
    Res = getaddrs_tm(Address, Family, Timer),
538
505
    stop_timer(Timer),
539
 
    Res.    
 
506
    Res.
540
507
 
541
 
-spec(getservbyport/2 :: (
542
 
        Port :: ip_port(),
543
 
        Protocol :: atom() | string()) ->
544
 
        {'ok', string()} | {'error', posix()}). 
 
508
-spec getservbyport(Port :: ip_port(), Protocol :: atom() | string()) ->
 
509
        {'ok', string()} | {'error', posix()}.
545
510
 
546
511
getservbyport(Port, Proto) ->
547
512
    case inet_udp:open(0, []) of
548
513
        {ok,U} ->
549
 
            Res = prim_inet:getservbyport(U,Port, Proto),
 
514
            Res = prim_inet:getservbyport(U, Port, Proto),
550
515
            inet_udp:close(U),
551
516
            Res;
552
517
        Error -> Error
553
518
    end.
554
519
 
555
 
-spec(getservbyname/2 :: (
556
 
        Name :: atom() | string(),
557
 
        Protocol :: atom() | string()) ->
558
 
        {'ok', ip_port()} | {'error', posix()}). 
 
520
-spec getservbyname(Name :: atom() | string(),
 
521
                    Protocol :: atom() | string()) ->
 
522
        {'ok', ip_port()} | {'error', posix()}.
559
523
 
560
 
getservbyname(Name, Proto) when is_atom(Name) ->
 
524
getservbyname(Name, Protocol) when is_atom(Name) ->
561
525
    case inet_udp:open(0, []) of
562
526
        {ok,U} ->
563
 
            Res = prim_inet:getservbyname(U,Name, Proto),
 
527
            Res = prim_inet:getservbyname(U, Name, Protocol),
564
528
            inet_udp:close(U),
565
529
            Res;
566
530
        Error -> Error
579
543
 
580
544
%% Return a list of statistics options
581
545
 
582
 
-spec(stats/0 :: () -> [stat_option(),...]).
 
546
-spec stats() -> [stat_option(),...].
583
547
 
584
548
stats() ->
585
549
    [recv_oct, recv_cnt, recv_max, recv_avg, recv_dvi,
825
789
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
826
790
 
827
791
add_opt(Name, Val, Opts, As) ->
828
 
    case member(Name, As) of
 
792
    case lists:member(Name, As) of
829
793
        true ->
830
794
            case prim_inet:is_sockopt_val(Name, Val) of
831
795
                true ->
976
940
        {error,formerr} -> {error, einval};
977
941
        {error,_} -> gethostbyaddr_tm(Addr,Timer,Opts);
978
942
        Result -> Result
979
 
    end;    
 
943
    end;
980
944
gethostbyaddr_tm(Addr, Timer, [yp | Opts]) ->
981
945
    gethostbyaddr_tm(Addr, Timer, [native | Opts]);
982
946
gethostbyaddr_tm(Addr, Timer, [nis | Opts]) ->
997
961
gethostbyaddr_tm(_Addr, _Timer, []) ->
998
962
    {error, nxdomain}.
999
963
 
1000
 
-spec(open/7 :: (
1001
 
        Fd :: integer(),
1002
 
        Addr :: ip_address(),
1003
 
        Port :: ip_port(),
1004
 
        Opts :: [socket_setopt()],
1005
 
        Protocol :: protocol_option(),
1006
 
        Family :: 'inet' | 'inet6',
1007
 
        Module :: atom()) ->
1008
 
        {'ok', socket()} | {'error', posix()}).
 
964
-spec open(Fd :: integer(),
 
965
           Addr :: ip_address(),
 
966
           Port :: ip_port(),
 
967
           Opts :: [socket_setopt()],
 
968
           Protocol :: protocol_option(),
 
969
           Family :: 'inet' | 'inet6',
 
970
           Module :: atom()) ->
 
971
        {'ok', socket()} | {'error', posix()}.
1009
972
 
1010
973
open(Fd, Addr, Port, Opts, Protocol, Family, Module) when Fd < 0 ->
1011
974
    case prim_inet:open(Protocol, Family) of
1038
1001
open(Fd, _Addr, _Port, Opts, Protocol, Family, Module) ->
1039
1002
    fdopen(Fd, Opts, Protocol, Family, Module).
1040
1003
 
1041
 
-spec(fdopen/5 :: (
1042
 
        Fd :: non_neg_integer(),
1043
 
        Opts :: [socket_setopt()],
1044
 
        Protocol :: protocol_option(),
1045
 
        Family :: family_option(),
1046
 
        Module :: atom()) ->
1047
 
        {'ok', socket()} | {'error', posix()}).
 
1004
-spec fdopen(Fd :: non_neg_integer(),
 
1005
             Opts :: [socket_setopt()],
 
1006
             Protocol :: protocol_option(),
 
1007
             Family :: family_option(),
 
1008
             Module :: atom()) ->
 
1009
        {'ok', socket()} | {'error', posix()}.
1048
1010
 
1049
1011
fdopen(Fd, Opts, Protocol, Family, Module) ->
1050
1012
    case prim_inet:fdopen(Protocol, Fd, Family) of
1078
1040
    Maxs = foldl(
1079
1041
             fun(Line,Max0) -> smax(Max0,Line) end, 
1080
1042
             duplicate(length(Fs),0),LLs),
1081
 
    Fmt = append(map(fun(N) -> "~-" ++ integer_to_list(N) ++ "s " end,
1082
 
                     Maxs)) ++ "\n",
1083
 
    foreach(
1084
 
      fun(Line) -> io:format(Fmt, Line) end, LLs).
 
1043
    Fmt = append(["~-" ++ integer_to_list(N) ++ "s " || N <- Maxs]) ++ "\n",
 
1044
    lists:foreach(fun(Line) -> io:format(Fmt, Line) end, LLs).
1085
1045
 
1086
1046
smax([Max|Ms], [Str|Strs]) ->
1087
1047
    N = length(Str),
1088
 
    [ if N > Max -> N; true -> Max end | smax(Ms, Strs)];
 
1048
    [if N > Max -> N; true -> Max end | smax(Ms, Strs)];
1089
1049
smax([], []) -> [].
1090
1050
 
1091
 
info_lines(Ss, Fs,Proto)  -> map(fun(S) -> i_line(S, Fs,Proto) end, Ss).
1092
 
i_line(S, Fs, Proto)      -> map(fun(F) -> info(S, F, Proto) end, Fs).
 
1051
info_lines(Ss, Fs, Proto) -> [i_line(S, Fs,Proto) || S <- Ss].
 
1052
i_line(S, Fs, Proto)      -> [info(S, F, Proto) || F <- Fs].
1093
1053
 
1094
 
h_line(Fs) -> map(fun(F) -> h_field(atom_to_list(F)) end, Fs).
 
1054
h_line(Fs) -> [h_field(atom_to_list(F)) || F <- Fs].
1095
1055
 
1096
1056
h_field([C|Cs]) -> [upper(C) | hh_field(Cs)].
1097
1057
 
1196
1156
tcp_sockets() -> port_list("tcp_inet").
1197
1157
udp_sockets() -> port_list("udp_inet").
1198
1158
 
1199
 
%% Return all port having the name 'Name'
 
1159
%% Return all ports having the name 'Name'
1200
1160
port_list(Name) ->
1201
1161
    filter(
1202
1162
      fun(Port) ->
1210
1170
%%  utils
1211
1171
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1212
1172
 
 
1173
-spec format_error(posix()) -> string().
 
1174
 
1213
1175
format_error(exbadport) -> "invalid port state";
1214
1176
format_error(exbadseq) ->  "bad command sequence";
1215
1177
format_error(Tag) ->
1242
1204
                {ok, A0} ->
1243
1205
                    prim_inet:setopt(S, active, false),
1244
1206
                    case tcp_sync_input(S, NewOwner, false) of
1245
 
                        true ->
1246
 
                            %%  %% socket already closed, 
 
1207
                        true ->  %% socket already closed, 
1247
1208
                            ok;
1248
1209
                        false ->
1249
 
                            case catch erlang:port_connect(S, NewOwner) of
 
1210
                            try erlang:port_connect(S, NewOwner) of
1250
1211
                                true -> 
1251
1212
                                    unlink(S), %% unlink from port
1252
1213
                                    prim_inet:setopt(S, active, A0),
1253
 
                                    ok;
1254
 
                                {'EXIT', Reason} -> 
 
1214
                                    ok
 
1215
                            catch
 
1216
                                error:Reason -> 
1255
1217
                                    {error, Reason}
1256
1218
                            end
1257
1219
                    end;
1287
1249
        {connected, Pid} when Pid =/= self() ->
1288
1250
            {error, not_owner};
1289
1251
        _ ->
1290
 
            {ok,A0} = prim_inet:getopt(S, active),
 
1252
            {ok, A0} = prim_inet:getopt(S, active),
1291
1253
            prim_inet:setopt(S, active, false),
1292
 
            case udp_sync_input(S, NewOwner, false) of
1293
 
                false ->
1294
 
                    case catch erlang:port_connect(S, NewOwner) of
1295
 
                        true -> 
1296
 
                            unlink(S),
1297
 
                            prim_inet:setopt(S, active, A0),
1298
 
                            ok;
1299
 
                        {'EXIT', Reason} -> 
1300
 
                            {error, Reason}
1301
 
                    end;
1302
 
                true ->
 
1254
            udp_sync_input(S, NewOwner),
 
1255
            try erlang:port_connect(S, NewOwner) of
 
1256
                true -> 
 
1257
                    unlink(S),
 
1258
                    prim_inet:setopt(S, active, A0),
1303
1259
                    ok
 
1260
            catch
 
1261
                error:Reason -> 
 
1262
                    {error, Reason}
1304
1263
            end
1305
1264
    end.
1306
1265
 
1307
 
udp_sync_input(S, Owner, Flag) ->
 
1266
udp_sync_input(S, Owner) ->
1308
1267
    receive
1309
 
        {sctp, S, _, _, _}=Msg    -> udp_sync_input(S, Owner, Flag, Msg);
1310
 
        {udp, S, _, _, _}=Msg     -> udp_sync_input(S, Owner, Flag, Msg);
1311
 
        {udp_closed, S}=Msg       -> udp_sync_input(S, Owner, Flag, Msg);
1312
 
        {S, {data,_}}=Msg         -> udp_sync_input(S, Owner, Flag, Msg);
1313
 
        {inet_async, S, _, _}=Msg -> udp_sync_input(S, Owner, Flag, Msg);
1314
 
        {inet_reply, S, _}=Msg    -> udp_sync_input(S, Owner, Flag, Msg)
1315
 
    after 0 -> 
1316
 
            Flag
 
1268
        {sctp, S, _, _, _}=Msg    -> udp_sync_input(S, Owner, Msg);
 
1269
        {udp, S, _, _, _}=Msg     -> udp_sync_input(S, Owner, Msg);
 
1270
        {udp_closed, S}=Msg       -> udp_sync_input(S, Owner, Msg);
 
1271
        {S, {data,_}}=Msg         -> udp_sync_input(S, Owner, Msg);
 
1272
        {inet_async, S, _, _}=Msg -> udp_sync_input(S, Owner, Msg);
 
1273
        {inet_reply, S, _}=Msg    -> udp_sync_input(S, Owner, Msg)
 
1274
    after 0 ->
 
1275
            ok
1317
1276
    end.
1318
1277
 
1319
 
udp_sync_input(S, Owner, Flag, Msg) ->
 
1278
udp_sync_input(S, Owner, Msg) ->
1320
1279
    Owner ! Msg,
1321
 
    udp_sync_input(S, Owner, Flag).
 
1280
    udp_sync_input(S, Owner).
1322
1281
 
1323
1282
start_timer(infinity) -> false;
1324
 
start_timer(Timeout) -> 
 
1283
start_timer(Timeout) ->
1325
1284
    erlang:start_timer(Timeout, self(), inet).
1326
1285
 
1327
1286
timeout(false) -> infinity;
1337
1296
    if TimerTime < Time -> TimerTime;
1338
1297
       true -> Time
1339
1298
    end.
1340
 
    
 
1299
 
1341
1300
stop_timer(false) -> false;
1342
1301
stop_timer(Timer) ->
1343
1302
    case erlang:cancel_timer(Timer) of
1349
1308
            end;
1350
1309
        T -> T
1351
1310
    end.
1352