File 1392-inets-fix-mod_esi-atom-leak.patch of Package erlang

From 5bc3105b94340705d991378d9f8f7ea109accaa4 Mon Sep 17 00:00:00 2001
From: Jakub Witczak <kuba@erlang.org>
Date: Tue, 15 Jun 2021 12:34:17 +0200
Subject: [PATCH] inets: fix mod_esi atom leak

- improve the way mod_esi handles input from client
- remove not needed load function
---
 .../src/http_server/httpd_script_env.erl      |  25 ++--
 lib/inets/src/http_server/mod_cgi.erl         |  44 +------
 lib/inets/src/http_server/mod_disk_log.erl    | 108 +-----------------
 lib/inets/src/http_server/mod_esi.erl         |  32 ++++--
 lib/inets/src/http_server/mod_security.erl    |  55 +--------
 lib/inets/test/httpd_SUITE.erl                |  33 +++++-
 6 files changed, 77 insertions(+), 220 deletions(-)

diff --git a/lib/inets/src/http_server/httpd_script_env.erl b/lib/inets/src/http_server/httpd_script_env.erl
index 055edca211..aa50538ec2 100644
--- a/lib/inets/src/http_server/httpd_script_env.erl
+++ b/lib/inets/src/http_server/httpd_script_env.erl
@@ -119,19 +119,30 @@ create_http_header_elements(ScriptType, [{Name, [Value | _] = Values } |
 					 Headers], Acc) 
   when is_list(Value) ->
     NewName = lists:map(fun(X) -> if X == $- -> $_; true -> X end end, Name),
-    Element = http_env_element(ScriptType, NewName, multi_value(Values)),
-    create_http_header_elements(ScriptType, Headers, [Element | Acc]);
-
+    try http_env_element(ScriptType, NewName, multi_value(Values)) of
+        Element ->
+            create_http_header_elements(ScriptType, Headers, [Element | Acc])
+    catch
+        _:_ ->
+            create_http_header_elements(ScriptType, Headers, Acc)
+    end;
 create_http_header_elements(ScriptType, [{Name, Value} | Headers], Acc) 
   when is_list(Value) ->
     NewName = re:replace(Name,"-","_", [{return,list}, global]),
-    Element = http_env_element(ScriptType, NewName, Value),
-    create_http_header_elements(ScriptType, Headers, [Element | Acc]).
+    try http_env_element(ScriptType, NewName, Value) of
+        Element ->
+            create_http_header_elements(ScriptType, Headers, [Element | Acc])
+    catch
+        _:_ ->
+            create_http_header_elements(ScriptType, Headers, Acc)
+    end.
 
 http_env_element(cgi, VarName, Value)  ->
     {"HTTP_"++ http_util:to_upper(VarName), Value};
 http_env_element(esi, VarName, Value)  ->
-    {list_to_atom("http_"++ http_util:to_lower(VarName)), Value}.
+    HeaderName = http_util:to_lower(VarName),
+    list_to_existing_atom(HeaderName),
+    {list_to_atom("http_"++ HeaderName), Value}.
 
 multi_value([]) ->
   [];
diff --git a/lib/inets/src/http_server/mod_cgi.erl b/lib/inets/src/http_server/mod_cgi.erl
index 1454332895..d961ac655f 100644
--- a/lib/inets/src/http_server/mod_cgi.erl
+++ b/lib/inets/src/http_server/mod_cgi.erl
@@ -1,7 +1,7 @@
 %%
 %% %CopyrightBegin%
 %%
-%% Copyright Ericsson AB 1997-2016. All Rights Reserved.
+%% Copyright Ericsson AB 1997-2021. All Rights Reserved.
 %%
 %% Licensed under the Apache License, Version 2.0 (the "License");
 %% you may not use this file except in compliance with the License.
@@ -25,7 +25,7 @@
 -export([env/3]).
 
 %%% Callback API
