File 0138-syntax_tools-Complete-the-transition-away-from-edoc-.patch of Package erlang

From bb098b3153e3bf750695cff16e71a43621ee3a72 Mon Sep 17 00:00:00 2001
From: Richard Carlsson <carlsson.richard@gmail.com>
Date: Sat, 6 Dec 2025 22:49:55 +0100
Subject: [PATCH] syntax_tools: Complete the transition away from edoc markup

---
 lib/syntax_tools/doc/overview.edoc            | 30 -------------
 lib/syntax_tools/examples/merl/basic.erl      | 24 ++++++----
 lib/syntax_tools/examples/merl/basic_test.erl | 24 ++++++----
 lib/syntax_tools/examples/merl/basicc.erl     | 24 ++++++----
 lib/syntax_tools/examples/merl/lisp.erl       | 24 ++++++----
 lib/syntax_tools/examples/merl/lisp_test.erl  | 24 ++++++----
 lib/syntax_tools/examples/merl/lispc.erl      | 24 ++++++----
 lib/syntax_tools/examples/merl/merl_build.erl | 44 +++++++++++--------
 lib/syntax_tools/src/epp_dodger.erl           |  6 +--
 lib/syntax_tools/src/erl_comment_scan.erl     |  5 ---
 lib/syntax_tools/src/erl_prettypr.erl         |  4 --
 lib/syntax_tools/src/erl_recomment.erl        |  4 --
 lib/syntax_tools/src/erl_syntax.erl           | 21 +++------
 lib/syntax_tools/src/erl_syntax_lib.erl       |  4 --
 lib/syntax_tools/src/merl.erl                 |  5 ---
 lib/syntax_tools/src/merl_tests.erl           |  5 +--
 lib/syntax_tools/src/merl_transform.erl       |  2 -
 lib/syntax_tools/src/prettypr.erl             |  6 +--
 18 files changed, 124 insertions(+), 156 deletions(-)
 delete mode 100644 lib/syntax_tools/doc/overview.edoc

diff --git a/lib/syntax_tools/doc/overview.edoc b/lib/syntax_tools/doc/overview.edoc
deleted file mode 100644
index a25521c046..0000000000
--- a/lib/syntax_tools/doc/overview.edoc
+++ /dev/null
@@ -1,30 +0,0 @@
-			-*- html -*-
-
-	Syntax Tools overview page
-
-@author Richard Carlsson <carlsson.richard@gmail.com>
-@copyright 1997-2014 Richard Carlsson
-@version {@version}
-@title Erlang Syntax and Metaprogramming tools
-
-@doc This package contains modules for handling abstract syntax trees (ASTs)
-in Erlang, in a way that is compatible with the "abstract format" parse
-trees of the stdlib module `erl_parse', together with utilities for reading
-source files, {@link erl_prettypr. pretty-printing syntax trees}, and doing
-{@link merl. metaprogramming} in Erlang.
-
-The abstract layer (defined in {@link erl_syntax}) is nicely
-structured and the node types are context-independent. The layer makes
-it possible to transparently attach source-code comments and user
-annotations to nodes of the tree. Using the abstract layer makes
-applications less sensitive to changes in the {@link //stdlib/erl_parse}
-data structures, only requiring the `erl_syntax' module to be up-to-date.
-
-The pretty printer {@link erl_prettypr} is implemented on top of the
-library module {@link prettypr}: this is a powerful and flexible generic
-pretty printing library, which is also distributed separately.
-
-For a short demonstration of parsing and pretty-printing, simply
-compile the included module <a href="demo.erl">`demo.erl'</a>,
-and execute `demo:run()' from the Erlang shell. It will compile the
-remaining modules and give you further instructions.
diff --git a/lib/syntax_tools/examples/merl/basic.erl b/lib/syntax_tools/examples/merl/basic.erl
index 9030059d11..81d851d48d 100644
--- a/lib/syntax_tools/examples/merl/basic.erl
+++ b/lib/syntax_tools/examples/merl/basic.erl
@@ -1,19 +1,25 @@
-%% ---------------------------------------------------------------------
-%% Licensed under the Apache License, Version 2.0 (the "License"); you may
-%% not use this file except in compliance with the License. You may obtain
-%% a copy of the License at <http://www.apache.org/licenses/LICENSE-2.0>
-%%
+%% %CopyrightBegin%
+%% 
+%% SPDX-License-Identifier: Apache-2.0
+%% 
+%% Copyright 2012 Richard Carlsson. All Rights Reserved.
+%% 
+%% Licensed under the Apache License, Version 2.0 (the "License");
+%% you may not use this file except in compliance with the License.
+%% You may obtain a copy of the License at
+%% 
+%%     http://www.apache.org/licenses/LICENSE-2.0
+%% 
 %% Unless required by applicable law or agreed to in writing, software
 %% distributed under the License is distributed on an "AS IS" BASIS,
 %% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
 %% See the License for the specific language governing permissions and
 %% limitations under the License.
