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

« back to all changes in this revision

Viewing changes to lib/cosFileTransfer/src/CosFileTransfer_FileTransferSession_impl.erl

  • Committer: Bazaar Package Importer
  • Author(s): Erlang Packagers, Sergei Golovan
  • Date: 2006-12-03 17:07:44 UTC
  • mfrom: (2.1.11 feisty)
  • Revision ID: james.westby@ubuntu.com-20061203170744-rghjwupacqlzs6kv
Tags: 1:11.b.2-4
[ Sergei Golovan ]
Fixed erlang-base and erlang-base-hipe prerm scripts.

Show diffs side-by-side

added added

removed removed

Lines of Context:
99
99
%%              {stop, Reason}
100
100
%% Description: Initiates the server
101
101
%%----------------------------------------------------------------------
102
 
init(['FTP', Host, Port, User, Password, Account, Protocol, Timeout]) ->
 
102
init(['FTP', Host, Port, User, Password, _Account, Protocol, Timeout]) ->
103
103
    {ok, Pid} = ftp:open(Host, Port, []),
104
104
    ok = ftp:user(Pid, User, Password),
105
105
    {ok, PWD} = ftp:pwd(Pid),
106
106
    {Connection, ProtocolSupport} = setup_local(Protocol),
107
107
    {ok, ?create_InitState(ProtocolSupport, Pid, 'FTP', 
108
108
                           PWD, ftp, Connection, Protocol, Timeout)};
109
 
init([{'NATIVE', Mod}, Host, Port, User, Password, Account, Protocol, Timeout]) ->
 
109
init([{'NATIVE', Mod}, Host, Port, User, Password, _Account, Protocol, Timeout]) ->
110
110
    {ok, Pid} = Mod:open(Host, Port),
111
111
    ok = Mod:user(Pid, User, Password),
112
112
    {ok, PWD} = Mod:pwd(Pid),
120
120
%% Returns    : any (ignored by gen_server)
121
121
%% Description: Shutdown the server
122
122
%%----------------------------------------------------------------------
123
 
terminate(Reason, State) ->
 
123
terminate(_Reason, State) ->
124
124
    case ?get_MyType(State) of
125
125
        ssl ->
126
126
            catch ssl:close(?get_Connection(State));
134
134
%% Returns    : {ok, NewState}
135
135
%% Description: Convert process state when code is changed
136
136
%%----------------------------------------------------------------------
137
 
code_change(OldVsn, State, Extra) ->
 
137
code_change(_OldVsn, State, _Extra) ->
138
138
    {ok, State}.
139
139
 
140
140
%%---------------------------------------------------------------------%
145
145
%%----------------------------------------------------------------------
146
146
handle_info(Info, State) ->
147
147
    case Info of
148
 
        {'EXIT', Pid, Reason} ->
 
148
        {'EXIT', _Pid, Reason} ->
149
149
            {stop, Reason, State};
150
 
        Other ->
 
150
        _Other ->
151
151
            {noreply, State}
152
152
    end.
153
153
 
164
164
%%              }; 
165
165
%% Description: 
166
166
%%----------------------------------------------------------------------
167
 
'_get_protocols_supported'(OE_This, State) ->
 
167
'_get_protocols_supported'(_OE_This, State) ->
168
168
    {reply, ?get_Protocols(State), State}.
169
169
 
170
170
%%----------------------------------------------------------------------
173
173
%% Returns    : 
174
174
%% Description: 
175
175
%%----------------------------------------------------------------------
176
 
set_directory(OE_This, State, Directory)  when ?is_FTP(State); ?is_NATIVE(State) ->
 
176
set_directory(_OE_This, State, Directory)  when ?is_FTP(State); ?is_NATIVE(State) ->
177
177
    Mod  = ?get_Module(State),
178
178
    Path = filename:join('CosFileTransfer_Directory':
179
179
                         '_get_complete_file_name'(Directory)),
244
244
get_file(OE_This, State, FileNameList) when ?is_FTP(State); 
245
245
                                            ?is_NATIVE(State) ->
246
246
    case check_type(OE_This, State, filename:join(FileNameList)) of
247
 
        {ndirectory, Listing} ->
 
247
        {ndirectory, _Listing} ->
248
248
            {reply, 
249
249
             #'CosFileTransfer_FileWrapper'{the_file = 
250
250
                                            cosFileTransferApp:
251
251
                                            create_dir(OE_This, 
252
 
                                                       FileNameList, 
253
 
                                                       Listing),
 
252
                                                       FileNameList),
