ocamldoc: add a -lib flag for prefixed libraries

master
Florian Angeletti 2018-09-01 16:56:57 +02:00 committed by Jérémie Dimino
parent 00a0807e96
commit 642504c5e7
12 changed files with 60 additions and 15 deletions

View File

@ -30,18 +30,23 @@ let init_path () = Compmisc.init_path false
(** Return the initial environment in which compilation proceeds. *)
let initial_env () =
let current = Env.get_unit_name () in
let initial = !Odoc_global.initially_opened_module in
let initially_opened_module =
let m = !Odoc_global.initially_opened_module in
if m = Env.get_unit_name () then
if initial = current then
None
else
Some m
Some initial
in
let open_implicit_modules =
let ln = !Odoc_global.library_namespace in
let ln = if current = ln || ln = initial || ln = "" then [] else [ln] in
ln @ List.rev !Clflags.open_modules in
Typemod.initial_env
~loc:(Location.in_file "ocamldoc command line")
~safe_string:(Config.safe_string || not !Clflags.unsafe_string)
~open_implicit_modules
~initially_opened_module
~open_implicit_modules:(List.rev !Clflags.open_modules)
(** Optionally preprocess a source file *)
let preprocess sourcefile =

View File

@ -258,6 +258,7 @@ let default_options = Options.list @
[
"-initially-opened-module", Arg.Set_string Odoc_global.initially_opened_module,
M.initially_opened_module;
"-lib", Arg.Set_string Odoc_global.library_namespace, M.library_namespace;
"-text", Arg.String (fun s ->
Odoc_global.files := !Odoc_global.files @ [Odoc_global.Text_file s]),
M.option_text ;

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,7 +400,10 @@ 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 mta_name =
Name.get_relative_opt
!Odoc_global.library_namespace
mta.mta_name in
let mt_opt =
try Some (lookup_module_type mta_name)
with Not_found -> None

View File

@ -79,3 +79,5 @@ let with_toc = ref true
let with_index = ref true
let initially_opened_module = ref "Stdlib"
let library_namespace = ref ""

View File

@ -105,3 +105,6 @@ val with_trailer : bool ref
(** Name of the module that is initially opened. *)
val initially_opened_module : string ref
(** Name of the library namespace for a prefixed library *)
val library_namespace: string ref

View File

@ -1240,12 +1240,13 @@ class html =
type (or class or class type) idents
have been replaced by links to the type referenced by the ident.*)
method create_fully_qualified_idents_links m_name s =
let ln = !Odoc_global.library_namespace in
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
let retry, match_s = if not (known_type || known_class) && ln <> "" then
true, Name.get_relative_opt ln match_s
else
false, match_s
in
@ -1279,9 +1280,10 @@ class html =
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 ln = !Odoc_global.library_namespace in
let retry, match_s =
if not known_module then
true, Name.get_relative "Stdlib" match_s
if not known_module && ln <> "" then
true, Name.get_relative_opt ln match_s
else
false, match_s in
let rel = Name.get_relative m_name match_s in

View File

@ -128,6 +128,10 @@ module Name :
(** Take two names n1 and n2 = n3.n4 and return n4 if n3=n1 or else n2. *)
val get_relative : t -> t -> t
(** Take two names n1 and n2 = n3.n4 and return n4 if n3=n1 and n1<>"" or else n2. *)
val get_relative_opt : t -> t -> t
(** Return the name of the 'father' (like [dirname] for a file name).*)
val father : t -> t
end

View File

@ -240,6 +240,11 @@ let merge_options =
let initially_opened_module = "<module> Name of the module that is initially opened"
let library_namespace =
"<module> Name of the library namespace for a prefixed library.\
Note: very experimental."
let help = " Display this list of options"

View File

@ -185,8 +185,21 @@ let get_relative n1 n2 =
else
n2
let stdlib_unprefix s =
let p = "Stdlib__" in
let get_relative_opt n1 n2 =
if n1 = "" then n2 else
if prefix n1 n2 then
let len1 = String.length n1 in
try
String.sub n2 (len1+1) ((String.length n2) - len1 - 1)
with
_ -> n2
else
n2
let alias_unprefix ln s =
if ln = "" then s else
let p = ln ^ "__" in
let n, k = String.(length p, length s) in
if k > n &&
String.sub s 0 n = p then

View File

@ -44,12 +44,18 @@ 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
(** remove a [Library__] prefix and capitalize the resulting name *)
val alias_unprefix: t -> 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
(** [get_relative_opt n1 n2] is [n2] if [n1=""] and
[get_relative n1 n2] otherwise *)
val get_relative_opt : t -> t -> t
(** Take two names n1=n3.n4 and n2 = n5.n6 and return n6 if n3=n5 or else n2. *)
val get_relative_raw : t -> t -> t

View File

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