File 3532-compiler-Cleanup-types-and-docs-in-cerl-modules.patch of Package erlang

From af02a0ca2b1a52553df2584f1b2585bc3b18f974 Mon Sep 17 00:00:00 2001
From: Lukas Larsson <lukas@erlang.org>
Date: Mon, 9 Oct 2023 15:33:01 +0200
Subject: [PATCH 2/3] compiler: Cleanup types and docs in cerl modules

The purpose of this cleanup is to make the types reflect
the documentation more.
---
 lib/compiler/src/cerl.erl         | 21 ++++++++-----------
 lib/compiler/src/cerl_clauses.erl | 17 ++++++++--------
 lib/compiler/src/cerl_trees.erl   | 34 +++++++++++++++----------------
 3 files changed, 35 insertions(+), 37 deletions(-)

diff --git a/lib/compiler/src/cerl.erl b/lib/compiler/src/cerl.erl
index 7e4e5af98c..8753976cdb 100644
--- a/lib/compiler/src/cerl.erl
+++ b/lib/compiler/src/cerl.erl
@@ -13,13 +13,11 @@
 %% @copyright 1999-2002 Richard Carlsson
 %% @author Richard Carlsson <carlsson.richard@gmail.com>
 %% @doc Core Erlang abstract syntax trees.
-%%
 %% <p> This module defines an abstract data type for representing Core
 %% Erlang source code as syntax trees.</p>
 %%
 %% <p>A recommended starting point for the first-time user is the
-%% documentation of the function <a
-%% href="#type-1"><code>type/1</code></a>.</p>
+%% documentation of the function {@link type/1}.</p>
 %%
 %% <h3><b>NOTES:</b></h3>
 %%
@@ -49,9 +47,9 @@
 %% @type cerl(). An abstract Core Erlang syntax tree.
 %%
 %% <p>Every abstract syntax tree has a <em>type</em>, given by the
-%% function <a href="#type-1"><code>type/1</code></a>.  In addition,
-%% each syntax tree has a list of <em>user annotations</em> (cf.  <a
-%% href="#get_ann-1"><code>get_ann/1</code></a>), which are included
+%% function {@link type/1}.  In addition,
+%% each syntax tree has a list of <em>user annotations</em>
+%% (cf. {@link get_ann/1}), which are included
 %% in the Core Erlang syntax.</p>
 
 -module(cerl).
@@ -192,6 +190,11 @@
 %% the annotation field only).
 %% =====================================================================
 
+-type ctype() :: 'alias'   | 'apply'  | 'binary' | 'bitstr' | 'call' | 'case'
+               | 'catch'   | 'clause' | 'cons'   | 'fun'    | 'let'  | 'letrec'
+               | 'literal' | 'map'  | 'map_pair' | 'module' | 'primop'
+               | 'receive' | 'seq'    | 'try'    | 'tuple'  | 'values' | 'var'.
+
 %% @spec type(Node::cerl()) -> atom()
 %%
 %% @doc Returns the type tag of <code>Node</code>. Current node types
@@ -264,12 +267,6 @@
 %% @see data_type/1
 %% @see subtrees/1
 %% @see meta/1
-
--type ctype() :: 'alias'   | 'apply'  | 'binary' | 'bitstr' | 'call' | 'case'
-               | 'catch'   | 'clause' | 'cons'   | 'fun'    | 'let'  | 'letrec'
-               | 'literal' | 'map'  | 'map_pair' | 'module' | 'primop'
-               | 'receive' | 'seq'    | 'try'    | 'tuple'  | 'values' | 'var'.
-
 -spec type(cerl()) -> ctype().
 
 type(#c_alias{}) -> alias;
diff --git a/lib/compiler/src/cerl_clauses.erl b/lib/compiler/src/cerl_clauses.erl
index 3fd7ddd181..63bdb5e07d 100644
--- a/lib/compiler/src/cerl_clauses.erl
+++ b/lib/compiler/src/cerl_clauses.erl
@@ -14,8 +14,7 @@
 %% @author Richard Carlsson <carlsson.richard@gmail.com>
 %% @doc Utility functions for Core Erlang case/receive clauses.
 %%
-%% <p>Syntax trees are defined in the module
-%% <a href="cerl"><code>cerl</code></a>.</p>
+%% <p>Syntax trees are defined in the module {@link cerl}.</p>
 %%
 %% @type cerl() = cerl:cerl()
 
@@ -29,6 +28,8 @@
 	       is_data/1, is_c_var/1, let_body/1, letrec_body/1,
 	       seq_body/1, try_arg/1, type/1, values_es/1]).
 
