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

« back to all changes in this revision

Viewing changes to erts/epmd/test/epmd_SUITE.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2010-03-09 17:34:57 UTC
  • mfrom: (10.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20100309173457-4yd6hlcb2osfhx31
Tags: 1:13.b.4-dfsg-3
Manpages in section 1 are needed even if only arch-dependent packages are
built. So, re-enabled them.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%%
2
2
%% %CopyrightBegin%
3
 
%% 
4
 
%% Copyright Ericsson AB 1998-2009. All Rights Reserved.
5
 
%% 
 
3
%%
 
4
%% Copyright Ericsson AB 1998-2010. All Rights Reserved.
 
5
%%
6
6
%% The contents of this file are subject to the Erlang Public License,
7
7
%% Version 1.1, (the "License"); you may not use this file except in
8
8
%% compliance with the License. You should have received a copy of the
9
9
%% Erlang Public License along with this software. If not, it can be
10
10
%% retrieved online at http://www.erlang.org/.
11
 
%% 
 
11
%%
12
12
%% Software distributed under the License is distributed on an "AS IS"
13
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
14
14
%% the License for the specific language governing rights and limitations
15
15
%% under the License.
16
 
%% 
 
16
%%
17
17
%% %CopyrightEnd%
18
18
%%
19
19
-module(epmd_SUITE).
31
31
-define(MEDIUM_PAUSE, ?t:seconds(1)).
32
32
-define(LONG_PAUSE, ?t:seconds(5)).
33
33
 
 
34
% Information about nodes
 
35
-record(node_info, {port, node_type, prot, lvsn, hvsn, node_name, extra}).
 
36
 
34
37
% Test server specific exports
35
38
-export([all/1, init_per_testcase/2, fin_per_testcase/2]).
36
39
 
57
60
    too_large/1,
58
61
    alive_req_too_small_1/1,
59
62
    alive_req_too_small_2/1,
60
 
    alive_req_too_large/1
 
63
    alive_req_too_large/1,
 
64
 
 
65
    returns_valid_empty_extra/1,
 
66
    returns_valid_populated_extra_with_nulls/1
61
67
   ]).
62
68
 
63
69
 
76
82
-define(REG_REPEAT_LIM,1000).
77
83
 
78
84
% Message codes in epmd protocol
79
 
-define(EPMD_ALIVE_REQ, $a).
80
 
-define(EPMD_ALIVE_OK_RESP, $Y).
81
 
-define(EPMD_PORT_REQ,  $p).
 
85
-define(EPMD_ALIVE_REQ,         $a).
 
86
-define(EPMD_ALIVE2_REQ,        $x).
 
87
-define(EPMD_ALIVE_OK_RESP,     $Y).
 
88
-define(EPMD_ALIVE2_RESP,       $y).
 
89
-define(EPMD_PORT_REQ,          $p).
 
90
-define(EPMD_PORT_PLEASE2_REQ,  $z).
 
91
-define(EPMD_PORT2_RESP,        $w).
82
92
-define(EPMD_NAMES_REQ, $n).
83
93
-define(EPMD_DUMP_REQ,  $d).
84
94
-define(EPMD_KILL_REQ,  $k).
111
121
     too_large,
112
122
     alive_req_too_small_1,
113
123
     alive_req_too_small_2,
114
 
     alive_req_too_large
 
124
     alive_req_too_large,
 
125
 
 
126
     returns_valid_empty_extra,
 
127
     returns_valid_populated_extra_with_nulls
115
128
    ].
116
129
 
117
130
%%
182
195
    register_node(Name,?DUMMY_PORT).
183
196
 
184
197
register_node(Name, Port) ->
185
 
    case connect() of
186
 
        {ok,Sock} ->
187
 
            M = [?EPMD_ALIVE_REQ, put16(Port), Name],
188
 
            case send(Sock, [size16(M), M]) of
189
 
                ok ->
190
 
                    case recv(Sock,3) of
191
 
                        {ok, [?EPMD_ALIVE_OK_RESP,_D1,_D0]} ->
192
 
                            {ok,Sock};
193
 
                        Other ->
194
 
                            test_server:format("recv on sock ~w: ~p~n",
195
 
                                               [Sock,Other]),
196
 
                            error
197
 
                    end;
198
 
                Other ->
199
 
                    test_server:format("send on sock ~w: ~w~n",[Sock,Other]),
200
 
                    error
201
 
            end;
 
198
    case send_req([?EPMD_ALIVE_REQ, put16(Port), Name]) of
 
199
        {ok,Sock} ->
 
200
            case recv(Sock,3) of
 
201
                {ok, [?EPMD_ALIVE_OK_RESP,_D1,_D0]} ->
 
202
                    {ok,Sock};
 
203
                Other ->
 
204
                    test_server:format("recv on sock ~w: ~p~n",
 
205
                                       [Sock,Other]),
 
206
                    error
 
207
            end;
 
208
        error ->
 
209
            error
 
210
    end.
 
211
 
 
212
register_node_v2(Port, NodeType, Prot, HVsn, LVsn, Name, Extra) ->
 