-%%
-%% @author Richard Carlsson <carlsson.richard@gmail.com>
-%% @copyright 2012 Richard Carlsson
-%% @doc Trivial Basic interpreter in Erlang
+%% 
+%% %CopyrightEnd%
 
 -module(basic).
+-moduledoc "Trivial Basic interpreter in Erlang.".
 
 -export([run/2]).
 
diff --git a/lib/syntax_tools/examples/merl/basic_test.erl b/lib/syntax_tools/examples/merl/basic_test.erl
index ff35de6325..5d3c2559b8 100644
--- a/lib/syntax_tools/examples/merl/basic_test.erl
+++ b/lib/syntax_tools/examples/merl/basic_test.erl
@@ -1,18 +1,24 @@
-%% ---------------------------------------------------------------------
-%% Licensed under the Apache License, Version 2.0 (the "License"); you may
-%% not use this file except in compliance with the License. You may obtain
-%% a copy of the License at <http://www.apache.org/licenses/LICENSE-2.0>
-%%
+%% %CopyrightBegin%
+%% 
+%% SPDX-License-Identifier: Apache-2.0
+%% 
+%% Copyright 2012 Richard Carlsson. All Rights Reserved.
+%% 
+%% Licensed under the Apache License, Version 2.0 (the "License");
+%% you may not use this file except in compliance with the License.
+%% You may obtain a copy of the License at
+%% 
+%%     http://www.apache.org/licenses/LICENSE-2.0
+%% 
 %% Unless required by applicable law or agreed to in writing, software
 %% distributed under the License is distributed on an "AS IS" BASIS,
 %% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
 %% See the License for the specific language governing permissions and
 %% limitations under the License.
-%%
-%% @author Richard Carlsson <carlsson.richard@gmail.com>
-%% @copyright 2012 Richard Carlsson
-%% @doc Tests. For including in another module.
+%% 
+%% %CopyrightEnd%
 
+%% Tests - for including in another module.
 %-module(basic_test).
 %-import(basic, run/1)
 
diff --git a/lib/syntax_tools/examples/merl/basicc.erl b/lib/syntax_tools/examples/merl/basicc.erl
index 531ac51538..eacae01202 100644
--- a/lib/syntax_tools/examples/merl/basicc.erl
+++ b/lib/syntax_tools/examples/merl/basicc.erl
@@ -1,19 +1,25 @@
-%% ---------------------------------------------------------------------
-%% Licensed under the Apache License, Version 2.0 (the "License"); you may
-%% not use this file except in compliance with the License. You may obtain
-%% a copy of the License at <http://www.apache.org/licenses/LICENSE-2.0>
-%%
+%% %CopyrightBegin%
+%% 
+%% SPDX-License-Identifier: Apache-2.0
+%% 
+%% Copyright 2012 Richard Carlsson. All Rights Reserved.
+%% 
+%% Licensed under the Apache License, Version 2.0 (the "License");
+%% you may not use this file except in compliance with the License.
+%% You may obtain a copy of the License at
+%% 
+%%     http://www.apache.org/licenses/LICENSE-2.0
+%% 
 %% Unless required by applicable law or agreed to in writing, software
 %% distributed under the License is distributed on an "AS IS" BASIS,
 %% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
 %% See the License for the specific language governing permissions and
 %% limitations under the License.