--export([do/1, load/2, store/2]).
+-export([do/1, store/2]).
 
 -include("http_internal.hrl").
 -include("httpd_internal.hrl").
@@ -77,46 +77,6 @@ do(ModData) ->
 	    end
     end.
 
-%%--------------------------------------------------------------------------
-%% load(Line, Context) ->  eof | ok | {ok, NewContext} | 
-%%                     {ok, NewContext, Directive} | 
-%%                     {ok, NewContext, DirectiveList} | {error, Reason}
-%% Line = string()
-%% Context = NewContext = DirectiveList = [Directive]
-%% Directive = {DirectiveKey , DirectiveValue}
-%% DirectiveKey = DirectiveValue = term()
-%% Reason = term() 
-%%
-%% Description: See httpd(3) ESWAPI CALLBACK FUNCTIONS
-%%-------------------------------------------------------------------------
-
-%% ScriptNoCache true|false, defines whether the server shall add     
-%%                           header fields to stop proxies and          
-%%                           clients from saving the page in history  
-%%                           or cache                                 
-%%                                                                             
-load("ScriptNoCache " ++ CacheArg, [])->
-    case catch list_to_atom(string:strip(CacheArg)) of
-        true ->
-	    {ok, [], {script_nocache, true}};
-	false ->
-	   {ok, [], {script_nocache, false}};
-	_ ->
-	   {error, ?NICE(string:strip(CacheArg)++
-			 " is an invalid ScriptNoCache directive")}
-    end;
-%% ScriptTimeout Seconds, The number of seconds that the server       
-%%                        maximum will wait for the script to         
-%%                        generate a part of the document   
-load("ScriptTimeout " ++ Timeout, [])->
-    case catch list_to_integer(string:strip(Timeout)) of
-	TimeoutSec when is_integer(TimeoutSec)  ->
-	   {ok, [], {script_timeout,TimeoutSec*1000}};
-	_ ->
-	   {error, ?NICE(string:strip(Timeout)++
-			 " is an invalid ScriptTimeout")}
-    end.
-
 %%--------------------------------------------------------------------------
 %% store(Directive, DirectiveList) -> {ok, NewDirective} | 
 %%                                    {ok, [NewDirective]} |
diff --git a/lib/inets/src/http_server/mod_disk_log.erl b/lib/inets/src/http_server/mod_disk_log.erl
index 190cf91416..812b2e7ee2 100644
--- a/lib/inets/src/http_server/mod_disk_log.erl
+++ b/lib/inets/src/http_server/mod_disk_log.erl
@@ -24,7 +24,7 @@
 -export([error_log/2, report_error/2, security_log/2]).
 
 %% Callback API
--export([do/1, load/2, store/2, remove/1]).
+-export([do/1, store/2, remove/1]).
 
 -define(VMODULE,"DISK_LOG").
 
@@ -125,102 +125,6 @@ do(Info) ->
 	    end
     end.
 