213
    Req = [?EPMD_ALIVE2_REQ, put16(Port), NodeType, Prot,
 
214
           put16(HVsn), put16(LVsn),
 
215
           size16(Name), Name,
 
216
           size16(Extra), Extra],
 
217
    case send_req(Req) of
 
218
        {ok,Sock} ->
 
219
            case recv(Sock,4) of
 
220
                {ok, [?EPMD_ALIVE2_RESP,_Res=0,_C0,_C1]} ->
 
221
                    {ok,Sock};
 
222
                Other ->
 
223
                    test_server:format("recv on sock ~w: ~p~n",
 
224
                                       [Sock,Other]),
 
225
                    error
 
226
            end;
 
227
        error ->
 
228
            error
 
229
    end.
 
230
 
 
231
% Internal function to fetch information about a node
 
232
 
 
233
port_please_v2(Name) ->
 
234
    case send_req([?EPMD_PORT_PLEASE2_REQ, Name]) of
 
235
        {ok,Sock} ->
 
236
            case recv_until_sock_closes(Sock) of
 
237
                {ok, Resp} ->
 
238
                    parse_port2_resp(Resp);
 
239
                Other ->
 
240
                    test_server:format("recv on sock ~w: ~p~n",
 
241
                                       [Sock,Other]),
 
242
                    error
 
243
            end;
 
244
        error ->
 
245
            error
 
246
    end.
 
247
 
 
248
parse_port2_resp(Resp) ->
 
249
    case list_to_binary(Resp) of
 
250
        <<?EPMD_PORT2_RESP,Res,Port:16,NodeType,Prot,HVsn:16,LVsn:16,
 
251
          NLen:16,NodeName:NLen/binary,
 
252
          ELen:16,Extra:ELen/binary>> when Res =:= 0 ->
 
253
            {ok, #node_info{port=Port,node_type=NodeType,prot=Prot,
 
254
                            hvsn=HVsn,lvsn=LVsn,
 
255
                            node_name=binary_to_list(NodeName),
 
256
                            extra=binary_to_list(Extra)}};
202
257
        Other ->
203
 
            test_server:format("Connect on port ~w: ~p~n",[Port,Other]),
 
258
            test_server:format("invalid port2 resp: ~p~n",
 
259
                               [Resp]),
204
260
            error
205
261
    end.
206
262
 
207
 
 
208
 
 
209
263
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
210
264
 
211
265
name_with_null_inside(doc) ->
631
685
    ok.
632
686
 
633
687
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
688
 
 
689
returns_valid_empty_extra(doc) ->
 
690
    ["Check that an empty extra is prefixed by a two byte length"];
 
691
returns_valid_empty_extra(suite) ->
 
692
    [];
 
693
returns_valid_empty_extra(Config) when list(Config) ->
 
694
    ?line ok = epmdrun(),
 
695
    ?line {ok,Sock} = register_node_v2(4711, 72, 0, 5, 5, "foo", []),
 
696
    ?line {ok,#node_info{extra=[]}} = port_please_v2("foo"),
 
697
    ?line ok = close(Sock),
 
698
    ok.
 
699
 
 
700
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
701
 
 
702
returns_valid_populated_extra_with_nulls(doc) ->
 
703
    ["Check a populated extra with embedded null characters"];
 
704
returns_valid_populated_extra_with_nulls(suite) ->
 
705
    [];
 
706
returns_valid_populated_extra_with_nulls(Config) when list(Config) ->
 
707
    ?line ok = epmdrun(),
 
708
    ?line {ok,Sock} = register_node_v2(4711, 72, 0, 5, 5, "foo", "ABC\000\000"),
 
709
    ?line {ok,#node_info{extra="ABC\000\000"}} = port_please_v2("foo"),
 
710
    ?line ok = close(Sock),
 
711
    ok.
 
712
 
 
713
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
634
714
% Terminate all tests with killing epmd.
635
715
 
636
716
cleanup() ->
813
893
            Any
814
894
    end.
815
895
 
 
896
send_req(Req) ->
 
897
    case connect() of
 
898
        {ok,Sock} ->
 
899
            case send(Sock, [size16(Req), Req]) of
 
900
                ok ->
 
901
                    {ok,Sock};
 
902
                Other ->
 
903
                    test_server:format("Failed to send ~w on sock ~w: ~w~n",
 
904
                                       [Req,Sock,Other]),
 
905
                    error
 
906
            end;
 
907
        Other ->
 
908
            test_server:format("Connect failed when sending ~w: ~p~n",
 
909
                               [Req, Other]),
 
910
            error
 
911
    end.
 
912
 
 
913
recv_until_sock_closes(Sock) ->
 
914
    recv_until_sock_closes_2(Sock,[]).
 
915
 
 
916
recv_until_sock_closes_2(Sock,AccData) ->
 
917
    case recv(Sock,0) of
 
918
        {ok,Data} ->
 
919
            recv_until_sock_closes_2(Sock,AccData++Data);
 
920
        closed ->
 
921
            {ok,AccData};
 
922
        Other ->
 
923
            Other
 
924
    end.
 
925
 
816
926
sleep(MilliSeconds) ->
817
927
    timer:sleep(MilliSeconds).
818
928