File 0588-parsetools-Fix-specs-for-all-documented-functions.patch of Package erlang
From b4ca300cad2724f8ba0b16ff0e605138237acd86 Mon Sep 17 00:00:00 2001
From: Lukas Larsson <lukas@erlang.org>
Date: Thu, 4 Jan 2024 15:20:40 +0100
Subject: [PATCH 4/6] parsetools: Fix specs for all documented functions
---
lib/compiler/src/compile.erl | 1 +
lib/parsetools/doc/src/yecc.xml | 1 +
lib/syntax_tools/src/erl_syntax.erl | 10 ++++++++++
lib/syntax_tools/src/merl.erl | 12 ++++++++++++
lib/syntax_tools/src/merl_transform.erl | 4 +++-
5 files changed, 27 insertions(+), 1 deletion(-)
diff --git a/lib/compiler/src/compile.erl b/lib/compiler/src/compile.erl
index 43d55bb5d9..a419341bf7 100644
--- a/lib/compiler/src/compile.erl
+++ b/lib/compiler/src/compile.erl
@@ -36,6 +36,7 @@
-export_type([option/0]).
-export_type([forms/0]).
+-export_type([comp_ret/0]).
-include("erl_compile.hrl").
-include("core_parse.hrl").
diff --git a/lib/parsetools/doc/src/yecc.xml b/lib/parsetools/doc/src/yecc.xml
index 4d639d1f21..9d54824f31 100644
--- a/lib/parsetools/doc/src/yecc.xml
+++ b/lib/parsetools/doc/src/yecc.xml
@@ -60,6 +60,7 @@
<name name="file" arity="1" since=""/>
<name name="file" arity="2" since=""/>
<fsummary>Give information about resolved and unresolved parse action conflicts.</fsummary>
+ <type name="option"/>
<type name="yecc_ret"/>
<type name="ok_ret"/>
<type name="error_ret"/>
diff --git a/lib/syntax_tools/src/erl_syntax.erl b/lib/syntax_tools/src/erl_syntax.erl
index 4797aa229e..ebba716460 100644
--- a/lib/syntax_tools/src/erl_syntax.erl
+++ b/lib/syntax_tools/src/erl_syntax.erl
@@ -2105,6 +2105,8 @@ atom_literal(Node) ->
%% @see atom_literal/1
%% @see string/1
+-spec atom_literal(syntaxTree(), utf8 | unicode | latin1) -> string().
+
atom_literal(Node, utf8) ->
io_lib:write_atom(atom_value(Node));
atom_literal(Node, unicode) ->
@@ -5251,6 +5253,8 @@ constrained_function_type_argument(Node) ->
%% =====================================================================
%% @equiv function_type(any_arity, Type)
+-spec function_type(syntaxTree()) -> syntaxTree().
+
function_type(Type) ->
function_type(any_arity, Type).
@@ -5535,6 +5539,8 @@ map_type_exact_value(Node) ->
%% =====================================================================
%% @equiv map_type(any_size)
+-spec map_type() -> syntaxTree().
+
map_type() ->
map_type(any_size).
@@ -5798,6 +5804,8 @@ record_type_field_type(Node) ->
%% =====================================================================
%% @equiv tuple_type(any_size)
+-spec tuple_type() -> syntaxTree().
+
tuple_type() ->
tuple_type(any_size).
@@ -6609,6 +6617,8 @@ case_expr_clauses(Node) ->
%% @see else_expr_clauses/1
%% @see clause/3
+-spec else_expr([syntaxTree()]) -> syntaxTree().
+
else_expr(Clauses) ->
tree(else_expr, Clauses).
diff --git a/lib/syntax_tools/src/merl.erl b/lib/syntax_tools/src/merl.erl
index 28cd1283e9..a634736bad 100644
--- a/lib/syntax_tools/src/merl.erl
+++ b/lib/syntax_tools/src/merl.erl
@@ -317,6 +317,9 @@
%% Compiling and loading code directly to memory
%% @equiv compile(Code, [])
+
+-spec compile(tree_or_trees()) -> compile:comp_ret().
+
compile(Code) ->
compile(Code, []).
@@ -324,6 +327,9 @@ compile(Code) ->
%% into a binary BEAM object.
%% @see compile_and_load/2
%% @see compile/1
+
+-spec compile(tree_or_trees(), [compile:option()]) -> compile:comp_ret().
+
compile(Code, Options) when not is_list(Code)->
case type(Code) of
form_list -> compile(erl_syntax:form_list_elements(Code));
@@ -336,6 +342,8 @@ compile(Code, Options0) when is_list(Options0) ->
%% @equiv compile_and_load(Code, [])
+-spec compile_and_load(tree_or_trees()) ->
+ {ok, binary()} | error | {error, Errors :: list(), Warnings :: list()}.
compile_and_load(Code) ->
compile_and_load(Code, []).
@@ -343,6 +351,8 @@ compile_and_load(Code) ->
%% and load the resulting module into memory.
%% @see compile/2
%% @see compile_and_load/1
+-spec compile_and_load(tree_or_trees(), [compile:option()]) ->
+ {ok, binary()} | error | {error, Errors :: list(), Warnings :: list()}.
compile_and_load(Code, Options) ->
case compile(Code, Options) of
{ok, ModuleName, Binary} ->
@@ -375,6 +385,7 @@ term(Term) ->
%% @doc Pretty-print a syntax tree or template to the standard output. This
%% is a utility function for development and debugging.
+-spec print(tree_or_trees()) -> ok.
print(Ts) when is_list(Ts) ->
lists:foreach(fun print/1, Ts);
print(T) ->
@@ -384,6 +395,7 @@ print(T) ->
%% @doc Print the structure of a syntax tree or template to the standard
%% output. This is a utility function for development and debugging.
+-spec show(tree_or_trees()) -> ok.
show(Ts) when is_list(Ts) ->
lists:foreach(fun show/1, Ts);
show(T) ->
diff --git a/lib/syntax_tools/src/merl_transform.erl b/lib/syntax_tools/src/merl_transform.erl
index 571d7e4d86..389106ab64 100644
--- a/lib/syntax_tools/src/merl_transform.erl
+++ b/lib/syntax_tools/src/merl_transform.erl
@@ -41,7 +41,9 @@
%% TODO: unroll calls to switch? it will probably get messy
%% TODO: use Igor to make resulting code independent of merl at runtime?
-
+-spec parse_transform(InForms, Options :: term()) -> OutForms when
+ InForms :: [erl_parse:abstract_form() | erl_parse:form_info()],
+ OutForms :: [erl_parse:abstract_form() | erl_parse:form_info()].
parse_transform(Forms, _Options) ->
erl_syntax:revert_forms(expand(erl_syntax:form_list(Forms))).
--
2.35.3