-%%
-%% @author Richard Carlsson <carlsson.richard@gmail.com>
-%% @copyright 2012 Richard Carlsson
-%% @doc Basic compiler in Erlang.
+%% 
+%% %CopyrightEnd%
 
 -module(basicc).
+-moduledoc "Basic compiler in Erlang.".
 
 -export([run/2, make_lines/1, bool/1]).
 
diff --git a/lib/syntax_tools/examples/merl/lisp.erl b/lib/syntax_tools/examples/merl/lisp.erl
index 371dc6b261..f0037a6556 100644
--- a/lib/syntax_tools/examples/merl/lisp.erl
+++ b/lib/syntax_tools/examples/merl/lisp.erl
@@ -1,19 +1,25 @@
-%% ---------------------------------------------------------------------
-%% Licensed under the Apache License, Version 2.0 (the "License"); you may
-%% not use this file except in compliance with the License. You may obtain
-%% a copy of the License at <http://www.apache.org/licenses/LICENSE-2.0>
-%%
+%% %CopyrightBegin%
+%% 
+%% SPDX-License-Identifier: Apache-2.0
+%% 
+%% Copyright 2012 Richard Carlsson. All Rights Reserved.
+%% 
+%% Licensed under the Apache License, Version 2.0 (the "License");
+%% you may not use this file except in compliance with the License.
+%% You may obtain a copy of the License at
+%% 
+%%     http://www.apache.org/licenses/LICENSE-2.0
+%% 
 %% Unless required by applicable law or agreed to in writing, software
 %% distributed under the License is distributed on an "AS IS" BASIS,
 %% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
 %% See the License for the specific language governing permissions and
 %% limitations under the License.
-%%
-%% @author Richard Carlsson <carlsson.richard@gmail.com>
-%% @copyright 2012 Richard Carlsson
-%% @doc Trivial Lisp interpreter in Erlang.
+%% 
+%% %CopyrightEnd%
 
 -module(lisp).
+-moduledoc "Trivial Lisp interpreter in Erlang.".
 
 -export([eval/1]).
 
diff --git a/lib/syntax_tools/examples/merl/lisp_test.erl b/lib/syntax_tools/examples/merl/lisp_test.erl
index cab8134b8f..0fa23c5c02 100644
--- a/lib/syntax_tools/examples/merl/lisp_test.erl
+++ b/lib/syntax_tools/examples/merl/lisp_test.erl
@@ -1,18 +1,24 @@
-%% ---------------------------------------------------------------------
-%% Licensed under the Apache License, Version 2.0 (the "License"); you may
-%% not use this file except in compliance with the License. You may obtain
-%% a copy of the License at <http://www.apache.org/licenses/LICENSE-2.0>
-%%
+%% %CopyrightBegin%
+%% 
+%% SPDX-License-Identifier: Apache-2.0
+%% 
+%% Copyright 2012 Richard Carlsson. All Rights Reserved.
+%% 
+%% Licensed under the Apache License, Version 2.0 (the "License");
+%% you may not use this file except in compliance with the License.
+%% You may obtain a copy of the License at
+%% 
+%%     http://www.apache.org/licenses/LICENSE-2.0
+%% 
 %% Unless required by applicable law or agreed to in writing, software
 %% distributed under the License is distributed on an "AS IS" BASIS,
 %% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
 %% See the License for the specific language governing permissions and
 %% limitations under the License.
-%%
-%% @author Richard Carlsson <carlsson.richard@gmail.com>
-%% @copyright 2012 Richard Carlsson
-%% @doc Tests. For including in another module.
+%% 
+%% %CopyrightEnd%
 
