ocamldoc: reimplement a slow function

With this minor change to a naively-implemented function, manpage generation
for the compiler (stdlib + compiler-libs) goes from 1.8s to 0.4s on my machine.
master
Gabriel Scherer 2019-07-26 20:40:59 +02:00
parent 7fface1a37
commit f4766cf0bb
3 changed files with 20 additions and 11 deletions

View File

@ -72,6 +72,14 @@ let list_concat sep =
in
iter
let remove_duplicates (type a) compare (li : a list) =
let module S = Set.Make(struct type t = a let compare = compare end) in
let maybe_cons ((set, rev_acc) as acc) x =
if S.mem x set then acc
else (S.add x set, x :: rev_acc) in
let (_, rev_acc) = List.fold_left maybe_cons (S.empty, []) li in
List.rev rev_acc
let rec string_of_longident li =
match li with
| Longident.Lident s -> s

View File

@ -102,6 +102,10 @@ val get_titles_in_text : Odoc_types.text -> (int * string option * Odoc_types.te
begin with a letter should be in the first returned list.*)
val create_index_lists : 'a list -> ('a -> string) -> 'a list list
(** [remove_duplicates compare li] removes the duplicates in the input list,
keeping the leftmost occurrence of each repeated element. *)
val remove_duplicates : ('a -> 'a -> int) -> 'a list -> 'a list
(** [remove_ending_newline s] returns [s] without the optional ending newline. *)
val remove_ending_newline : string -> string

View File

@ -325,17 +325,14 @@ module Search =
l
and search module_list v =
List.fold_left
(fun acc -> fun m ->
List.fold_left
(fun acc2 -> fun ele ->
if List.mem ele acc2 then acc2 else acc2 @ [ele]
)
acc
(search_module m v)
)
[]
module_list
let results_with_duplicates =
List.fold_left
(fun rev_acc m ->
List.rev_append (search_module m v) rev_acc)
[] module_list
|> List.rev
in
Odoc_misc.remove_duplicates Stdlib.compare results_with_duplicates
end
module P_name =