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

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-05-07 15:07:37 UTC
  • mfrom: (1.2.1 upstream) (5.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20090507150737-i4yb5elwinm7r0hc
Tags: 1:13.b-dfsg1-1
* Removed another bunch of non-free RFCs from original tarball
  (closes: #527053).
* Fixed build-dependencies list by adding missing comma. This requires
  libsctp-dev again. Also, added libsctp1 dependency to erlang-base and
  erlang-base-hipe packages because the shared library is loaded via
  dlopen now and cannot be added using dh_slibdeps (closes: #526682).
* Weakened dependency of erlang-webtool on erlang-observer to recommends
  to avoid circular dependencies (closes: #526627).
* Added solaris-i386 to HiPE enabled architectures.
* Made script sources in /usr/lib/erlang/erts-*/bin directory executable,
  which is more convenient if a user wants to create a target Erlang system.
* Shortened extended description line for erlang-dev package to make it
  fit 80x25 terminals.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
 
%% ``The contents of this file are subject to the Erlang Public License,
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%% 
 
4
%% Copyright Ericsson AB 1997-2009. All Rights Reserved.
 
5
%% 
 
6
%% The contents of this file are subject to the Erlang Public License,
2
7
%% Version 1.1, (the "License"); you may not use this file except in
3
8
%% compliance with the License. You should have received a copy of the
4
9
%% Erlang Public License along with this software. If not, it can be
5
 
%% retrieved via the world wide web at http://www.erlang.org/.
 
10
%% retrieved online at http://www.erlang.org/.
6
11
%% 
7
12
%% Software distributed under the License is distributed on an "AS IS"
8
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
9
14
%% the License for the specific language governing rights and limitations
10
15
%% under the License.
11
16
%% 
12
 
%% The Initial Developer of the Original Code is Ericsson Utvecklings AB.
13
 
%% Portions created by Ericsson are Copyright 1999, Ericsson Utvecklings
14
 
%% AB. All Rights Reserved.''
15
 
%% 
16
 
%%     $Id$
 
17
%% %CopyrightEnd%
17
18
%%
18
19
-module(inet6_udp).
19
20
 
36
37
 
37
38
open(Port) -> open(Port, []).
38
39
 
39
 
open(Port, Opts) when is_integer(Port), Port >= 0, Port =< 65535 ->
 
40
open(Port, Opts) ->
40
41
    case inet:udp_options([{port,Port} | Opts], inet6) of
41
42
        {error, Reason} -> exit(Reason);
42
 
        {ok, R} ->
43
 
            Fd       = R#udp_opts.fd,
44
 
            BAddr    = R#udp_opts.ifaddr,
45
 
            BPort    = R#udp_opts.port,
46
 
            SockOpts = R#udp_opts.opts,
47
 
            inet:open(Fd,BAddr,BPort,SockOpts,udp,inet6,?MODULE)
 
43
        {ok, #udp_opts{fd=Fd,
 
44
                       ifaddr=BAddr={A,B,C,D,E,F,G,H},
 
45
                       port=BPort,
 
46
                       opts=SockOpts}}
 
47
        when ?ip6(A,B,C,D,E,F,G,H), ?port(BPort) ->
 
48
            inet:open(Fd,BAddr,BPort,SockOpts,udp,inet6,?MODULE);
 
49
        {ok, _} -> exit(badarg)
48
50
    end.
49
51
 
50
 
send(S, Addr = {A,B,C,D,E,F,G,H}, P, Data) 
51
 
  when ?ip6(A,B,C,D,E,F,G,H), is_integer(P), P > 0, P =< 65535 ->
 
52
send(S, Addr = {A,B,C,D,E,F,G,H}, P, Data)
 
53
  when ?ip6(A,B,C,D,E,F,G,H), ?port(P) ->
52
54
    prim_inet:sendto(S, Addr, P, Data).
53
55
 
54
56
send(S, Data) ->
55
57
    prim_inet:sendto(S, {0,0,0,0,0,0,0,0}, 0, Data).
56
58
    
57
59
connect(S, Addr = {A,B,C,D,E,F,G,H}, P) 
58
 
  when ?ip6(A,B,C,D,E,F,G,H), is_integer(P), P > 0, P =< 65535 ->
 
60
  when ?ip6(A,B,C,D,E,F,G,H), ?port(P) ->
59
61
    prim_inet:connect(S, Addr, P).
60
62
 
61
63
recv(S,Len) ->