~ubuntu-branches/ubuntu/trusty/erlang/trusty

« back to all changes in this revision

Viewing changes to lib/inets/test/tftp_SUITE.erl

  • Committer: Bazaar Package Importer
  • Author(s): Clint Byrum
  • Date: 2011-05-05 15:48:43 UTC
  • mfrom: (3.5.13 sid)
  • Revision ID: james.westby@ubuntu.com-20110505154843-0om6ekzg6m7ugj27
Tags: 1:14.b.2-dfsg-3ubuntu1
* Merge from debian unstable.  Remaining changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to.
  - Drop erlang-wx binary.
  - Drop erlang-wx dependency from -megaco, -common-test, and -reltool, they
    do not really need wx. Also drop it from -debugger; the GUI needs wx,
    but it apparently has CLI bits as well, and is also needed by -megaco,
    so let's keep the package for now.
  - debian/patches/series: Do what I meant, and enable build-options.patch
    instead.
* Additional changes:
  - Drop erlang-wx from -et
* Dropped Changes:
  - patches/pcre-crash.patch: CVE-2008-2371: outer level option with
    alternatives caused crash. (Applied Upstream)
  - fix for ssl certificate verification in newSSL: 
    ssl_cacertfile_fix.patch (Applied Upstream)
  - debian/patches/series: Enable native.patch again, to get stripped beam
    files and reduce the package size again. (build-options is what
    actually accomplished this)
  - Remove build-options.patch on advice from upstream and because it caused
    odd build failures.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%% 
 
4
%% Copyright Ericsson AB 2006-2011. All Rights Reserved.
 
5
%% 
 
6
%% The contents of this file are subject to the Erlang Public License,
 
7
%% Version 1.1, (the "License"); you may not use this file except in
 
8
%% compliance with the License. You should have received a copy of the
 
9
%% Erlang Public License along with this software. If not, it can be
 
10
%% retrieved online at http://www.erlang.org/.
 
11
%% 
 
12
%% Software distributed under the License is distributed on an "AS IS"
 
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
14
%% the License for the specific language governing rights and limitations
 
15
%% under the License.
 
16
%% 
 
17
%% %CopyrightEnd%
 
18
%%
 
19
 
 
20
-module(tftp_SUITE).
 
21
 
 
22
-compile(export_all).
 
23
 
 
24
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
25
%% Includes and defines
 
26
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
27
 
 
28
-include("tftp_test_lib.hrl").
 
29
 
 
30
-define(START_DAEMON(PortX, OptionsX),
 
31
        fun(Port, Options) ->
 
32
                {ok, Pid} = ?VERIFY({ok, _Pid}, tftp:start([{port, Port} | Options])),
 
33
                if
 
34
                    Port == 0 ->
 
35
                        {ok, ActualOptions} = ?IGNORE(tftp:info(Pid)),
 
36
                        {value, {port, ActualPort}} =
 
37
                            lists:keysearch(port, 1, ActualOptions),
 
38
                        {ActualPort, Pid};
 
39
                    true ->
 
40
                        {Port, Pid}
 
41
                end
 
42
        end(PortX, OptionsX)).
 
43
 
 
44
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
45
%% API
 
46
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
47
 
 
48
t() -> 
 
49
    tftp_test_lib:t([{?MODULE, all}]).
 
50
 
 
51
t(Cases) ->
 
52
    tftp_test_lib:t(Cases, default_config()).
 
53
 
 
54
t(Cases, Config) ->
 
55
    tftp_test_lib:t(Cases, Config).
 
56
 
 
57
default_config() ->
 
58
    [].
 
59
 
 
60
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
61
%% Test server callbacks
 
62
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
63
 
 
64
init_per_testcase(Case, Config) ->
 
65
    tftp_test_lib:init_per_testcase(Case, Config).
 
66
 
 
67
end_per_testcase(Case, Config) when is_list(Config) ->
 
68
    tftp_test_lib:end_per_testcase(Case, Config).
 
69
 
 
70
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
71
%% Top test case
 
72
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
73
 
 
74
suite() -> [{ct_hooks,[ts_install_cth]}].
 
75
 
 
76
all() -> 
 
77
    [simple, extra, reuse_connection, resend_client,
 
78
     resend_server].
 
79
 
 
80
groups() -> 
 
81
    [].
 
82
 
 
83
init_per_suite(Config) ->
 
84
    Config.
 
85
 
 
86
end_per_suite(_Config) ->
 
87
    ok.
 
88
 
 
89
init_per_group(_GroupName, Config) ->
 
90
    Config.
 
91
 
 
92
end_per_group(_GroupName, Config) ->
 
93
    Config.
 
94
 
 
95
 
 
96
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
97
%% Simple
 
98
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
99
 
 
100
simple(doc) ->
 
101
    ["Start the daemon and perform simple a read and write."];
 
102
simple(suite) ->
 
103
    [];
 
104
simple(Config) when is_list(Config) ->
 
105
    ?VERIFY(ok, application:start(inets)),
 
106
 
 
107
    {Port, DaemonPid} = ?IGNORE(?START_DAEMON(0, [{debug, brief}])),
 
108
 
 
109
    %% Read fail
 
110
    RemoteFilename = "tftp_temporary_remote_test_file.txt",
 
111
    LocalFilename = "tftp_temporary_local_test_file.txt",
 
112
    Blob = list_to_binary(lists:duplicate(2000, $1)),
 
113
    %% Blob = <<"Some file contents\n">>,
 
114
    Size = size(Blob),
 
115
    ?IGNORE(file:delete(RemoteFilename)),
 
116
    ?VERIFY({error, {client_open, enoent, _}},
 
117
            tftp:read_file(RemoteFilename, binary, [{port, Port}])),
 
118
    
 
119
    %% Write and read
 
120
    ?VERIFY({ok, Size}, tftp:write_file(RemoteFilename, Blob, [{port, Port}])),
 
121
    ?VERIFY({ok, Blob}, tftp:read_file(RemoteFilename, binary, [{port, Port}])),
 
122
    ?IGNORE(file:delete(LocalFilename)),
 
123
    ?VERIFY({ok, Size}, tftp:read_file(RemoteFilename, LocalFilename, [{port, Port}])),
 
124
 
 
125
    %% Cleanup
 
126
    unlink(DaemonPid),
 
127
    exit(DaemonPid, kill),
 
128
    ?VERIFY(ok, file:delete(LocalFilename)),
 
