File 2266-stdlib-Let-epp-handle-long-file-names.patch of Package erlang

From ba7074f76765c9aecc2868198a763f3cd68a7ae0 Mon Sep 17 00:00:00 2001
From: Hans Bolinder <hasse@erlang.org>
Date: Fri, 10 Jun 2016 08:46:08 +0200
Subject: [PATCH] stdlib: Let epp handle long file names

---
 lib/stdlib/src/epp.erl           | 46 +++++++++++++++++++++++++++---------
 lib/stdlib/src/erl_pp.erl        | 50 ++++++++++++++++++++--------------------
 lib/stdlib/test/erl_pp_SUITE.erl | 24 +++++++++++++++++--
 3 files changed, 82 insertions(+), 38 deletions(-)

diff --git a/lib/stdlib/src/epp.erl b/lib/stdlib/src/epp.erl
index 73934e0..40eba4a 100644
--- a/lib/stdlib/src/epp.erl
+++ b/lib/stdlib/src/epp.erl
@@ -954,11 +954,15 @@ scan_undef(_Toks, Undef, From, St) ->
 
 %% scan_include(Tokens, IncludeToken, From, St)
 
-scan_include([{'(',_Llp},{string,_Lf,NewName0},{')',_Lrp},{dot,_Ld}], Inc,
-	     From, St) ->
+scan_include(Tokens0, Inc, From, St) ->
+    Tokens = coalesce_strings(Tokens0),
+    scan_include1(Tokens, Inc, From, St).
+
+scan_include1([{'(',_Llp},{string,_Lf,NewName0},{')',_Lrp},{dot,_Ld}], Inc,
+              From, St) ->
     NewName = expand_var(NewName0),
     enter_file(NewName, Inc, From, St);
-scan_include(_Toks, Inc, From, St) ->
+scan_include1(_Toks, Inc, From, St) ->
     epp_reply(From, {error,{loc(Inc),epp,{bad,include}}}),
     wait_req_scan(St).
 
@@ -977,13 +981,17 @@ expand_lib_dir(Name) ->
 	    error
     end.
 
