]> granicus.if.org Git - ejabberd/commitdiff
RFC5389 (STUN) support: stand-alone server, binding usage only
authorEvgeniy Khramtsov <xramtsov@gmail.com>
Sun, 9 Aug 2009 10:44:16 +0000 (10:44 +0000)
committerEvgeniy Khramtsov <xramtsov@gmail.com>
Sun, 9 Aug 2009 10:44:16 +0000 (10:44 +0000)
SVN Revision: 2450

src/ejabberd_listener.erl
src/ejabberd_sup.erl
src/stun/Makefile.in [new file with mode: 0644]
src/stun/Makefile.win32 [new file with mode: 0644]
src/stun/ejabberd_stun.erl [new file with mode: 0644]
src/stun/stun.hrl [new file with mode: 0644]
src/stun/stun_codec.erl [new file with mode: 0644]

index adffe66802edf2c8086d728051b8911191bf5258..f612723d8ff381be23faeceefe87fab4ecca233a 100644 (file)
@@ -96,8 +96,8 @@ start_dependent(Port, Module, Opts) ->
            {error, Error}
     end.
 
-init(PortIP, Module, Opts1) ->
-    {Port, IPT, IPS, IPV, OptsClean} = parse_listener_portip(PortIP, Opts1),
+init(PortIP, Module, RawOpts) ->
+    {Port, IPT, IPS, IPV, OptsClean} = parse_listener_portip(PortIP, RawOpts),
     %% The first inet|inet6 and the last {ip, _} work,
     %% so overriding those in Opts
     Opts = [IPV | OptsClean] ++ [{ip, IPT}],
@@ -106,6 +106,27 @@ init(PortIP, Module, Opts1) ->
                               (inet) -> true;
                               (_) -> false
                            end, Opts),
+    case lists:member(udp, RawOpts) of
+       true ->
+           init_udp(PortIP, Module, Opts, SockOpts, Port, IPS);
+       false ->
+           init_tcp(PortIP, Module, Opts, SockOpts, Port, IPS)
+    end.
+
+init_udp(PortIP, Module, Opts, SockOpts, Port, IPS) ->
+    case gen_udp:open(Port, [binary,
+                            {active, false},
+                            {reuseaddr, true} |
+                            SockOpts]) of
+       {ok, Socket} ->
+           %% Inform my parent that this port was opened succesfully
+           proc_lib:init_ack({ok, self()}),
+           udp_recv(Socket, Module, Opts);
+       {error, Reason} ->
+           socket_error(Reason, PortIP, Module, SockOpts, Port, IPS)
+    end.
+
+init_tcp(PortIP, Module, Opts, SockOpts, Port, IPS) ->
     Res = gen_tcp:listen(Port, [binary,
                                {packet, 0},
                                {active, false},
@@ -116,19 +137,12 @@ init(PortIP, Module, Opts1) ->
                                SockOpts]),
     case Res of
        {ok, ListenSocket} ->
-               %% Inform my parent that this port was opened succesfully
-               proc_lib:init_ack({ok, self()}),
-               %% And now start accepting connection attempts
+           %% Inform my parent that this port was opened succesfully
+           proc_lib:init_ack({ok, self()}),
+           %% And now start accepting connection attempts
            accept(ListenSocket, Module, Opts);
        {error, Reason} ->
-           ReasonT = case Reason of
-                         eaddrnotavail -> "IP address not available: " ++ IPS;
-                         eaddrinuse -> "IP address and port number already used: "++IPS++" "++integer_to_list(Port);
-                         _ -> atom_to_list(Reason)
-                     end,
-           ?ERROR_MSG("Failed to open socket:~n  ~p~nReason: ~s",
-                      [{Port, Module, SockOpts}, ReasonT]),
-           throw({Reason, PortIP})
+           socket_error(Reason, PortIP, Module, SockOpts, Port, IPS)
     end.
 
 %% @spec (PortIP, Opts) -> {Port, IPT, IPS, IPV, OptsClean}
@@ -215,6 +229,24 @@ accept(ListenSocket, Module, Opts) ->
            accept(ListenSocket, Module, Opts)
     end.
 
+udp_recv(Socket, Module, Opts) ->
+    case gen_udp:recv(Socket, 0) of
+       {ok, {Addr, Port, Packet}} ->
+           case catch Module:udp_recv(Socket, Addr, Port, Packet, Opts) of
+               {'EXIT', Reason} ->
+                   ?ERROR_MSG("failed to process UDP packet:~n"
+                              "** Source: {~p, ~p}~n"
+                              "** Reason: ~p~n** Packet: ~p",
+                              [Addr, Port, Reason, Packet]);
+               _ ->
+                   ok
+           end,
+           udp_recv(Socket, Module, Opts);
+       {error, Reason} ->
+           ?ERROR_MSG("unexpected UDP error: ~s", [format_error(Reason)]),
+           throw({error, Reason})
+    end.
+
 %% @spec (Port, Module, Opts) -> {ok, Pid} | {error, Error}
 start_listener(Port, Module, Opts) ->
     case start_listener2(Port, Module, Opts) of