+%% Tests - for including in another module.
 %-module(lisp_test).
 %-import(lisp, eval/1)
 
diff --git a/lib/syntax_tools/examples/merl/lispc.erl b/lib/syntax_tools/examples/merl/lispc.erl
index 97072cdab7..04d1f82904 100644
--- a/lib/syntax_tools/examples/merl/lispc.erl
+++ b/lib/syntax_tools/examples/merl/lispc.erl
@@ -1,19 +1,25 @@
-%% ---------------------------------------------------------------------
-%% Licensed under the Apache License, Version 2.0 (the "License"); you may
-%% not use this file except in compliance with the License. You may obtain
-%% a copy of the License at <http://www.apache.org/licenses/LICENSE-2.0>
-%%
+%% %CopyrightBegin%
+%% 
+%% SPDX-License-Identifier: Apache-2.0
+%% 
+%% Copyright 2012 Richard Carlsson. All Rights Reserved.
+%% 
+%% Licensed under the Apache License, Version 2.0 (the "License");
+%% you may not use this file except in compliance with the License.
+%% You may obtain a copy of the License at
+%% 
+%%     http://www.apache.org/licenses/LICENSE-2.0
+%% 
 %% Unless required by applicable law or agreed to in writing, software
 %% distributed under the License is distributed on an "AS IS" BASIS,
 %% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
 %% See the License for the specific language governing permissions and
 %% limitations under the License.
-%%
-%% @author Richard Carlsson <carlsson.richard@gmail.com>
-%% @copyright 2012 Richard Carlsson
-%% @doc Lisp compiler in Erlang.
+%% 
+%% %CopyrightEnd%
 
 -module(lispc).
+-moduledoc "Lisp compiler in Erlang.".
 
 -export([eval/1]).
 
diff --git a/lib/syntax_tools/examples/merl/merl_build.erl b/lib/syntax_tools/examples/merl/merl_build.erl
index c539f8e2af..97e8b77fbb 100644
--- a/lib/syntax_tools/examples/merl/merl_build.erl
+++ b/lib/syntax_tools/examples/merl/merl_build.erl
@@ -1,19 +1,25 @@
-%% ---------------------------------------------------------------------
-%% Licensed under the Apache License, Version 2.0 (the "License"); you may
-%% not use this file except in compliance with the License. You may obtain
-%% a copy of the License at <http://www.apache.org/licenses/LICENSE-2.0>
-%%
+%% %CopyrightBegin%
+%% 
+%% SPDX-License-Identifier: Apache-2.0
+%% 
+%% Copyright 2012 Richard Carlsson. All Rights Reserved.
+%% 
+%% Licensed under the Apache License, Version 2.0 (the "License");
+%% you may not use this file except in compliance with the License.
+%% You may obtain a copy of the License at
+%% 
+%%     http://www.apache.org/licenses/LICENSE-2.0
+%% 
 %% Unless required by applicable law or agreed to in writing, software
 %% distributed under the License is distributed on an "AS IS" BASIS,
 %% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
 %% See the License for the specific language governing permissions and
 %% limitations under the License.
-%%
-%% @author Richard Carlsson <carlsson.richard@gmail.com>
-%% @copyright 2012 Richard Carlsson
-%% @doc Making it simple to build a module with merl
+%% 
+%% %CopyrightEnd%
 
 -module(merl_build).
+-moduledoc "Making it simple to build a module with merl."
 
 -export([init_module/1, module_forms/1, add_function/4, add_record/3,
          add_import/3, add_attribute/3, set_file/2]).
@@ -36,13 +42,13 @@
 
 %% TODO: init module from a list of forms (from various sources)
 
-%% @doc Create a new module representation, using the given module name.
+-doc "Create a new module representation, using the given module name.".
 init_module(Name) when is_atom(Name) ->
     %% use the module name as the default file name - better than nothing
     #module{name=Name, file=atom_to_list(Name)}.
 