-scan_include_lib([{'(',_Llp},{string,_Lf,_NewName0},{')',_Lrp},{dot,_Ld}],
-                 Inc, From, St)
+scan_include_lib(Tokens0, Inc, From, St) ->
+    Tokens = coalesce_strings(Tokens0),
+    scan_include_lib1(Tokens, Inc, From, St).
+
+scan_include_lib1([{'(',_Llp},{string,_Lf,_NewName0},{')',_Lrp},{dot,_Ld}],
+                  Inc, From, St)
   when length(St#epp.sstk) >= 8 ->
     epp_reply(From, {error,{loc(Inc),epp,{depth,"include_lib"}}}),
     wait_req_scan(St);
-scan_include_lib([{'(',_Llp},{string,_Lf,NewName0},{')',_Lrp},{dot,_Ld}],
-                 Inc, From, St) ->
+scan_include_lib1([{'(',_Llp},{string,_Lf,NewName0},{')',_Lrp},{dot,_Ld}],
+                  Inc, From, St) ->
     NewName = expand_var(NewName0),
     Loc = start_loc(St#epp.location),
     case file:path_open(St#epp.path, NewName, [read]) of
@@ -1008,7 +1016,7 @@ scan_include_lib([{'(',_Llp},{string,_Lf,NewName0},{')',_Lrp},{dot,_Ld}],
 		    wait_req_scan(St)
 	    end
     end;
-scan_include_lib(_Toks, Inc, From, St) ->
+scan_include_lib1(_Toks, Inc, From, St) ->
     epp_reply(From, {error,{loc(Inc),epp,{bad,include_lib}}}),
     wait_req_scan(St).
 
@@ -1110,8 +1118,12 @@ scan_endif(_Toks, Endif, From, St) ->
 %%  Set the current file and line to the given file and line.
 %%  Note that the line of the attribute itself is kept.
 
-scan_file([{'(',_Llp},{string,_Ls,Name},{',',_Lc},{integer,_Li,Ln},{')',_Lrp},
-           {dot,_Ld}], Tf, From, St) ->
+scan_file(Tokens0, Tf, From, St) ->
+    Tokens = coalesce_strings(Tokens0),
+    scan_file1(Tokens, Tf, From, St).
+
+scan_file1([{'(',_Llp},{string,_Ls,Name},{',',_Lc},{integer,_Li,Ln},{')',_Lrp},
+            {dot,_Ld}], Tf, From, St) ->
     Anno = erl_anno:new(Ln),
     enter_file_reply(From, Name, Anno, loc(Tf), generated),
     Ms0 = St#epp.macs,
@@ -1120,7 +1132,7 @@ scan_file([{'(',_Llp},{string,_Ls,Name},{',',_Lc},{integer,_Li,Ln},{')',_Lrp},
     NewLoc = new_location(Ln, St#epp.location, Locf),
     Delta = get_line(element(2, Tf))-Ln + St#epp.delta,
     wait_req_scan(St#epp{name2=Name,location=NewLoc,delta=Delta,macs=Ms});
-scan_file(_Toks, Tf, From, St) ->
+scan_file1(_Toks, Tf, From, St) ->
     epp_reply(From, {error,{loc(Tf),epp,{bad,file}}}),
     wait_req_scan(St).
 
@@ -1537,6 +1549,18 @@ stringify(Ts, L) ->
     [$\s | S] = lists:flatten(stringify1(Ts)),
     [{string, L, S}].
 
+coalesce_strings([{string,A,S} | Tokens]) ->
+    coalesce_strings(Tokens, A, [S]);
+coalesce_strings([T | Tokens]) ->
+    [T | coalesce_strings(Tokens)];
+coalesce_strings([]) ->
+    [].
+
+coalesce_strings([{string,_,S}|Tokens], A, S0) ->
+    coalesce_strings(Tokens, A, [S | S0]);
+coalesce_strings(Tokens, A, S) ->
+    [{string,A,lists:append(lists:reverse(S))} | coalesce_strings(Tokens)].
+
 %% epp_request(Epp)
 %% epp_request(Epp, Request)
 %% epp_reply(From, Reply)
diff --git a/lib/stdlib/src/erl_pp.erl b/lib/stdlib/src/erl_pp.erl
index 016962f..d30cd50 100644
--- a/lib/stdlib/src/erl_pp.erl
+++ b/lib/stdlib/src/erl_pp.erl
@@ -82,7 +82,7 @@ form(Thing) ->
 form(Thing, Options) ->
     ?TEST(Thing),
     State = state(Options),
-    frmt(lform(Thing, options(Options), State), State).
+    frmt(lform(Thing, options(Options)), State).
 
 -spec(attribute(Attribute) -> io_lib:chars() when
       Attribute :: erl_parse:abstract_form()).
@@ -97,7 +97,7 @@ attribute(Thing) ->
 attribute(Thing, Options) ->
     ?TEST(Thing),
     State = state(Options),
-    frmt(lattribute(Thing, options(Options), State), State).
+    frmt(lattribute(Thing, options(Options)), State).
 
 -spec(function(Function) -> io_lib:chars() when
       Function :: erl_parse:abstract_form()).
@@ -217,55 +217,55 @@ encoding(Options) ->
         unicode -> unicode
     end.
 
-lform({attribute,Line,Name,Arg}, Opts, State) ->
-    lattribute({attribute,Line,Name,Arg}, Opts, State);
-lform({function,Line,Name,Arity,Clauses}, Opts, _State) ->
+lform({attribute,Line,Name,Arg}, Opts) ->
+    lattribute({attribute,Line,Name,Arg}, Opts);
+lform({function,Line,Name,Arity,Clauses}, Opts) ->
     lfunction({function,Line,Name,Arity,Clauses}, Opts);
 %% These are specials to make it easier for the compiler.
-lform({error,E}, _Opts, _State) ->
+lform({error,E}, _Opts) ->
     leaf(format("~p\n", [{error,E}]));
-lform({warning,W}, _Opts, _State) ->
+lform({warning,W}, _Opts) ->
     leaf(format("~p\n", [{warning,W}]));
-lform({eof,_Line}, _Opts, _State) ->
+lform({eof,_Line}, _Opts) ->
     $\n.
 
-lattribute({attribute,_Line,type,Type}, Opts, _State) ->
+lattribute({attribute,_Line,type,Type}, Opts) ->
     [typeattr(type, Type, Opts),leaf(".\n")];
-lattribute({attribute,_Line,opaque,Type}, Opts, _State) ->
+lattribute({attribute,_Line,opaque,Type}, Opts) ->
     [typeattr(opaque, Type, Opts),leaf(".\n")];
-lattribute({attribute,_Line,spec,Arg}, _Opts, _State) ->
+lattribute({attribute,_Line,spec,Arg}, _Opts) ->
     [specattr(spec, Arg),leaf(".\n")];
-lattribute({attribute,_Line,callback,Arg}, _Opts, _State) ->
+lattribute({attribute,_Line,callback,Arg}, _Opts) ->
     [specattr(callback, Arg),leaf(".\n")];
-lattribute({attribute,_Line,Name,Arg}, Opts, State) ->
-    [lattribute(Name, Arg, Opts, State),leaf(".\n")].
+lattribute({attribute,_Line,Name,Arg}, Opts) ->
+    [lattribute(Name, Arg, Opts),leaf(".\n")].
 
-lattribute(module, {M,Vs}, _Opts, _State) ->
+lattribute(module, {M,Vs}, _Opts) ->
     A = a0(),
     attr("module",[{var,A,pname(M)},
                    foldr(fun(V, C) -> {cons,A,{var,A,V},C}
                          end, {nil,A}, Vs)]);
-lattribute(module, M, _Opts, _State) ->
+lattribute(module, M, _Opts) ->
     attr("module", [{var,a0(),pname(M)}]);
-lattribute(export, Falist, _Opts, _State) ->
+lattribute(export, Falist, _Opts) ->
     call({var,a0(),"-export"}, [falist(Falist)], 0, options(none));
-lattribute(import, Name, _Opts, _State) when is_list(Name) ->
+lattribute(import, Name, _Opts) when is_list(Name) ->
     attr("import", [{var,a0(),pname(Name)}]);
-lattribute(import, {From,Falist}, _Opts, _State) ->
+lattribute(import, {From,Falist}, _Opts) ->
     attr("import",[{var,a0(),pname(From)},falist(Falist)]);
-lattribute(export_type, Talist, _Opts, _State) ->
+lattribute(export_type, Talist, _Opts) ->
     call({var,a0(),"-export_type"}, [falist(Talist)], 0, options(none));
-lattribute(optional_callbacks, Falist, Opts, _State) ->
+lattribute(optional_callbacks, Falist, Opts) ->
     ArgL = try falist(Falist)
            catch _:_ -> abstract(Falist, Opts)
            end,
     call({var,a0(),"-optional_callbacks"}, [ArgL], 0, options(none));
-lattribute(file, {Name,Line}, _Opts, State) ->
-    attr("file", [{var,a0(),(State#pp.string_fun)(Name)},{integer,a0(),Line}]);
-lattribute(record, {Name,Is}, Opts, _State) ->
+lattribute(file, {Name,Line}, _Opts) ->
+    attr("file", [{string,a0(),Name},{integer,a0(),Line}]);
+lattribute(record, {Name,Is}, Opts) ->
     Nl = leaf(format("-record(~w,", [Name])),
     [{first,Nl,record_fields(Is, Opts)},$)];
-lattribute(Name, Arg, Options, _State) ->
+lattribute(Name, Arg, Options) ->
     attr(write(Name), [abstract(Arg, Options)]).
 
 abstract(Arg, #options{encoding = Encoding}) ->
diff --git a/lib/stdlib/test/erl_pp_SUITE.erl b/lib/stdlib/test/erl_pp_SUITE.erl
index 951a17d..a103f6d 100644
--- a/lib/stdlib/test/erl_pp_SUITE.erl
+++ b/lib/stdlib/test/erl_pp_SUITE.erl
@@ -51,6 +51,7 @@
 	  otp_6321/1, otp_6911/1, otp_6914/1, otp_8150/1, otp_8238/1,
 	  otp_8473/1, otp_8522/1, otp_8567/1, otp_8664/1, otp_9147/1,
           otp_10302/1, otp_10820/1, otp_11100/1, otp_11861/1,
+          otp_13662/1,
           gh_5093/1]).
 
 %% Internal export.
@@ -84,7 +85,7 @@ groups() ->
      {tickets, [],
       [otp_6321, otp_6911, otp_6914, otp_8150, otp_8238,
        otp_8473, otp_8522, otp_8567, otp_8664, otp_9147,
-       otp_10302, otp_10820, otp_11100, otp_11861,
+       otp_10302, otp_10820, otp_11100, otp_11861, otp_13662,
        gh_5093]}].
 
 init_per_suite(Config) ->
@@ -1188,6 +1189,25 @@ pr_1014(Config) ->
 pf(Form) ->
     lists:flatten(erl_pp:form(Form, none)).
 
+otp_13662(Config) ->
+    Include = "abcdefghijabcdefghijabcdefghijabcdefghijabcde"
+              "fghij-xxxxxxxxxxxxxxxxxxxxxxxxxxxxxx.hrl",
+    IncludeFile = filename(Include, Config),
+    ok = file:write_file(IncludeFile, <<>>),
+    Ts = [{otp_13662,
+          <<"-file(\"abcdefghijabcdefghijabcdefghijabcdefghijabcde\"\n
+                   \"fghij-xxxxxxxxxxxxxxxxxxxxxxxxxxxxxx.erl\", 0).\n
+            -include(\"abcdefghijabcdefghijabcdefghijabcdefghijabcde\"
+                     \"fghij-xxxxxxxxxxxxxxxxxxxxxxxxxxxxxx.hrl\").\n
+            -include_lib(\"abcdefghijabcdefghijabcdefghijabcdefghijabcde\"
+                         \"fghij-xxxxxxxxxxxxxxxxxxxxxxxxxxxxxx.hrl\").
+            -compile(export_all).\n
+            t() ->\n
+                \"aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa\"\n
+                \"aaaaaaaaaaaaaaaaaaaaaa\".\n">>}
+          ],
+    compile(Config, Ts).
+
 gh_5093(_Config) ->
   assert_same("f() ->\n    -1.\n"),
   assert_same("f() ->\n    +1.\n"),
-- 
2.1.4

openSUSE Build Service is sponsored by