129
    ?VERIFY(ok, file:delete(RemoteFilename)),
 
130
    ?VERIFY(ok, application:stop(inets)),
 
131
    ok.
 
132
 
 
133
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
134
%% Extra
 
135
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
136
 
 
137
extra(doc) ->
 
138
    ["Verify new stuff for IS 1.2."];
 
139
extra(suite) ->
 
140
    [];
 
141
extra(Config) when is_list(Config) ->
 
142
    ?VERIFY({'EXIT', {badarg,{fake_key, fake_flag}}},
 
143
            tftp:start([{port, 0}, {fake_key, fake_flag}])),
 
144
 
 
145
    {Port, DaemonPid} = ?IGNORE(?START_DAEMON(0, [{debug, brief}])),
 
146
    
 
147
    RemoteFilename = "tftp_extra_temporary_remote_test_file.txt",
 
148
    LocalFilename = "tftp_extra_temporary_local_test_file.txt",
 
149
    Blob = <<"Some file contents\n">>,
 
150
    Size = size(Blob),
 
151
    Host = "127.0.0.1",
 
152
    Peer = {inet, Host, Port},
 
153
    Generic =
 
154
        [
 
155
         {state,   []},
 
156
         {prepare, fun extra_prepare/6},
 
157
         {open,    fun extra_open/6},
 
158
         {read,    fun extra_read/1},
 
159
         {write,   fun extra_write/2},
 
160
         {abort,   fun extra_abort/3 }
 
161
        ],
 
162
    Options = [{host, Host},
 
163
               {port, Port},
 
164
               %%{ debug,all},
 
165
               {callback, {".*", tftp_test_lib, Generic}}],
 
166
    ?VERIFY(ok, file:write_file(LocalFilename, Blob)),
 
167
    ?VERIFY({ok, [{count, Size}, Peer]},
 
168
            tftp:write_file(RemoteFilename, LocalFilename, Options)),
 
169
    ?VERIFY(ok, file:delete(LocalFilename)),
 
170
    
 
171
    ?VERIFY({ok,[{bin, Blob}, Peer]}, 
 
172
            tftp:read_file(RemoteFilename, LocalFilename, Options)),
 
173
 
 
174
    %% Cleanup
 
175
    unlink(DaemonPid),
 
176
    exit(DaemonPid, kill),
 
177
    ?VERIFY(ok, file:delete(LocalFilename)),
 
178
    ?VERIFY(ok, file:delete(RemoteFilename)),
 
179
    ok.
 
180
 
 
181
-record(extra_state,  {file, blksize, count, acc, peer}).
 
182
 
 
183
%%-------------------------------------------------------------------
 
184
%% Prepare
 
185
%%-------------------------------------------------------------------
 
186
 
 
187
extra_prepare(Peer, Access, LocalFilename, Mode, SuggestedOptions, []) ->
 
188
    %% Client side
 
189
    BlkSize = list_to_integer(tftp_test_lib:lookup_option("blksize", "512", SuggestedOptions)),
 
190
    State = #extra_state{blksize = BlkSize, peer = Peer},
 
191
    extra_open(Peer, Access, LocalFilename, Mode, SuggestedOptions, State),
 
192
    {ok, SuggestedOptions, State};
 
193
extra_prepare(_Peer, _Access, _Bin, _Mode, _SuggestedOptions, _Initial) ->
 
194
    {error, {undef, "Illegal callback options."}}.
 
195
 
 
196
%%-------------------------------------------------------------------
 
197
%% Open
 
198
%%-------------------------------------------------------------------
 
199
 
 
200
extra_open(Peer, Access, LocalFilename, Mode, SuggestedOptions, []) ->
 
201
    %% Server side
 
202
    case extra_prepare(Peer, Access, LocalFilename, Mode, SuggestedOptions, []) of
 
203
        {ok, AcceptedOptions, []} ->
 
204
            BlkSize = list_to_integer(tftp_test_lib:lookup_option("blksize", "512", AcceptedOptions)),
 
205
            State = #extra_state{blksize = BlkSize, peer = Peer},
 
206
            extra_open(Peer, Access, LocalFilename, Mode, AcceptedOptions, State);
 
207
        {error, {Code, Text}} ->
 
208
            {error, {Code, Text}}
 
209
    end;
 