+-type cerl() :: cerl:cerl().
+
 %% ---------------------------------------------------------------------
 
 %% @spec is_catchall(Clause::cerl()) -> boolean()
@@ -81,7 +82,7 @@ all_vars([]) ->
 %%
 %% @see is_catchall/1
 
--spec any_catchall([cerl:cerl()]) -> boolean().
+-spec any_catchall([cerl()]) -> boolean().
 
 any_catchall([C | Cs]) ->
     case is_catchall(C) of
@@ -112,7 +113,7 @@ any_catchall([]) ->
 %% This function could possibly be improved further, but constant
 %% folding should in general be performed elsewhere.
 
--spec eval_guard(cerl:cerl()) -> 'none' | {'value', term()}.
+-spec eval_guard(cerl()) -> 'none' | {'value', term()}.
 
 eval_guard(E) ->
     case type(E) of
@@ -140,7 +141,7 @@ eval_guard(E) ->
 
 %% ---------------------------------------------------------------------
 
--type bindings() :: [{cerl:cerl(), cerl:cerl()}].
+-type bindings() :: [{cerl(), cerl()}].
 
 %% @spec reduce(Clauses) -> {true, {Clause, Bindings}}
 %%                        | {false, Clauses}
@@ -196,7 +197,7 @@ reduce(Cs) ->
 %% @see match/2
 %% @see match_list/2
 
--type expr() :: 'any' | cerl:cerl().
+-type expr() :: 'any' | cerl().
 
 -spec reduce([cerl:c_clause()], [expr()]) ->
         {'true', {cerl:c_clause(), bindings()}} | {'false', [cerl:c_clause()]}.
@@ -313,7 +314,7 @@ reduce([], _, Cs) ->
 
 -type match_ret() :: 'none' | {'true', bindings()} | {'false', bindings()}.
 
--spec match(cerl:cerl(), expr()) -> match_ret().
+-spec match(cerl(), expr()) -> match_ret().
 
 match(P, E) ->
     match(P, E, []).
@@ -430,7 +431,7 @@ match_1(P, E, Bs) ->
 %%
 %% @see match/2
 
--spec match_list([cerl:cerl()], [expr()]) -> match_ret().
+-spec match_list([cerl()], [expr()]) -> match_ret().
 
 match_list([], []) ->
     {true, []};    % no patterns always match
diff --git a/lib/compiler/src/cerl_trees.erl b/lib/compiler/src/cerl_trees.erl
index 58863b24f9..ef17d5ee17 100644
--- a/lib/compiler/src/cerl_trees.erl
+++ b/lib/compiler/src/cerl_trees.erl
@@ -14,8 +14,7 @@
 %% @author Richard Carlsson <carlsson.richard@gmail.com>
 %% @doc Basic functions on Core Erlang abstract syntax trees.
 %%
-%% <p>Syntax trees are defined in the module <a
-%% href="cerl"><code>cerl</code></a>.</p>
+%% <p>Syntax trees are defined in the module {@link cerl}.</p>
 %%
 %% @type cerl() = cerl:cerl()
 
@@ -63,6 +62,7 @@
 	       update_c_map_pair/4
 	   ]).
 
+-type cerl() :: cerl:cerl().
 
 %% ---------------------------------------------------------------------
 
@@ -72,7 +72,7 @@
 %% node has depth zero, the tree representing "<code>{foo,
 %% bar}</code>" has depth one, etc.
 
--spec depth(cerl:cerl()) -> non_neg_integer().
+-spec depth(cerl()) -> non_neg_integer().
 
 depth(T) ->
     case subtrees(T) of
@@ -91,7 +91,7 @@ depth_1(Ts) ->
 %%
 %% @doc Returns the number of nodes in <code>Tree</code>.
 
--spec size(cerl:cerl()) -> non_neg_integer().
+-spec size(cerl()) -> non_neg_integer().
 
 size(T) ->
     fold(fun (_, S) -> S + 1 end, 0, T).
