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

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Soren Hansen
  • Date: 2007-05-01 16:57:10 UTC
  • mfrom: (1.1.9 upstream)
  • Revision ID: james.westby@ubuntu.com-20070501165710-2sapk0hp2gf3o0ip
Tags: 1:11.b.4-2ubuntu1
* Merge with Debian Unstable. Remaining changes:
  - Add -fno-stack-protector to fix broken crypto_drv.
* DebianMaintainerField update.

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,
 
2
%% Version 1.1, (the "License"); you may not use this file except in
 
3
%% compliance with the License. You should have received a copy of the
 
4
%% Erlang Public License along with this software. If not, it can be
 
5
%% retrieved via the world wide web at http://www.erlang.org/.
 
6
%% 
 
7
%% Software distributed under the License is distributed on an "AS IS"
 
8
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
9
%% the License for the specific language governing rights and limitations
 
10
%% under the License.
 
11
%% 
 
12
%% The Initial Developer of the Original Code is Ericsson Utvecklings AB.
 
13
%% Portions created by Ericsson are Copyright 2007, Ericsson Utvecklings
 
14
%% AB. All Rights Reserved.''
 
15
%% 
 
16
%% The SCTP protocol was added 2006
 
17
%% by Leonid Timochouk <l.timochouk@gmail.com>
 
18
%% and Serge Aleynikov  <serge@hq.idt.net>
 
19
%% at IDT Corp. Adapted by the OTP team at Ericsson AB.
 
20
%%
 
21
%%     $Id$
 
22
%%
 
23
-module(inet_sctp).
 
24
 
 
25
%% This module provides functions for communicating with
 
26
%% sockets using the SCTP protocol.  The implementation assumes that
 
27
%% the OS kernel supports SCTP providing user-level SCTP Socket API:
 
28
%%     http://tools.ietf.org/html/draft-ietf-tsvwg-sctpsocket-13
 
29
 
 
30
-include("inet_sctp.hrl").
 
31
-include("inet_int.hrl").
 
32
 
 
33
-define(FAMILY, inet).
 
34
-export([getserv/1,getaddr/2,translate_ip/1]).
 
35
-export([open/1,close/1,listen/2,connect/5,sendmsg/3,recv/2]).
 
36
 
 
37
 
 
38
 
 
39
getserv(Port) when Port band 16#ffff =:= Port -> {ok, Port};
 
40
getserv(Name) when atom(Name) ->
 
41
    inet:getservbyname(Name, sctp);
 
42
getserv(_) ->
 
43
    {error,einval}.
 
44
 
 
45
getaddr(Address, Timer) ->
 
46
    inet:getaddr_tm(Address, ?FAMILY, Timer).
 
47
 
 
48
translate_ip(IP) ->
 
49
    inet:translate_ip(IP, ?FAMILY).
 
50
 
 
51
 
 
52
    
 
53
open(Opts) ->
 
54
    case inet:sctp_options(Opts, ?MODULE) of
 
55
        {ok,#sctp_opts{fd=Fd,ifaddr=Addr,port=Port,opts=SOs}} ->
 
56
            inet:open(Fd, Addr, Port, SOs, sctp, ?FAMILY, ?MODULE);
 
57
        Error -> Error
 
58
    end.
 
59
 
 
60
close(S) ->
 
61
    prim_inet:close(S).
 
62
 
 
63
listen(S, Flag) ->
 
64
    prim_inet:listen(S, Flag).
 
65
        
 
66
connect(S, Addr, Port, Opts, Timer) ->
 
67
    case prim_inet:chgopts(S, Opts) of
 
68
        ok ->
 
69
            Timeout = inet:timeout(Timer),
 
70
            case prim_inet:connect(S, Addr, Port, Timeout) of
 
71
                ok ->
 
72
                    connect_get_assoc(S, Addr, Port, Timer);
 
73
                Error -> Error
 
74
            end;
 
75
        Error -> Error
 
76
    end.
 
77
 
 
78
connect_get_assoc(S, Addr, Port, Timer) ->
 
79
    case recv(S, inet:timeout(Timer)) of
 
80
        {ok, {Addr, Port, [], Ev = #sctp_assoc_change{}}} ->
 
81
            %% Yes, got Assoc Change on this destination:
 
82
            %% check the status:
 
83
            case Ev of
 
84
                #sctp_assoc_change{state=comm_up} ->
 
85
                    %% Yes, successfully connected, return the whole
 
86
                    %% sctp_assoc_change event (containing, in particular,
 
87
                    %% the AssocID).
 
88
                    %% NB: we consider the connection to be successful
 
89
                    %% even if the number of OutStreams is not the same
 
90
                    %% as requested by the user:
 
91
                    {ok,Ev};
 
92
                _ ->
 
93
                    %% Any other event: Error:
 
94
                    {error,Ev}
 
95
            end;
 
96
    % Any other message received instead of that Assoc Change:
 
97
    % currently treated as an error:
 
98
    {error,_}=Error ->
 
99
        Error;
 
100
    Hmm ->
 
101
        % FIXME: this should never happen
 
102
        {error,Hmm}
 
103
    end.
 
104
 
 
105
sendmsg(S, SRI, Data) ->
 
106
    prim_inet:sendmsg(S, SRI, Data).
 
107
 
 
108
recv(S, Timeout) ->
 
109
    prim_inet:recvfrom(S, 0, Timeout).