-%%--------------------------------------------------------------------------
-%% load(Line, Context) ->  eof | ok | {ok, NewContext} | 
-%%                     {ok, NewContext, Directive} | 
-%%                     {ok, NewContext, DirectiveList} | {error, Reason}
-%% Line = string()
-%% Context = NewContext = DirectiveList = [Directive]
-%% Directive = {DirectiveKey , DirectiveValue}
-%% DirectiveKey = DirectiveValue = term()
-%% Reason = term() 
-%%
-%% Description: See httpd(3) ESWAPI CALLBACK FUNCTIONS
-%%-------------------------------------------------------------------------
-load("TransferDiskLogSize " ++ TransferDiskLogSize, []) ->
-    try re:split(TransferDiskLogSize, " ",  [{return, list}]) of
-	[MaxBytes, MaxFiles] ->
-	    case make_integer(MaxBytes) of
-		{ok,MaxBytesInteger} ->
-		    case make_integer(MaxFiles) of
-			{ok,MaxFilesInteger} ->
-			    {ok,[],{transfer_disk_log_size,
-				    {MaxBytesInteger,MaxFilesInteger}}};
-			{error,_} ->
-			    {error,
-			     ?NICE(string:strip(TransferDiskLogSize)++
-				   " is an invalid TransferDiskLogSize")}
-		    end;
-		_ ->
-		    {error,?NICE(string:strip(TransferDiskLogSize)++
-				     " is an invalid TransferDiskLogSize")}
-	    end
-    catch _:_ ->
-	    {error,?NICE(string:strip(TransferDiskLogSize) ++
-			     " is an invalid TransferDiskLogSize")}   
-    end;
-load("TransferDiskLog " ++ TransferDiskLog,[]) ->
-    {ok,[],{transfer_disk_log,string:strip(TransferDiskLog)}};
- 
-load("ErrorDiskLogSize " ++  ErrorDiskLogSize, []) ->
-    try re:split(ErrorDiskLogSize," ", [{return, list}]) of
-	[MaxBytes,MaxFiles] ->
-	    case make_integer(MaxBytes) of
-		{ok,MaxBytesInteger} ->
-		    case make_integer(MaxFiles) of
-			{ok,MaxFilesInteger} ->
-			    {ok,[],{error_disk_log_size,
-				    {MaxBytesInteger,MaxFilesInteger}}};
-			{error,_} ->
-			    {error,?NICE(string:strip(ErrorDiskLogSize)++
-					 " is an invalid ErrorDiskLogSize")}
-		    end;
-		{error,_} ->
-		    {error,?NICE(string:strip(ErrorDiskLogSize)++
-				 " is an invalid ErrorDiskLogSize")}
-	    end
-    catch _:_ ->
-	    {error,?NICE(string:strip(ErrorDiskLogSize) ++
-			     " is an invalid TransferDiskLogSize")}   
-    end;
-load("ErrorDiskLog " ++ ErrorDiskLog, []) ->
-    {ok, [], {error_disk_log, string:strip(ErrorDiskLog)}};
-
-load("SecurityDiskLogSize " ++ SecurityDiskLogSize, []) ->
-    try re:split(SecurityDiskLogSize, " ", [{return, list}]) of
-	[MaxBytes, MaxFiles] ->
-	    case make_integer(MaxBytes) of
-		{ok, MaxBytesInteger} ->
-		    case make_integer(MaxFiles) of
-			{ok, MaxFilesInteger} ->
-			    {ok, [], {security_disk_log_size,
-				      {MaxBytesInteger, MaxFilesInteger}}};
-			{error,_} ->
-			    {error, 
-			     ?NICE(string:strip(SecurityDiskLogSize) ++
-				   " is an invalid SecurityDiskLogSize")}
-		    end;
-		{error, _} ->
-		    {error, ?NICE(string:strip(SecurityDiskLogSize) ++
-				  " is an invalid SecurityDiskLogSize")}
-	    end
-    catch _:_ ->
-	    {error,?NICE(string:strip(SecurityDiskLogSize) ++
-			     " is an invalid SecurityDiskLogSize")}   	
-    end;
-load("SecurityDiskLog " ++ SecurityDiskLog, []) ->
-    {ok, [], {security_disk_log, string:strip(SecurityDiskLog)}};
-
-load("DiskLogFormat " ++ Format, []) ->
-    case string:strip(Format) of
-	"internal" ->
-	    {ok, [], {disk_log_format,internal}};
-	"external" ->
-	    {ok, [], {disk_log_format,external}};
-	_Default ->
-	    {ok, [], {disk_log_format,external}}
-    end.
-
 %%--------------------------------------------------------------------------
 %% store(Directive, DirectiveList) -> {ok, NewDirective} | 
 %%                                    {ok, [NewDirective]} |
