File 2921-edoc-support-multiple-clauses-in-spec.patch of Package erlang

From 532122992bfa0ab8d2345c84315c8dbee942701d Mon Sep 17 00:00:00 2001
From: Anton Thomasson <anton.thomasson@ericsson.com>
Date: Wed, 4 Sep 2019 17:13:20 +0200
Subject: [PATCH] edoc: support multiple clauses in -spec

---
 lib/edoc/src/edoc_data.erl                | 36 +++++++++++++++--------
 lib/edoc/src/edoc_extract.erl             |  2 +-
 lib/edoc/src/edoc_layout.erl              | 49 +++++++++++++++++--------------
 lib/edoc/src/edoc_specs.erl               | 30 +++++++++++--------
 lib/erl_docgen/src/docgen_edoc_xml_cb.erl | 49 ++++++++++++++++---------------
 5 files changed, 95 insertions(+), 71 deletions(-)

diff --git a/lib/edoc/src/edoc_data.erl b/lib/edoc/src/edoc_data.erl
index ed81c9f4c3..3075e47942 100644
--- a/lib/edoc/src/edoc_data.erl
+++ b/lib/edoc/src/edoc_data.erl
@@ -230,9 +230,11 @@ callback({N, A}, _Env, _Opts) ->
 %% <!ELEMENT throws (type, localdef*)>
 %% <!ELEMENT equiv (expr, see?)>
 %% <!ELEMENT expr (#PCDATA)>
-
-function({N, A}, As, Export, Ts, Env, Opts) ->
-    {Args, Ret, Spec} = signature(Ts, As, Env),
+function({N, A}, []=As, Export, Ts, Env, Opts)->
+    function({N, A}, [As], Export, Ts, Env, Opts);
+function({N, A}, [HAs | _]=As, Export, Ts, Env, Opts) when not is_list(HAs) ->
+    function({N, A}, [As], Export, Ts, Env, Opts);
+function({N, A}, As0, Export, Ts, Env, Opts) ->
     {function, [{name, atom_to_list(N)},
 		{arity, integer_to_list(A)},
       		{exported, case Export of
@@ -240,13 +242,8 @@ function({N, A}, As, Export, Ts, Env, Opts) ->
 			       false -> "no"
 			   end},
 		{label, edoc_refs:to_label(edoc_refs:function(N, A))}],
-     [{args, [{arg, [{argName, [atom_to_list(A)]}] ++ description(D)}
-	      || {A, D} <- Args]}]
-     ++ Spec
-     ++ case Ret of
-	    [] -> [];
-	    _ -> [{returns, description(Ret)}]
-	end
+     lists:append([get_args(lists:nth(Clause, As0), Ts, Clause, Env)
+                   || Clause <- lists:seq(1, length(As0))])
      ++ get_throws(Ts, Env)
      ++ get_equiv(Ts, Env)
      ++ get_doc(Ts)
@@ -256,6 +253,16 @@ function({N, A}, As, Export, Ts, Env, Opts) ->
      ++ todos(Ts, Opts)
     }.
 
+get_args(As, Ts, Clause, Env) ->
+    {Args, Ret, Spec} = signature(Ts, As, Clause, Env),
+    [{args, [{arg, [{argName, [atom_to_list(A)]}] ++ description(D)}
+     || {A, D} <- Args]}]
+    ++ Spec
+    ++ case Ret of
+           [] -> [];
+           _ -> [{returns, description(Ret)}]
+       end.
+
 get_throws(Ts, Env) ->
     case get_tags(throws, Ts) of
 	[Throws] ->
@@ -406,10 +413,10 @@ todos(Tags, Opts) ->
 	    []
     end.
 
-signature(Ts, As, Env) ->
+signature(Ts, As, Clause, Env) ->
     case get_tags(spec, Ts) of
 	[T] ->
-	    Spec = T#tag.data,
+            Spec = maybe_nth(Clause, T#tag.data),
 	    R = merge_returns(Spec, Ts),
 	    As0 = edoc_types:arg_names(Spec),
 	    Ds0 = edoc_types:arg_descs(Spec),
@@ -424,6 +431,11 @@ signature(Ts, As, Env) ->
 	    {[{A, ""} || A <- fix_argnames(As, S, 1)], [], []}
     end.
 
+maybe_nth(N, List) when is_list(List) ->
+    lists:nth(N, List);
+maybe_nth(1, Other) ->
+    Other.
+
 params(Ts) ->
     [T#tag.data || T <- get_tags(param, Ts)].
 
diff --git a/lib/edoc/src/edoc_extract.erl b/lib/edoc/src/edoc_extract.erl
index 390851e9ef..f7e2c28b6f 100644
--- a/lib/edoc/src/edoc_extract.erl
+++ b/lib/edoc/src/edoc_extract.erl
@@ -634,7 +634,7 @@ select_spec(Ts, _Where, _Specs) ->
 selected_specs([], Ts) ->
     Ts;
 selected_specs([F], [_ | Ts]) ->
-    [edoc_specs:spec(F, _Clause=1) | Ts].
+    [edoc_specs:spec(F) | Ts].
 
 %% Macros for modules
 
diff --git a/lib/edoc/src/edoc_layout.erl b/lib/edoc/src/edoc_layout.erl
index 47ff7b21fc..3643419ba1 100644
--- a/lib/edoc/src/edoc_layout.erl
+++ b/lib/edoc/src/edoc_layout.erl
@@ -357,10 +357,10 @@ label_href(Content, F) ->
 functions(Fs, Opts) ->
     Es = lists:flatmap(fun ({Name, E}) -> function(Name, E, Opts) end, Fs),
     if Es == [] -> [];
-       true ->
-	    [?NL,
-	     {h2, [{a, [{name, ?FUNCTIONS_LABEL}], [?FUNCTIONS_TITLE]}]},
-	     ?NL | Es]
+        true ->
+            [?NL,
+             {h2, [{a, [{name, ?FUNCTIONS_LABEL}], [?FUNCTIONS_TITLE]}]},
+             ?NL | Es]
     end.
 
 function(Name, E=#xmlElement{content = Es}, Opts) ->
@@ -369,22 +369,24 @@ function(Name, E=#xmlElement{content = Es}, Opts) ->
        label_anchor(function_header(Name, E, " *"), E)},
       ?NL]
      ++ [{'div',  [{class, "spec"}],
-	  [?NL,
-	   {p,
-	    case typespec(get_content(typespec, Es), Opts) of
+	    case [typespec(T, Opts) || T <- get_contents(typespec, Es)] of
 		[] ->
-		    signature(get_content(args, Es),
-			      atom(get_attrval(name, E), Opts));
-		Spec -> Spec
-	    end},
-	   ?NL]
-	  ++ case params(get_content(args, Es)) of
+            [?NL,{p,
+            signature(get_content(args, Es),
+			      atom(get_attrval(name, E), Opts))
+            },?NL];
+		Specs ->
+            [?NL]++[{p, Spec} || Spec <- Specs]++[?NL]
+	    end
+	  ++ case [params(A) || A <- get_contents(args, Es)] of
 		 [] -> [];
-		 Ps -> [{p, Ps}, ?NL]
+		 As ->
+             lists:append([[{p, Ps}, ?NL] || Ps <- As])
 	     end
-	  ++ case returns(get_content(returns, Es)) of
+	  ++ case [returns(Ret) || Ret <- get_contents(returns, Es)] of
 		 [] -> [];
-		 Rs -> [{p, Rs}, ?NL]
+		 Rets ->
+             lists:append([[{p, Rs}, ?NL] || Rs <- Rets])
 	     end}]
      ++ throws(Es, Opts)
      ++ equiv_p(Es)
@@ -968,12 +970,8 @@ seq(F, [E | Es], Sep, Tail) ->
 seq(_F, [], _Sep, Tail) ->
     Tail.
 
-get_elem(Name, [#xmlElement{name = Name} = E | Es]) ->
-    [E | get_elem(Name, Es)];
-get_elem(Name, [_ | Es]) ->
-    get_elem(Name, Es);
-get_elem(_, []) ->
-    [].
+get_elem(Name, Es) ->
+    [E || #xmlElement{name=N}=E <- Es, N=:=Name].
 
 get_attr(Name, [#xmlAttribute{name = Name} = A | As]) ->
     [A | get_attr(Name, As)];
@@ -989,6 +987,13 @@ get_attrval(Name, #xmlElement{attributes = As}) ->
 	[] -> ""
     end.
 
+get_contents(Name, Es) ->
+    case get_elem(Name, Es) of
+        [] -> [];
+        Elems ->
+            [Es1 || #xmlElement{content = Es1} <- Elems]
+    end.
+
 get_content(Name, Es) ->
     case get_elem(Name, Es) of
 	[#xmlElement{content = Es1}] ->
diff --git a/lib/edoc/src/edoc_specs.erl b/lib/edoc/src/edoc_specs.erl
index 7b451c43f8..19f890ed8b 100644
--- a/lib/edoc/src/edoc_specs.erl
+++ b/lib/edoc/src/edoc_specs.erl
@@ -21,7 +21,7 @@
 
 -module(edoc_specs).
 
--export([type/2, spec/2, dummy_spec/1, docs/2]).
+-export([type/2, spec/1, dummy_spec/1, docs/2]).
 
 -export([add_data/4, tag/1, is_tag/1]).
 
@@ -67,15 +67,14 @@ type(Form, TypeDocs) ->
                             type = d2e(opaque2abstr(Name, Type))},
                  Doc}}.
 
--spec spec(Form::syntaxTree(), ClauseN::pos_integer()) -> #tag{}.
+-spec spec(Form::syntaxTree()) -> #tag{}.
 
 %% @doc Convert an Erlang spec to EDoc representation.
-spec(Form, Clause) ->
+spec(Form) ->
     {Name, _Arity, TypeSpecs} = get_spec(Form),
-    TypeSpec = lists:nth(Clause, TypeSpecs),
-    #tag{name = spec, line = get_line(element(2, TypeSpec)),
+    #tag{name = spec, line = get_line(element(2, lists:nth(1, TypeSpecs))),
          origin = code,
-         data = aspec(d2e(TypeSpec), Name)}.
+         data = [aspec(d2e(TypeSpec), Name) || TypeSpec <- TypeSpecs]}.
 
 -spec dummy_spec(Form::syntaxTree()) -> #tag{}.
 
@@ -264,8 +263,9 @@ use_tags([#tag{origin = code}=T | Ts], E, TypeTable, NTs) ->
 use_tags([T | Ts], E, TypeTable, NTs) ->
     use_tags(Ts, E, TypeTable, [T | NTs]).
 
-params(#tag{name = spec, data=#t_spec{type = #t_fun{args = As}}}, Default) ->
-    parms(As, Default).
+
+params(#tag{name = spec, data=Data}, Default) when is_list(Data) ->
+    [parms(As, Default) || #t_spec{type = #t_fun{args = As}} <- Data].
 
 parms([], []) ->
     [];
@@ -485,13 +485,17 @@ entries([E0 | Es], P, Opts) ->
 entries([], _P, _Opts) ->
     [].
 
-specs([#tag{line = L, name = spec, origin = code, data = Spec}=Tag0 | Tags],
+specs([#tag{line = L, name = spec, origin = code, data = Specs}=Tag0 | Tags],
       P0) ->
-    #t_spec{type = Type0, defs = Defs0} = Spec,
     P = P0#parms{line = L},
-    Type = xrecs(Type0, P),
-    Defs = xrecs(Defs0, P),
-    Tag = Tag0#tag{data = Spec#t_spec{type = Type, defs = Defs}},
+    Data =
+    [ begin
+        #t_spec{type = Type0, defs = Defs0} = Spec,
+        Type = xrecs(Type0, P),
+        Defs = xrecs(Defs0, P),
+        Spec#t_spec{type = Type, defs = Defs}
+    end || Spec <- Specs],
+    Tag = Tag0#tag{data = Data},
     [Tag | specs(Tags, P)];
 specs([Tag | Tags], P) ->
     [Tag | specs(Tags, P)];
diff --git a/lib/erl_docgen/src/docgen_edoc_xml_cb.erl b/lib/erl_docgen/src/docgen_edoc_xml_cb.erl
index 3354597de8..0d02f14fe7 100644
--- a/lib/erl_docgen/src/docgen_edoc_xml_cb.erl
+++ b/lib/erl_docgen/src/docgen_edoc_xml_cb.erl
@@ -780,23 +780,21 @@ functions(Fs) ->
 
 function(_Name, E=#xmlElement{content = Es}) ->
     TypeSpec = get_content(typespec, Es),
-    [?NL,{func, [ ?NL,
-		  {name, 
-			  case funcheader(TypeSpec) of
-			      [] ->
-				  signature(get_content(args, Es),
-					    get_attrval(name, E));
-			      Spec -> Spec
-			  end
-			 },
-		  ?NL,{fsummary, fsummary(Es)},
-		  ?NL,local_types(TypeSpec),
-		  ?NL,{desc,
-		       label_anchor(E)++
-		       deprecated(Es)++
-		       fulldesc(Es)++
-		       seealso_function(Es)}
-	   ]}].
+    FuncHeaders =
+        case funcheader(TypeSpec) of
+            [] ->
+                [signature(get_content(args, Es), get_attrval(name, E))];
+            Specs ->
+                Specs
+        end,
+    [?NL, {func, [?NL]++
+		 [{name, Spec} || Spec <- FuncHeaders]++
+		 [?NL, {fsummary, fsummary(Es)},
+		  ?NL, local_types(TypeSpec),
+		  ?NL, {desc, label_anchor(E)++
+		              deprecated(Es)++
+		              fulldesc(Es)++
+		              seealso_function(Es)}]}].
 
 fsummary([]) -> ["\s"];
 fsummary(Es) ->
@@ -840,7 +838,9 @@ arg(#xmlElement{content = Es}) ->
 
 funcheader([]) -> [];
 funcheader(Es) ->
-    [t_name(get_elem(erlangName, Es))] ++ t_utype(get_elem(type, Es)).
+    Name = t_name(get_elem(erlangName, Es)),
+    [ [Name] ++ t_utype([E]) || E <- get_elem(type, Es)].
+
 
 local_types([]) -> [];
 local_types(Es) ->
@@ -1020,7 +1020,7 @@ author(E=#xmlElement{}) ->
 	   end,
     [?NL,{aname,[Name]},?NL,{email,[Mail]}].
 
-t_name([E]) ->
+t_name([E | _]) ->
     N = get_attrval(name, E),
     case get_attrval(module, E) of
 	"" -> N;
@@ -1231,12 +1231,15 @@ get_attrval(Name, #xmlElement{attributes = As}) ->
 
 %% get_content(Tag, Es1) -> Es2
 %% If there is one element in Es1 with name Tag, returns its contents,
-%% otherwise []
+%% if there are no tags, return [],
+%% if there are multiple, merge their contents.
 get_content(Name, Es) ->
     case get_elem(Name, Es) of
-	[#xmlElement{content = Es1}] ->
-	    Es1;
-	[] -> []
+        [#xmlElement{content = Es1}] ->
+            Es1;
+        [] -> [];
+        Elems ->
+            lists:append([Es1 || #xmlElement{content = Es1} <- Elems])
     end.
 
 %% get_text(Tag, Es) -> string()
-- 
2.16.4

openSUSE Build Service is sponsored by