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

« back to all changes in this revision

Viewing changes to lib/inets/src/tftp/tftp_engine.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-02-15 16:42:52 UTC
  • mfrom: (3.1.2 squeeze)
  • Revision ID: james.westby@ubuntu.com-20090215164252-q5x4rcf8a5pbesb1
Tags: 1:12.b.5-dfsg-2
Upload to unstable after lenny is released.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%%<copyright>
 
2
%% <year>2005-2008</year>
 
3
%% <holder>Ericsson AB, All Rights Reserved</holder>
 
4
%%</copyright>
 
5
%%<legalnotice>
 
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
%% The Initial Developer of the Original Code is Ericsson AB.
 
18
%%</legalnotice>
 
19
%%
 
20
 
1
21
%%%-------------------------------------------------------------------
2
22
%%% File    : tftp_engine.erl
3
23
%%% Author  : Hakan Mattsson <hakan@erix.ericsson.se>
41
61
 
42
62
-include("tftp.hrl").
43
63
 
 
64
-type prep_status() :: 'error' | 'last' | 'more' | 'terminate'.
 
65
 
44
66
-record(daemon_state, {config, n_servers, server_tab, file_tab}).
45
67
-record(server_info, {pid, req, peer}).
46
68
-record(file_info, {peer_req, pid}).
47
69
-record(sys_misc, {module, function, arguments}).
48
70
-record(error, {where, code, text, filename}).
49
 
-record(prepared, {status, result, block_no, next_data, prev_data}).
 
71
-record(prepared, {status :: prep_status(), result, block_no, next_data, prev_data}).
50
72
-record(transfer_res, {status, decoded_msg, prepared}).
51
73
-define(ERROR(Where, Code, Text, Filename),
52
74
        #error{where = Where, code = Code, text = Text, filename = Filename}).
353
375
            end;
354
376
        #error{} = Error ->
355
377
            terminate(Config2, Req, Error)
356
 
    end.
 
378
    end;
 
379
server_init(Config, Req) when is_record(Req, tftp_msg_req) ->
 
380
    Config2 = upgrade_config(Config),
 
381
    server_init(Config2, Req).
357
382
 
358
383
%%%-------------------------------------------------------------------
359
384
%%% Client
576
601
    Config2 = upgrade_config(Config),
577
602
    common_loop(Config2, Callback, Req, TransferRes, LocalAccess, ExpectedBlockNo).
578
603
 
 
604
-spec common_read(#config{}, #callback{}, _, 'read', _, _, #prepared{}) -> no_return().
 
605
 
579
606
common_read(Config, _, Req, _, _, _, #prepared{status = terminate, result = Result}) ->
580
607
    terminate(Config, Req, {ok, Result});
581
608
common_read(Config, Callback, Req, LocalAccess, ExpectedBlockNo, ActualBlockNo, Prepared)
605
632
            terminate(Config, Req, ?ERROR(read, Code, Text, Req#tftp_msg_req.filename))
606
633
    end;
607
634
common_read(Config, Callback, Req, LocalAccess, ExpectedBlockNo, ActualBlockNo, Prepared) 
608
 
  when ActualBlockNo =< ExpectedBlockNo , is_record(Prepared, prepared) ->
 
635
  when ActualBlockNo =< ExpectedBlockNo, is_record(Prepared, prepared) ->
609
636
    %% error_logger:error_msg("TFTP READ ~s: Expected block ~p but got block ~p - IGNORED\n",
610
637
    %%                     [Req#tftp_msg_req.filename, ExpectedBlockNo, ActualBlockNo]),
611
638
    case Prepared of
634
661
    send_msg(Config, Req, Error),
635
662
    terminate(Config, Req, ?ERROR(read, Code, Text, Req#tftp_msg_req.filename)).
636
663
 
 
664
-spec do_common_read(#config{}, #callback{} | undefined, _, 'read', integer(), binary(), #prepared{}) -> no_return().
 
665
 
637
666
do_common_read(Config, Callback, Req, LocalAccess, BlockNo, Data, Prepared)
638
667
  when is_binary(Data), is_record(Prepared, prepared) ->
639
668
    NextBlockNo = BlockNo + 1,
653
682
            terminate(Config, Req, ?ERROR(read, Code, Text, Req#tftp_msg_req.filename))
654
683
    end.
655
684
 
 
685
-spec common_write(#config{}, #callback{}, _, 'write', integer(), integer(), _, #prepared{}) -> no_return().
 
686
 
656
687
common_write(Config, _, Req, _, _, _, _, #prepared{status = terminate, result = Result}) ->
657
688
    terminate(Config, Req, {ok, Result});
658
689
common_write(Config, Callback, Req, LocalAccess, ExpectedBlockNo, ActualBlockNo, Data, Prepared)
676
707
            {undefined, Error} =
677
708
                callback({abort, {Code, Text}}, Config, Callback, Req),
678
709
            send_msg(Config, Req, Error),
679
 
            Error = #tftp_msg_error{code = Code, text = Text},
680
 
            {undefined, #prepared{status = error, result = Error}}
 
710
            terminate(Config, Req, ?ERROR(write, Code, Text, Req#tftp_msg_req.filename))
681
711
    end;
682
712
common_write(Config, Callback, Req, LocalAccess, ExpectedBlockNo, ActualBlockNo, Data, Prepared)
683
713
  when ActualBlockNo =:= (ExpectedBlockNo - 1), is_binary(Data), is_record(Prepared, prepared) ->
730
760
            Config#config{polite_ack = true}
731
761
    end.
732
762
 
 
763
-spec terminate(#config{}, #tftp_msg_req{}, {'ok', _} | #error{}) -> no_return().
 
764
 
733
765
terminate(Config, Req, Result) ->
734
766
    Result2 =
735
767
        case Result of
1441
1473
    %% Handle upgrade from old releases. Please, remove this clause in next release.
1442
1474
    system_continue(Parent, Debug, #sys_misc{module = ?MODULE, function = Fun, arguments = Args}).
1443
1475
 
 
1476
-spec system_terminate(_, _, _, #sys_misc{} | {_, _}) -> no_return().
 
1477
 
1444
1478
system_terminate(Reason, _Parent, _Debug, #sys_misc{}) ->
1445
1479
    exit(Reason);
1446
1480
system_terminate(Reason, Parent, Debug, {Fun, Args}) ->