@@ -432,11 +336,3 @@ log_internal_info(Info,Date,[{internal_info,Reason}|Rest]) ->
 log_internal_info(Info,Date,[_|Rest]) ->
     log_internal_info(Info,Date,Rest).
 
-make_integer(List) ->
-    try list_to_integer(List) of
-	N ->
-	    {ok, N}
-    catch 
-	_:_ ->
-	    {error, {badarg, list_to_integer, List}}
-    end.
diff --git a/lib/inets/src/http_server/mod_esi.erl b/lib/inets/src/http_server/mod_esi.erl
index 3da503a5f2..ba53a66f80 100644
--- a/lib/inets/src/http_server/mod_esi.erl
+++ b/lib/inets/src/http_server/mod_esi.erl
@@ -170,12 +170,12 @@ erl(#mod{method = Method} = ModData, ESIBody, Modules)
 	    case httpd_util:split(FuncAndInput,"[\?/]",2) of
 		{ok, [FunctionName, Input]} ->
 		    generate_webpage(ModData, ESIBody, Modules, 
-				     list_to_atom(ModuleName), 
-				     FunctionName, Input, 
+				     ModuleName,
+				     FunctionName, Input,
 				     script_elements(FuncAndInput, Input));
 		{ok, [FunctionName]} ->
 		    generate_webpage(ModData, ESIBody, Modules, 
-				     list_to_atom(ModuleName),
+				     ModuleName,
 				     FunctionName, "", 
 				     script_elements(FuncAndInput, ""));
 		{ok, BadRequest} ->
@@ -194,12 +194,12 @@ erl(#mod{method = Method, entity_body = Body} = ModData,
 	    case httpd_util:split(FuncAndInput,"[\?/]",2) of
 		{ok, [FunctionName, Input]} ->
 		    generate_webpage(ModData, ESIBody, Modules,
-				     list_to_atom(ModuleName),
+				     ModuleName,
 				     FunctionName, {Input,Body},
 				     script_elements(FuncAndInput, Input));
 		{ok, [FunctionName]} ->
 		    generate_webpage(ModData, ESIBody, Modules,
-				     list_to_atom(ModuleName),
+				     ModuleName,
 				     FunctionName, {undefined,Body},
 				     script_elements(FuncAndInput, ""));
 		{ok, BadRequest} ->
@@ -214,7 +214,7 @@ erl(#mod{method = "POST", entity_body = Body} = ModData, ESIBody, Modules) ->
     case httpd_util:split(ESIBody,":|%3A|/",2) of
 	{ok,[ModuleName, Function]} ->
 	    generate_webpage(ModData, ESIBody, Modules, 
-			     list_to_atom(ModuleName), 
+			     ModuleName,
 			     Function, Body, []);
 	{ok, BadRequest} ->
 	    {proceed,[{status, {400, none, BadRequest}} | ModData#mod.data]}
@@ -224,9 +224,8 @@ generate_webpage(ModData, ESIBody, [all], Module, FunctionName,
 		 Input, ScriptElements) ->
     generate_webpage(ModData, ESIBody, [Module], Module,
 		     FunctionName, Input, ScriptElements);
-generate_webpage(ModData, ESIBody, Modules, Module, FunctionName,
-		 Input, ScriptElements) ->
-    Function = list_to_atom(FunctionName),
+generate_webpage(ModData, ESIBody, Modules, Module, Function,
+		 Input, ScriptElements) when is_atom(Module), is_atom(Function) ->
     case lists:member(Module, Modules) of
 	true ->
 	    Env = httpd_script_env:create_env(esi, ModData, ScriptElements),
@@ -242,6 +241,19 @@ generate_webpage(ModData, ESIBody, Modules, Module, FunctionName,
 	    {proceed, [{status, {403, ModData#mod.request_uri,
 				 ?NICE("Client not authorized to evaluate: "
 				       ++  ESIBody)}} | ModData#mod.data]}
+    end;
+generate_webpage(ModData, ESIBody, Modules, ModuleName, FunctionName,
+		 Input, ScriptElements) ->
+    try
+        Module = list_to_existing_atom(ModuleName),
+        _ = code:ensure_loaded(Module),
+        Function = list_to_existing_atom(FunctionName),
+        generate_webpage(ModData, ESIBody, Modules, Module, Function,
+                         Input, ScriptElements)
+    catch
+        _:_ ->
+            {proceed, [{status, {404, ModData#mod.request_uri, "Not found"}}
+                      | ModData#mod.data]}
     end.
 
 %% Old API that waits for the dymnamic webpage to be totally generated
diff --git a/lib/inets/src/http_server/mod_security.erl b/lib/inets/src/http_server/mod_security.erl
index e7fc043217..7d9fd5fa2d 100644
--- a/lib/inets/src/http_server/mod_security.erl
+++ b/lib/inets/src/http_server/mod_security.erl
@@ -1,7 +1,7 @@
 %%
 %% %CopyrightBegin%
 %% 
-%% Copyright Ericsson AB 1998-2016. All Rights Reserved.
+%% Copyright Ericsson AB 1998-2021. All Rights Reserved.
 %% 
 %% Licensed under the Apache License, Version 2.0 (the "License");
 %% you may not use this file except in compliance with the License.
@@ -29,7 +29,7 @@
 	 list_auth_users/1, list_auth_users/2, list_auth_users/3]).
 
 %% module API exports
--export([do/1, load/2, store/2, remove/1]).
+-export([do/1, store/2, remove/1]).
 
 -include("httpd.hrl").
 -include("httpd_internal.hrl").
@@ -101,43 +101,6 @@ do(Info) ->
 	    end
     end.
 
-load("<Directory " ++ Directory, []) ->
-    Dir = string:strip(string:strip(Directory),right, $>),
-    {ok, [{security_directory, {Dir, [{path, Dir}]}}]};
-load(eof,[{security_directory, {Directory, _DirData}}|_]) ->
-    {error, ?NICE("Premature end-of-file in "++Directory)};
-load("SecurityDataFile " ++ FileName, 
-     [{security_directory, {Dir, DirData}}]) ->
-    File = string:strip(FileName),
-    {ok, [{security_directory, {Dir, [{data_file, File}|DirData]}}]};
-load("SecurityCallbackModule " ++ ModuleName,
-     [{security_directory, {Dir, DirData}}]) ->
-    Mod = list_to_atom(string:strip(ModuleName)),
-    {ok, [{security_directory, {Dir, [{callback_module, Mod}|DirData]}}]};
-load("SecurityMaxRetries " ++ Retries,
-     [{security_directory, {Dir, DirData}}]) ->
-    load_return_int_tag("SecurityMaxRetries", max_retries, 
-			string:strip(Retries), Dir, DirData);
-load("SecurityBlockTime " ++ Time,
-      [{security_directory, {Dir, DirData}}]) ->
-    load_return_int_tag("SecurityBlockTime", block_time,
-			string:strip(Time), Dir, DirData);
-load("SecurityFailExpireTime " ++ Time,
-     [{security_directory, {Dir, DirData}}]) ->
-    load_return_int_tag("SecurityFailExpireTime", fail_expire_time,
-			string:strip(Time), Dir, DirData);
-load("SecurityAuthTimeout " ++ Time0,
-     [{security_directory, {Dir, DirData}}]) ->
-    Time = string:strip(Time0),
-    load_return_int_tag("SecurityAuthTimeout", auth_timeout,
-			string:strip(Time), Dir, DirData);
-load("AuthName " ++ Name0,
-     [{security_directory, {Dir, DirData}}]) ->
-    Name = string:strip(Name0),
-    {ok, [{security_directory, {Dir, [{auth_name, Name}|DirData]}}]};
-load("</Directory>",[{security_directory, {Dir, DirData}}]) ->
-    {ok, [], {security_directory, {Dir, DirData}}}.
-
 store({security_directory, {Dir, DirData}}, ConfigList) 
   when is_list(Dir) andalso is_list(DirData) ->
     Addr = proplists:get_value(bind_address, ConfigList),
@@ -285,17 +248,3 @@ secret_path(Path, [[NewDir]|Rest], Dir) ->
     end.
 
 
-
-load_return_int_tag(Name, Atom, Time, Dir, DirData) ->
-    case Time of
-	"infinity" ->
-	    {ok, [{security_directory, {Dir, 
-		   [{Atom, 99999999999999999999999999999} | DirData]}}]};
-	_Int ->
-	    case catch list_to_integer(Time) of
-		{'EXIT', _} ->
-		    {error, Time++" is an invalid "++Name};
-		Val ->
-		    {ok, [{security_directory, {Dir, [{Atom, Val}|DirData]}}]}
-	    end
-    end.
diff --git a/lib/inets/test/httpd_SUITE.erl b/lib/inets/test/httpd_SUITE.erl
index 1445ff89ac..9d82bd0a4a 100644
--- a/lib/inets/test/httpd_SUITE.erl
+++ b/lib/inets/test/httpd_SUITE.erl
@@ -143,7 +143,7 @@ groups() ->
      {http_1_1, [],
       [host, chunked, expect, cgi, cgi_chunked_encoding_test,
        trace, range, if_modified_since, mod_esi_chunk_timeout,
-       esi_put, esi_post, esi_proagate] ++ http_head() ++ http_get() ++ load()},
+       esi_put, esi_post, esi_proagate, esi_atom_leak] ++ http_head() ++ http_get() ++ load()},
      {http_1_0, [], [host, cgi, trace] ++ http_head() ++ http_get() ++ load()},
      {http_0_9, [], http_head() ++ http_get() ++ load()},
      {not_sup, [], [put_not_sup]}
@@ -1066,6 +1066,35 @@ esi_proagate(Config)  when is_list(Config) ->
         Err ->
             ct:fail(Err)
     end.        
+%%-------------------------------------------------------------------------
+esi_atom_leak() ->
+    [{doc, "Test mod_esi for atom leakage - verify module, function names and HTTP headers"}].
+
+esi_atom_leak(Config) when is_list(Config) ->
+    NumberStrings = [integer_to_list(N) || N <- lists:seq(1, 10)],
+
+    NotExistingModule =
+        ["GET /cgi-bin/erl/not_existing_" ++ S ++":get " || S <- NumberStrings],
+    %% check atom count after first HTTP call, to ignore count increase upon initial module loading
+    GetFun = fun(Url, HeadersAndBody, Expected) ->
+                     ok = http_status(Url, HeadersAndBody, Config, Expected),
+                     erlang:system_info(atom_count)
+             end,
+    AtomCount1 = [GetFun(U, {"", ""}, [{statuscode, 404}]) || U <- NotExistingModule],
+    IsStable = fun(L) -> lists:max(L) == lists:min(L) end,
+    true = IsStable(AtomCount1),
+
+    NotExistingFunction =
+        ["GET /cgi-bin/erl/httpd_example:not_existing" ++ S ++ " "
+         || S <- NumberStrings],
+    AtomCount2 = [GetFun(U, {"", ""}, [{statuscode, 404}]) || U <- NotExistingFunction],
+    true = IsStable(AtomCount2),
+
+    NotExistingHdr =
+        [{"NotExistingHeader_" ++ S ++ ":100 \r\n", ""} || S <- NumberStrings],
+    AtomCount3 = [GetFun("GET /cgi-bin/erl/httpd_example:get ", H, [{statuscode, 200}])
+                  || H <- NotExistingHdr],
+    true = IsStable(AtomCount3).
 
 %%-------------------------------------------------------------------------
 cgi() ->
-- 
2.26.2

openSUSE Build Service is sponsored by