03a1981
From: Sergei Golovan <sgolovan@gmail.com>
03a1981
Date: Sun, 9 Feb 2014 23:06:25 +0400
03a1981
Subject: [PATCH] lib/inets/src/ftp/ftp.erl: Check the filenames, usernames,
03a1981
 passwords etc.     for <CR> and <LF> in them and return error if these
03a1981
 offending chars     are found. See
03a1981
 http://erlang.org/pipermail/erlang-bugs/2014-January/003998.html     for
03a1981
 details. lib/inets/test/ftp_suite_lib.erl: Added checks for <CR><LF> in file
03a1981
 and directory     names.
03a1981
03a1981
03a1981
diff --git a/lib/inets/src/ftp/ftp.erl b/lib/inets/src/ftp/ftp.erl
03a1981
index 520db1b..5674599 100644
03a1981
--- a/lib/inets/src/ftp/ftp.erl
03a1981
+++ b/lib/inets/src/ftp/ftp.erl
03a1981
@@ -192,7 +192,12 @@ do_open(Pid, OpenOptions, TLSOpts) ->
03a1981
     'ok' | {'error', Reason :: 'euser' | common_reason()}.
03a1981
 
03a1981
 user(Pid, User, Pass) ->
03a1981
-    call(Pid, {user, User, Pass}, atom).
03a1981
+    case {is_name_sane(User), is_name_sane(Pass)} of
03a1981
+	{true, true} ->
03a1981
+	    call(Pid, {user, User, Pass}, atom);
03a1981
+	_ ->
03a1981
+	    {error, euser}
03a1981
+    end.
03a1981
 