@@ -368,3 +400,25 @@ certfile_readable(Opts) ->
                false -> {false, Path}
            end
     end.
+
+socket_error(Reason, PortIP, Module, SockOpts, Port, IPS) ->
+    ReasonT = case Reason of
+                 eaddrnotavail ->
+                     "IP address not available: " ++ IPS;
+                 eaddrinuse ->
+                     "IP address and port number already used: "
+                         ++IPS++" "++integer_to_list(Port);
+                 _ ->
+                     format_error(Reason)
+             end,
+    ?ERROR_MSG("Failed to open socket:~n  ~p~nReason: ~s",
+              [{Port, Module, SockOpts}, ReasonT]),
+    throw({Reason, PortIP}).
+
+format_error(Reason) ->
+    case inet:format_error(Reason) of
+       "unknown POSIX error" ->
+           atom_to_list(Reason);
+       ReasonStr ->
+           ReasonStr
+    end.
index 6163dfee0832c19082f36fbbb1da48ca7619eef6..11c56037c09f5d78dbc05d455dfefc98c010e828 100644 (file)
@@ -169,6 +169,14 @@ init([]) ->
         infinity,
         supervisor,
         [ejabberd_tmp_sup]},
+    STUNSupervisor =
+       {ejabberd_stun_sup,
+        {ejabberd_tmp_sup, start_link,
+         [ejabberd_stun_sup, ejabberd_stun]},
+        permanent,
+        infinity,
+        supervisor,
+        [ejabberd_tmp_sup]},
     {ok, {{one_for_one, 10, 1},
          [Hooks,
           NodeGroups,
@@ -186,6 +194,7 @@ init([]) ->
           HTTPSupervisor,
           HTTPPollSupervisor,
           IQSupervisor,
+          STUNSupervisor,
           FrontendSocketSupervisor,
           Listener]}}.
 