210
extra_open(_Peer, Access, LocalFilename, _Mode, NegotiatedOptions, #extra_state{} = State) ->
 
211
    {File, Acc} =
 
212
        case Access of
 
213
            read ->
 
214
                if
 
215
                    is_binary(LocalFilename) ->
 
216
                        {undefined, LocalFilename};
 
217
                    is_list(LocalFilename) ->
 
218
                        {ok, Bin} = file:read_file(LocalFilename),
 
219
                        {LocalFilename, Bin}
 
220
            end;
 
221
            write -> 
 
222
                {LocalFilename, []}
 
223
        end,
 
224
    %% Both sides
 
225
    State2 = State#extra_state{file = File, acc = Acc, count = 0},
 
226
    {ok, NegotiatedOptions, State2}.
 
227
 
 
228
%%-------------------------------------------------------------------
 
229
%% Read
 
230
%%-------------------------------------------------------------------
 
231
 
 
232
extra_read(#extra_state{acc = Bin} = State) when is_binary(Bin) ->
 
233
    BlkSize = State#extra_state.blksize,
 
234
    Count = State#extra_state.count + size(Bin),
 
235
    if
 
236
        size(Bin) >= BlkSize ->
 
237
            <<Block:BlkSize/binary, Bin2/binary>> = Bin,
 
238
            State2 = State#extra_state{acc = Bin2, count = Count},
 
239
            {more, Block, State2};
 
240
        size(Bin) < BlkSize ->
 
241
            Res = [{count, Count}, State#extra_state.peer],
 
242
            {last, Bin, Res}
 
243
    end.
 
244
 
 
245
%%-------------------------------------------------------------------
 
246
%% Write
 
247
%%-------------------------------------------------------------------
 
248
 
 
249
extra_write(Bin, #extra_state{acc = List} = State) when is_binary(Bin), is_list(List) ->
 
250
    Size = size(Bin),
 
251
    BlkSize = State#extra_state.blksize,
 
252
    if
 
253
        Size == BlkSize ->
 
254
            {more, State#extra_state{acc = [Bin | List]}};
 
255
        Size < BlkSize ->
 
256
            Bin2 = list_to_binary(lists:reverse([Bin | List])),
 
257
            Res = [{bin,  Bin2}, State#extra_state.peer],
 
258
            file:write_file(State#extra_state.file, Bin2),
 
259
            {last, Res}
 
260
    end.
 
261
 
 
262
%%-------------------------------------------------------------------
 
263
%% Abort
 
264
%%-------------------------------------------------------------------
 
265
 
 
266
extra_abort(_Code, _Text, #extra_state{}) ->
 
267
    ok.
 
268
 
 
269
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
270
%% Re-send client
 
271
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
272
 
 
273
resend_client(doc) ->
 
274
    ["Verify that the server behaves correctly when the client re-sends packets."];
 
275
resend_client(suite) ->
 
276
    [];
 
277
resend_client(Config) when is_list(Config) ->
 
278
    Host = {127, 0, 0, 1},
 
279
    {Port, DaemonPid} = ?IGNORE(?START_DAEMON(0, [{debug, all}])),
 
280
 
 
281
    ?VERIFY(ok, resend_read_client(Host, Port, 10)),
 
282
    ?VERIFY(ok, resend_read_client(Host, Port, 512)),
 
283
    ?VERIFY(ok, resend_read_client(Host, Port, 1025)),
 
284
 
 
285
    ?VERIFY(ok, resend_write_client(Host, Port, 10)),
 
286
    ?VERIFY(ok, resend_write_client(Host, Port, 512)),
 
287
    ?VERIFY(ok, resend_write_client(Host, Port, 1025)),
 
288
    
 
289
    %% Cleanup
 
290
    unlink(DaemonPid),
 
291
    exit(DaemonPid, kill),
 
292
    ok.
 
293
 
 
294
resend_read_client(Host, Port, BlkSize) ->
 
295
    RemoteFilename = "tftp_resend_read_client.tmp",
 
296
    Block1 = lists:duplicate(BlkSize, $1),
 
297
    Block2 = lists:duplicate(BlkSize, $2),
 
298
    Block3 = lists:duplicate(BlkSize, $3),
 
299
    Block4 = lists:duplicate(BlkSize, $4),
 
300
    Block5 = lists:duplicate(BlkSize, $5),
 
301
    Blocks = [Block1, Block2, Block3, Block4, Block5],
 
302
    Blob = list_to_binary(Blocks),
 
303
    ?VERIFY(ok, file:write_file(RemoteFilename, Blob)),
 
304
 
 
305
    Timeout = timer:seconds(3),
 
306
    ?VERIFY(timeout, recv(0)),
 
307
 
 
308
    %% Open socket
 
309
    {ok, Socket} = ?VERIFY({ok, _}, gen_udp:open(0, [binary, {reuseaddr, true}, {active, true}])),
 
310
 
 
311
    ReadList = [0, 1, RemoteFilename, 0, "octet", 0],
 
312
    Data1Bin = list_to_binary([0, 3, 0, 1 | Block1]),
 
313
    NewPort =
 
314
        if
 
315
            BlkSize =:= 512 ->
 
316
                %% Send READ
 
317
                ReadBin = list_to_binary(ReadList),
 
318
                ?VERIFY(ok, gen_udp:send(Socket, Host, Port, ReadBin)),
 
319
 
 
320
                %% Sleep a while in order to provoke the server to re-send the packet
 
321
                timer:sleep(Timeout + timer:seconds(1)),
 
322
 
 
323
                %% Recv DATA #1 (the packet that the server think that we have lost)
 
324
                {udp, _, _, NewPort0, _} = ?VERIFY({udp, Socket, Host, _, Data1Bin}, recv(Timeout)),
 
325
                NewPort0;
 
326
            true ->
 
327
                %% Send READ
 
328
                BlkSizeList = integer_to_list(BlkSize),
 
329
                Options = ["blksize", 0, BlkSizeList, 0],
 
330
                ReadBin = list_to_binary([ReadList | Options]),
 
331
                ?VERIFY(ok, gen_udp:send(Socket, Host, Port, ReadBin)),
 
332
 
 
333
                %% Recv OACK
 
334
                OptionAckBin = list_to_binary([0, 6 | Options]),
 
335
                {udp, _, _, NewPort0, _} = ?VERIFY({udp, Socket, Host, _, OptionAckBin}, recv(Timeout)),
 
336
 
 
337
                %% Send ACK #0
 
338
                Ack0Bin = <<0, 4, 0, 0>>,
 
339
                ?VERIFY(ok, gen_udp:send(Socket, Host, NewPort0, Ack0Bin)),
 
340
 
 
341
                %% Send ACK #0 AGAIN (pretend that we timed out)
 
342
                timer:sleep(timer:seconds(1)),
 
343
                ?VERIFY(ok, gen_udp:send(Socket, Host, NewPort0, Ack0Bin)),
 
344
 
 
345
                %% Recv DATA #1 (the packet that the server think that we have lost)
 
346
                ?VERIFY({udp, Socket, Host, NewPort0, Data1Bin}, recv(Timeout)),
 
347
                NewPort0
 
348
        end,
 
349
 
 
350
    %% Recv DATA #1 AGAIN (the re-sent package)
 
351
    ?VERIFY({udp, Socket, Host, NewPort, Data1Bin}, recv(Timeout)),
 
352
 
 
353
    %% Send ACK #1
 
354
    Ack1Bin = <<0, 4, 0, 1>>,
 
355
    ?VERIFY(ok, gen_udp:send(Socket, Host, NewPort, Ack1Bin)),
 
356
 
 
357
    %% Recv DATA #2
 
358
    Data2Bin = list_to_binary([0, 3, 0, 2 | Block2]),
 
359
    ?VERIFY({udp, Socket, Host, NewPort, Data2Bin}, recv(Timeout)),
 
360
 
 
361
    %% Send ACK #2
 
362
    Ack2Bin = <<0, 4, 0, 2>>,
 
363
    ?VERIFY(ok, gen_udp:send(Socket, Host, NewPort, Ack2Bin)),
 
364
 
 
365
    %% Recv DATA #3
 
366
    Data3Bin = list_to_binary([0, 3, 0, 3 | Block3]),
 
367
    ?VERIFY({udp, Socket, Host, NewPort, Data3Bin}, recv(Timeout)),
 
368
 
 
369
    %% Send ACK #3
 
370
    Ack3Bin = <<0, 4, 0, 3>>,
 
371
    ?VERIFY(ok, gen_udp:send(Socket, Host, NewPort, Ack3Bin)),
 
372
 
 
373
    %% Send ACK #3 AGAIN (pretend that we timed out)
 
374
    timer:sleep(timer:seconds(1)),
 
375
    ?VERIFY(ok, gen_udp:send(Socket, Host, NewPort, Ack3Bin)),
 
376
 
 
377
    %% Recv DATA #4 (the packet that the server think that we have lost)
 
378
    Data4Bin = list_to_binary([0, 3, 0, 4 | Block4]),
 
379
    ?VERIFY({udp, Socket, Host, NewPort, Data4Bin}, recv(Timeout)),
 
380
 
 
381
    %% Recv DATA #4 AGAIN (the re-sent package)
 
382
    ?VERIFY({udp, Socket, Host, NewPort, Data4Bin}, recv(Timeout)),
 
383
 
 
384
    %% Send ACK #2 which is out of range
 
385
    ?VERIFY(ok, gen_udp:send(Socket, Host, NewPort, Ack2Bin)),
 
386
 
 
387
    %% Send ACK #4
 
388
    Ack4Bin = <<0, 4, 0, 4>>,
 
389
    ?VERIFY(ok, gen_udp:send(Socket, Host, NewPort, Ack4Bin)),
 
390
 
 
391
    %% Recv DATA #5
 
392
    Data5Bin = list_to_binary([0, 3, 0, 5 | Block5]),
 
393
    ?VERIFY({udp, Socket, Host, NewPort, Data5Bin}, recv(Timeout)),
 
394
 
 
395
    %% Send ACK #5
 
396
    Ack5Bin = <<0, 4, 0, 5>>,
 
397
    ?VERIFY(ok, gen_udp:send(Socket, Host, NewPort, Ack5Bin)),
 
398
 
 
399
    %% Close socket
 
400
    ?VERIFY(ok, gen_udp:close(Socket)),
 
401
 
 
402
    ?VERIFY(timeout, recv(Timeout)),
 
403
    ?VERIFY(ok, file:delete(RemoteFilename)),
 
404
    ok.
 
405
 
 
406
resend_write_client(Host, Port, BlkSize) ->
 
407
    RemoteFilename = "tftp_resend_write_client.tmp",
 
408
    Block1 = lists:duplicate(BlkSize, $1),
 
409
    Block2 = lists:duplicate(BlkSize, $2),
 
410
    Block3 = lists:duplicate(BlkSize, $3),
 
411
    Block4 = lists:duplicate(BlkSize, $4),
 
412
    Block5 = lists:duplicate(BlkSize, $5),
 
413
    Blocks = [Block1, Block2, Block3, Block4, Block5],
 
414
    Blob = list_to_binary(Blocks),
 
415
    ?IGNORE(file:delete(RemoteFilename)),
 
416
    ?VERIFY({error, enoent}, file:read_file(RemoteFilename)),
 
417
 
 
418
    Timeout = timer:seconds(3),
 
419
    ?VERIFY(timeout, recv(0)),
 
420
 
 
421
    %% Open socket
 
422
    {ok, Socket} = ?VERIFY({ok, _}, gen_udp:open(0, [binary, {reuseaddr, true}, {active, true}])),
 
423
 
 
424
    WriteList = [0, 2, RemoteFilename, 0, "octet", 0],
 
425
    NewPort =
 
426
        if
 
427
            BlkSize =:= 512 ->
 
428
                %% Send WRITE
 
429
                WriteBin = list_to_binary(WriteList),
 
430
                ?VERIFY(ok,  gen_udp:send(Socket, Host, Port, WriteBin)),
 
431
 
 
432
                %% Sleep a while in order to provoke the server to re-send the packet
 
433
                timer:sleep(Timeout + timer:seconds(1)),
 
434
 
 
435
                %% Recv ACK #0 (the packet that the server think that we have lost)
 
436
                Ack0Bin = <<0, 4, 0, 0>>,
 
437
                ?VERIFY({udp, Socket, Host, _, Ack0Bin}, recv(Timeout)),
 
438
 
 
439
                %% Recv ACK #0  AGAIN (the re-sent package)
 
440
                {udp, _, _, NewPort0, _} = ?VERIFY({udp, Socket, Host, _, Ack0Bin}, recv(Timeout)),
 
441
                NewPort0;
 
442
            true ->
 
443
                %% Send WRITE
 
444
                BlkSizeList = integer_to_list(BlkSize),
 
445
                WriteBin = list_to_binary([WriteList, "blksize", 0, BlkSizeList, 0]),
 
446
                ?VERIFY(ok,  gen_udp:send(Socket, Host, Port, WriteBin)),
 
447
 
 
448
                %% Sleep a while in order to provoke the server to re-send the packet
 
449
                timer:sleep(timer:seconds(1)),
 
450
 
 
451
                %% Recv OACK (the packet that the server think that we have lost)
 
452
                OptionAckBin = list_to_binary([0, 6, "blksize",0, BlkSizeList, 0]),
 
453
                ?VERIFY({udp, Socket, Host, _, OptionAckBin}, recv(Timeout)),
 
454
                
 
455
                %% Recv OACK AGAIN (the re-sent package)
 
456
                {udp, _, _, NewPort0, _} = ?VERIFY({udp, Socket, Host, _, OptionAckBin}, recv(Timeout)),
 
457
                NewPort0
 
458
        end,
 
459
 
 
460
    %% Send DATA #1
 
461
    Data1Bin = list_to_binary([0, 3, 0, 1 | Block1]),
 
462
    ?VERIFY(ok, gen_udp:send(Socket, Host, NewPort, Data1Bin)),
 
463
 
 
464
    %% Recv ACK #1 
 
465
    Ack1Bin = <<0, 4, 0, 1>>,
 
466
    ?VERIFY({udp, Socket, Host, NewPort, Ack1Bin}, recv(Timeout)),
 
467
 
 
468
    %% Send DATA #2
 
469
    Data2Bin = list_to_binary([0, 3, 0, 2 | Block2]),
 
470
    ?VERIFY(ok, gen_udp:send(Socket, Host, NewPort, Data2Bin)),
 
471
 
 
472
    %% Recv ACK #2
 
473
    Ack2Bin = <<0, 4, 0, 2>>,
 
474
    ?VERIFY({udp, Socket, Host, NewPort, Ack2Bin}, recv(Timeout)),
 
475
 
 
476
    %% Send DATA #3
 
477
    Data3Bin = list_to_binary([0, 3, 0, 3 | Block3]),
 
478
    ?VERIFY(ok, gen_udp:send(Socket, Host, NewPort, Data3Bin)),
 
479
 
 
480
    %% Recv ACK #3
 
481
    Ack3Bin = <<0, 4, 0, 3>>,
 
482
    ?VERIFY({udp, Socket, Host, NewPort, Ack3Bin}, recv(Timeout)),
 
483
 
 
484
    %% Send DATA #3 AGAIN (pretend that we timed out)
 
485
    timer:sleep(timer:seconds(1)),
 
486
    ?VERIFY(ok, gen_udp:send(Socket, Host, NewPort, Data3Bin)),
 
487
 
 
488
    %% Recv ACK #3 AGAIN (the packet that the server think that we have lost)
 
489
    ?VERIFY({udp, Socket, Host, NewPort, Ack3Bin}, recv(Timeout)),
 
490
 
 
491
    %% Send DATA #2 which is out of range
 
492
    ?VERIFY(ok, gen_udp:send(Socket, Host, NewPort, Data2Bin)),
 
493
 
 
494
    %% Send DATA #4
 
495
    Data4Bin = list_to_binary([0, 3, 0, 4 | Block4]),
 
496
    ?VERIFY(ok, gen_udp:send(Socket, Host, NewPort, Data4Bin)),
 
497
 
 
498
    %% Recv ACK #4
 
499
    Ack4Bin = <<0, 4, 0, 4>>,
 
500
    ?VERIFY({udp, Socket, Host, NewPort, Ack4Bin}, recv(Timeout)),
 
501
 
 
502
    %% Send DATA #5
 
503
    Data5Bin = list_to_binary([0, 3, 0, 5 | Block5]),
 
504
    ?VERIFY(ok, gen_udp:send(Socket, Host, NewPort, Data5Bin)),
 
505
 
 
506
    %% Recv ACK #5
 
507
    Ack5Bin = <<0, 4, 0, 5>>,
 
508
    ?VERIFY({udp, Socket, Host, NewPort, Ack5Bin}, recv(Timeout)),
 
509
 
 
510
    %% Close socket
 
511
    ?VERIFY(ok, gen_udp:close(Socket)),
 
512
 
 
513
    ?VERIFY(timeout, recv(Timeout)),
 
514
    ?VERIFY({ok, Blob}, file:read_file(RemoteFilename)),
 
515
    ?VERIFY(ok, file:delete(RemoteFilename)),
 
516
    ok.
 
517
 
 
518
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
519
%% Re-send server
 
520
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
521
 
 
522
resend_server(doc) ->
 
523
    ["Verify that the server behaves correctly when the server re-sends packets."];
 
524
resend_server(suite) ->
 
525
    [];
 
526
resend_server(Config) when is_list(Config) ->
 
527
    Host = {127, 0, 0, 1},
 
528
 
 
529
    ?VERIFY(ok, resend_read_server(Host, 10)),
 
530
    ?VERIFY(ok, resend_read_server(Host, 512)),
 
531
    ?VERIFY(ok, resend_read_server(Host, 1025)),
 
532
    
 
533
    ?VERIFY(ok, resend_write_server(Host, 10)),
 
534
    ?VERIFY(ok, resend_write_server(Host, 512)),
 
535
    ?VERIFY(ok, resend_write_server(Host, 1025)),
 
536
    ok.
 
537
 
 
538
resend_read_server(Host, BlkSize) ->
 
539
    RemoteFilename = "tftp_resend_read_server.tmp",
 
540
    Block1 = lists:duplicate(BlkSize, $1),
 
541
    Block2 = lists:duplicate(BlkSize, $2),
 
542
    Block3 = lists:duplicate(BlkSize, $3),
 
543
    Block4 = lists:duplicate(BlkSize, $4),
 
544
    Block5 = lists:duplicate(BlkSize, $5),
 
545
    Block6 = [],
 
546
    Blocks = [Block1, Block2, Block3, Block4, Block5, Block6],
 
547
    Blob = list_to_binary(Blocks),
 
548
 
 
549
    Timeout = timer:seconds(3),
 
550
    ?VERIFY(timeout, recv(0)),
 
551
 
 
552
    %% Open daemon socket
 
553
    {ok, DaemonSocket} = ?VERIFY({ok, _}, gen_udp:open(0, [binary, {reuseaddr, true}, {active, true}])),
 
554
    {ok, DaemonPort} = ?IGNORE(inet:port(DaemonSocket)),
 
555
 
 
556
    %% Open server socket
 
557
    {ok, ServerSocket} = ?VERIFY({ok, _}, gen_udp:open(0, [binary, {reuseaddr, true}, {active, true}])),
 
558
    ?IGNORE(inet:port(ServerSocket)),
 
559
 
 
560
    %% Prepare client process
 
561
    ReplyTo = self(),
 
562
    ClientFun =
 
563
        fun(Extra) ->
 
564
                Options = [{port, DaemonPort}, {debug, brief}] ++ Extra,
 
565
                Res = ?VERIFY({ok, Blob}, tftp:read_file(RemoteFilename, binary, Options)),
 
566
                ReplyTo ! {self(), {tftp_client_reply, Res}},
 
567
                exit(normal)
 
568
        end,
 
569
 
 
570
    ReadList = [0, 1, RemoteFilename, 0, "octet", 0],
 
571
    Data1Bin = list_to_binary([0, 3, 0, 1 | Block1]),
 
572
    Ack1Bin = <<0, 4, 0, 1>>,
 
573
    {ClientPort, ClientPid} =
 
574
        if
 
575
            BlkSize =:= 512 ->
 
576
                %% Start client process
 
577
                ClientPid0 = spawn_link(fun() -> ClientFun([]) end),
 
578
 
 
579
                %% Recv READ
 
580
                ReadBin = list_to_binary(ReadList),
 
581
                {udp, _, _, ClientPort0, _} = ?VERIFY({udp, DaemonSocket, Host, _, ReadBin}, recv(Timeout)),
 
582
 
 
583
                %% Send DATA #1
 
584
                ?VERIFY(ok,  gen_udp:send(ServerSocket, Host, ClientPort0, Data1Bin)),
 
585
 
 
586
                %% Sleep a while in order to provoke the client to re-send the packet
 
587
                timer:sleep(Timeout + timer:seconds(1)),
 
588
 
 
589
                %% Recv ACK #1 (the packet that the server think that we have lost)
 
590
                ?VERIFY({udp, ServerSocket, Host, ClientPort0, Ack1Bin}, recv(Timeout)),
 
591
 
 
592
                %% Recv ACK #1 AGAIN (the re-sent package)
 
593
                ?VERIFY({udp, ServerSocket, Host, _, Ack1Bin}, recv(Timeout)),
 
594
                {ClientPort0, ClientPid0};
 
595
            true ->
 
596
                %% Start client process
 
597
                BlkSizeList = integer_to_list(BlkSize),
 
598
                ClientPid0 = spawn_link(fun() -> ClientFun([{"blksize", BlkSizeList}]) end),
 
599
                
 
600
                %% Recv READ
 
601
                Options = ["blksize", 0, BlkSizeList, 0],
 
602
                ReadBin = list_to_binary([ReadList | Options]),
 
603
                {udp, _, _, ClientPort0, _} = ?VERIFY({udp, DaemonSocket, Host, _, ReadBin}, recv(Timeout)),
 
604
 
 
605
                %% Send OACK
 
606
                BlkSizeList = integer_to_list(BlkSize),
 
607
                OptionAckBin = list_to_binary([0, 6, "blksize",0, BlkSizeList, 0]),
 
608
                ?VERIFY(ok, gen_udp:send(ServerSocket, Host, ClientPort0, OptionAckBin)),
 
609
 
 
610
                %% Sleep a while in order to provoke the client to re-send the packet
 
611
                timer:sleep(Timeout + timer:seconds(1)),
 
612
 
 
613
                %% Recv ACK #0 (the packet that the server think that we have lost)
 
614
                Ack0Bin = <<0, 4, 0, 0>>,
 
615
                ?VERIFY({udp, ServerSocket, Host, ClientPort0, Ack0Bin}, recv(Timeout)),
 
616
 
 
617
                %% Recv ACK #0 AGAIN (the re-sent package)
 
618
                ?VERIFY({udp, ServerSocket, Host, ClientPort0, Ack0Bin}, recv(Timeout)),
 
619
 
 
620
                %% Send DATA #1
 
621
                ?VERIFY(ok, gen_udp:send(ServerSocket, Host, ClientPort0, Data1Bin)),
 
622
 
 
623
                %% Recv ACK #1
 
624
                ?VERIFY({udp, ServerSocket, Host, _, Ack1Bin}, recv(Timeout)),
 
625
                {ClientPort0, ClientPid0}
 
626
        end,
 
627
 
 
628
    %% Send DATA #2
 
629
    Data2Bin = list_to_binary([0, 3, 0, 2 | Block2]),
 
630
    ?VERIFY(ok, gen_udp:send(ServerSocket, Host, ClientPort, Data2Bin)),
 
631
 
 
632
    %% Recv ACK #2
 
633
    Ack2Bin = <<0, 4, 0, 2>>,
 
634
    ?VERIFY({udp, ServerSocket, Host, ClientPort, Ack2Bin}, recv(Timeout)),
 
635
 
 
636
    %% Send DATA #3
 
637
    Data3Bin = list_to_binary([0, 3, 0, 3 | Block3]),
 
638
    ?VERIFY(ok, gen_udp:send(ServerSocket, Host, ClientPort, Data3Bin)),
 
639
 
 
640
    %% Recv ACK #3
 
641
    Ack3Bin = <<0, 4, 0, 3>>,
 
642
    ?VERIFY({udp, ServerSocket, Host, ClientPort, Ack3Bin}, recv(Timeout)),
 
643
 
 
644
    %% Send DATA #3 AGAIN (pretend that we timed out)
 
645
    timer:sleep(timer:seconds(1)),
 
646
    ?VERIFY(ok, gen_udp:send(ServerSocket, Host, ClientPort, Data3Bin)),
 
647
 
 
648
    %% Recv ACK #3 AGAIN (the packet that the server think that we have lost)
 
649
    ?VERIFY({udp, ServerSocket, Host, ClientPort, Ack3Bin}, recv(Timeout)),
 
650
 
 
651
    %% Send DATA #4
 
652
    Data4Bin = list_to_binary([0, 3, 0, 4 | Block4]),
 
653
    ?VERIFY(ok, gen_udp:send(ServerSocket, Host, ClientPort, Data4Bin)),
 
654
 
 
655
    %% Recv ACK #4
 
656
    Ack4Bin = <<0, 4, 0, 4>>,
 
657
    ?VERIFY({udp, ServerSocket, Host, ClientPort, Ack4Bin}, recv(Timeout)),
 
658
 
 
659
    %% Send DATA #3 which is out of range
 
660
    ?VERIFY(ok, gen_udp:send(ServerSocket, Host, ClientPort, Data3Bin)),
 
661
 
 
662
    %% Send DATA #5
 
663
    Data5Bin = list_to_binary([0, 3, 0, 5 | Block5]),
 
664
    ?VERIFY(ok, gen_udp:send(ServerSocket, Host, ClientPort, Data5Bin)),
 
665
 
 
666
    %% Recv ACK #5
 
667
    Ack5Bin = <<0, 4, 0, 5>>,
 
668
    ?VERIFY({udp, ServerSocket, Host, ClientPort, Ack5Bin}, recv(Timeout)),
 
669
 
 
670
    %% Send DATA #6
 
671
    Data6Bin = list_to_binary([0, 3, 0, 6 | Block6]),
 
672
    ?VERIFY(ok, gen_udp:send(ServerSocket, Host, ClientPort, Data6Bin)),
 
673
 
 
674
    %% Close daemon and server sockets
 
675
    ?VERIFY(ok, gen_udp:close(ServerSocket)),
 
676
    ?VERIFY(ok, gen_udp:close(DaemonSocket)),
 
677
 
 
678
    ?VERIFY({ClientPid, {tftp_client_reply, {ok, Blob}}}, recv(Timeout)),
 
679
 
 
680
    ?VERIFY(timeout, recv(Timeout)),
 
681
    ok.
 
682
 
 
683
resend_write_server(Host, BlkSize) ->
 
684
    RemoteFilename = "tftp_resend_write_server.tmp",
 
685
    Block1 = lists:duplicate(BlkSize, $1),
 
686
    Block2 = lists:duplicate(BlkSize, $2),
 
687
    Block3 = lists:duplicate(BlkSize, $3),
 
688
    Block4 = lists:duplicate(BlkSize, $4),
 
689
    Block5 = lists:duplicate(BlkSize, $5),
 
690
    Block6 = [],
 
691
    Blocks = [Block1, Block2, Block3, Block4, Block5, Block6],
 
692
    Blob = list_to_binary(Blocks),
 
693
    Size = size(Blob),
 
694
 
 
695
    Timeout = timer:seconds(3),
 
696
    ?VERIFY(timeout, recv(0)),
 
697
 
 
698
    %% Open daemon socket
 
699
    {ok, DaemonSocket} = ?VERIFY({ok, _}, gen_udp:open(0, [binary, {reuseaddr, true}, {active, true}])),
 
700
    {ok, DaemonPort} = ?IGNORE(inet:port(DaemonSocket)),
 
701
 
 
702
    %% Open server socket
 
703
    {ok, ServerSocket} = ?VERIFY({ok, _}, gen_udp:open(0, [binary, {reuseaddr, true}, {active, true}])),
 
704
    ?IGNORE(inet:port(ServerSocket)),
 
705
 
 
706
    %% Prepare client process
 
707
    ReplyTo = self(),
 
708
    ClientFun =
 
709
        fun(Extra) ->
 
710
                Options = [{port, DaemonPort}, {debug, brief}] ++ Extra,
 
711
                Res = ?VERIFY({ok, Size}, tftp:write_file(RemoteFilename, Blob, Options)),
 
712
                ReplyTo ! {self(), {tftp_client_reply, Res}},
 
713
                exit(normal)
 
714
        end,
 
715
 
 
716
    WriteList = [0, 2, RemoteFilename, 0, "octet", 0],
 
717
    Data1Bin = list_to_binary([0, 3, 0, 1 | Block1]),
 
718
    {ClientPort, ClientPid} =
 
719
        if
 
720
            BlkSize =:= 512 ->
 
721
                %% Start client process
 
722
                ClientPid0 = spawn_link(fun() -> ClientFun([]) end),
 
723
 
 
724
                %% Recv WRITE
 
725
                WriteBin = list_to_binary(WriteList),
 
726
                io:format("WriteBin ~p\n", [WriteBin]),
 
727
                {udp, _, _, ClientPort0, _} = ?VERIFY({udp, DaemonSocket, Host, _, WriteBin}, recv(Timeout)),
 
728
 
 
729
                %% Send ACK #1
 
730
                Ack0Bin = <<0, 4, 0, 0>>,
 
731
                ?VERIFY(ok,  gen_udp:send(ServerSocket, Host, ClientPort0, Ack0Bin)),
 
732
 
 
733
                %% Sleep a while in order to provoke the client to re-send the packet
 
734
                timer:sleep(Timeout + timer:seconds(1)),
 
735
 
 
736
                %% Recv DATA #1 (the packet that the server think that we have lost)
 
737
                ?VERIFY({udp, ServerSocket, Host, ClientPort0, Data1Bin}, recv(Timeout)),
 
738
 
 
739
                %% Recv DATA #1 AGAIN (the re-sent package)
 
740
                ?VERIFY({udp, ServerSocket, Host, _, Data1Bin}, recv(Timeout)),
 
741
                {ClientPort0, ClientPid0};
 
742
            true ->
 
743
                %% Start client process
 
744
                BlkSizeList = integer_to_list(BlkSize),
 
745
                ClientPid0 = spawn_link(fun() -> ClientFun([{"blksize", BlkSizeList}]) end),
 
746
                
 
747
                %% Recv WRITE
 
748
                Options = ["blksize", 0, BlkSizeList, 0],
 
749
                WriteBin = list_to_binary([WriteList | Options]),
 
750
                {udp, _, _, ClientPort0, _} = ?VERIFY({udp, DaemonSocket, Host, _, WriteBin}, recv(Timeout)),
 
751
 
 
752
                %% Send OACK
 
753
                BlkSizeList = integer_to_list(BlkSize),
 
754
                OptionAckBin = list_to_binary([0, 6, "blksize",0, BlkSizeList, 0]),
 
755
                ?VERIFY(ok, gen_udp:send(ServerSocket, Host, ClientPort0, OptionAckBin)),
 
756
 
 
757
                %% Sleep a while in order to provoke the client to re-send the packet
 
758
                timer:sleep(Timeout + timer:seconds(1)),
 
759
 
 
760
                %% Recv DATA #1 (the packet that the server think that we have lost)
 
761
                ?VERIFY({udp, ServerSocket, Host, ClientPort0, Data1Bin}, recv(Timeout)),
 
762
 
 
763
                %% Recv DATA #1 AGAIN (the re-sent package)
 
764
                ?VERIFY({udp, ServerSocket, Host, ClientPort0, Data1Bin}, recv(Timeout)),
 
765
                {ClientPort0, ClientPid0}
 
766
        end,
 
767
 
 
768
    %% Send ACK #1
 
769
    Ack1Bin = <<0, 4, 0, 1>>,
 
770
    ?VERIFY(ok, gen_udp:send(ServerSocket, Host, ClientPort, Ack1Bin)),
 
771
 
 
772
    %% Recv DATA #2
 
773
    Data2Bin = list_to_binary([0, 3, 0, 2 | Block2]),
 
774
    ?VERIFY({udp, ServerSocket, Host, ClientPort, Data2Bin}, recv(Timeout)),
 
775
 
 
776
    %% Send ACK #2
 
777
    Ack2Bin = <<0, 4, 0, 2>>,
 
778
    ?VERIFY(ok, gen_udp:send(ServerSocket, Host, ClientPort, Ack2Bin)),
 
779
 
 
780
    %% Recv DATA #3
 
781
    Data3Bin = list_to_binary([0, 3, 0, 3 | Block3]),
 
782
    ?VERIFY({udp, ServerSocket, Host, ClientPort, Data3Bin}, recv(Timeout)),
 
783
 
 
784
    %% Send ACK #3
 
785
    Ack3Bin = <<0, 4, 0, 3>>,
 
786
    ?VERIFY(ok, gen_udp:send(ServerSocket, Host, ClientPort, Ack3Bin)),
 
787
 
 
788
    %% Send ACK #3 AGAIN (pretend that we timed out)
 
789
    timer:sleep(timer:seconds(1)),
 
790
    ?VERIFY(ok, gen_udp:send(ServerSocket, Host, ClientPort, Ack3Bin)),
 
791
 
 
792
    %% Recv DATA #4 (the packet that the server think that we have lost)
 
793
    Data4Bin = list_to_binary([0, 3, 0, 4 | Block4]),
 
794
    ?VERIFY({udp, ServerSocket, Host, ClientPort, Data4Bin}, recv(Timeout)),
 
795
 
 
796
    %% Recv DATA #4 AGAIN (the re-sent package)
 
797
    ?VERIFY({udp, ServerSocket, Host, ClientPort, Data4Bin}, recv(Timeout)),
 
798
 
 
799
    %% Send ACK #4
 
800
    Ack4Bin = <<0, 4, 0, 4>>,
 
801
    ?VERIFY(ok, gen_udp:send(ServerSocket, Host, ClientPort, Ack4Bin)),
 
802
 
 
803
    %% Recv DATA #5
 
804
    Data5Bin = list_to_binary([0, 3, 0, 5 | Block5]),
 
805
    ?VERIFY({udp, ServerSocket, Host, ClientPort, Data5Bin}, recv(Timeout)),
 
806
 
 
807
    %% Send ACK #3 which is out of range
 
808
    ?VERIFY(ok, gen_udp:send(ServerSocket, Host, ClientPort, Ack3Bin)),
 
809
 
 
810
    %% Send ACK #5
 
811
    Ack5Bin = <<0, 4, 0, 5>>,
 
812
    ?VERIFY(ok, gen_udp:send(ServerSocket, Host, ClientPort, Ack5Bin)),
 
813
 
 
814
    %% Recv DATA #6
 
815
    Data6Bin = list_to_binary([0, 3, 0, 6 | Block6]),
 
816
    ?VERIFY({udp, ServerSocket, Host, ClientPort, Data6Bin}, recv(Timeout)),
 
817
 
 
818
    %% Send ACK #6
 
819
    Ack6Bin = <<0, 4, 0, 6>>,
 
820
    ?VERIFY(ok, gen_udp:send(ServerSocket, Host, ClientPort, Ack6Bin)),
 
821
 
 
822
    %% Close daemon and server sockets
 
823
    ?VERIFY(ok, gen_udp:close(ServerSocket)),
 
824
    ?VERIFY(ok, gen_udp:close(DaemonSocket)),
 
825
 
 
826
    ?VERIFY({ClientPid, {tftp_client_reply, {ok, Size}}}, recv(Timeout)),
 
827
 
 
828
    ?VERIFY(timeout, recv(Timeout)),
 
829
    ok.
 
830
 
 
831
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
832
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
833
 
 
834
reuse_connection(doc) ->
 
835
    ["Verify that the server can reuse an ongiong connection when same client resends request."];
 
836
reuse_connection(suite) ->
 
837
    [];
 
838
reuse_connection(Config) when is_list(Config) ->
 
839
    Host = {127, 0, 0, 1},
 
840
    {Port, DaemonPid} = ?IGNORE(?START_DAEMON(0, [{debug, all}])),
 
841
 
 
842
    RemoteFilename = "reuse_connection.tmp",
 
843
    BlkSize = 512,
 
844
    Block1 = lists:duplicate(BlkSize, $1),
 
845
    Block2 = lists:duplicate(BlkSize div 2, $2),
 
846
    Blocks = [Block1, Block2],
 
847
    Blob = list_to_binary(Blocks),
 
848
    ?VERIFY(ok, file:write_file(RemoteFilename, Blob)),
 
849
    
 
850
    Seconds = 3,
 
851
    Timeout = timer:seconds(Seconds),
 
852
    ?VERIFY(timeout, recv(0)),
 
853
    
 
854
    %% Open socket
 
855
    {ok, Socket} = ?VERIFY({ok, _}, gen_udp:open(0, [binary, {reuseaddr, true}, {active, true}])),
 
856
    
 
857
    ReadList = [0, 1, RemoteFilename, 0, "octet", 0],
 
858
    Data1Bin = list_to_binary([0, 3, 0, 1 | Block1]),
 
859
    
 
860
    %% Send READ
 
861
    TimeoutList = integer_to_list(Seconds),
 
862
    Options = ["timeout", 0, TimeoutList, 0],
 
863
    ReadBin = list_to_binary([ReadList | Options]),
 
864
    ?VERIFY(ok, gen_udp:send(Socket, Host, Port, ReadBin)),
 
865
 
 
866
    %% Send yet another READ for same file
 
867
    ?VERIFY(ok, gen_udp:send(Socket, Host, Port, ReadBin)),
 
868
 
 
869
    %% Recv OACK
 
870
    OptionAckBin = list_to_binary([0, 6 | Options]),
 
871
    {udp, _, _, NewPort, _} = ?VERIFY({udp, Socket, Host, _, OptionAckBin}, recv(Timeout)),
 
872
 
 
873
    %% Send ACK #0
 
874
    Ack0Bin = <<0, 4, 0, 0>>,
 
875
    ?VERIFY(ok, gen_udp:send(Socket, Host, NewPort, Ack0Bin)),
 
876
 
 
877
    %% Recv DATA #1
 
878
    ?VERIFY({udp, Socket, Host, NewPort, Data1Bin}, recv(Timeout)),
 
879
 
 
880
    %% Send ACK #1
 
881
    Ack1Bin = <<0, 4, 0, 1>>,
 
882
    ?VERIFY(ok, gen_udp:send(Socket, Host, NewPort, Ack1Bin)),
 
883
 
 
884
    %% Recv DATA #2
 
885
    Data2Bin = list_to_binary([0, 3, 0, 2 | Block2]),
 
886
    ?VERIFY({udp, Socket, Host, NewPort, Data2Bin}, recv(Timeout)),
 
887
 
 
888
    %% Send ACK #2
 
889
    Ack2Bin = <<0, 4, 0, 2>>,
 
890
    ?VERIFY(ok, gen_udp:send(Socket, Host, NewPort, Ack2Bin)),
 
891
 
 
892
    %% Close socket
 
893
    ?VERIFY(ok, gen_udp:close(Socket)),
 
894
 
 
895
    ?VERIFY(timeout, recv(Timeout)),
 
896
    ?VERIFY(ok, file:delete(RemoteFilename)),
 
897
 
 
898
    %% Cleanup
 
899
    unlink(DaemonPid),
 
900
    exit(DaemonPid, kill),
 
901
    ok.
 
902
 
 
903
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
904
%% Goodies
 
905
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
906
 
 
907
recv(Timeout) ->
 
908
    receive
 
909
        Msg ->
 
910
            Msg
 
911
    after Timeout ->
 
912
            timeout
 
913
    end.