03a1981
 -spec user(Pid  :: pid(), 
03a1981
 	   User :: string(), 
03a1981
@@ -201,7 +206,12 @@ user(Pid, User, Pass) ->
03a1981
     'ok' | {'error', Reason :: 'euser' | common_reason()}.
03a1981
 
03a1981
 user(Pid, User, Pass, Acc) ->
03a1981
-    call(Pid, {user, User, Pass, Acc}, atom).
03a1981
+    case {is_name_sane(User), is_name_sane(Pass), is_name_sane(Acc)} of
03a1981
+	{true, true, true} ->
03a1981
+	    call(Pid, {user, User, Pass, Acc}, atom);
03a1981
+	_ ->
03a1981
+	    {error, euser}
03a1981
+    end.
03a1981
 
03a1981
 
03a1981
 %%--------------------------------------------------------------------------
03a1981
@@ -216,7 +226,12 @@ user(Pid, User, Pass, Acc) ->
03a1981
     'ok' | {'error', Reason :: 'eacct' | common_reason()}.
03a1981
 
03a1981
 account(Pid, Acc) ->
03a1981
-    call(Pid, {account, Acc}, atom).
03a1981
+    case is_name_sane(Acc) of
03a1981
+	true ->
03a1981
+	    call(Pid, {account, Acc}, atom);
03a1981
+	_ ->
03a1981
+	    {error, eacct}
03a1981
+    end.
03a1981
 
03a1981
 
03a1981
 %%--------------------------------------------------------------------------
03a1981
@@ -262,7 +277,12 @@ lpwd(Pid) ->
03a1981
     'ok' | {'error', Reason :: restriction_reason() | common_reason()}.
03a1981
 
03a1981
 cd(Pid, Dir) ->
03a1981
-    call(Pid, {cd, Dir}, atom).
03a1981
+    case is_name_sane(Dir) of
03a1981
+	true ->
03a1981
+	    call(Pid, {cd, Dir}, atom);
03a1981
+	_ ->
03a1981
+	    {error, efnamena}
03a1981
+    end.
03a1981
 
03a1981
 
03a1981
 %%--------------------------------------------------------------------------
03a1981
@@ -305,7 +325,12 @@ ls(Pid) ->
03a1981
 	{'error', Reason ::  restriction_reason() | common_reason()}.
03a1981
 
03a1981
 ls(Pid, Dir) ->
03a1981
-    call(Pid, {dir, long, Dir}, string).
03a1981
+    case is_name_sane(Dir) of
03a1981
+	true ->
03a1981
+	    call(Pid, {dir, long, Dir}, string);
03a1981
+	_ ->
03a1981
+	    {error, efnamena}
03a1981
+    end.
03a1981
 
03a1981
 
03a1981
 %%--------------------------------------------------------------------------
03a1981
@@ -333,7 +358,12 @@ nlist(Pid) ->
03a1981
 	{'error', Reason :: restriction_reason() | common_reason()}.
03a1981
 
03a1981
 nlist(Pid, Dir) ->
03a1981
-    call(Pid, {dir, short, Dir}, string).
03a1981
+    case is_name_sane(Dir) of
03a1981
+	true ->
03a1981
+	    call(Pid, {dir, short, Dir}, string);
03a1981
+	_ ->
03a1981
+	    {error, efnamena}
03a1981
+    end.
03a1981
 
03a1981
 
03a1981
 %%--------------------------------------------------------------------------
03a1981
@@ -349,7 +379,12 @@ nlist(Pid, Dir) ->
03a1981
     'ok' | {'error', Reason :: restriction_reason() | common_reason()}.
03a1981
 
03a1981
 rename(Pid, Old, New) ->
03a1981
-    call(Pid, {rename, Old, New}, string).
03a1981
+    case {is_name_sane(Old), is_name_sane(New)} of
03a1981
+	{true, true} ->
03a1981
+	    call(Pid, {rename, Old, New}, string);
03a1981
+	_ ->
03a1981
+	    {error, efnamena}
03a1981
+    end.
03a1981
 
03a1981
 
03a1981
 %%--------------------------------------------------------------------------
03a1981
@@ -365,7 +400,12 @@ rename(Pid, Old, New) ->
03a1981
     'ok' | {'error', Reason :: restriction_reason() | common_reason()}.
03a1981
 
03a1981
 delete(Pid, File) ->
03a1981
-    call(Pid, {delete, File}, string).
03a1981
+    case is_name_sane(File) of
03a1981
+	true ->
03a1981
+	    call(Pid, {delete, File}, string);
03a1981
+	_ ->
03a1981
+	    {error, efnamena}
03a1981
+    end.
03a1981
 
03a1981
 
03a1981
 %%--------------------------------------------------------------------------
03a1981
@@ -380,7 +420,12 @@ delete(Pid, File) ->
03a1981
     'ok' | {'error', Reason :: restriction_reason() | common_reason()}.
03a1981
 
03a1981
 mkdir(Pid, Dir) ->
03a1981
-    call(Pid, {mkdir, Dir}, atom).
03a1981
+    case is_name_sane(Dir) of
03a1981
+	true ->
03a1981
+	    call(Pid, {mkdir, Dir}, atom);
03a1981
+	_ ->
03a1981
+	    {error, efnamena}
03a1981
+    end.
03a1981
 
03a1981
 
03a1981
 %%--------------------------------------------------------------------------
03a1981
@@ -395,7 +440,12 @@ mkdir(Pid, Dir) ->
03a1981
     'ok' | {'error', Reason :: restriction_reason() | common_reason()}.
03a1981
 
03a1981
 rmdir(Pid, Dir) ->
03a1981
-    call(Pid, {rmdir, Dir}, atom).
03a1981
+    case is_name_sane(Dir) of
03a1981
+	true ->
03a1981
+	    call(Pid, {rmdir, Dir}, atom);
03a1981
+	_ ->
03a1981
+	    {error, efnamena}
03a1981
+    end.
03a1981
 
03a1981
 
03a1981
 %%--------------------------------------------------------------------------
03a1981
@@ -437,7 +487,12 @@ recv(Pid, RemotFileName) ->
03a1981
     'ok' | {'error', Reason :: term()}.
03a1981
 
03a1981
 recv(Pid, RemotFileName, LocalFileName) ->
03a1981
-    call(Pid, {recv, RemotFileName, LocalFileName}, atom).
03a1981
+    case is_name_sane(RemotFileName) of
03a1981
+	true ->
03a1981
+	    call(Pid, {recv, RemotFileName, LocalFileName}, atom);
03a1981
+	_ ->
03a1981
+	    {error, efnamena}
03a1981
+    end.
03a1981
 
03a1981
 
03a1981
 %%--------------------------------------------------------------------------
03a1981
@@ -456,7 +511,12 @@ recv(Pid, RemotFileName, LocalFileName) ->
03a1981
 	{'error', Reason :: restriction_reason() | common_reason()}.
03a1981
 
03a1981
 recv_bin(Pid, RemoteFile) ->
03a1981
-    call(Pid, {recv_bin, RemoteFile}, bin).
03a1981
+    case is_name_sane(RemoteFile) of
03a1981
+	true ->
03a1981
+	    call(Pid, {recv_bin, RemoteFile}, bin);
03a1981
+	_ ->
03a1981
+	    {error, efnamena}
03a1981
+    end.
03a1981
 
03a1981
 
03a1981
 %%--------------------------------------------------------------------------
03a1981
@@ -473,7 +533,12 @@ recv_bin(Pid, RemoteFile) ->
03a1981
     'ok' | {'error', Reason :: restriction_reason() | common_reason()}.
03a1981
 
03a1981
 recv_chunk_start(Pid, RemoteFile) ->
03a1981
-    call(Pid, {recv_chunk_start, RemoteFile}, atom).
03a1981
+    case is_name_sane(RemoteFile) of
03a1981
+	true ->
03a1981
+	    call(Pid, {recv_chunk_start, RemoteFile}, atom);
03a1981
+	_ ->
03a1981
+	    {error, efnamena}
03a1981
+    end.
03a1981
 
03a1981
 
03a1981
 %%--------------------------------------------------------------------------
03a1981
@@ -521,7 +586,12 @@ send(Pid, LocalFileName) ->
03a1981
                             shortage_reason()}.