254
253
                                            file_type = ndirectory}, 
255
254
             State};
256
255
        nfile ->
272
271
%% Returns    : -
273
272
%% Description: 
274
273
%%----------------------------------------------------------------------
275
 
delete(OE_This, State, File) when ?is_FTP(State); ?is_NATIVE(State) ->
 
274
delete(_OE_This, State, File) when ?is_FTP(State); ?is_NATIVE(State) ->
276
275
    Mod = ?get_Module(State),
277
276
    Result =
278
277
        case 'CosPropertyService_PropertySet':
325
324
                      filename:join(SrcName)),
326
325
            check_reply(Pid),
327
326
            {reply, ok, State};
328
 
        {target, SourceFTS} ->
 
327
        {target, _SourceFTS} ->
329
328
            DestName = 'CosFileTransfer_File':'_get_complete_file_name'(DestFile),
330
329
            receive_file(?get_MyType(State), ?get_Connection(State), 
331
330
                         ?get_ConnectionTimeout(State),
336
335
    case which_FTS_type(OE_This, SrcFile, DestFile) of
337
336
        {source, TargetFTS} ->
338
337
            source_FTS_operation(State, SrcFile, DestFile, transfer, 0, TargetFTS);
339
 
        {target, SourceFTS} ->
 
338
        {target, _SourceFTS} ->
340
339
            target_FTS_operation(State, SrcFile, DestFile, send, 0)
341
340
    end.
342
341
 
362
361
                      SrcName),
363
362
            check_reply(Pid),
364
363
            {reply, ok, State};
365
 
        {target, SourceFTS} ->
 
364
        {target, _SourceFTS} ->
366
365
            DestName = filename:join('CosFileTransfer_File':
367
366
                                     '_get_complete_file_name'(DestFile)),
368
367
            check_type(OE_This, State, DestName),
374
373
    case which_FTS_type(OE_This, SrcFile, DestFile) of
375
374
        {source, TargetFTS} ->
376
375
            source_FTS_operation(State, SrcFile, DestFile, append, 0, TargetFTS);
377
 
        {target, SourceFTS} ->
 
376
        {target, _SourceFTS} ->
378
377
            target_FTS_operation(State, SrcFile, DestFile, append, 0)
379
378
    end;
380
 
append(OE_This, State, SrcFile, DestFile) ->
 
