File 0865-Improve-spec-indentation.patch of Package erlang

From 2ff321c693d873f1c42391c7a09a15549bcb4f40 Mon Sep 17 00:00:00 2001
From: Dan Gudmundsson <dgud@erlang.org>
Date: Tue, 8 Oct 2019 13:33:46 +0200
Subject: [PATCH] Improve spec indentation

Decrease result type indentation.
---
 lib/tools/emacs/erlang.el                  | 18 ++++++++++++------
 lib/tools/test/emacs_SUITE_data/type_specs | 30 +++++++++++++++++-------------
 2 files changed, 29 insertions(+), 19 deletions(-)

diff --git a/lib/tools/emacs/erlang.el b/lib/tools/emacs/erlang.el
index 0b3a2319e2..30efd78328 100644
--- a/lib/tools/emacs/erlang.el
+++ b/lib/tools/emacs/erlang.el
@@ -2679,8 +2679,9 @@ Value is list (stack token-start token-type in-what)."
         (if stack
             (forward-char 1)
           (forward-char 6)
-          (skip-chars-forward "^(\n")
           (erlang-push (list 'spec (point) (current-column)) stack)
+          (skip-chars-forward "^(\n")
+          (erlang-push (list 'spec_arg (point) (current-column)) stack)
           ))
 
        ;; Type spec delimiter
@@ -2797,7 +2798,7 @@ Return nil if inside string, t if in a comment."
                  (t
                   (erlang-indent-to-first-element stack-top 2))))
 
-          ((memq (car stack-top) '(icr fun spec))
+          ((memq (car stack-top) '(icr fun spec_arg))
            ;; The default indentation is the column of the option
            ;; directly following the keyword. (This does not apply to
            ;; `case'.)  Should no option be on the same line, the
@@ -2844,10 +2845,11 @@ Return nil if inside string, t if in a comment."
                      ((eq (car stack-top) '->)
                       ;; If in fun definition use standard indent level not double
                       ;;(if (not (eq (car (car (cdr stack))) 'fun))
-                      ;; Removed it made multi clause fun's look too bad
-                      (setq off (+ erlang-indent-level (if (not erlang-icr-indent)
-                                                           erlang-indent-level
-                                                         erlang-icr-indent)))))
+                      ;; Removed it made multi clause Named fun's look too bad
+                      (setq off (+ erlang-indent-level
+                                   (if (not erlang-icr-indent)
+                                       erlang-indent-level
+                                     erlang-icr-indent)))))
                (let ((base (erlang-indent-find-base stack indent-point off skip)))
                  ;; Special cases
                  (goto-char indent-point)
@@ -2873,6 +2875,10 @@ Return nil if inside string, t if in a comment."
                                        (erlang-caddr (car stack))
                                      0)))
                                 (t (erlang-indent-standard indent-point token base 'nil))))) ;; old catch
+                       ;; Indent result types
+                       ((eq (car (car (cdr stack))) 'spec_arg)
+                        (setq base (+ (erlang-caddr (car (last stack))) erlang-indent-level))
+                        (erlang-indent-standard indent-point token base 'nil))
                        (t
                         (erlang-indent-standard indent-point token base 'nil)
                         ))))
diff --git a/lib/tools/test/emacs_SUITE_data/type_specs b/lib/tools/test/emacs_SUITE_data/type_specs
index e71841cc7a..f9b15d7914 100644
--- a/lib/tools/test/emacs_SUITE_data/type_specs
+++ b/lib/tools/test/emacs_SUITE_data/type_specs
@@ -71,11 +71,14 @@
 -spec t1(FooBar :: t99()) -> t99();
         (t2()) -> t2();
         (t4()) -> t4() when is_subtype(t4(), t24);
-        (t23()) -> t23() when is_subtype(t23(), atom()),
-                              is_subtype(t23(), t14());
-        (t24()) -> t24() when is_subtype(t24(), atom()),
-                              is_subtype(t24(), t14()),
-                              is_subtype(t24(), t4()).
+        (t23()) ->
+          t23() when is_subtype(t23(), atom()),
+                     is_subtype(t23(), t14());
+        (t24()) ->
+          t24() when
+      is_subtype(t24(), atom()),
+      is_subtype(t24(), t14()),
+      is_subtype(t24(), t4()).
 
 -spec over(I :: integer()) -> R1 :: foo:typen();
           (A :: atom()) -> R2 :: foo:atomen();
@@ -83,23 +86,24 @@
 
 -spec mod:t2() -> any().
 
--spec handle_cast(Cast :: {'exchange', node(), [[name(),...]]}
-                        | {'del_member', name(), pid()},
-                  #state{}) -> {'noreply', #state{}}.
+-spec handle_cast(
+        Cast :: {'exchange', node(), [[name(),...]]}
+              | {'del_member', name(), pid()},
+        #state{}) -> {'noreply', #state{}}.
 
 -spec handle_cast(Cast ::
                     {'exchange', node(), [[name(),...]]}
                   | {'del_member', name(), pid()},
                   #state{}) ->
-                         {'noreply', #state{}}. %% left to col 10?
+          {'noreply', #state{}}.
 
 -spec all(fun((T) -> boolean()), List :: [T]) ->
-                 boolean() when is_subtype(T, term()). % (*)
+          boolean() when is_subtype(T, term()). % (*)
 
 -spec get_closest_pid(term()) ->
-                             Return :: pid()  %% left to col 10?
-                                     | {'error', {'no_process', term()}} %% left to col 10?
-                                     | {'no_such_group', term()}. %% left to col 10?
+          Return :: pid()
+                  | {'error', {'no_process', term()}} %% left to col 10?
+                  | {'no_such_group', term()}. %% left to col 10?
 
 -spec add( X :: integer()
          , Y :: integer()
-- 
2.16.4

openSUSE Build Service is sponsored by