@@ -109,7 +109,7 @@ size(T) ->
 %%
 %% @see mapfold/3
 
--spec map(fun((cerl:cerl()) -> cerl:cerl()), cerl:cerl()) -> cerl:cerl().
+-spec map(fun((cerl()) -> cerl()), cerl()) -> cerl().
 
 map(F, T) ->
     F(map_1(F, T)).
@@ -225,7 +225,7 @@ map_pairs(_, []) ->
 %%
 %% @see mapfold/3
 
--spec fold(fun((cerl:cerl(), term()) -> term()), term(), cerl:cerl()) -> term().
+-spec fold(fun((cerl(), term()) -> term()), term(), cerl()) -> term().
 
 fold(F, S, T) ->
     F(T, fold_1(F, S, T)).
@@ -348,8 +348,8 @@ fold_pairs(_, S, []) ->
 %% @see fold/3
 %% @see mapfold/4
 
--spec mapfold(fun((cerl:cerl(), term()) -> {cerl:cerl(), term()}),
-	      term(), cerl:cerl()) -> {cerl:cerl(), term()}.
+-spec mapfold(fun((cerl(), term()) -> {cerl(), term()}),
+	      term(), cerl()) -> {cerl(), term()}.
 
 mapfold(F, S0, T) ->
   mapfold(fun(T0, A) -> {T0, A} end, F, S0, T).
@@ -373,9 +373,9 @@ mapfold(F, S0, T) ->
 %% If <code>skip</code> is returned, it returns the tree and accumulator
 %% as is.
 
--spec mapfold(fun((cerl:cerl(), term()) -> {cerl:cerl(), term()} | skip),
-              fun((cerl:cerl(), term()) -> {cerl:cerl(), term()}),
-	      term(), cerl:cerl()) -> {cerl:cerl(), term()}.
+-spec mapfold(fun((cerl(), term()) -> {cerl(), term()} | skip),
+              fun((cerl(), term()) -> {cerl(), term()}),
+	      term(), cerl()) -> {cerl(), term()}.
 
 mapfold(Pre, Post, S00, T0) ->
     case Pre(T0, S00) of
@@ -525,7 +525,7 @@ mapfold_pairs(_, _, S, []) ->
 %% @see free_variables/1
 %% @see next_free_variable_name/1
 
--spec variables(cerl:cerl()) -> [cerl:var_name()].
+-spec variables(cerl()) -> [cerl:var_name()].
 
 variables(T) ->
     variables(T, false).
@@ -539,7 +539,7 @@ variables(T) ->
 %% @see next_free_variable_name/1
 %% @see variables/1
 
--spec free_variables(cerl:cerl()) -> [cerl:var_name()].
+-spec free_variables(cerl()) -> [cerl:var_name()].
 
 free_variables(T) ->
     variables(T, true).
@@ -712,7 +712,7 @@ var_list_names([], A) ->
 %% @see variables/1
 %% @see free_variables/1
 
--spec next_free_variable_name(cerl:cerl()) -> integer().
+-spec next_free_variable_name(cerl()) -> integer().
 
 next_free_variable_name(T) ->
     1 + next_free(T, -1).
@@ -811,7 +811,7 @@ next_free_in_defs([], Max) ->
 %%
 %% @equiv label(Tree, 0)
 
--spec label(cerl:cerl()) -> {cerl:cerl(), integer()}.
+-spec label(cerl()) -> {cerl(), integer()}.
 
 label(T) ->
     label(T, 0).
@@ -840,7 +840,7 @@ label(T) ->
 %% @see label/1
 %% @see size/1
 
--spec label(cerl:cerl(), integer()) -> {cerl:cerl(), integer()}.
+-spec label(cerl(), integer()) -> {cerl(), integer()}.
 
 label(T, N) ->
     label(T, N, #{}).
@@ -1024,7 +1024,7 @@ filter_labels([A | As]) ->
 filter_labels([]) ->
     [].
 
--spec get_label(cerl:cerl()) -> 'top' | integer().
+-spec get_label(cerl()) -> 'top' | integer().
 
 get_label(T) ->
     case get_ann(T) of
-- 
2.35.3

openSUSE Build Service is sponsored by