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

« 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-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:
36
36
 
37
37
%%--------------------------------------------------------------------
38
38
%% External exports
39
 
-export([listen/1, listen/2, listen/3, stop/1]).
 
39
-export([subsystem_spec/1,
 
40
         listen/1, listen/2, listen/3, stop/1]).
40
41
 
41
42
%% gen_server callbacks
42
43
-export([init/1, handle_call/3, handle_cast/2, handle_info/2,
58
59
%%====================================================================
59
60
%% API
60
61
%%====================================================================
 
62
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}}.
 
71
 
61
72
%%--------------------------------------------------------------------
62
73
%% Function: listen() -> Pid | {error,Error}
63
74
%% Description: Starts the server
67
78
listen(Port, Options) ->
68
79
    listen(any, Port, Options).
69
80
listen(Addr, Port, Options) ->
70
 
    ssh_cm:listen(fun() ->
71
 
                          {ok,Pid} = 
72
 
                              gen_server:start_link(?MODULE, [Options], []),
73
 
                          Pid
74
 
                  end, Addr, Port, Options).
 
81
    SubSystems = [subsystem_spec(Options)],
 
82
    ssh:daemon(Addr, Port, [{subsystems, SubSystems} |Options]).
75
83
 
76
84
%%--------------------------------------------------------------------
77
85
%% Function: stop(Pid) -> ok
135
143
%%                                       {stop, Reason, State}
136
144
%% Description: Handling all non call/cast messages
137
145
%%--------------------------------------------------------------------
138
 
handle_info({ssh_cm, CM, {open, Channel, RemoteChannel, _}}, State) ->
 
146
 
 
147
handle_info({ssh_cm, CM, {open, Channel, RemoteChannel, _Type}}, State) ->
139
148
    XF = #ssh_xfer{vsn = 5, ext = [], cm = CM, channel = Channel},
140
149
    State1 = State#state{xf = XF, remote_channel = RemoteChannel},
141
150
    {noreply, State1};
142
151
handle_info({ssh_cm, CM, {data, Channel, Type, Data}}, State) ->
143
 
    ssh_cm:adjust_window(CM, Channel, size(Data)),
 
152
    ssh_connection:adjust_window(CM, Channel, size(Data)),
144
153
    State1 = handle_data(Type, Data, State),
145
154
    {noreply, State1};
146
 
handle_info({ssh_cm, CM, {subsystem, _Channel, WantsReply, "sftp"}}, State) ->
147
 
    CM = (State#state.xf)#ssh_xfer.cm,          % hmmm going through xf...
148
 
    CM ! {same_user, self()},
149
 
    case WantsReply of
150
 
        true -> CM ! {ssh_cm, self(), {success, State#state.remote_channel}}
151
 
    end,
 
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),
152
159
    {noreply, State};
153
160
 
154
161
%% The client has terminated the session
157
164
            State = #state{xf = #ssh_xfer{channel = Channel}}) ->
158
165
    {stop, normal, State};
159
166
 
 
167
handle_info({ssh_cm, _CM, {closed, _Channel}}, State) ->
 
168
    %% ignore -- we'll get an {eof, Channel} soon??
 
169
    {noreply, State};
 
170
 
160
171
handle_info(_Info, State) ->
161
 
    io:format("handle_info ~p\n", [_Info]),
162
172
    ?dbg(true, "handle_info: Info=~p State=~p\n", [_Info, State]),
163
173
    {noreply, State}.
164
174
 
607
617
        File ->
608
618
            File;
609
619
        Root ->
610
 
            NewFile = relate(string:strip(File, left, $/), Root),
 
620
            NewFile = relate(make_relative_filename(File), Root),
611
621
            within_root(Root, NewFile)
612
622
    end.
613
623
 
619
629
            Root
620
630
    end.
621
631
 
 
632
%% Remove leading slash (/), if any, in order to make the filename
 
633
%% relative (to the root)
 
634
make_relative_filename("/")       -> "./"; % Make it relative and preserve /
 
635
make_relative_filename("/"++File) -> File;
 
636
make_relative_filename(File)      -> File.
 
637
 
622
638
relate(File0, Path) ->
623
639
    File1 = filename:absname(File0, Path),
624
640
    Parts = fix_file_name(filename:split(File1), []),
625
 
    filename:join(Parts).
 
641
    File2 = filename:join(Parts),
 
642
    ensure_trailing_slash_is_preserved(File0, File2).
 
643
 
 
644
%% It seems as if the openssh client (observed with the
 
645
%% openssh-4.2p1-18.30 package on SLED 10), and possibly other clients
 
646
%% as well (Maverick?), rely on the fact that a trailing slash (/) is
 
647
%% preserved.  If trailing slashes aren't preserved, symlinks which
 
648
%% point at directories won't be properly identified as directories.
 
649
%%
 
650
%% A failing example: 
 
651
%%
 
652
%%    1) assume the following directory structure:
 
653
%%       $ mkdir /tmp/symlink-target
 
654
%%       $ touch /tmp/symlink-target/foo
 
655
%%       $ ln -s /tmp/symlink-target /tmp/symlink
 
656
%%
 
657
%%    2) login using the sftp client in openssh
 
658
%%       sftp> cd /tmp/
 
659
%%       sftp> ls symlink-target
 
660
%%       symlink-target/foo   
 
661
%%       sftp> ls symlink
 
662
%%       symlink/                 <===== foo should have been visible here
 
663
%%       sftp> cd symlink-target
 
664
%%       sftp> ls
 
665
%%       foo  
 
666
%%       sftp> cd ..
 
667
%%       sftp> cd symlink
 
668
%%       sftp> ls
 
669
%%                                <===== foo should have been visible here
 
670
%%
 
671
%% The symlinks are resolved by file:read_link_info/1 only if the path
 
672
%% has a trailing slash, which seems to something that some of the
 
673
%% sftp clients utilize:
 
674
%%
 
675
%%    1> file:read_link_info(".../symlink").
 
676
%%    {ok,{file_info,4,symlink,read_write,
 
677
%%                   {{2008,10,20},{10,25,26}},
 
678
%%                   {{2008,10,17},{16,22,33}},
 
679
%%                   {{2008,10,17},{16,22,33}},
 
680
%%                   41471,1,2053,0,570447,20996,9935}}
 
681
%%    
 
682
%%    2> file:read_link_info(".../symlink/").
 
683
%%    {ok,{file_info,8192,directory,read_write,
 
684
%%                   {{2008,10,20},{10,36,2}},
 
685
%%                   {{2008,10,20},{10,44,35}},
 
686
%%                   {{2008,10,20},{10,44,35}},
 
687
%%                   17407,29,2053,0,521224,0,0}}
 
688
ensure_trailing_slash_is_preserved(File0, File1) ->
 
689
    case {lists:suffix("/", File0), lists:suffix("/", File1)} of
 
690
        {true, false} -> File1 ++ "/";
 
691
        _Other        -> File1
 
692
    end.
 
693
            
 
694
    
626
695
 
627
696
%%% fix file just a little: a/b/.. -> a and a/. -> a
628
697
fix_file_name([".." | Rest], ["/"] = Acc) ->