File 3012-kernel-Add-code-get_doc-2.patch of Package erlang

From d2cc35f89c304999106f99c57b1af60822d103e9 Mon Sep 17 00:00:00 2001
From: frazze-jobb <frazze@erlang.org>
Date: Thu, 15 Sep 2022 16:07:32 +0200
Subject: [PATCH 2/9] kernel: Add code:get_doc/2

---
 lib/kernel/src/code.erl | 54 +++++++++++++++++++++++++++++++----------
 1 file changed, 41 insertions(+), 13 deletions(-)

diff --git a/lib/kernel/src/code.erl b/lib/kernel/src/code.erl
index a178958397..acf145d59f 100644
--- a/lib/kernel/src/code.erl
+++ b/lib/kernel/src/code.erl
@@ -71,6 +71,7 @@
 	 start_link/0,
 	 which/1,
          get_doc/1,
+         get_doc/2,
 	 where_is_file/1,
 	 where_is_file/2,
 	 set_primary_archive/4,
@@ -860,25 +861,40 @@ where_is_file(Tail, File, Path, Files) ->
       Res :: #docs_v1{},
       Reason :: non_existing | missing | file:posix().
 get_doc(Mod) when is_atom(Mod) ->
+    get_doc(Mod, #{sources => [eep48, debug_info]}).
+
+get_doc(Mod, #{sources:=[Source|Sources]}=Options) ->
+    GetDoc = fun(Fn) -> R = case Source of
+            debug_info -> get_doc_chunk_from_ast(Fn);
+            eep48 -> get_doc_chunk(Fn, Mod)
+        end,
+        case R of
+            {error, missing} -> get_doc(Mod, Options#{sources=>Sources});
+            _ -> R
+        end
+    end,
     case which(Mod) of
         preloaded ->
-            Fn = filename:join([code:lib_dir(erts),"ebin",atom_to_list(Mod) ++ ".beam"]),
-            get_doc_chunk(Fn, Mod);
+            ErtsDir = code:lib_dir(erts),
+            ErtsEbinDir =
+                case filelib:is_dir(filename:join([ErtsDir,"ebin"])) of
+                    true -> filename:join([ErtsDir,"ebin"]);
+                    false -> filename:join([ErtsDir,"preloaded","ebin"])
+                end,
+            Fn = filename:join([ErtsEbinDir, atom_to_list(Mod) ++ ".beam"]),
+            GetDoc(Fn);
         Error when is_atom(Error) ->
             {error, Error};
         Fn ->
-            get_doc_chunk(Fn, Mod)
-    end.
+            GetDoc(Fn)
+    end;
+get_doc(_, #{sources:=[]}) ->
+    {error, missing}.
 
 get_doc_chunk(Filename, Mod) when is_atom(Mod) ->
     case beam_lib:chunks(Filename, ["Docs"]) of
         {error,beam_lib,{missing_chunk,_,_}} ->
-            case get_doc_chunk(Filename, atom_to_list(Mod)) of
-                {error,missing} ->
-                    get_doc_chunk_from_ast(Filename);
-                Error ->
-                    Error
-            end;
+            get_doc_chunk(Filename, atom_to_list(Mod));
         {error,beam_lib,{file_error,_Filename,_Err}} ->
             get_doc_chunk(Filename, atom_to_list(Mod));
         {ok, {Mod, [{"Docs",Bin}]}} ->
@@ -907,24 +923,36 @@ get_doc_chunk_from_ast(Filename) ->
     case beam_lib:chunks(Filename, [abstract_code]) of
         {error,beam_lib,{missing_chunk,_,_}} ->
             {error,missing};
+        {error,beam_lib,{file_error,_,_}} ->
+            {error, missing};
         {ok, {_Mod, [{abstract_code,
                       {raw_abstract_v1, AST}}]}} ->
             Docs = get_function_docs_from_ast(AST),
+            Types = get_type_docs_from_ast(AST),
             {ok, #docs_v1{ anno = 0, beam_language = erlang,
                            module_doc = none,
-                           metadata = #{ generated => true, otp_doc_vsn => ?CURR_DOC_VERSION },
-                           docs = Docs }};
+                           metadata = #{ generated => true, otp_doc_vsn => ?CURR_DOC_VERSION},
+                           docs = Docs++Types }};
         {ok, {_Mod, [{abstract_code,no_abstract_code}]}} ->
             {error,missing};
         Error ->
             Error
     end.
 
+get_type_docs_from_ast(AST) ->
+    lists:flatmap(fun(E) -> get_type_docs_from_ast(E, AST) end, AST).
+get_type_docs_from_ast({attribute, Anno, type, {TypeName, _, Ps}}=Meta, _) ->
+    Arity = length(Ps),
+    Signature = io_lib:format("~p/~p",[TypeName,Arity]),
+    [{{type, TypeName, Arity},Anno,[unicode:characters_to_binary(Signature)],none,#{signature => [Meta]}}];
+get_type_docs_from_ast(_, _) ->
+    [].
+
 get_function_docs_from_ast(AST) ->
     lists:flatmap(fun(E) -> get_function_docs_from_ast(E, AST) end, AST).
 get_function_docs_from_ast({function,Anno,Name,Arity,_Code}, AST) ->
     Signature = io_lib:format("~p/~p",[Name,Arity]),
-    Specs =  lists:filter(
+    Specs = lists:filter(
                fun({attribute,_Ln,spec,{FA,_}}) ->
                        case FA of
                            {F,A} ->
-- 
2.35.3

openSUSE Build Service is sponsored by