03a1981
 
03a1981
 send(Pid, LocalFileName, RemotFileName) ->
03a1981
-    call(Pid, {send, LocalFileName, RemotFileName}, atom).
03a1981
+    case is_name_sane(RemotFileName) of
03a1981
+	true ->
03a1981
+	    call(Pid, {send, LocalFileName, RemotFileName}, atom);
03a1981
+	_ ->
03a1981
+	    {error, efnamena}
03a1981
+    end.
03a1981
 
03a1981
 
03a1981
 %%--------------------------------------------------------------------------
03a1981
@@ -541,7 +611,12 @@ send(Pid, LocalFileName, RemotFileName) ->
03a1981
                             shortage_reason()}.
03a1981
 
03a1981
 send_bin(Pid, Bin, RemoteFile) when is_binary(Bin) ->
03a1981
-    call(Pid, {send_bin, Bin, RemoteFile}, atom);
03a1981
+    case is_name_sane(RemoteFile) of
03a1981
+	true ->
03a1981
+	    call(Pid, {send_bin, Bin, RemoteFile}, atom);
03a1981
+	_ ->
03a1981
+	    {error, efnamena}
03a1981
+    end;
03a1981
 send_bin(_Pid, _Bin, _RemoteFile) ->
03a1981
   {error, enotbinary}.
03a1981
 
03a1981
@@ -559,7 +634,12 @@ send_bin(_Pid, _Bin, _RemoteFile) ->
03a1981
     'ok' | {'error', Reason :: restriction_reason() | common_reason()}.
03a1981
 
03a1981
 send_chunk_start(Pid, RemoteFile) ->
03a1981
-    call(Pid, {send_chunk_start, RemoteFile}, atom).
03a1981
+    case is_name_sane(RemoteFile) of
03a1981
+	true ->
03a1981
+	    call(Pid, {send_chunk_start, RemoteFile}, atom);
03a1981
+	_ ->
03a1981
+	    {error, efnamena}
03a1981
+    end.
03a1981
 
03a1981
 
03a1981
 %%--------------------------------------------------------------------------
03a1981
@@ -575,7 +655,12 @@ send_chunk_start(Pid, RemoteFile) ->
03a1981
     'ok' | {'error', Reason :: term()}.
03a1981
 
03a1981
 append_chunk_start(Pid, RemoteFile) ->
03a1981
-    call(Pid, {append_chunk_start, RemoteFile}, atom).
03a1981
+    case is_name_sane(RemoteFile) of
03a1981
+	true ->
03a1981
+	    call(Pid, {append_chunk_start, RemoteFile}, atom);
03a1981
+	_ ->
03a1981
+	    {error, efnamena}
03a1981
+    end.
03a1981
 
03a1981
 
03a1981
 %%--------------------------------------------------------------------------
