File 0140-xmerl-Remove-remnants-of-edoc-markup.patch of Package erlang

From 6643ddcf04df400ca7e966935581f76dbca236cf Mon Sep 17 00:00:00 2001
From: Richard Carlsson <carlsson.richard@gmail.com>
Date: Sat, 6 Dec 2025 16:28:59 +0100
Subject: [PATCH] xmerl: Remove remnants of edoc markup

---
 lib/xmerl/src/xmerl.erl       |  2 --
 lib/xmerl/src/xmerl_lib.erl   | 24 +++++++++++-------------
 lib/xmerl/src/xmerl_scan.erl  |  5 -----
 lib/xmerl/src/xmerl_xpath.erl |  4 ----
 lib/xmerl/src/xmerl_xs.erl    | 25 -------------------------
 5 files changed, 11 insertions(+), 49 deletions(-)

diff --git a/lib/xmerl/src/xmerl.erl b/lib/xmerl/src/xmerl.erl
index aa9f1ddaaf..176d1d04b4 100644
--- a/lib/xmerl/src/xmerl.erl
+++ b/lib/xmerl/src/xmerl.erl
@@ -274,8 +274,6 @@ export_content([E | Es], Callbacks) ->
 export_content([], _Callbacks) ->
     [].
 
-%% @doc Exports a simple XML element directly, without further context.
-
 -doc "Export a simple XML element directly, without further context.".
 -spec export_simple_element(Element, Callback) -> _ when
 	Element  :: simple_element(),
diff --git a/lib/xmerl/src/xmerl_lib.erl b/lib/xmerl/src/xmerl_lib.erl
index 3cc59614ec..6904e49524 100644
--- a/lib/xmerl/src/xmerl_lib.erl
+++ b/lib/xmerl/src/xmerl_lib.erl
@@ -451,25 +451,23 @@ mapfoldxml(Fun, Accu, List) when is_list(List) ->
 mapfoldxml(Fun, Accu, E) ->
     Fun(E,Accu).
 
+-type charset_info() :: {auto,'iso-10646-utf-1',Content::list()} |
+                        {external,'iso-10646-utf-1',Content::list()} |
+                        {undefined,undefined,Content::list()} |
+                        {external,ExtCharset::atom(),Content::list()}.
 
-%%% @spec detect_charset(T::list()) -> charset_info()
-%%% @equiv detect_charset(undefined,T)
+-spec detect_charset(Content::list()) -> charset_info().
+-doc #{equiv => detect_charset(undefined,Content)}.
 detect_charset(Content) ->
     detect_charset(undefined,Content).
 
-%%% FIXME! Whatabout aliases etc? Shouldn't transforming with ucs be optional?
-%%% @spec detect_charset(ExtCharset::atom(),T::list()) -> charset_info()
-%%% @doc Automatically decides character set used in XML document.
-%%%  charset_info() is
-%%%  <table>
-%%%    <tr><td><code>{auto,'iso-10646-utf-1',Content} |</code></td></tr>
-%%%    <tr><td><code>{external,'iso-10646-utf-1',Content} |</code></td></tr>
-%%%    <tr><td><code>{undefined,undefined,Content} |</code></td></tr>
-%%%    <tr><td><code>{external,ExtCharset,Content}</code></td></tr>
-%%%  </table>
+%%% Automatically decides character set used in XML document.
 %%%   ExtCharset is any externally declared character set (e.g. in HTTP
 %%%   Content-Type header) and Content is an XML Document.
-%%% 
+%%% FIXME! Whatabout aliases etc? Shouldn't transforming with ucs be optional?
+
+-spec detect_charset(ExtCharset::atom(), Content::list()) -> charset_info().
+
 detect_charset(ExtCharset,Content) when is_list(ExtCharset) ->
     %% FIXME! Don't allow both atom and list for character set names
     detect_charset(list_to_atom(ExtCharset),Content);
diff --git a/lib/xmerl/src/xmerl_scan.erl b/lib/xmerl/src/xmerl_scan.erl
index 57e78fbe25..65df20a4fe 100644
--- a/lib/xmerl/src/xmerl_scan.erl
+++ b/lib/xmerl/src/xmerl_scan.erl
@@ -174,7 +174,6 @@ The record definition is found in `xmerl.hrl`.
 """.
 -type xmlDocument() :: xmerl:xmlDocument().
 
-%% @type document() = xmlElement() | xmlDocument(). <p>
 -doc """
 An XML document.
 
