File 2943-Expressions-in-clauses-on-separate-lines.patch of Package erlang

From 603a20859f73ac43675e3e87dc21a69a9a6b0ded Mon Sep 17 00:00:00 2001
From: Pierre Krafft <kpierre@outlook.com>
Date: Thu, 7 Nov 2019 23:10:02 +0100
Subject: [PATCH 3/5] Expressions in clauses on separate lines

Expressions that are separated by at least one empty line will
be separated by exactly one empty line in the output.
---
 lib/syntax_tools/src/erl_prettypr.erl | 32 ++++++++++++++++++++++-----
 lib/syntax_tools/src/erl_tidy.erl     | 41 +++++++++++++++--------------------
 lib/syntax_tools/src/prettypr.erl     |  3 +++
 3 files changed, 48 insertions(+), 28 deletions(-)

diff --git a/lib/syntax_tools/src/erl_prettypr.erl b/lib/syntax_tools/src/erl_prettypr.erl
index 9fcc49c7dd..5e39557e68 100644
--- a/lib/syntax_tools/src/erl_prettypr.erl
+++ b/lib/syntax_tools/src/erl_prettypr.erl
@@ -66,7 +66,8 @@
 	       paper = ?PAPER     :: integer(),
 	       ribbon = ?RIBBON   :: integer(),
 	       user = ?NOUSER     :: term(),
-               encoding = epp:default_encoding() :: epp:source_encoding()}).
+               encoding = epp:default_encoding() :: epp:source_encoding(),
+	       empty_lines = sets:new() :: sets:set(integer())}).
 
 -type context() :: #ctxt{}.
 
@@ -358,7 +359,8 @@ layout(Node, Options) ->
 	      ribbon = proplists:get_value(ribbon, Options, ?RIBBON),
 	      user = proplists:get_value(user, Options),
               encoding = proplists:get_value(encoding, Options,
-                                             epp:default_encoding())}).
+                                             epp:default_encoding()),
+              empty_lines = proplists:get_value(empty_lines, Options, sets:new())}).
 
 lay(Node, Ctxt) ->
     case erl_syntax:get_ann(Node) of
@@ -576,9 +578,7 @@ lay_2(Node, Ctxt) ->
 		     G ->
 			 lay(G, Ctxt1)
 		 end,
-	    D3 = sep(seq(erl_syntax:clause_body(Node),
-			 floating(text(",")), Ctxt1,
-			 fun lay/2)),
+	    D3 = lay_clause_expressions(erl_syntax:clause_body(Node), Ctxt1),
 	    case Ctxt#ctxt.clause of
 		fun_expr ->
 		    make_fun_clause(D1, D2, D3, Ctxt);
@@ -1494,5 +1494,27 @@ tidy_float_2([$e | Cs]) -> tidy_float_2([$e, $+ | Cs]);
 tidy_float_2([_C | Cs]) -> tidy_float_2(Cs);
 tidy_float_2([]) -> [].
 
