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

« back to all changes in this revision

Viewing changes to lib/ssh/src/ssh_sftpd.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-05-07 15:07:37 UTC
  • mfrom: (1.2.1 upstream) (5.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20090507150737-i4yb5elwinm7r0hc
Tags: 1:13.b-dfsg1-1
* Removed another bunch of non-free RFCs from original tarball
  (closes: #527053).
* Fixed build-dependencies list by adding missing comma. This requires
  libsctp-dev again. Also, added libsctp1 dependency to erlang-base and
  erlang-base-hipe packages because the shared library is loaded via
  dlopen now and cannot be added using dh_slibdeps (closes: #526682).
* Weakened dependency of erlang-webtool on erlang-observer to recommends
  to avoid circular dependencies (closes: #526627).
* Added solaris-i386 to HiPE enabled architectures.
* Made script sources in /usr/lib/erlang/erts-*/bin directory executable,
  which is more convenient if a user wants to create a target Erlang system.
* Shortened extended description line for erlang-dev package to make it
  fit 80x25 terminals.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
 
%%<copyright>
2
 
%% <year>2004-2007</year>
3
 
%% <holder>Ericsson AB, All Rights Reserved</holder>
4
 
%%</copyright>
5
 
%%<legalnotice>
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%% 
 
4
%% Copyright Ericsson AB 2005-2009. 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
%% 
 
17
%% %CopyrightEnd%
16
18
%%
17
 
%% The Initial Developer of the Original Code is Ericsson AB.
18
 
%%</legalnotice>
 
19
 
19
20
%%
20
21
 
21
22
%%% Description: SFTP server daemon
22
23
 
23
24
-module(ssh_sftpd).
24
25
 
25
 
-behaviour(gen_server).
 
26
%%-behaviour(gen_server).
 
27
-behaviour(ssh_channel).
26
28
 
27
 
%%--------------------------------------------------------------------
28
 
%% Include files
29
 
%%--------------------------------------------------------------------
30
29
-include_lib("kernel/include/file.hrl").
31
30
 
32
31
-include("ssh.hrl").
33
32
-include("ssh_xfer.hrl").
34
33
 
35
 
-define(DEFAULT_TIMEOUT, 5000).
36
 
 
37
34
%%--------------------------------------------------------------------
38
35
%% External exports
39
36
-export([subsystem_spec/1,
40
37
         listen/1, listen/2, listen/3, stop/1]).
41
38
 
42
 
%% gen_server callbacks
43
 
-export([init/1, handle_call/3, handle_cast/2, handle_info/2,
44
 
         terminate/2, code_change/3]).
 
39
-export([init/1, handle_ssh_msg/2, handle_msg/2, terminate/2, code_change/3]).
45
40
 
46
41
-record(state, {
47
42
          xf,                           % [{channel,ssh_xfer states}...]
51
46
          pending,                      % binary() 
52
47
          file_handler,                 % atom() - callback module 
53
48
          file_state,                   % state for the file callback module
 
49
          max_files,                    % integer >= 0 max no files sent during READDIR
54
50
          handles                       % list of open handles
55
51
          %% handle is either {<int>, directory, {Path, unread|eof}} or
56
52
          %% {<int>, file, {Path, IoDevice}}
60
56
%% API
61
57
%%====================================================================
62
58
subsystem_spec(Options) ->
63
 
    Name = make_ref(),
64
 
    StartFunc = {gen_server, 
65
 
                 start_link, [ssh_sftpd, [Options], []]},
66
 
    Restart = transient, 
67
 
    Shutdown = 3600,
68
 
    Modules = [ssh_sftpd],
69
 
    Type = worker,
70
 
    {"sftp", {Name, StartFunc, Restart, Shutdown, Type, Modules}}.
 
59
    {"sftp", {?MODULE, Options}}.
 
60
 
 
61
%%% DEPRECATED START %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
71
62
 
72
63
%%--------------------------------------------------------------------
73
64
%% Function: listen() -> Pid | {error,Error}
88
79
stop(Pid) ->
89
80
    ssh_cli:stop(Pid).
90
81
 
 
82
 
 
83
%%% DEPRECATED END %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
84
 
91
85
%%====================================================================
92
 
%% gen_server callbacks
 
86
%% subsystem callbacks
93
87
%%====================================================================
94
88
 
95
89
%%--------------------------------------------------------------------
96
 
%% Function: init(Args) -> {ok, State} |
97
 
%%                         {ok, State, Timeout} |
98
 
%%                         ignore               |
99
 
%%                         {stop, Reason}
 
90
%% Function: init(Args) -> {ok, State}
100
91
%% Description: Initiates the server
101
92
%%--------------------------------------------------------------------
102
 
init([Options]) ->
 
93
init(Options) ->
103
94
    {FileMod, FS0} = case proplists:get_value(file_handler, Options, 
104
95
                                              {ssh_sftpd_file,[]}) of
105
96
                         {F, S} ->
110
101
    
111
102
    {{ok, Default}, FS1} = FileMod:get_cwd(FS0),
112
103
    CWD = proplists:get_value(cwd, Options, Default),
113
 
    Root = proplists:get_value(root, Options, ""),
114
 
    State = #state{cwd = CWD, root = Root, handles = [], pending = <<>>,
115
 
                   file_handler = FileMod, file_state = FS1},
 
104
    
 
105
    Root0 = proplists:get_value(root, Options, ""),
 
106
    
 
107
    %% Get the root of the file system (symlinks must be followed,
 
108
    %% otherwise the realpath call won't work). But since symbolic links
 
109
    %% isn't supported on all plattforms we have to use the root property
 
110
    %% supplied by the user.
 
111
    {Root, State} = 
 
112
        case resolve_symlinks(Root0, 
 
113
                              #state{root = Root0,
 
114
                                     file_handler = FileMod, 
 
115
                                     file_state = FS1}) of
 
116
            {{ok, Root1}, State0} ->
 
117
                {Root1, State0};
 
118
            {{error, _}, State0} ->
 
119
                {Root0, State0}
 
120
        end,
 
121
    MaxLength = proplists:get_value(max_files, Options, 0),
 
122
 
 
123
    Vsn = proplists:get_value(vsn, Options, 5),
 
124
 
 
125
    {ok,  State#state{cwd = CWD, root = Root, max_files = MaxLength,
 
126
                      handles = [], pending = <<>>,
 
127
                      xf = #ssh_xfer{vsn = Vsn, ext = []}}}.
 
128
 
 
129
 
 
130
%%--------------------------------------------------------------------
 
131
%% Function: code_change(OldVsn, State, Extra) -> {ok, NewState}
 
132
%% Description: 
 
133
%%--------------------------------------------------------------------
 
134
code_change(_OldVsn, State, _Extra) -> 
116
135
    {ok, State}.
117
136
 
118
 
%%--------------------------------------------------------------------
119
 
%% Function: %% handle_call(Request, From, State) -> {reply, Reply, State} |
120
 
%%                                      {reply, Reply, State, Timeout} |
121
 
%%                                      {noreply, State} |
122
 
%%                                      {noreply, State, Timeout} |
123
 
%%                                      {stop, Reason, Reply, State} |
124
 
%%                                      {stop, Reason, State}
125
 
%% Description: Handling call messages
126
 
%%--------------------------------------------------------------------
127
 
handle_call(_Request, _From, State) ->
128
 
    Reply = ok,
129
 
    {reply, Reply, State}.
130
 
 
131
 
%%--------------------------------------------------------------------
132
 
%% Function: handle_cast(Msg, State) -> {noreply, State} |
133
 
%%                                      {noreply, State, Timeout} |
134
 
%%                                      {stop, Reason, State}
135
 
%% Description: Handling cast messages
136
 
%%--------------------------------------------------------------------
137
 
handle_cast(_Msg, State) ->
138
 
    {noreply, State}.
139
 
 
140
 
%%--------------------------------------------------------------------
141
 
%% Function: handle_info(Info, State) -> {noreply, State} |
142
 
%%                                       {noreply, State, Timeout} |
143
 
%%                                       {stop, Reason, State}
144
 
%% Description: Handling all non call/cast messages
145
 
%%--------------------------------------------------------------------
146
 
 
147
 
handle_info({ssh_cm, CM, {open, Channel, RemoteChannel, _Type}}, State) ->
148
 
    XF = #ssh_xfer{vsn = 5, ext = [], cm = CM, channel = Channel},
149
 
    State1 = State#state{xf = XF, remote_channel = RemoteChannel},
150
 
    {noreply, State1};
151
 
handle_info({ssh_cm, CM, {data, Channel, Type, Data}}, State) ->
152
 
    ssh_connection:adjust_window(CM, Channel, size(Data)),
 
137
 
 
138
%%--------------------------------------------------------------------
 
139
%% Function: handle_ssh_msg(Args) -> {ok, State} | {stop, ChannelId, State}
 
140
%%                        
 
141
%% Description: Handles channel messages
 
142
%%--------------------------------------------------------------------
 
143
handle_ssh_msg({ssh_cm, _ConnectionManager,
 
144
                {data, _ChannelId, Type, Data}}, State) ->
153
145
    State1 = handle_data(Type, Data, State),
154
 
    {noreply, State1};
155
 
 
156
 
handle_info({ssh_cm, CM, {subsystem, _, WantReply, "sftp"}}, 
157
 
            #state{remote_channel = ChannelId} = State) ->
158
 
    ssh_connection:reply_request(CM, WantReply, success, ChannelId),
159
 
    {noreply, State};
160
 
 
161
 
%% The client has terminated the session
162
 
%% TODO: why check channel in xf ssh_xfer?
163
 
handle_info({ssh_cm, _, {eof, Channel}}, 
164
 
            State = #state{xf = #ssh_xfer{channel = Channel}}) ->
165
 
    {stop, normal, State};
166
 
 
167
 
handle_info({ssh_cm, _CM, {closed, _Channel}}, State) ->
168
 
    %% ignore -- we'll get an {eof, Channel} soon??
169
 
    {noreply, State};
170
 
 
171
 
handle_info(_Info, State) ->
172
 
    ?dbg(true, "handle_info: Info=~p State=~p\n", [_Info, State]),
173
 
    {noreply, State}.
174
 
 
 
146
    {ok, State1};
 
147
 
 
148
handle_ssh_msg({ssh_cm, _, {eof, ChannelId}}, State) ->
 
149
    {stop, ChannelId, State};
 
150
 
 
151
handle_ssh_msg({ssh_cm, _, {signal, _, _}}, State) ->
 
152
    %% Ignore signals according to RFC 4254 section 6.9.
 
153
    {ok, State};
 
154
 
 
155
handle_ssh_msg({ssh_cm, _, {exit_signal, ChannelId, _, Error, _}}, State) ->
 
156
    Report = io_lib:format("Connection closed by peer ~n Error ~p~n",
 
157
                           [Error]),
 
158
    error_logger:error_report(Report),
 
159
    {stop, ChannelId,  State};
 
160
 
 
161
handle_ssh_msg({ssh_cm, _, {exit_status, ChannelId, 0}}, State) ->
 
162
    {stop, ChannelId, State};
 
163
 
 
164
handle_ssh_msg({ssh_cm, _, {exit_status, ChannelId, Status}}, State) ->
 
165
    
 
166
    Report = io_lib:format("Connection closed by peer ~n Status ~p~n",
 
167
                           [Status]),
 
168
    error_logger:error_report(Report),
 
169
    {stop, ChannelId, State}.
 
170
 
 
171
%%--------------------------------------------------------------------
 
172
%% Function: handle_ssh_msg(Args) -> {ok, State} | {stop, ChannelId, State}
 
173
%%                        
 
174
%% Description: Handles other messages
 
175
%%--------------------------------------------------------------------
 
176
handle_msg({ssh_channel_up, ChannelId,  ConnectionManager}, 
 
177
           #state{xf =Xf} = State) ->
 
178
    {ok,  State#state{xf = Xf#ssh_xfer{cm = ConnectionManager,
 
179
                                       channel = ChannelId}}}.
 
180
 
 
181
%%--------------------------------------------------------------------
 
182
%% Function: terminate(Reason, State) -> void()
 
183
%% Description: This function is called by a gen_server when it is about to
 
184
%% terminate. It should be the opposite of Module:init/1 and do any necessary
 
185
%% cleaning up. When it returns, the gen_server terminates with Reason.
 
186
%% The return value is ignored.
 
187
%%--------------------------------------------------------------------
 
188
terminate(_, #state{handles=Handles, file_handler=FileMod, file_state=FS}) ->
 
189
    CloseFun = fun({_, file, {_, Fd}}, FS0) ->
 
190
                       {_Res, FS1} = FileMod:close(Fd, FS0),
 
191
                       FS1;
 
192
                  (_, FS0) ->
 
193
                       FS0
 
194
               end,
 
195
    lists:foldl(CloseFun, FS, Handles),
 
196
    ok.
 
197
 
 
198
%%--------------------------------------------------------------------
 
199
%%% Internal functions
 
200
%%--------------------------------------------------------------------
175
201
handle_data(0, <<?UINT32(Len), Msg:Len/binary, Rest/binary>>, 
176
202
            State = #state{pending = <<>>}) ->
177
203
    <<Op, ?UINT32(ReqId), Data/binary>> = Msg,
188
214
 
189
215
handle_data(Type, Data, State = #state{pending = Pending}) -> 
190
216
     handle_data(Type, <<Pending/binary, Data/binary>>, 
191
 
                 State#state{pending = <<>>});
 
217
                 State#state{pending = <<>>}).
192
218
 
193
 
handle_data(_, Data, State) ->
194
 
    error_logger:format("ssh: STDERR: ~s\n", [binary_to_list(Data)]),
195
 
    State.
196
 
 
197
219
handle_op(?SSH_FXP_INIT, Version, B, State) when is_binary(B) ->
198
220
    XF = State#state.xf,
199
221
    Vsn = lists:min([XF#ssh_xfer.vsn, Version]),
202
224
    State#state{xf = XF1};
203
225
handle_op(?SSH_FXP_REALPATH, ReqId,
204
226
          <<?UINT32(Rlen), RPath:Rlen/binary>>,
205
 
          #state{root = Root} = State) ->
206
 
    RelPath = binary_to_list(RPath),
207
 
    AbsPath = relate_file_name(RelPath, State),
208
 
    NewAbsPath = case AbsPath of
209
 
                     Root -> 
210
 
                         "/";
211
 
                     Other ->
212
 
                         Other -- Root
213
 
                 end,
214
 
    ?dbg(true, "handle_op ?SSH_FXP_REALPATH: RelPath=~p AbsPath=~p\n",
215
 
         [RelPath, NewAbsPath]),
216
 
    XF = State#state.xf,
217
 
    Attr = #ssh_xfer_attr{type=directory},
218
 
    ssh_xfer:xf_send_name(XF, ReqId, NewAbsPath, Attr),
219
 
    State;
 
227
          State0) ->
 
228
    RelPath0 = binary_to_list(RPath),
 
229
    RelPath = relate_file_name(RelPath0, State0, _Canonicalize=false),
 
230
    {Res, State} = resolve_symlinks(RelPath, State0),
 
231
    case Res of
 
232
        {ok, AbsPath} ->
 
233
            NewAbsPath = chroot_filename(AbsPath, State),
 
234
            ?dbg(true, "handle_op ?SSH_FXP_REALPATH: RelPath=~p AbsPath=~p\n",
 
235
                 [RelPath, NewAbsPath]),
 
236
            XF = State#state.xf,
 
237
            Attr = #ssh_xfer_attr{type=directory},
 
238
            ssh_xfer:xf_send_name(XF, ReqId, NewAbsPath, Attr),
 
239
            State;
 
240
        {error, _} = Error ->
 
241
            send_status(Error, ReqId, State)
 
242
    end;
220
243
handle_op(?SSH_FXP_OPENDIR, ReqId,
221
244
         <<?UINT32(RLen), RPath:RLen/binary>>,
222
245
          State0 = #state{file_handler = FileMod, file_state = FS0}) ->
242
265
        {_Handle, directory, {_RelPath, eof}} ->
243
266
            ssh_xfer:xf_send_status(XF, ReqId, ?SSH_FX_EOF),
244
267
            State;
245
 
        {Handle, directory, {RelPath, _}} ->
246
 
            read_dir(State, XF, ReqId, Handle, RelPath);
 
268
        {Handle, directory, {RelPath, Status}} ->
 
269
            read_dir(State, XF, ReqId, Handle, RelPath, Status);
247
270
        _ ->
248
271
            ssh_xfer:xf_send_status(XF, ReqId, ?SSH_FX_INVALID_HANDLE),
249
272
            State
407
430
    State1 = State0#state{file_state = FS1},
408
431
    send_status(Status, ReqId, State1).
409
432
 
410
 
%%--------------------------------------------------------------------
411
 
%% Function: terminate(Reason, State) -> void()
412
 
%% Description: This function is called by a gen_server when it is about to
413
 
%% terminate. It should be the opposite of Module:init/1 and do any necessary
414
 
%% cleaning up. When it returns, the gen_server terminates with Reason.
415
 
%% The return value is ignored.
416
 
%%--------------------------------------------------------------------
417
 
terminate(_, #state{handles=Handles, file_handler=FileMod, file_state=FS}) ->
418
 
    CloseFun = fun({_, file, {_, Fd}}, FS0) ->
419
 
                       {_Res, FS1} = FileMod:close(Fd, FS0),
420
 
                       FS1;
421
 
                  (_, FS0) ->
422
 
                       FS0
423
 
               end,
424
 
    lists:foldl(CloseFun, FS, Handles),
425
 
    ok.
426
 
 
427
 
%%--------------------------------------------------------------------
428
 
%% Func: code_change(OldVsn, State, Extra) -> {ok, NewState}
429
 
%% Description: Convert process state when code is changed
430
 
%%--------------------------------------------------------------------
431
 
code_change(_OldVsn, State, _Extra) ->
432
 
    {ok, State}.
433
 
 
434
 
%%--------------------------------------------------------------------
435
 
%%% Internal functions
436
 
%%--------------------------------------------------------------------
437
 
 
438
433
new_handle([], H) ->
439
434
    H;
440
435
new_handle([{N, _} | Rest], H) when N > H ->
450
445
    
451
446
get_handle(Handles, BinHandle) ->
452
447
    case (catch list_to_integer(binary_to_list(BinHandle))) of
453
 
        I when integer(I) ->
 
448
        I when is_integer(I) ->
454
449
            case lists:keysearch(I, 1, Handles) of
455
450
                {value, T} -> T;
456
451
                false -> error
460
455
    end.
461
456
 
462
457
%%% read_dir/5: read directory, send names, and return new state
463
 
read_dir(State0 = #state{file_handler = FileMod, file_state = FS0},
464
 
         XF, ReqId, Handle, RelPath) ->
 
458
read_dir(State0 = #state{file_handler = FileMod, max_files = MaxLength, file_state = FS0},
 
459
         XF, ReqId, Handle, RelPath, {cache, Files}) ->
 
460
    AbsPath = relate_file_name(RelPath, State0),
 
461
    ?dbg(true, "read_dir: AbsPath=~p\n", [AbsPath]),
 
462
    if
 
463
        length(Files) > MaxLength ->
 
464
            {ToSend, NewCache} = lists:split(MaxLength, Files),
 
465
            {NamesAndAttrs, FS1} = get_attrs(AbsPath, ToSend, FileMod, FS0),
 
466
            ssh_xfer:xf_send_names(XF, ReqId, NamesAndAttrs),
 
467
            Handles = lists:keyreplace(Handle, 1,
 
468
                                       State0#state.handles,
 
469
                                       {Handle, directory, {RelPath,{cache, NewCache}}}),
 
470
            State0#state{handles = Handles, file_state = FS1};
 
471
        true ->
 
472
            {NamesAndAttrs, FS1} = get_attrs(AbsPath, Files, FileMod, FS0),
 
473
            ssh_xfer:xf_send_names(XF, ReqId, NamesAndAttrs),
 
474
            Handles = lists:keyreplace(Handle, 1,
 
475
                                       State0#state.handles,
 
476
                                       {Handle, directory, {RelPath,eof}}),
 
477
            State0#state{handles = Handles, file_state = FS1}
 
478
    end;
 
479
read_dir(State0 = #state{file_handler = FileMod, max_files = MaxLength, file_state = FS0},
 
480
         XF, ReqId, Handle, RelPath, _Status) ->
465
481
    AbsPath = relate_file_name(RelPath, State0),
466
482
    ?dbg(true, "read_dir: AbsPath=~p\n", [AbsPath]),
467
483
    {Res, FS1} = FileMod:list_dir(AbsPath, FS0),
468
484
    case Res of
 
485
        {ok, Files} when MaxLength == 0 orelse MaxLength > length(Files) ->
 
486
            {NamesAndAttrs, FS2} = get_attrs(AbsPath, Files, FileMod, FS1),
 
487
            ssh_xfer:xf_send_names(XF, ReqId, NamesAndAttrs),
 
488
            Handles = lists:keyreplace(Handle, 1,
 
489
                                       State0#state.handles,
 
490
                                       {Handle, directory, {RelPath,eof}}),
 
491
            State0#state{handles = Handles, file_state = FS2};
469
492
        {ok, Files} ->
470
 
            {NamesAndAttrs, FS2} = get_attrs(AbsPath, Files, FileMod, FS1),
 
493
            {ToSend, Cache} = lists:split(MaxLength, Files),
 
494
            {NamesAndAttrs, FS2} = get_attrs(AbsPath, ToSend, FileMod, FS1),
471
495
            ssh_xfer:xf_send_names(XF, ReqId, NamesAndAttrs),
472
496
            Handles = lists:keyreplace(Handle, 1,
473
497
                                       State0#state.handles,
474
 
                                       {Handle, directory, {RelPath,eof}}),
 
498
                                       {Handle, directory, {RelPath,{cache, Cache}}}),
475
499
            State0#state{handles = Handles, file_state = FS2};
476
500
        {error, Error} ->
477
501
            State1 = State0#state{file_state = FS1},
478
502
            send_status({error, Error}, ReqId, State1)
479
503
    end.
480
504
 
 
505
 
481
506
%%% get_attrs: get stat of each file and return
482
507
get_attrs(RelPath, Files, FileMod, FS) ->
483
508
    get_attrs(RelPath, Files, FileMod, FS, []).
549
574
decode_4_open_flag(truncate_existing) ->
550
575
    [write];
551
576
decode_4_open_flag(open_existing) ->
552
 
    [read,write].
 
577
    [read].
553
578
 
554
579
decode_4_flags([OpenFlag | Flags]) ->
555
580
    decode_4_flags(Flags, decode_4_open_flag(OpenFlag)).
563
588
decode_4_flags([_|R], Flags) ->
564
589
    decode_4_flags(R, Flags).
565
590
 
 
591
decode_4_access_flag(read_data) ->
 
592
    [read];
 
593
decode_4_access_flag(list_directory) ->
 
594
    [read];
 
595
decode_4_access_flag(write_data) ->
 
596
    [write];
 
597
decode_4_access_flag(add_file) ->
 
598
    [write];
 
599
decode_4_access_flag(add_subdirectory) ->
 
600
    [read];
 
601
decode_4_access_flag(append_data) ->
 
602
    [append];
 
603
decode_4_access_flag(_) ->
 
604
    [read].
 
605
 
 
606
decode_4_acess([_ | _] = Flags) ->
 
607
    lists:map(fun(Flag) -> 
 
608
                      [decode_4_access_flag(Flag)]
 
609
              end, Flags);
 
610
decode_4_acess([]) ->
 
611
    [].
 
612
 
566
613
open(Vsn, ReqId, Data, State) when Vsn =< 3 ->
567
614
    <<?UINT32(BLen), BPath:BLen/binary, ?UINT32(PFlags),
568
615
     _Attrs/binary>> = Data,
571
618
    ?dbg(true, "open: Flags=~p\n", [Flags]),
572
619
    do_open(ReqId, State, Path, Flags);
573
620
open(Vsn, ReqId, Data, State) when Vsn >= 4 ->
574
 
    <<?UINT32(BLen), BPath:BLen/binary, ?UINT32(_Access),
 
621
    <<?UINT32(BLen), BPath:BLen/binary, ?UINT32(Access),
575
622
     ?UINT32(PFlags), _Attrs/binary>> = Data,
576
623
    Path = binary_to_list(BPath),
577
 
    Fl = ssh_xfer:decode_open_flags(Vsn, PFlags),
578
 
    ?dbg(true, "open: Fl=~p\n", [Fl]),
579
 
    Flags = decode_4_flags(Fl),
 
624
    FlagBits = ssh_xfer:decode_open_flags(Vsn, PFlags),
 
625
    AcessBits = ssh_xfer:decode_ace_mask(Access),
 
626
    ?dbg(true, "open: Fl=~p\n", [FlagBits]),
 
627
    %% TODO: This is to make sure the Access flags are not ignored
 
628
    %% but this should be thought through better. This solution should
 
629
    %% be considered a hack in order to buy some time. At least
 
630
    %% it works better than when the Access flags where totally ignored.
 
631
    %% A better solution may need some code refactoring that we do
 
632
    %% not have time for right now.
 
633
    AcessFlags = decode_4_acess(AcessBits),
 
634
    Flags = lists:append(lists:umerge(
 
635
                           [[decode_4_flags(FlagBits)] | AcessFlags])),
 
636
 
580
637
    ?dbg(true, "open: Flags=~p\n", [Flags]),
 
638
    
581
639
    do_open(ReqId, State, Path, Flags).
582
640
 
583
641
do_open(ReqId, State0, Path, Flags) ->
608
666
            State1
609
667
    end.
610
668
 
611
 
relate_file_name(File, State) when binary(File) ->
612
 
    relate_file_name(binary_to_list(File), State);
613
 
relate_file_name(File, #state{cwd = CWD, root = ""}) ->
614
 
    relate(File, CWD);
615
 
relate_file_name(File, #state{root = Root}) ->
616
 
    case within_root(Root, File) of
617
 
        File ->
618
 
            File;
619
 
        Root ->
620
 
            NewFile = relate(make_relative_filename(File), Root),
621
 
            within_root(Root, NewFile)
622
 
    end.
623
 
 
624
 
within_root(Root, File) ->
625
 
    case lists:prefix(Root, File) of
 
669
%% resolve all symlinks in a path
 
670
resolve_symlinks(Path, State) ->
 
671
    resolve_symlinks(Path, _LinkCnt=32, State).
 
672
 
 
673
resolve_symlinks(Path, LinkCnt, State0) ->
 
674
    resolve_symlinks_2(filename:split(Path), State0, LinkCnt, []).
 
675
 
 
676
resolve_symlinks_2(_Path, State, LinkCnt, _AccPath) when LinkCnt =:= 0 ->
 
677
    %% Too many links (there might be a symlink loop)
 
678
    {{error, emlink}, State};
 
679
resolve_symlinks_2(["." | RestPath], State0, LinkCnt, AccPath) ->
 
680
    resolve_symlinks_2(RestPath, State0, LinkCnt, AccPath);
 
681
resolve_symlinks_2([".." | RestPath], State0, LinkCnt, AccPath) ->
 
682
    %% Remove the last path component
 
683
    AccPathComps0 = filename:split(AccPath),
 
684
    Path =  case lists:reverse(tl(lists:reverse(AccPathComps0))) of
 
685
                [] ->
 
686
                    "";
 
687
                AccPathComps ->
 
688
                    filename:join(AccPathComps)
 
689
            end,
 
690
    resolve_symlinks_2(RestPath, State0, LinkCnt, Path);
 
691
resolve_symlinks_2([PathComp | RestPath], State0, LinkCnt, AccPath0) ->
 
692
    #state{file_handler = FileMod, file_state = FS0} = State0,
 
693
    AccPath1 = filename:join(AccPath0, PathComp),
 
694
    {Res, FS1} = FileMod:read_link(AccPath1, FS0),
 
695
    State1 = State0#state{file_state = FS1},
 
696
    case Res of
 
697
        {ok, Target0} ->     % path is a symlink
 
698
            %% The target may be a relative or an absolute path and
 
699
            %% may contain symlinks
 
700
            Target1 = filename:absname(Target0, AccPath0),
 
701
            {FollowRes, State2} = resolve_symlinks(Target1, LinkCnt-1, State1),
 
702
            case FollowRes of
 
703
                {ok, Target} ->
 
704
                    resolve_symlinks_2(RestPath, State2, LinkCnt-1, Target);
 
705
                {error, _} = Error ->
 
706
                    {Error, State2}
 
707
            end;
 
708
        {error, einval} ->   % path exists, but is not a symlink
 
709
            resolve_symlinks_2(RestPath, State1, LinkCnt, AccPath1);
 
710
        {error, _} = Error ->
 
711
            {Error, State1}
 
712
    end;
 
713
resolve_symlinks_2([], State, _LinkCnt, AccPath) ->
 
714
    {{ok, AccPath}, State}.
 
715
 
 
716
 
 
717
relate_file_name(File, State) ->
 
718
    relate_file_name(File, State, _Canonicalize=true).
 
719
 
 
720
relate_file_name(File, State, Canonicalize) when is_binary(File) ->
 
721
    relate_file_name(binary_to_list(File), State, Canonicalize);
 
722
relate_file_name(File, #state{cwd = CWD, root = ""}, Canonicalize) ->
 
723
    relate_filename_to_path(File, CWD, Canonicalize);
 
724
relate_file_name(File, #state{root = Root}, Canonicalize) ->
 
725
    case is_within_root(Root, File) of
626
726
        true ->
627
727
            File;
628
728
        false ->
629
 
            Root
 
729
            RelFile = make_relative_filename(File),
 
730
            NewFile = relate_filename_to_path(RelFile, Root, Canonicalize),
 
731
            case is_within_root(Root, NewFile) of
 
732
                true ->
 
733
                    NewFile;
 
734
                false ->
 
735
                    Root
 
736
            end
630
737
    end.
631
738
 
 
739
is_within_root(Root, File) ->
 
740
    lists:prefix(Root, File).
 
741
 
632
742
%% Remove leading slash (/), if any, in order to make the filename
633
743
%% relative (to the root)
634
744
make_relative_filename("/")       -> "./"; % Make it relative and preserve /
635
745
make_relative_filename("/"++File) -> File;
636
746
make_relative_filename(File)      -> File.
637
747
 
638
 
relate(File0, Path) ->
 
748
relate_filename_to_path(File0, Path, Canonicalize) ->
639
749
    File1 = filename:absname(File0, Path),
640
 
    Parts = fix_file_name(filename:split(File1), []),
641
 
    File2 = filename:join(Parts),
 
750
    File2 = if Canonicalize -> canonicalize_filename(File1);
 
751
               true         -> File1
 
752
            end,
642
753
    ensure_trailing_slash_is_preserved(File0, File2).
643
754
 
644
755
%% It seems as if the openssh client (observed with the
694
805
    
695
806
 
696
807
%%% fix file just a little: a/b/.. -> a and a/. -> a
697
 
fix_file_name([".." | Rest], ["/"] = Acc) ->
698
 
    fix_file_name(Rest, Acc);
699
 
fix_file_name([".." | Rest], [_Dir | Paths]) ->
700
 
    fix_file_name(Rest, Paths);
701
 
fix_file_name(["." | Rest], Acc) ->
702
 
    fix_file_name(Rest, Acc);
703
 
fix_file_name([A | Rest], Acc) ->
704
 
    fix_file_name(Rest, [A | Acc]);
705
 
fix_file_name([], Acc) ->
 
808
canonicalize_filename(File0) ->
 
809
    File = filename:join(canonicalize_filename_2(filename:split(File0), [])),
 
810
    ensure_trailing_slash_is_preserved(File0, File).
 
811
 
 
812
canonicalize_filename_2([".." | Rest], ["/"] = Acc) ->
 
813
    canonicalize_filename_2(Rest, Acc);
 
814
canonicalize_filename_2([".." | Rest], [_Dir | Paths]) ->
 
815
    canonicalize_filename_2(Rest, Paths);
 
816
canonicalize_filename_2(["." | Rest], Acc) ->
 
817
    canonicalize_filename_2(Rest, Acc);
 
818
canonicalize_filename_2([A | Rest], Acc) ->
 
819
    canonicalize_filename_2(Rest, [A | Acc]);
 
820
canonicalize_filename_2([], Acc) ->
706
821
    lists:reverse(Acc).
707
 
    
 
822
 
 
823
%% return a filename which is relative to the root directory
 
824
%% (any filename that's outside the root directory is forced to the root)
 
825
chroot_filename(Filename, #state{root = Root}) ->
 
826
    FilenameComps0 = filename:split(Filename),
 
827
    RootComps = filename:split(Root),
 
828
    filename:join(chroot_filename_2(FilenameComps0, RootComps)).
 
829
 
 
830
chroot_filename_2([PathComp | FilenameRest], [PathComp | RootRest]) ->
 
831
    chroot_filename_2(FilenameRest, RootRest);
 
832
chroot_filename_2(FilenameComps, []) when length(FilenameComps) > 0 ->
 
833
    %% Ensure there's a leading / (filename:join above will take care
 
834
    %% of any duplicates)
 
835
    ["/" | FilenameComps];
 
836
chroot_filename_2(_FilenameComps, _RootComps) ->
 
837
    %% The filename is either outside the root or at the root.  In
 
838
    %% both cases we want to force the filename to the root.
 
839
    ["/"].
 
840
 
 
841
 
708
842
read_file(ReqId, IoDevice, Offset, Len, 
709
843
          State0 = #state{file_handler = FileMod, file_state = FS0}) ->
710
844
    {Res1, FS1} = FileMod:position(IoDevice, {bof, Offset}, FS0),
750
884
    ssh_xfer:xf_send_status(State#state.xf, ReqId, get_status(Status)),
751
885
    State.
752
886
 
753
 
%%
754
887
set_stat(<<>>, _Path, State) ->
755
888
    {ok, State};
756
889
set_stat(Attr, Path,