ocamldoc: adhoc support for prefixed stdlib

master
octachron 2018-08-24 01:32:50 +02:00 committed by Jérémie Dimino
parent f058a3e809
commit 00a0807e96
7 changed files with 44 additions and 9 deletions

View File

@ -1699,7 +1699,7 @@ module Analyser =
Typedtree.Tmod_constraint
({Typedtree.mod_desc = Typedtree.Tmod_ident (path, _)}, _, _, _))
->
let alias_name = Odoc_env.full_module_name env (Name.from_path path) in
let alias_name = Odoc_env.full_module_name env (Name.from_path path) in
{ m_base with m_kind = Module_alias { ma_name = alias_name ;
ma_module = None ; } }

View File

@ -400,8 +400,9 @@ and associate_in_module_type module_list (acc_b_modif, acc_incomplete_top_module
Some _ ->
(acc_b, acc_inc, acc_names)
| None ->
let mta_name = Name.get_relative "Stdlib" mta.mta_name in
let mt_opt =
try Some (lookup_module_type mta.mta_name)
try Some (lookup_module_type mta_name)
with Not_found -> None
in
match mt_opt with
@ -412,7 +413,7 @@ and associate_in_module_type module_list (acc_b_modif, acc_incomplete_top_module
mta.mta_name = Odoc_messages.sig_end then
acc_names
else
(NF_mt mta.mta_name) :: acc_names)
(NF_mt mta_name) :: acc_names)
)
| Some mt ->
mta.mta_module <- Some mt ;

View File

@ -1242,18 +1242,27 @@ class html =
method create_fully_qualified_idents_links m_name s =
let f str_t =
let match_s = Str.matched_string str_t in
let known_type = String.Set.mem match_s known_types_names in
let known_class = String.Set.mem match_s known_classes_names in
let retry, match_s = if not (known_type || known_class) then
true, Name.get_relative "Stdlib" match_s
else
false, match_s
in
let rel = Name.get_relative m_name match_s in
let s_final = Odoc_info.apply_if_equal
Odoc_info.use_hidden_modules
match_s
rel
in
if String.Set.mem match_s known_types_names then
if known_type ||
(retry && String.Set.mem match_s known_types_names) then
"<a href=\""^(Naming.complete_target Naming.mark_type match_s)^"\">"^
s_final^
"</a>"
else
if String.Set.mem match_s known_classes_names then
if known_class ||
(retry && String.Set.mem match_s known_classes_names) then
let (html_file, _) = Naming.html_files match_s in
"<a href=\""^html_file^"\">"^s_final^"</a>"
else
@ -1269,13 +1278,20 @@ class html =
method create_fully_qualified_module_idents_links m_name s =
let f str_t =
let match_s = Str.matched_string str_t in
let known_module = String.Set.mem match_s known_modules_names in
let retry, match_s =
if not known_module then
true, Name.get_relative "Stdlib" match_s
else
false, match_s in
let rel = Name.get_relative m_name match_s in
let s_final = Odoc_info.apply_if_equal
Odoc_info.use_hidden_modules
match_s
rel
in
if String.Set.mem match_s known_modules_names then
if known_module ||
(retry && String.Set.mem match_s known_modules_names) then
let (html_file, _) = Naming.html_files match_s in
"<a href=\""^html_file^"\">"^s_final^"</a>"
else
@ -2400,12 +2416,17 @@ class html =
let f_ele e =
let simple_name = Name.simple (name e) in
let father_name = Name.father (name e) in
if father_name = "Stdlib" && father_name <> simple_name then
(* avoid duplicata *) ()
else
begin
bp b "<tr><td><a href=\"%s\">%s</a> " (target e) (self#escape simple_name);
if simple_name <> father_name && father_name <> "" then
bp b "[<a href=\"%s\">%s</a>]" (fst (Naming.html_files father_name)) father_name;
bs b "</td>\n<td>";
self#html_of_info_first_sentence b (info e);
bs b "</td></tr>\n";
bs b "</td></tr>\n"
end
in
let f_group l =
match l with

View File

@ -185,6 +185,15 @@ let get_relative n1 n2 =
else
n2
let stdlib_unprefix s =
let p = "Stdlib__" in
let n, k = String.(length p, length s) in
if k > n &&
String.sub s 0 n = p then
String.( capitalize_ascii @@ sub s n (k-n) )
else
s
let hide_given_modules l s =
let rec iter = function
[] -> s

View File

@ -44,6 +44,9 @@ val depth : t -> int
If the two names are equal, then it is false (strict prefix).*)
val prefix : t -> t -> bool
(** remove a [Stdlib__] prefix and capitalize the resulting name *)
val stdlib_unprefix: t -> t
(** Take two names n1 and n2 = n3.n4 and return n4 if n3=n1 or else n2. *)
val get_relative : t -> t -> t

View File

@ -1498,7 +1498,8 @@ module Analyser =
begin
match sig_module_type with
Types.Mty_alias(_, path) ->
let alias_name = Odoc_env.full_module_name env (Name.from_path path) in
let alias_name = Odoc_env.full_module_name env
Name.(stdlib_unprefix @@ from_path path) in
let ma = { ma_name = alias_name ; ma_module = None } in
Module_alias ma
| _ ->

View File

@ -16,7 +16,7 @@
<pre><span id="MODULEModule_whitespace"><span class="keyword">module</span> Module_whitespace</span>: <code class="code"><span class="keyword">sig</span></code> <a href="Module_whitespace.html">..</a> <code class="code"><span class="keyword">end</span></code></pre><hr width="100%">
<pre><span id="MODULEM"><span class="keyword">module</span> <a href="Module_whitespace.M.html">M</a></span>: <code class="type">Stdlib.Set.Make</code><code class="code">(</code><code class="code"><span class="keyword">sig</span></code></pre><div class="sig_block">
<pre><span id="MODULEM"><span class="keyword">module</span> <a href="Module_whitespace.M.html">M</a></span>: <code class="type">Set.Make</code><code class="code">(</code><code class="code"><span class="keyword">sig</span></code></pre><div class="sig_block">
<pre><span id="TYPEt"><span class="keyword">type</span> <code class="type"></code>t</span> = <code class="type">int</code> </pre>