+lay_clause_expressions([H], Ctxt) ->
+	lay(H, Ctxt);
+lay_clause_expressions([H | T], Ctxt) ->
+    Clause = beside(lay(H, Ctxt), floating(text(","))),
+    Next = lay_clause_expressions(T, Ctxt),
+    case is_last_and_before_empty_line(H, T, Ctxt) of
+	true ->
+	    above(above(Clause, text("")), Next);
+        false ->
+            above(Clause, Next)
+    end;
+lay_clause_expressions([], _) ->
+    empty().
+
+is_last_and_before_empty_line(H, [], #ctxt{empty_lines = EmptyLines}) ->
+    try sets:is_element(erl_syntax:get_pos(H) + 1, EmptyLines)
+    catch error:badarith -> false
+    end;
+is_last_and_before_empty_line(H, [H2 | _], #ctxt{empty_lines = EmptyLines}) ->
+    try ((erl_syntax:get_pos(H2) - erl_syntax:get_pos(H)) >= 2) and sets:is_element(erl_syntax:get_pos(H) + 1, EmptyLines)
+    catch error:badarith -> false
+    end.
 
 %% =====================================================================
diff --git a/lib/syntax_tools/src/erl_tidy.erl b/lib/syntax_tools/src/erl_tidy.erl
index 1ced48ecb3..d97afda0ea 100644
--- a/lib/syntax_tools/src/erl_tidy.erl
+++ b/lib/syntax_tools/src/erl_tidy.erl
@@ -319,7 +319,8 @@ file_1(Parent, Name, Opts) ->
 
 file_2(Name, Opts) ->
     Opts1 = Opts ++ file__defaults(),
-    Forms = read_module(Name, Opts1),
+    {Forms, EmptyLines} = read_module(Name, Opts1),
+    Opts2 = [{empty_lines, EmptyLines} | Opts1],
     Comments = erl_comment_scan:file(Name),
     Forms1 = erl_recomment:recomment_forms(Forms, Comments),
     Tree = module(Forms1, [{file, Name} | Opts1]),
@@ -329,10 +330,10 @@ file_2(Name, Opts) ->
         false ->
 			case proplists:get_bool(stdout, Opts1) of
 				true ->
-					print_module(Tree, Opts1),
+					print_module(Tree, Opts2),
 					ok;
 				false ->
-					write_module(Tree, Name, Opts1),
+					write_module(Tree, Name, Opts2),
 					ok
 			end
 	end.
@@ -341,31 +342,25 @@ read_module(Name, Opts) ->
     verbose("reading module `~ts'.", [filename(Name)], Opts),
     case epp_dodger:parse_file(Name, [no_fail]) of
         {ok, Forms} ->
-            check_forms(Forms, Name),
-            Forms;
+            {Forms, empty_lines(Name)};
         {error, R} ->
             error_read_file(Name),
             exit({error, R})
     end.
 
-check_forms(Fs, Name) ->
-    Fun = fun (F) ->
-                  case erl_syntax:type(F) of
-                      error_marker ->
-                          S = case erl_syntax:error_marker_info(F) of
-                                  {_, M, D} ->
-                                      M:format_error(D);
-                                  _ ->
-                                      "unknown error"
-                              end,
-                          report_error({Name, erl_syntax:get_pos(F),
-                                        "\n  ~ts"}, [S]),
-                          exit(error);
-                      _ ->
-                          ok
-                  end
-          end,
-    lists:foreach(Fun, Fs).
+empty_lines(Name) ->
+    {ok, Data} = file:read_file(Name),
+    List = binary:split(Data, [<<"\n">>], [global]),
+    {ok, NonEmptyLineRe} = re:compile("\\S"),
+    {Res, _} = lists:foldl(
+        fun(Line, {Set, N}) ->
+            case re:run(Line, NonEmptyLineRe) of
+                {match, _} -> {Set, N + 1};
+                nomatch -> {sets:add_element(N, Set), N + 1}
+            end
+        end,
+        {sets:new(), 1}, List),
+    Res.
 
 %% Create the target directory and make a backup file if necessary,
 %% then open the file, output the text and close the file
diff --git a/lib/syntax_tools/src/prettypr.erl b/lib/syntax_tools/src/prettypr.erl
index 61a8993b84..4e5ce334ab 100644
--- a/lib/syntax_tools/src/prettypr.erl
+++ b/lib/syntax_tools/src/prettypr.erl
@@ -569,6 +569,9 @@ format(D, W, R) ->
 layout(L) ->
     lists:reverse(layout(0, L, [])).
 
+layout(N, #above{d1 = #text{s = [_ | ""]}, d2 = L}, Cs) ->
+    %% Text for this line is empty. Print newline but no indentation.
+    layout(N, L, [$\n | Cs]);
 layout(N, #above{d1 = #text{s = S}, d2 = L}, Cs) ->
     layout(N, L, [$\n | flatrev(string_chars(S), indent(N, Cs))]);
 layout(N, #nest{n = N1, d = L}, Cs) ->
-- 
2.16.4

openSUSE Build Service is sponsored by