@@ -303,10 +302,6 @@ rules_state(X, S=#xmerl_scanner{fun_states = FS}) ->
     FS1 = FS#xmerl_fun_states{rules = X},
     S#xmerl_scanner{fun_states = FS1}.
 
-%%% @spec fetch_state(FetchState, S::global_state()) -> global_state()
-%%% @doc For controlling the FetchState, to be used in a fetch
-%%% function, and called when the parser fetch an external resource (eg. a DTD).
-%%% See <a href="xmerl_examples.html">tutorial</a> on customization functions.
 -doc """
 Set the FetchState, to be used in a fetch function.
 
diff --git a/lib/xmerl/src/xmerl_xpath.erl b/lib/xmerl/src/xmerl_xpath.erl
index a978f76ef4..aae59d597a 100644
--- a/lib/xmerl/src/xmerl_xpath.erl
+++ b/lib/xmerl/src/xmerl_xpath.erl
@@ -309,7 +309,6 @@ eval_pred(Predicate, S = #state{context = C =
 
 %% write_node(Node::xmlNode()) -> {Type,Pos,Name,Parents}
 %% Helper function to access essential information from the xmlNode record.
-%% @hidden
 -doc false.
 write_node(#xmlNode{pos = Pos,
 		    node = #xmlAttribute{name = Name,
@@ -340,7 +339,6 @@ write_node(_) ->
 
 %% eval_path(Type,Arg,S::state()) -> state()
 %% Eval path
-%% @hidden
 -doc false.
 eval_path(union, {PathExpr1, PathExpr2}, C = #xmlContext{}) ->
     S = #state{context = C},
@@ -376,7 +374,6 @@ eval_primary_expr(PrimExpr, S = #state{context = Context}) ->
 
 %% axis(Axis,NodeTest,Context::xmlContext()) -> xmlContext()
 %% axis(Axis,NodeTest,Context,[])
-%% @hidden
 -doc false.
 axis(Axis, NodeTest, Context) ->
     axis(Axis, NodeTest, Context, []).
@@ -386,7 +383,6 @@ axis(Axis, NodeTest, Context) ->
 %%
 %% An axis specifies the tree relationship between the nodes selected by
 %% the location step and the context node.
-%% @hidden
 -doc false.
 axis(Axis, NodeTest, Context = #xmlContext{nodeset = NS0}, Acc) ->
     NewNodeSet=lists:foldr(
diff --git a/lib/xmerl/src/xmerl_xs.erl b/lib/xmerl/src/xmerl_xs.erl
index 7a87a385d5..04e08f10c0 100644
--- a/lib/xmerl/src/xmerl_xs.erl
+++ b/lib/xmerl/src/xmerl_xs.erl
@@ -22,31 +22,6 @@
 
 %% Description  : Implements XSLT like transformations in Erlang
 
-%% @doc
-%       Erlang has similarities to XSLT since both languages
-% 	have a functional programming approach. Using <code>xmerl_xpath</code>
-% 	it is possible to write XSLT like transforms in Erlang.
-%
-%     <p>XSLT stylesheets are often used when transforming XML
-%       documents, to other XML documents or (X)HTML for presentation.
-%       XSLT contains quite many
-%       functions and learning them all may take some effort.
-%       This document assumes a basic level of
-%       understanding of XSLT.
-%     </p>
-%     <p>Since XSLT is based on a functional programming approach
-%       with pattern matching and recursion it is possible to write
-%       similar style sheets in Erlang. At least for basic
-%       transforms. This
-%       document describes how to use the XPath implementation together
-%       with Erlangs pattern matching and a couple of functions to write
-%       XSLT like transforms.</p>
-%     <p>This approach is probably easier for an Erlanger but
-%       if you need to use real XSLT stylesheets in order to "comply to
-%       the standard" there is an adapter available to the Sablotron
-%       XSLT package which is written i C++.
-% See also the <a href="xmerl_xs_examples.html">Tutorial</a>.
-%     </p>
 -module(xmerl_xs).
 -moduledoc """
 XSLT-like XML document transformations.
-- 
2.51.0

openSUSE Build Service is sponsored by