03a1981
@@ -683,7 +768,12 @@ append(Pid, LocalFileName) ->
03a1981
     'ok' | {'error', Reason :: term()}.
03a1981
 
03a1981
 append(Pid, LocalFileName, RemotFileName) ->
03a1981
-    call(Pid, {append, LocalFileName, RemotFileName}, atom).
03a1981
+    case is_name_sane(RemotFileName) of
03a1981
+	true ->
03a1981
+	    call(Pid, {append, LocalFileName, RemotFileName}, atom);
03a1981
+	_ ->
03a1981
+	    {error, efnamena}
03a1981
+    end.
03a1981
 
03a1981
 
03a1981
 %%--------------------------------------------------------------------------
03a1981
@@ -705,7 +795,12 @@ append(Pid, LocalFileName, RemotFileName) ->
03a1981
                             shortage_reason()}.
03a1981
 
03a1981
 append_bin(Pid, Bin, RemoteFile) when is_binary(Bin) ->
03a1981
-    call(Pid, {append_bin, Bin, RemoteFile}, atom);
03a1981
+    case is_name_sane(RemoteFile) of
03a1981
+	true ->
03a1981
+	    call(Pid, {append_bin, Bin, RemoteFile}, atom);
03a1981
+	_ ->
03a1981
+	    {error, efnamena}
03a1981
+    end;
03a1981
 append_bin(_Pid, _Bin, _RemoteFile) ->
03a1981
     {error, enotbinary}.
03a1981
 
03a1981
@@ -2302,6 +2397,15 @@ send_bin(State, Bin) ->
03a1981
 mk_cmd(Fmt, Args) ->
03a1981
     [io_lib:format(Fmt, Args)| [?CR, ?LF]].		% Deep list ok.
03a1981
 
03a1981
+is_name_sane([]) ->
03a1981
+    true;
03a1981
+is_name_sane([?CR| _]) ->
03a1981
+    false;
03a1981
+is_name_sane([?LF| _]) ->
03a1981
+    false;
03a1981
+is_name_sane([_| Rest]) ->
03a1981
+    is_name_sane(Rest).
03a1981
+
03a1981
 pwd_result(Lines) ->
03a1981
     {_, [?DOUBLE_QUOTE | Rest]} = 
03a1981
 	lists:splitwith(fun(?DOUBLE_QUOTE) -> false; (_) -> true end, Lines),
03a1981
diff --git a/lib/inets/test/ftp_suite_lib.erl b/lib/inets/test/ftp_suite_lib.erl
03a1981
index 35f21cc..daee1bd 100644
03a1981
--- a/lib/inets/test/ftp_suite_lib.erl
03a1981
+++ b/lib/inets/test/ftp_suite_lib.erl
03a1981
@@ -1266,6 +1266,8 @@ read_log_6035([]) ->
03a1981
 %%--------------------------------------------------------------------
03a1981
 do_user(Pid) ->
03a1981
     {error, euser} = ftp:user(Pid, ?BAD_USER, ?FTP_PASS),
03a1981
+    {error, euser} = ftp:user(Pid, ?FTP_USER++"\r\nPASS "++?FTP_PASS, ?FTP_PASS),
03a1981
+    {error, euser} = ftp:user(Pid, ?FTP_USER, ?FTP_PASS++"\r\nCWD ."),
03a1981
     ok = ftp:user(Pid, ?FTP_USER, ?FTP_PASS),
03a1981
     ok.
03a1981
 
03a1981
@@ -1278,6 +1280,7 @@ do_pwd(Pid) ->
03a1981
 do_cd(Pid) ->
03a1981
     ok = ftp:cd(Pid, "/pub"),
03a1981
     {error, epath} = ftp:cd(Pid, ?BAD_DIR),
03a1981
+    {error, efnamena} = ftp:cd(Pid, "/pub\r\nCWD ."),
03a1981
     ok.
03a1981
 
03a1981
 do_lcd(Pid, Dir) ->
03a1981
@@ -1294,11 +1297,14 @@ do_ls(Pid) ->
03a1981
     %% directory, but can also be a filename or a group 
03a1981
     %% of files (including wildcards).
03a1981
     {ok, _} = ftp:ls(Pid, "incom*"),
