File 3512-Add-maybe-and-else-to-erlang-mode-for-Emacs.patch of Package erlang
From 831842d7df8496b98ccee509f71c714939ea7cfb Mon Sep 17 00:00:00 2001
From: Dan Gudmundsson <dgud@erlang.org>
Date: Tue, 16 Nov 2021 15:21:02 +0100
Subject: [PATCH 12/12] Add 'maybe' and 'else' to erlang-mode for Emacs
---
lib/tools/emacs/erlang.el | 27 ++++++++++++++------
lib/tools/test/emacs_SUITE_data/icr | 39 +++++++++++++++++++++++++++++
2 files changed, 58 insertions(+), 8 deletions(-)
diff --git a/lib/tools/emacs/erlang.el b/lib/tools/emacs/erlang.el
index ade51beb7c..065e180804 100644
--- a/lib/tools/emacs/erlang.el
+++ b/lib/tools/emacs/erlang.el
@@ -678,6 +678,8 @@ resulting regexp is surrounded by \\_< and \\_>."
"of"
"receive"
"try"
+ "maybe"
+ "else"
"when")
"Erlang reserved keywords"))
@@ -2730,13 +2732,13 @@ Value is list (stack token-start token-type in-what)."
;; Word constituent: check and handle keywords.
((= cs ?w)
- (cond ((looking-at "\\(end\\|after\\)[^_a-zA-Z0-9]")
+ (cond ((looking-at "\\(end\\|after\\|else\\)[^_a-zA-Z0-9]")
;; Must pop top icr layer, `after' will push a new
;; layer next.
(progn
(while (and stack (eq (car (car stack)) '->))
(erlang-pop stack))
- (if (and stack (memq (car (car stack)) '(icr begin fun try)))
+ (if (and stack (memq (car (car stack)) '(icr begin fun try maybe)))
(erlang-pop stack))))
((looking-at "catch\\b.*of")
t)
@@ -2746,7 +2748,7 @@ Value is list (stack token-start token-type in-what)."
(progn
(while (and stack (eq (car (car stack)) '->))
(erlang-pop stack))
- (if (and stack (memq (car (car stack)) '(icr begin try)))
+ (if (and stack (memq (car (car stack)) '(icr begin try maybe)))
(erlang-pop stack))))
)
(cond ((looking-at "\\(if\\|case\\|receive\\)[^_a-zA-Z0-9]")
@@ -2783,6 +2785,11 @@ Value is list (stack token-start token-type in-what)."
(erlang-push (list 'fun token (current-column)) stack)))
((looking-at "\\(begin\\)[^_a-zA-Z0-9]")
(erlang-push (list 'begin token (current-column)) stack))
+ ((looking-at "\\(maybe\\)[^_a-zA-Z0-9]")
+ (erlang-push (list 'begin token (current-column)) stack))
+ ((looking-at "\\(else\\)[^_a-zA-Z0-9]")
+ (erlang-push (list 'icr token (current-column)) stack))
+
;; Normal when case
;;((looking-at "when\\s ")
;;((looking-at "when\\s *\\($\\|%\\)")
@@ -2875,7 +2882,7 @@ Value is list (stack token-start token-type in-what)."
(erlang-pop stack))
(cond ((eq (car (car stack)) '<<)
(erlang-pop stack))
- ((memq (car (car stack)) '(icr begin fun))
+ ((memq (car (car stack)) '(icr begin maybe fun))
(error "Missing `end'"))
(t
(error "Unbalanced parentheses")))
@@ -2947,6 +2954,8 @@ Value is list (stack token-start token-type in-what)."
))
((eq (car (car stack)) 'begin)
(error "Missing `end'"))
+ ((eq (car (car stack)) 'maybe)
+ (error "Missing `end'"))
(t
(error "Unbalanced parenthesis"))
)
@@ -3048,7 +3057,7 @@ Return nil if inside string, t if in a comment."
((and (eq (car stack-top) '||) (looking-at "\\(]\\|>>\\)[^_a-zA-Z0-9]"))
(nth 2 (car (cdr stack))))
;; Real indentation, where operators create extra indentation etc.
- ((memq (car stack-top) '(-> || try begin))
+ ((memq (car stack-top) '(-> || try begin maybe))
(if (looking-at "\\(of\\)[^_a-zA-Z0-9]")
(nth 2 stack-top)
(goto-char (nth 1 stack-top))
@@ -3060,6 +3069,8 @@ Return nil if inside string, t if in a comment."
(cond ((null (cdr stack))) ; Top level in function.
((eq (car stack-top) 'begin)
(setq skip 5))
+ ((eq (car stack-top) 'maybe)
+ (setq skip 5))
((eq (car stack-top) 'try)
(setq skip 5))
((eq (car stack-top) '->)
@@ -3073,7 +3084,7 @@ Return nil if inside string, t if in a comment."
(let ((base (erlang-indent-find-base stack indent-point off skip)))
;; Special cases
(goto-char indent-point)
- (cond ((looking-at "\\(;\\|end\\|after\\)\\($\\|[^_a-zA-Z0-9]\\)")
+ (cond ((looking-at "\\(;\\|end\\|after\\|else\\)\\($\\|[^_a-zA-Z0-9]\\)")
(if (eq (car stack-top) '->)
(erlang-pop stack))
(cond ((and stack (looking-at ";"))
@@ -3324,8 +3335,8 @@ This assumes that the preceding expression is either simple
(defun erlang-at-keyword ()
"Are we looking at an Erlang keyword which will increase indentation?"
- (looking-at (concat "\\(when\\|if\\|fun\\|case\\|begin\\|"
- "of\\|receive\\|after\\|catch\\|try\\)\\b")))
+ (looking-at (concat "\\(when\\|if\\|fun\\|case\\|begin\\|maybe\\|"
+ "of\\|receive\\|after\\|catch\\|try\\|else\\)\\b")))
(defun erlang-at-operator ()
"Are we looking at an Erlang operator?"
diff --git a/lib/tools/test/emacs_SUITE_data/icr b/lib/tools/test/emacs_SUITE_data/icr
index 8445c1a74d..aa25ad04ff 100644
--- a/lib/tools/test/emacs_SUITE_data/icr
+++ b/lib/tools/test/emacs_SUITE_data/icr
@@ -155,3 +155,42 @@ indent_receive() ->
5*43
end,
ok.
+
+indent_maybe(1) ->
+ begin
+ maybe_should_be_indented_as_begin,
+ end,
+ maybe
+ 1 = foo(X),
+ 2 ?= asd(X),
+ line_with_break =
+ foo(X+1),
+ line_with_break ?=
+ foo(X+1)
+ end,
+ ok;
+indent_maybe(1) ->
+ maybe
+ 2 ?= foo(X),
+ 3 ?= bar(Y)
+ else
+ %% else indented as a standard icr (if-case-receive)
+ {error, Z} when Z == 1 ->
+ error1;
+ {error, Z}
+ when Z == 2 ->
+ error2
+ end;
+indent_maybe(3) ->
+ maybe
+ 2 ?= foo(x),
+ maybe
+ nested ?= foo(y)
+ else
+ error ->
+ ok
+ end
+ else
+ error -> ok
+ end.
+
--
2.34.1