379
append(_OE_This, _State, _SrcFile, _DestFile) ->
381
380
    corba:raise(#'NO_IMPLEMENT'{completion_status=?COMPLETED_NO}).
382
381
 
383
382
 
405
404
            {reply, ok, State};
406
405
        {source, TargetFTS} ->
407
406
            source_FTS_operation(State, SrcFile, DestFile, insert, Offset, TargetFTS);
408
 
        {target, SourceFTS} ->
 
407
        {target, _SourceFTS} ->
409
408
            target_FTS_operation(State, SrcFile, DestFile, insert, Offset)
410
409
    end;
411
 
insert(OE_This, State, SrcFile, DestFile, Offset) ->
 
410
insert(_OE_This, _State, _SrcFile, _DestFile, _Offset) ->
412
411
    corba:raise(#'NO_IMPLEMENT'{completion_status=?COMPLETED_NO}).
413
412
 
414
413
 
418
417
%% Returns    : -
419
418
%% Description: 
420
419
%%----------------------------------------------------------------------
421
 
logout(OE_This, State) when ?is_FTP(State); ?is_NATIVE(State) ->
 
420
logout(_OE_This, State) when ?is_FTP(State); ?is_NATIVE(State) ->
422
421
    Mod = ?get_Module(State),
423
422
    catch Mod:close(?get_Server(State)),
424
423
    {stop, normal, ok, State}.
438
437
    Mod = ?get_Module(State),
439
438
    FileNameList = filename:split(?get_CurrentDir(State)),
440
439
    case Mod:nlist(?get_Server(State), ?get_CurrentDir(State)) of
441
 
        {ok, Listing} ->
 
440
        {ok, _Listing} ->
442
441
            {reply, cosFileTransferApp:create_dir(OE_This, FileNameList), 
443
442
             State};
444
443
        {error, epath} ->
465
464
    Mod = ?get_Module(State),
466
465
    case Mod:nlist(?get_Server(State), filename:join(FileNameList)) of
467
466
        {ok, Listing} ->
468
 
            create_content(Listing, OE_This, State, Parent);
 
467
            create_content(Listing, OE_This, State, Parent, FileNameList);
469
468
        {error, epath} ->
470
469
            {reply, [], State};
471
470
        _ ->
643
642
%% Returns    : 
644
643
%% Description: 
645
644
%%----------------------------------------------------------------------
646
 
create_content(Listing, OE_This, State, Parent) ->
 
645
create_content(Listing, OE_This, State, Parent, PathList) ->
647
646
    create_content(string:tokens(Listing, ?SEPARATOR), OE_This, 
648
 
                   State, Parent, []).
 
647
                   State, Parent, PathList, []).
649
648
 
650
 
create_content([], OE_This, State, Parent, Acc) ->
 
649
create_content([], _OE_This, State, _Parent, _PathList, Acc) ->
651
650
    {reply, Acc, State};
652
 
create_content([H|T], OE_This, State, Parent, Acc) ->
653
 
    case check_type(OE_This, State, H) of
 
651
create_content([H|T], OE_This, State, Parent, PathList, Acc) ->
 
652
    FullPathList = PathList ++[filename:basename(H)],
 
653
    case check_type(OE_This, State, filename:join(FullPathList)) of
654
654
        nfile ->
655
 
            create_content(T, OE_This, State, Parent, 
 
655
            create_content(T, OE_This, State, Parent, PathList, 
656
656
                           [#'CosFileTransfer_FileWrapper'
657
657
                            {the_file = cosFileTransferApp:create_file(OE_This, 
658
 
                                                                       filename:split(H), 
 
658
                                                                       FullPathList, 
659
659
                                                                       Parent),
660
660
                             file_type = nfile}|Acc]);
661
 
        {ndirectory, Members} ->
662
 
            create_content(T, OE_This, State, Parent, 
 
661
        {ndirectory, _Members} ->
 
662
            create_content(T, OE_This, State, Parent, PathList, 
663
663
                           [#'CosFileTransfer_FileWrapper'
664
664
                            {the_file = cosFileTransferApp:create_dir(OE_This, 
665
 
                                                                      filename:split(H), 
 
665
                                                                      FullPathList, 
666
666
                                                                      Parent),
667
667
                             file_type = ndirectory}|Acc]);
668
 
         Other ->
 
668
        Other ->
669
669
            Other
670
670
    end.
671
671
    
764
764
%% Returns    : 
765
765
%% Description: 
766
766
%%----------------------------------------------------------------------
767
 
target_FTS_operation(State, SrcFile, DestFile, Op, Offset) ->
 
767
target_FTS_operation(State, _SrcFile, DestFile, Op, Offset) ->
768
768
    Mod = ?get_Module(State),
769
769
    DestName = 'CosFileTransfer_File':'_get_complete_file_name'(DestFile),
770
770
    TempName = cosFileTransferApp:create_name("TemporaryDestFile"),
943
943
%% 
944
944
%% Furthermore, no need for traversing Listings etc.
945
945
%%----------------------------------------------------------------------
946
 
check_type(OE_This, State, FullName) when ?is_FTP(State); ?is_NATIVE(State) ->
 
946
check_type(_OE_This, State, FullName) when ?is_FTP(State); ?is_NATIVE(State) ->
947
947
    Mod = ?get_Module(State),
948
948
    Result =
949
949
        case Mod:nlist(?get_Server(State), FullName) of
972
972
                                          #'CosFileTransfer_RequestFailureException'
973
973
                                          {reason="Unknown error."}}, State}
974
974
                                end;
 
975
                            {error, E} ->
 
976
                                {error, E};     
975
977
                            _ ->
976
978
                                nfile
977
979
                        end
978
980
                end;
 
981
            {error, epath} ->
 
982
                %% Might be a file.
 
983
                DirName = filename:dirname(FullName),
 
984
                case Mod:nlist(?get_Server(State), DirName) of
 
985
                    {ok,  Listing} when length(Listing) > 0->
 
986
                        Members = string:tokens(Listing, ?SEPARATOR),
 
987
                        case lists:member(FullName, Members) of
 
988
                            true ->
 
989
                                nfile;
 
990
                            _ ->
 
991
                                BName = filename:basename(FullName),
 
992
                                case lists:member(BName, Members) of
 
993
                                    true ->
 
994
                                        nfile;
 
995
                                    _ ->
 
996
                                        {error, epath}
 
997
                                end
 
998
                        end;
 
999
                    _ ->
 
1000
                        {error, epath}
 
1001
                end;
979
1002
            _ ->
980
1003
                case Mod:cd(?get_Server(State), FullName) of
981
1004
                    ok ->