diff --git a/src/stun/Makefile.in b/src/stun/Makefile.in
new file mode 100644 (file)
index 0000000..e77da84
--- /dev/null
@@ -0,0 +1,38 @@
+# $Id: Makefile.in 1453 2008-07-16 16:58:42Z badlop $
+
+CC = @CC@
+CFLAGS = @CFLAGS@
+CPPFLAGS = @CPPFLAGS@
+LDFLAGS = @LDFLAGS@
+LIBS = @LIBS@
+
+ERLANG_CFLAGS = @ERLANG_CFLAGS@
+ERLANG_LIBS = @ERLANG_LIBS@
+
+EFLAGS += -I ..
+EFLAGS += -pz ..
+
+# make debug=true to compile Erlang module with debug informations.
+ifdef debug
+       EFLAGS+=+debug_info
+endif
+
+OUTDIR = ..
+SOURCES = $(wildcard *.erl)
+BEAMS = $(addprefix $(OUTDIR)/,$(SOURCES:.erl=.beam))
+
+
+all:    $(BEAMS)
+
+$(OUTDIR)/%.beam:       %.erl
+       @ERLC@ -W $(EFLAGS) -o $(OUTDIR) $<
+
+clean:
+       rm -f $(BEAMS)
+
+distclean: clean
+       rm -f Makefile
+
+TAGS:
+       etags *.erl
+
diff --git a/src/stun/Makefile.win32 b/src/stun/Makefile.win32
new file mode 100644 (file)
index 0000000..e70aba9
--- /dev/null
@@ -0,0 +1,18 @@
+
+include ..\Makefile.inc
+
+EFLAGS = -I .. -pz ..
+
+OUTDIR = ..
+BEAMS = ..\stun_codec.beam ..\ejabberd_stun.beam
+
+ALL : $(BEAMS)
+
+CLEAN :
+       -@erase $(BEAMS)
+
+$(OUTDIR)\stun_codec.beam : stun_codec.erl
+       erlc -W $(EFLAGS) -o $(OUTDIR) stun_codec.erl
+
+$(OUTDIR)\ejabberd_stun.beam : ejabberd_stun.erl
+       erlc -W $(EFLAGS) -o $(OUTDIR) ejabberd_stun.erl
diff --git a/src/stun/ejabberd_stun.erl b/src/stun/ejabberd_stun.erl
new file mode 100644 (file)
index 0000000..ca880c1
--- /dev/null
@@ -0,0 +1,261 @@
+%%%-------------------------------------------------------------------
+%%% File    : ejabberd_stun.erl
+%%% Author  : Evgeniy Khramtsov <ekhramtsov@process-one.net>
+%%% Description : RFC5389 implementation.
+%%%               Currently only Binding usage is supported.
+%%%
+%%% Created :  8 Aug 2009 by Evgeniy Khramtsov <ekhramtsov@process-one.net>
+%%%
+%%%
+%%% ejabberd, Copyright (C) 2002-2009   ProcessOne
+%%%
+%%% This program is free software; you can redistribute it and/or
+%%% modify it under the terms of the GNU General Public License as
+%%% published by the Free Software Foundation; either version 2 of the
+%%% License, or (at your option) any later version.
+%%%
+%%% This program is distributed in the hope that it will be useful,
+%%% but WITHOUT ANY WARRANTY; without even the implied warranty of
+%%% MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
+%%% General Public License for more details.
+%%%
+%%% You should have received a copy of the GNU General Public License
+%%% along with this program; if not, write to the Free Software
+%%% Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA
+%%% 02111-1307 USA
+%%%
+%%%-------------------------------------------------------------------
+-module(ejabberd_stun).
+
+-behaviour(gen_fsm).
+
+%% API
+-export([start_link/2,
+        start/2,
+        socket_type/0,
+        udp_recv/5]).
+
+%% gen_fsm callbacks
+-export([init/1,
+        handle_event/3,
+        handle_sync_event/4,
+        handle_info/3,
+        terminate/3,
+        code_change/4]).
+
+%% gen_fsm states
+-export([wait_for_tls/2,
+        session_established/2]).
+
+-include("ejabberd.hrl").
+-include("stun.hrl").
+
+-define(MAX_BUF_SIZE, 64*1024). %% 64kb
+-define(TIMEOUT, 10000). %% 10 sec
+
+-record(state, {sock,
+               sock_mod = gen_tcp,
+               certfile,
+               peer,
+               tref,
+               buf = <<>>}).
+
+%%====================================================================
+%% API
+%%====================================================================
+start({gen_tcp, Sock}, Opts) ->
+    supervisor:start_child(ejabberd_stun_sup, [Sock, Opts]).
+
+start_link(Sock, Opts) ->
+    gen_fsm:start_link(?MODULE, [Sock, Opts], []).
+
+socket_type() ->
+    raw.
+
+udp_recv(Sock, Addr, Port, Data, _Opts) ->
+    case stun_codec:decode(Data) of
+       {ok, Msg, <<>>} ->
+           ?DEBUG("got:~n~s", [stun_codec:pp(Msg)]),
+           case process(Addr, Port, Msg) of
+               RespMsg when is_record(RespMsg, stun) ->
+                   ?DEBUG("sent:~n~s", [stun_codec:pp(RespMsg)]),
+                   Data1 = stun_codec:encode(RespMsg),
+                   gen_udp:send(Sock, Addr, Port, Data1);
+               _ ->
+                   ok
+           end;
+       _ ->
+           ok
+    end.
+
+%%====================================================================
+%% gen_fsm callbacks
+%%====================================================================
+init([Sock, Opts]) ->
+    case inet:peername(Sock) of
+       {ok, Addr} ->
+           inet:setopts(Sock, [{active, once}]),
+           TRef = erlang:start_timer(?TIMEOUT, self(), stop),
+           State = #state{sock = Sock, peer = Addr, tref = TRef},
+           case proplists:get_value(certfile, Opts) of
+               undefined ->
+                   {ok, session_established, State};
+               CertFile ->
+                   {ok, wait_for_tls, State#state{certfile = CertFile}}
+           end;
+       Err ->
+           Err
+    end.
+
+wait_for_tls(Event, State) ->
+    ?INFO_MSG("unexpected event in wait_for_tls: ~p", [Event]),
+    {next_state, wait_for_tls, State}.
+
+session_established(Msg, State) when is_record(Msg, stun) ->
+    ?DEBUG("got:~n~s", [stun_codec:pp(Msg)]),
+    {Addr, Port} = State#state.peer,
+    case process(Addr, Port, Msg) of
+       Resp when is_record(Resp, stun) ->
+           ?DEBUG("sent:~n~s", [stun_codec:pp(Resp)]),
+           Data = stun_codec:encode(Resp),
+           (State#state.sock_mod):send(State#state.sock, Data);
+       _ ->
+           ok
+    end,
+    {next_state, session_established, State};
+session_established(Event, State) ->
+    ?INFO_MSG("unexpected event in session_established: ~p", [Event]),
+    {next_state, session_established, State}.
+
+handle_event(_Event, StateName, State) ->
+    {next_state, StateName, State}.
+
+handle_sync_event(_Event, _From, StateName, State) ->
+    {reply, {error, badarg}, StateName, State}.
+
+handle_info({tcp, Sock, TLSData}, wait_for_tls, State) ->
+    Buf = <<(State#state.buf)/binary, TLSData/binary>>,
+    %% Check if the initial message is a TLS handshake
+    case Buf of
+       _ when size(Buf) < 3 ->
+           {next_state, wait_for_tls,
+            update_state(State#state{buf = Buf})};
+       <<_:16, 1, _/binary>> ->
+           TLSOpts = [{certfile, State#state.certfile}],
+           {ok, TLSSock} = tls:tcp_to_tls(Sock, TLSOpts),
+           case tls:recv_data(TLSSock, Buf) of
+               {ok, Data} ->
+                   process_data(session_established,
+                                State#state{sock = TLSSock,
+                                            buf = <<>>,
+                                            sock_mod = tls},
+                                Data);
+               _Err ->
+                   {stop, normal, State}
+           end;
+       _ ->
+           process_data(session_established, State, TLSData)
+    end;
+handle_info({tcp, _Sock, TLSData}, StateName,
+           #state{sock_mod = tls} = State) ->
+    case tls:recv_data(State#state.sock, TLSData) of
+       {ok, Data} ->
+           process_data(StateName, State, Data);
+       _Err ->
+           {stop, normal, State}
+    end;
+handle_info({tcp, _Sock, Data}, StateName, State) ->
+    process_data(StateName, State, Data);
+handle_info({tcp_closed, _Sock}, _StateName, State) ->
+    ?DEBUG("connection reset by peer", []),
+    {stop, normal, State};
+handle_info({tcp_error, _Sock, Reason}, _StateName, State) ->
+    ?DEBUG("connection error: ~p", [Reason]),
+    {stop, normal, State};
+handle_info({timeout, TRef, stop}, _StateName,
+           #state{tref = TRef} = State) ->
+    {stop, normal, State};
+handle_info(Info, StateName, State) ->
+    ?INFO_MSG("unexpected info: ~p", [Info]),
+    {next_state, StateName, State}.
+
+terminate(_Reason, _StateName, State) ->
+    catch (State#state.sock_mod):close(State#state.sock),
+    ok.
+
+code_change(_OldVsn, StateName, State, _Extra) ->
+    {ok, StateName, State}.
+
+%%--------------------------------------------------------------------
+%%% Internal functions
+%%--------------------------------------------------------------------
+process(Addr, Port, #stun{class = request, unsupported = []} = Msg) ->
+    Resp = prepare_response(Msg),
+    if Msg#stun.method == ?STUN_METHOD_BINDING ->
+           case stun_codec:version(Msg) of
+               old ->
+                   Resp#stun{class = response,
+                             'MAPPED-ADDRESS' = {Addr, Port}};
+               new ->
+                   Resp#stun{class = response,
+                             'MAPPED-ADDRESS' = {Addr, Port},
+                             'XOR-MAPPED-ADDRESS' = {Addr, Port}}
+           end;
+       true ->
+           Resp#stun{class = error,
+                     'ERROR-CODE' = {405, <<"Method Not Allowed">>}}
+    end;
+process(_Addr, _Port, #stun{class = request} = Msg) ->
+    Resp = prepare_response(Msg),
+    Resp#stun{class = error,
+             'UNKNOWN-ATTRIBUTES' = Msg#stun.unsupported,
+             'ERROR-CODE' = {420, stun_codec:reason(420)}};
+process(_Addr, _Port, _Msg) ->
+    pass.
+
+prepare_response(Msg) ->
+    Version = list_to_binary("ejabberd " ++ ?VERSION),
+    #stun{method = Msg#stun.method,
+         magic = Msg#stun.magic,
+         trid = Msg#stun.trid,
+         'SOFTWARE' = Version}.
+
+process_data(NextStateName, #state{buf = Buf} = State, Data) ->
+    NewBuf = <<Buf/binary, Data/binary>>,
+    case stun_codec:decode(NewBuf) of
+       {ok, Msg, Tail} ->
+           gen_fsm:send_event(self(), Msg),
+           process_data(NextStateName, State#state{buf = <<>>}, Tail);
+       empty ->
+           NewState = State#state{buf = <<>>},
+           {next_state, NextStateName, update_state(NewState)};
+       more when size(NewBuf) < ?MAX_BUF_SIZE ->
+           NewState = State#state{buf = NewBuf},
+           {next_state, NextStateName, update_state(NewState)};
+       _ ->
+           {stop, normal, State}
+    end.
+
+update_state(#state{sock = Sock} = State) ->
+    case State#state.sock_mod of
+       gen_tcp ->
+           inet:setopts(Sock, [{active, once}]);
+       SockMod ->
+           SockMod:setopts(Sock, [{active, once}])
+    end,
+    cancel_timer(State#state.tref),
+    TRef = erlang:start_timer(?TIMEOUT, self(), stop),
+    State#state{tref = TRef}.
+
+cancel_timer(TRef) ->
+    case erlang:cancel_timer(TRef) of
+       false ->
+           receive
+                {timeout, TRef, _} ->
+                    ok
+            after 0 ->
+                    ok
+            end;
+        _ ->
+            ok
+    end.
diff --git a/src/stun/stun.hrl b/src/stun/stun.hrl
new file mode 100644 (file)
index 0000000..c221844
--- /dev/null
@@ -0,0 +1,78 @@
+%%%-------------------------------------------------------------------
+%%% File    : stun.hrl
+%%% Author  : Evgeniy Khramtsov <ekhramtsov@process-one.net>
+%%% Description : STUN values
+%%% Created :  8 Aug 2009 by Evgeniy Khramtsov <ekhramtsov@process-one.net>
+%%%
+%%%
+%%% ejabberd, Copyright (C) 2002-2009   ProcessOne
+%%%
+%%% This program is free software; you can redistribute it and/or
+%%% modify it under the terms of the GNU General Public License as
+%%% published by the Free Software Foundation; either version 2 of the
+%%% License, or (at your option) any later version.
+%%%
+%%% This program is distributed in the hope that it will be useful,
+%%% but WITHOUT ANY WARRANTY; without even the implied warranty of
+%%% MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
+%%% General Public License for more details.
+%%%
+%%% You should have received a copy of the GNU General Public License
+%%% along with this program; if not, write to the Free Software
+%%% Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA
+%%% 02111-1307 USA
+%%%
+%%%-------------------------------------------------------------------
+-define(STUN_MAGIC, 16#2112a442).
+
+%% I know, this is terrible. Refer to 'STUN Message Structure' of
+%% RFC5389 to understand this.
+-define(STUN_METHOD(Type),
+       ((Type band 16#3e00) bsr 2) bor
+       ((Type band 16#e0) bsr 1) bor (Type band 16#f)).
+-define(STUN_CLASS(Type),
+       ((Type band 16#100) bsr 7) bor
+       ((Type band 16#10) bsr 4)).
+-define(STUN_TYPE(C, M),
+       (((M band 16#f80) bsl 2)
+        bor ((M band 16#70) bsl 1)
+        bor (M band 16#f) )
+       bor (((C band 16#2) bsl 7) bor ((C band 16#1) bsl 4))).
+
+-define(is_required(A), (A =< 16#7fff)).
+
+-define(STUN_METHOD_BINDING, 16#001).
+
+%% Comprehension-required range (0x0000-0x7FFF)
+-define(STUN_ATTR_MAPPED_ADDRESS, 16#0001).
+-define(STUN_ATTR_USERNAME, 16#0006).
+-define(STUN_ATTR_MESSAGE_INTEGRITY, 16#0008).
+-define(STUN_ATTR_ERROR_CODE, 16#0009).
+-define(STUN_ATTR_UNKNOWN_ATTRIBUTES, 16#000a).
+-define(STUN_ATTR_REALM, 16#0014).
+-define(STUN_ATTR_NONCE, 16#0015).
+-define(STUN_ATTR_XOR_MAPPED_ADDRESS, 16#0020).
+
+%% Comprehension-optional range (0x8000-0xFFFF)
+-define(STUN_ATTR_SOFTWARE, 16#8022).
+-define(STUN_ATTR_ALTERNATE_SERVER, 16#8023).
+-define(STUN_ATTR_FINGERPRINT, 16#8028).
+
+-record(stun, {class,
+              method,
+              magic = ?STUN_MAGIC,
+              trid,
+              unsupported = [],
+              'SOFTWARE',
+              'ALTERNATE-SERVER',
+              'MAPPED-ADDRESS',
+              'XOR-MAPPED-ADDRESS',
+              'USERNAME',
+              'REALM',
+              'NONCE',
+              'MESSAGE-INTEGRITY',
+              'ERROR-CODE',
+              'UNKNOWN-ATTRIBUTES' = []}).
+
+%% Workarounds.
+%%-define(NO_PADDING, true).
diff --git a/src/stun/stun_codec.erl b/src/stun/stun_codec.erl
new file mode 100644 (file)
index 0000000..2539da9
--- /dev/null
@@ -0,0 +1,343 @@
+%%%-------------------------------------------------------------------
+%%% File    : stun_codec.erl
+%%% Author  : Evgeniy Khramtsov <ekhramtsov@process-one.net>
+%%% Description : STUN codec
+%%% Created :  7 Aug 2009 by Evgeniy Khramtsov <ekhramtsov@process-one.net>
+%%%
+%%%
+%%% ejabberd, Copyright (C) 2002-2009   ProcessOne
+%%%
+%%% This program is free software; you can redistribute it and/or
+%%% modify it under the terms of the GNU General Public License as
+%%% published by the Free Software Foundation; either version 2 of the
+%%% License, or (at your option) any later version.
+%%%
+%%% This program is distributed in the hope that it will be useful,
+%%% but WITHOUT ANY WARRANTY; without even the implied warranty of
+%%% MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
+%%% General Public License for more details.
+%%%
+%%% You should have received a copy of the GNU General Public License
+%%% along with this program; if not, write to the Free Software
+%%% Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA
+%%% 02111-1307 USA
+%%%
+%%%-------------------------------------------------------------------
+-module(stun_codec).
+
+%% API
+-export([decode/1,
+        encode/1,
+        version/1,
+        reason/1,
+        pp/1]).
+
+%% Tests
+-export([test_udp/2,
+        test_tcp/2,
+        test_tls/2,
+        test_public/0]).
+
+-include("stun.hrl").
+
+%%====================================================================
+%% API
+%%====================================================================
+decode(<<0:2, Type:14, Len:16, Magic:32, TrID:96,
+       Body:Len/binary, Tail/binary>>) ->
+    case catch decode(Type, Magic, TrID, Body) of
+       {'EXIT', _} ->
+           {error, unparsed};
+       Res ->
+           {ok, Res, Tail}
+    end;
+decode(<<0:2, _/binary>>) ->
+    more;
+decode(<<>>) ->
+    empty;
+decode(_) ->
+    {error, unparsed}.
+
+encode(#stun{class = Class,
+            method = Method,
+            magic = Magic,
+            trid = TrID} = Msg) ->
+    ClassCode = case Class of
+                   request -> 0;
+                   indication -> 1;
+                   response -> 2;
+                   error -> 3
+               end,
+    Type = ?STUN_TYPE(ClassCode, Method),
+    Attrs = enc_attrs(Msg),
+    Len = size(Attrs),
+    <<0:2, Type:14, Len:16, Magic:32, TrID:96, Attrs/binary>>.
+
+pp(Term) ->
+    io_lib_pretty:print(Term, fun pp/2).
+
+version(#stun{magic = ?STUN_MAGIC}) ->
+    new;
+version(#stun{}) ->
+    old.
+
+reason(300) -> <<"Try Alternate">>;
+reason(400) -> <<"Bad Request">>;
+reason(401) -> <<"Unauthorized">>;
+reason(420) -> <<"Unknown Attribute">>;
+reason(438) -> <<"Stale Nonce">>;
+reason(500) -> <<"Server Error">>;
+reason(_) -> <<"Undefined Error">>.
+
+%%====================================================================
+%% Internal functions
+%%====================================================================
+decode(Type, Magic, TrID, Body) ->
+    Method = ?STUN_METHOD(Type),
+    Class = case ?STUN_CLASS(Type) of
+               0 -> request;
+               1 -> indication;
+               2 -> response;
+               3 -> error
+           end,
+    dec_attrs(Body, #stun{class = Class,
+                         method = Method,
+                         magic = Magic,
+                         trid = TrID}).
+
+dec_attrs(<<Type:16, Len:16, Rest/binary>>, Msg) ->
+    PaddLen = padd_len(Len),
+    <<Val:Len/binary, _:PaddLen, Tail/binary>> = Rest,
+    NewMsg = dec_attr(Type, Val, Msg),
+    if Type == ?STUN_ATTR_MESSAGE_INTEGRITY ->
+           NewMsg;
+       true ->
+           dec_attrs(Tail, NewMsg)
+    end;
+dec_attrs(<<>>, Msg) ->
+    Msg.
+
+enc_attrs(Msg) ->
+    concat_binary(
+      [enc_attr(?STUN_ATTR_SOFTWARE, Msg#stun.'SOFTWARE'),
+       enc_addr(?STUN_ATTR_MAPPED_ADDRESS, Msg#stun.'MAPPED-ADDRESS'),
+       enc_xor_addr(?STUN_ATTR_XOR_MAPPED_ADDRESS,
+                   Msg#stun.magic, Msg#stun.trid,
+                   Msg#stun.'XOR-MAPPED-ADDRESS'),
+       enc_addr(?STUN_ATTR_ALTERNATE_SERVER, Msg#stun.'ALTERNATE-SERVER'),
+       enc_attr(?STUN_ATTR_USERNAME, Msg#stun.'USERNAME'),
+       enc_attr(?STUN_ATTR_REALM, Msg#stun.'REALM'),
+       enc_attr(?STUN_ATTR_NONCE, Msg#stun.'NONCE'),
+       enc_error_code(Msg#stun.'ERROR-CODE'),
+       enc_unknown_attrs(Msg#stun.'UNKNOWN-ATTRIBUTES')]).
+
+dec_attr(?STUN_ATTR_MAPPED_ADDRESS, Val, Msg) ->
+    <<_, Family, Port:16, AddrBin/binary>> = Val,
+    Addr = dec_addr(Family, AddrBin),
+    Msg#stun{'MAPPED-ADDRESS' = {Addr, Port}};
+dec_attr(?STUN_ATTR_XOR_MAPPED_ADDRESS, Val, Msg) ->
+    <<_, Family, XPort:16, XAddr/binary>> = Val,
+    Magic = Msg#stun.magic,
+    Port = XPort bxor (Magic bsr 16),
+    Addr = dec_xor_addr(Family, Magic, Msg#stun.trid, XAddr),
+    Msg#stun{'XOR-MAPPED-ADDRESS' = {Addr, Port}};
+dec_attr(?STUN_ATTR_SOFTWARE, Val, Msg) ->
+    Msg#stun{'SOFTWARE' = Val};
+dec_attr(?STUN_ATTR_USERNAME, Val, Msg) ->
+    Msg#stun{'USERNAME' = Val};
+dec_attr(?STUN_ATTR_REALM, Val, Msg) ->
+    Msg#stun{'REALM' = Val};
+dec_attr(?STUN_ATTR_NONCE, Val, Msg) ->
+    Msg#stun{'NONCE' = Val};
+dec_attr(?STUN_ATTR_MESSAGE_INTEGRITY, Val, Msg) ->
+    Msg#stun{'MESSAGE-INTEGRITY' = Val};
+dec_attr(?STUN_ATTR_ALTERNATE_SERVER, Val, Msg) ->
+    <<_, Family, Port:16, Address/binary>> = Val,
+    IP = dec_addr(Family, Address),
+    Msg#stun{'ALTERNATE-SERVER' = {IP, Port}};
+dec_attr(?STUN_ATTR_ERROR_CODE, Val, Msg) ->
+    <<_:21, Class:3, Number:8, Reason/binary>> = Val,
+    if Class >=3, Class =< 6, Number >=0, Number =< 99 ->
+           Code = Class * 100 + Number,
+           Msg#stun{'ERROR-CODE' = {Code, Reason}}
+    end;
+dec_attr(?STUN_ATTR_UNKNOWN_ATTRIBUTES, Val, Msg) ->
+    Attrs = dec_unknown_attrs(Val, []),
+    Msg#stun{'UNKNOWN-ATTRIBUTES' = Attrs};
+dec_attr(Attr, _Val, #stun{unsupported = Attrs} = Msg)
+  when Attr =< 16#7fff ->
+    Msg#stun{unsupported = [Attr|Attrs]};
+dec_attr(_Attr, _Val, Msg) ->
+    Msg.
+
+dec_addr(1, <<A1, A2, A3, A4>>) ->
+    {A1, A2, A3, A4};
+dec_addr(2, <<A1:16, A2:16, A3:16, A4:16,
+            A5:16, A6:16, A7:16, A8:16>>) ->
+    {A1, A2, A3, A4, A5, A6, A7, A8}.
+
+dec_xor_addr(1, Magic, _TrID, <<XAddr:32>>) ->
+    Addr = XAddr bxor Magic,
+    dec_addr(1, <<Addr:32>>);
+dec_xor_addr(2, Magic, TrID, <<XAddr:128>>) ->
+    Addr = XAddr bxor ((Magic bsl 96) bor TrID),
+    dec_addr(2, <<Addr:128>>).
+
+dec_unknown_attrs(<<Attr:16, Tail/binary>>, Acc) ->
+    dec_unknown_attrs(Tail, [Attr|Acc]);
+dec_unknown_attrs(<<>>, Acc) ->
+    lists:reverse(Acc).
+
+enc_attr(_Attr, undefined) ->
+    <<>>;
+enc_attr(Attr, Val) ->
+    Len = size(Val),
+    PaddLen = padd_len(Len),
+    <<Attr:16, Len:16, Val/binary, 0:PaddLen>>.
+
+enc_addr(_Type, undefined) ->
+    <<>>;
+enc_addr(Type, {{A1, A2, A3, A4}, Port}) ->
+    enc_attr(Type, <<0, 1, Port:16, A1, A2, A3, A4>>);
+enc_addr(Type, {{A1, A2, A3, A4, A5, A6, A7, A8}, Port}) ->
+    enc_attr(Type, <<0, 2, Port:16, A1:16, A2:16, A3:16,
+                   A4:16, A5:16, A6:16, A7:16, A8:16>>).
+
+enc_xor_addr(_Type, _Magic, _TrID, undefined) ->
+    <<>>;
+enc_xor_addr(Type, Magic, _TrID, {{A1, A2, A3, A4}, Port}) ->
+    XPort = Port bxor (Magic bsr 16),
+    <<Addr:32>> = <<A1, A2, A3, A4>>,
+    XAddr = Addr bxor Magic,
+    enc_attr(Type, <<0, 1, XPort:16, XAddr:32>>);
+enc_xor_addr(Type, Magic, TrID,
+            {{A1, A2, A3, A4, A5, A6, A7, A8}, Port}) ->
+    XPort = Port bxor (Magic bsr 16),
+    <<Addr:128>> = <<A1:16, A2:16, A3:16, A4:16,
+                   A5:16, A6:16, A7:16, A8:16>>,
+    XAddr = Addr bxor ((Magic bsl 96) bor TrID),
+    enc_attr(Type, <<0, 2, XPort:16, XAddr:128>>).
+
+enc_error_code(undefined) ->
+    <<>>;
+enc_error_code({Code, Reason}) ->
+    Class = Code div 100,
+    Number = Code rem 100,
+    enc_attr(?STUN_ATTR_ERROR_CODE,
+            <<0:21, Class:3, Number:8, Reason/binary>>).
+
+enc_unknown_attrs([]) ->
+    <<>>;
+enc_unknown_attrs(Attrs) ->
+    enc_attr(?STUN_ATTR_UNKNOWN_ATTRIBUTES,
+            concat_binary([<<Attr:16>> || Attr <- Attrs])).
+
+%%====================================================================
+%% Auxiliary functions
+%%====================================================================
+pp(Tag, N) ->
+    try
+       pp1(Tag, N)
+    catch _:_ ->
+           no
+    end.
+
+pp1(stun, N) ->
+    N = record_info(size, stun) - 1,
+    record_info(fields, stun);
+pp1(_, _) ->
+    no.
+
+%% Workaround for stupid clients.
+-ifdef(NO_PADDING).
+padd_len(_Len) ->
+    0.
+-else.
+padd_len(Len) ->
+    case Len rem 4 of
+       0 -> 0;
+       N -> 8*(4-N)
+    end.
+-endif.
+
+%%====================================================================
+%% Test functions
+%%====================================================================
+bind_msg() ->
+    Msg = #stun{method = ?STUN_METHOD_BINDING,
+               class = request,
+               trid = random:uniform(1 bsl 96),
+               'SOFTWARE' = <<"test">>},
+    encode(Msg).
+
+test_udp(Addr, Port) ->
+    test(Addr, Port, gen_udp).
+
+test_tcp(Addr, Port) ->
+    test(Addr, Port, gen_tcp).
+
+test_tls(Addr, Port) ->
+    test(Addr, Port, ssl).
+
+test(Addr, Port, Mod) ->
+    Res = case Mod of
+             gen_udp ->
+                 Mod:open(0, [binary, {active, false}]);
+             _ ->
+                 Mod:connect(Addr, Port,
+                             [binary, {active, false}], 1000)
+         end,
+    case Res of
+       {ok, Sock} ->
+           if Mod == gen_udp ->
+                   Mod:send(Sock, Addr, Port, bind_msg());
+              true ->
+                   Mod:send(Sock, bind_msg())
+           end,
+           case Mod:recv(Sock, 0, 1000) of
+               {ok, {_, _, Data}} ->
+                   try_dec(Data);
+               {ok, Data} ->
+                   try_dec(Data);
+               Err ->
+                   io:format("err: ~p~n", [Err])
+           end,
+           Mod:close(Sock);
+       Err ->
+           io:format("err: ~p~n", [Err])
+    end.
+
+try_dec(Data) ->
+    case decode(Data) of
+       {ok, Msg, _} ->
+           io:format("got:~n~s~n", [pp(Msg)]);
+       Err ->
+           io:format("err: ~p~n", [Err])
+    end.
+
+public_servers() ->
+    [{"stun.ekiga.net", 3478, 3478, 5349},
+     {"stun.fwdnet.net", 3478, 3478, 5349},
+     {"stun.ideasip.com", 3478, 3478, 5349},
+     {"stun01.sipphone.com", 3478, 3478, 5349},
+     {"stun.softjoys.com", 3478, 3478, 5349},
+     {"stun.voipbuster.com", 3478, 3478, 5349},
+     {"stun.voxgratia.org", 3478, 3478, 5349},
+     {"stun.xten.com", 3478, 3478, 5349},
+     {"stunserver.org", 3478, 3478, 5349},
+     {"stun.sipgate.net", 10000, 10000, 5349},
+     {"numb.viagenie.ca", 3478, 3478, 5349},
+     {"stun.ipshka.com", 3478, 3478, 5349},
+     {"localhost", 3478, 5349, 5349}].
+
+test_public() ->
+    ssl:start(),
+    lists:foreach(
+      fun({Addr, UDPPort, TCPPort, TLSPort}) ->
+             io:format("trying ~s:~p on UDP... ", [Addr, UDPPort]),
+             test_udp(Addr, UDPPort),
+             io:format("trying ~s:~p on TCP... ", [Addr, TCPPort]),
+             test_tcp(Addr, TCPPort),
+             io:format("trying ~s:~p on TLS... ", [Addr, TLSPort]),
+             test_tls(Addr, TLSPort)
+      end, public_servers()).