03a1981
+    %% but \r\n can't be in the wildcard
03a1981
+    {error, efnamena} = ftp:ls(Pid, "incoming\r\nCWD ."),
03a1981
     ok.
03a1981
 
03a1981
 do_nlist(Pid, WildcardSupport) ->
03a1981
     {ok, _} = ftp:nlist(Pid),
03a1981
     {ok, _} = ftp:nlist(Pid, "incoming"),
03a1981
+    {error, efnamena} = ftp:ls(Pid, "incoming\r\nCWD ."),
03a1981
     %% neither nlist nor ls operates on a directory
03a1981
     %% they operate on a pathname, which *can* be a 
03a1981
     %% directory, but can also be a filename or a group 
03a1981
@@ -1324,6 +1330,8 @@ do_rename(Pid, Config) ->
03a1981
     ftp:delete(Pid, NewLFile),		% reset
03a1981
     ok = ftp:send(Pid, LFile), 
03a1981
     {error, epath} = ftp:rename(Pid, NewLFile, LFile),
03a1981
+    {error, efnamena} = ftp:rename(Pid, NewLFile++"\r\nRNTO "++LFile++"\r\nRNFR "++NewLFile, LFile),
03a1981
+    {error, efnamena} = ftp:rename(Pid, NewLFile, LFile++"\r\nCWD ."),
03a1981
     ok = ftp:rename(Pid, LFile, NewLFile),
03a1981
     ftp:delete(Pid, LFile),		% cleanup
03a1981
     ftp:delete(Pid, NewLFile),		% cleanup
03a1981
@@ -1338,6 +1346,7 @@ do_delete(Pid, Config) ->
03a1981
     ok = ftp:cd(Pid, "incoming"),
03a1981
     ok = ftp:lcd(Pid, PrivDir),
03a1981
     ftp:delete(Pid,LFile),		% reset
03a1981
+    {error, efnamena} = ftp:delete(Pid,LFile++"\r\nCWD ."),
03a1981
     ok = ftp:send(Pid, LFile),
03a1981
     ok = ftp:delete(Pid,LFile),
03a1981
     ok.
03a1981
@@ -1348,6 +1357,8 @@ do_mkdir(Pid) ->
03a1981
 	integer_to_list(B) ++ "_" ++ integer_to_list(C),
03a1981
     ok = ftp:cd(Pid, "incoming"),
03a1981
     {ok, CurrDir} = ftp:pwd(Pid),
03a1981
+    {error, efnamena} = ftp:mkdir(Pid, NewDir++"\r\nCWD ."),
03a1981
+    {error, efnamena} = ftp:rmdir(Pid, NewDir++"\r\nCWD ."),
03a1981
     ok = ftp:mkdir(Pid, NewDir),
03a1981
     ok = ftp:cd(Pid, NewDir),
03a1981
     ok = ftp:cd(Pid, CurrDir),
03a1981
@@ -1363,6 +1374,7 @@ do_send(Pid, Config) ->
03a1981
     ok = file:write_file(AbsLFile, list_to_binary(Contents)),
03a1981
     ok = ftp:cd(Pid, "incoming"),
03a1981
     ok = ftp:lcd(Pid, PrivDir),
03a1981
+    {error, efnamena} = ftp:send(Pid, LFile, RFile++"1\r\nCWD ."),
03a1981
     ok = ftp:send(Pid, LFile, RFile),
03a1981
     {ok, RFilesString} = ftp:nlist(Pid),
03a1981
     RFiles = split(RFilesString),
03a1981
@@ -1392,6 +1404,7 @@ do_append(Pid, Config) ->
03a1981
     ftp:delete(Pid, RFile),
03a1981
     ftp:delete(Pid, LFile),
03a1981
 
03a1981
+    {error, efnamena} = ftp:append(Pid, LFile, RFile++"1\r\nCWD ."),
03a1981
     ok = ftp:append(Pid, LFile, RFile),
03a1981
     ok = ftp:append(Pid, LFile, RFile),
03a1981
     ok = ftp:append(Pid, LFile),
03a1981
@@ -1413,6 +1426,7 @@ do_send_bin(Pid, Config) ->
03a1981
     Bin = list_to_binary(Contents),
03a1981
     ok = ftp:cd(Pid, "incoming"),