-%% @doc Get the list of syntax tree forms for a module representation. This can
-%% be passed to compile/2.
+-doc "Get the list of syntax tree forms for a module representation. This can
+be passed to `compile/2`.".
 module_forms(#module{name=Name,
                      exports=Xs,
                      imports=Is,
@@ -71,12 +77,12 @@ module_forms(#module{name=Name,
                     F <- [erl_syntax:function(term(N), Cs)]],
     lists:flatten([Module, Export, Imports, Attrs, Records, Functions]).
 
-%% @doc Set the source file name for all subsequently added functions,
-%% records, and attributes.
+-doc "Set the source file name for all subsequently added functions,
+records, and attributes.".
 set_file(Filename, #module{}=M) ->
     M#module{file=filename:flatten(Filename)}.
 
-%% @doc Add a function to a module representation.
+-doc "Add a function to a module representation.".
 add_function(Exported, Name, Clauses,
              #module{file=File, exports=Xs, functions=Fs}=M)
   when is_boolean(Exported), is_atom(Name), Clauses =/= [] ->
@@ -87,18 +93,18 @@ add_function(Exported, Name, Clauses,
           end,
     M#module{exports=Xs1, functions=[{File, Name, Clauses} | Fs]}.
 
-%% @doc Add a record declaration to a module representation.
+-doc "Add a record declaration to a module representation.".
 add_record(Name, Fields, #module{file=File, records=Rs}=M)
   when is_atom(Name) ->
     M#module{records=[{File, Name, Fields} | Rs]}.
 
-%% @doc Add a "wild" attribute, such as `-compile(Opts)' to a module
-%% representation. Note that such attributes can only have a single argument.
+-doc "Add a 'wild' attribute, such as `-compile(Opts)` to a module
+representation. Note that such attributes can only have a single argument.".
 add_attribute(Name, Term, #module{file=File, attributes=As}=M)
   when is_atom(Name) ->
     M#module{attributes=[{File, Name, Term} | As]}.
 
-%% @doc Add an import declaration to a module representation.
+-doc "Add an import declaration to a module representation."
 add_import(From, Names, #module{imports=Is}=M)
   when is_atom(From), is_list(Names) ->
     M#module{imports=[{From, Names} | Is]}.
diff --git a/lib/syntax_tools/src/epp_dodger.erl b/lib/syntax_tools/src/epp_dodger.erl
index 18e08942ae..a660928575 100644
--- a/lib/syntax_tools/src/epp_dodger.erl
+++ b/lib/syntax_tools/src/epp_dodger.erl
@@ -29,10 +29,6 @@
 %% either the Apache License or the LGPL.
 %%
 %% %CopyrightEnd%
-%%
-%% @author Richard Carlsson <carlsson.richard@gmail.com>
-%% @end
-%% =====================================================================
 
 %% NOTES:
 %%
@@ -485,7 +481,7 @@ quick_macro_string(A) ->
     "(?" ++ atom_to_list(A) ++ ")".
 
 %% Skipping to the end of a macro call, tracking open/close constructs.
-%% @spec (Tokens) -> {Skipped, Rest}
+-spec skip_macro_args([term()]) -> {Skipped::[term()], Rest::[term()]}.
 
 skip_macro_args([{'(',_}=T | Ts]) ->
     skip_macro_args(Ts, [')'], [T]);
diff --git a/lib/syntax_tools/src/erl_comment_scan.erl b/lib/syntax_tools/src/erl_comment_scan.erl
index c0682ffb2e..9a613b28c5 100644
--- a/lib/syntax_tools/src/erl_comment_scan.erl
+++ b/lib/syntax_tools/src/erl_comment_scan.erl
@@ -29,11 +29,6 @@
 %% either the Apache License or the LGPL.
 %%
 %% %CopyrightEnd%
-%%
-%% =====================================================================
-%% @author Richard Carlsson <carlsson.richard@gmail.com>
-%% @end
-%% =====================================================================
 
 -module(erl_comment_scan).
 -moduledoc "Functions for reading comment lines from Erlang source code.".
diff --git a/lib/syntax_tools/src/erl_prettypr.erl b/lib/syntax_tools/src/erl_prettypr.erl
index c946339862..0ff00ef5cb 100644
--- a/lib/syntax_tools/src/erl_prettypr.erl
+++ b/lib/syntax_tools/src/erl_prettypr.erl
@@ -29,10 +29,6 @@
 %% either the Apache License or the LGPL.
 %%
 %% %CopyrightEnd%
-%%
-%% @author Richard Carlsson <carlsson.richard@gmail.com>
-%% @end
-%% =====================================================================
 
 -module(erl_prettypr).
 -moduledoc """
diff --git a/lib/syntax_tools/src/erl_recomment.erl b/lib/syntax_tools/src/erl_recomment.erl
index bde7647827..288f516b82 100644
--- a/lib/syntax_tools/src/erl_recomment.erl
+++ b/lib/syntax_tools/src/erl_recomment.erl
@@ -29,10 +29,6 @@
 %% either the Apache License or the LGPL.
 %%
 %% %CopyrightEnd%
-%%
-%% @author Richard Carlsson <carlsson.richard@gmail.com>
-%% @end
-%% =====================================================================
 
 -module(erl_recomment).
 -moduledoc """
diff --git a/lib/syntax_tools/src/erl_syntax.erl b/lib/syntax_tools/src/erl_syntax.erl
index 5811c7b09b..b17aeb2a08 100644
--- a/lib/syntax_tools/src/erl_syntax.erl
+++ b/lib/syntax_tools/src/erl_syntax.erl
@@ -29,10 +29,6 @@
 %% either the Apache License or the LGPL.
 %%
 %% %CopyrightEnd%
-%%
-%% @author Richard Carlsson <carlsson.richard@gmail.com>
-%% @end
-%% =====================================================================
 
 -module(erl_syntax).
 -moduledoc """
@@ -389,17 +385,16 @@ trees.
 %% first element is an atom which uniquely identifies the type of the
 %% node. (In the backwards-compatible representation, the
 %% interpretation is also often dependent on the context; the second
-%% element generally holds the annotation (see module {@link
-%% //stdlib/erl_anno} for details) which includes the position
+%% element generally holds the annotation (see module `erl_anno` for
+%% details) which includes the position
 %% information - with a couple of exceptions; see `get_pos' and
 %% `set_pos' for details.) In the documentation of this module, `Pos'
 %% is the annotation associated with a node. No assumptions are made
 %% in this module regarding the format or interpretation of the
 %% annotations. Use module erl_anno to inspect and modify annotations.
-%% In particular, use {@link //stdlib/erl_anno:location/1} to get the
-%% position information, and use {@link
-%% //stdlib/erl_anno:set_location/2} or {@link
-%% //stdlib/erl_anno:set_line/2} to change the position information.
+%% In particular, use `erl_anno:location/1` to get the
+%% position information, and use `erl_anno:set_location/2` or
+%% `erl_anno:set_line/2` to change the position information.
 %% When a syntax tree node is constructed, its associated position is
 %% by default set to the integer zero.
 %% =====================================================================
@@ -485,7 +480,7 @@ trees.
                    | erl_parse:af_remote_function().
 
 %% The representation built by the Erlang standard library parser
-%% `erl_parse'. This is a subset of the {@link syntaxTree()} type.
+%% `erl_parse'. This is a subset of the `syntaxTree()` type.
 
 %% =====================================================================
 %%
@@ -2253,8 +2248,6 @@ tuple_size(Node) ->
 
 
 %% =====================================================================
-%% @equiv list(List, none)
-
 -doc #{equiv => list(List, none)}.
 -spec list([syntaxTree()]) -> syntaxTree().
 
@@ -3070,8 +3063,6 @@ revert_eof_marker(Node) ->
 
 
 %% =====================================================================
-%% @equiv attribute(Name, none)
-
 -doc #{equiv => attribute(Name, none)}.
 -spec attribute(syntaxTree()) -> syntaxTree().
 
diff --git a/lib/syntax_tools/src/erl_syntax_lib.erl b/lib/syntax_tools/src/erl_syntax_lib.erl
index 66559173a5..8ab68f60ff 100644
--- a/lib/syntax_tools/src/erl_syntax_lib.erl
+++ b/lib/syntax_tools/src/erl_syntax_lib.erl
@@ -29,10 +29,6 @@
 %% either the Apache License or the LGPL.
 %%
 %% %CopyrightEnd%
-%%
-%% @author Richard Carlsson <carlsson.richard@gmail.com>
-%% @end
-%% =====================================================================
 
 -module(erl_syntax_lib).
 -moduledoc """
diff --git a/lib/syntax_tools/src/merl.erl b/lib/syntax_tools/src/merl.erl
index b6b10fd3f5..03620c634a 100644
--- a/lib/syntax_tools/src/merl.erl
+++ b/lib/syntax_tools/src/merl.erl
@@ -29,9 +29,6 @@
 %% either the Apache License or the LGPL.
 %%
 %% %CopyrightEnd%
-%%
-%% @author Richard Carlsson <carlsson.richard@gmail.com>
-%%
 
 -module(merl).
 -moduledoc """
@@ -405,8 +402,6 @@ Thus, the following pattern matches all possible clauses:
 %% ------------------------------------------------------------------------
 %% Compiling and loading code directly to memory
 
-%% @equiv compile(Code, [])
-
 -doc #{equiv => compile(Code, [])}.
 -spec compile(tree_or_trees()) -> compile:comp_ret().
 
diff --git a/lib/syntax_tools/src/merl_tests.erl b/lib/syntax_tools/src/merl_tests.erl
index 552c165622..de9b76b441 100644
--- a/lib/syntax_tools/src/merl_tests.erl
+++ b/lib/syntax_tools/src/merl_tests.erl
@@ -29,12 +29,9 @@
 %% either the Apache License or the LGPL.
 %%
 %% %CopyrightEnd%
-%%
-%% @author Richard Carlsson <carlsson.richard@gmail.com>
-%% @doc Unit tests for merl.
-%% @private
 
 -module(merl_tests).
+-moduledoc false.
 
 %-define(MERL_NO_TRANSFORM, true).
 -include("merl.hrl").
diff --git a/lib/syntax_tools/src/merl_transform.erl b/lib/syntax_tools/src/merl_transform.erl
index 28ab224f39..bd1e33e698 100644
--- a/lib/syntax_tools/src/merl_transform.erl
+++ b/lib/syntax_tools/src/merl_transform.erl
@@ -29,8 +29,6 @@
 %% either the Apache License or the LGPL.
 %%
 %% %CopyrightEnd%
-%%
-%% @author Richard Carlsson <carlsson.richard@gmail.com>
 
 -module(merl_transform).
 -moduledoc """
diff --git a/lib/syntax_tools/src/prettypr.erl b/lib/syntax_tools/src/prettypr.erl
index aa6f004a5d..3a44150057 100644
--- a/lib/syntax_tools/src/prettypr.erl
+++ b/lib/syntax_tools/src/prettypr.erl
@@ -29,12 +29,8 @@
 %% either the Apache License or the LGPL.
 %%
 %% %CopyrightEnd%
-%%
-%% @author Richard Carlsson <carlsson.richard@gmail.com>
-%% @end
-%% =====================================================================
 
-%% @TODO can floats be moved in/out of sep:s without too much pain?
+%% TODO: can floats be moved in/out of sep:s without too much pain?
 
 -module(prettypr).
 -moduledoc """
-- 
2.51.0

openSUSE Build Service is sponsored by