03a1981
     {error, enotbinary} = ftp:send_bin(Pid, Contents, File),
03a1981
+    {error, efnamena} = ftp:send_bin(Pid, Bin, File++"1\r\nCWD ."),
03a1981
     ok = ftp:send_bin(Pid, Bin, File),
03a1981
     {ok, RFilesString} = ftp:nlist(Pid),
03a1981
     RFiles = split(RFilesString),
03a1981
@@ -1426,6 +1440,7 @@ do_append_bin(Pid, Config) ->
03a1981
     Bin = list_to_binary(Contents),
03a1981
     ok = ftp:cd(Pid, "incoming"),
03a1981
     {error, enotbinary} = ftp:append_bin(Pid, Contents, File),
03a1981
+    {error, efnamena} = ftp:append_bin(Pid, Bin, File++"1\r\nCWD ."),
03a1981
     ok = ftp:append_bin(Pid, Bin, File),
03a1981
     ok = ftp:append_bin(Pid, Bin, File),
03a1981
     %% Control the contents of the file
03a1981
@@ -1438,6 +1453,7 @@ do_send_chunk(Pid, Config) ->
03a1981
     Contents = "ftp_SUITE test ...",
03a1981
     Bin = list_to_binary(Contents),
03a1981
     ok = ftp:cd(Pid, "incoming"),
03a1981
+    {error, efnamena} = ftp:send_chunk_start(Pid, File++"1\r\nCWD ."),
03a1981
     ok = ftp:send_chunk_start(Pid, File),
03a1981
     {error, echunk} = ftp:cd(Pid, "incoming"),
03a1981
     {error, enotbinary} = ftp:send_chunk(Pid, Contents),
03a1981
@@ -1454,6 +1470,7 @@ do_append_chunk(Pid, Config) ->
03a1981
     File = ?config(file, Config),
03a1981
     Contents = ["ER","LE","RL"],
03a1981
     ok = ftp:cd(Pid, "incoming"),
03a1981
+    {error, efnamena} = ftp:append_chunk_start(Pid, File++"1\r\nCWD ."),
03a1981
     ok = ftp:append_chunk_start(Pid, File),
03a1981
     {error, enotbinary} = ftp:append_chunk(Pid, lists:nth(1,Contents)),
03a1981
     ok = ftp:append_chunk(Pid,list_to_binary(lists:nth(1,Contents))),
03a1981
@@ -1480,6 +1497,7 @@ do_recv(Pid, Config) ->
03a1981
     ok = file:delete(AbsFile),		% cleanup
03a1981
     test_server:sleep(100),
03a1981
     ok = ftp:lcd(Pid, PrivDir),
03a1981
+    {error, efnamena} = ftp:recv(Pid, File++"\r\nCWD ."),
03a1981
     ok = ftp:recv(Pid, File),
03a1981
     {ok, Files} = file:list_dir(PrivDir),
03a1981
     true = lists:member(File, Files),
03a1981
@@ -1495,6 +1513,7 @@ do_recv_bin(Pid, Config) ->
03a1981
     ok = ftp:cd(Pid, "incoming"),
03a1981
     ok = ftp:send_bin(Pid, Bin1, File),
03a1981
     test_server:sleep(100),
03a1981
+    {error, efnamena} = ftp:recv_bin(Pid, File++"\r\nCWD ."),
03a1981
     {ok, Bin2}  = ftp:recv_bin(Pid, File),
03a1981
     ok = ftp:delete(Pid, File),		% cleanup
03a1981
     Contents2 = binary_to_list(Bin2),
03a1981
@@ -1520,6 +1539,7 @@ do_recv_chunk(Pid, Config) ->
03a1981
     ok = ftp:send_bin(Pid, Bin1, File),
03a1981
     test_server:sleep(100),
03a1981
     {error, "ftp:recv_chunk_start/2 not called"} = recv_chunk(Pid, <<>>),
03a1981
+    {error, efnamena} = ftp:recv_chunk_start(Pid, File++"\r\nCWD ."),
03a1981
     ok = ftp:recv_chunk_start(Pid, File),
03a1981
     {ok, Contents2} = recv_chunk(Pid, <<>>),
03a1981
     ok = ftp:delete(Pid, File),		% cleanup