From e8cb86d9516ce0a257961b93d4c7919dca8be46a Mon Sep 17 00:00:00 2001 From: Paul-Elliot Date: Tue, 20 Feb 2024 14:54:17 +0100 Subject: [PATCH 1/6] Fix wrong id being given to doc comments Standalone documentation comments currently do not have an id. This id was carried as the accumulator of the field, which yielded wrong results! Signed-off-by: Paul-Elliot --- src/model/fold.ml | 39 +++++++++------------ src/model/fold.mli | 62 ++++++++++++++++++++++++++++++--- test/search/html_search.t/run.t | 1 + 3 files changed, 75 insertions(+), 27 deletions(-) diff --git a/src/model/fold.ml b/src/model/fold.ml index f6f740ee6c..2ee46ea6b9 100644 --- a/src/model/fold.ml +++ b/src/model/fold.ml @@ -30,8 +30,9 @@ and signature ~f id acc (s : Signature.t) = and signature_item ~f id acc s_item = match s_item with - | Module (_, m) -> module_ ~f acc m - | ModuleType mt -> module_type ~f acc mt + | Module (_, m) -> module_ ~f (m.id :> Paths.Identifier.LabelParent.t) acc m + | ModuleType mt -> + module_type ~f (mt.id :> Paths.Identifier.LabelParent.t) acc mt | ModuleSubstitution _ -> acc | ModuleTypeSubstitution _ -> acc | Open _ -> acc @@ -40,8 +41,9 @@ and signature_item ~f id acc s_item = | TypExt te -> type_extension ~f acc te | Exception exc -> exception_ ~f acc exc | Value v -> value ~f acc v - | Class (_, cl) -> class_ ~f acc cl - | ClassType (_, clt) -> class_type ~f acc clt + | Class (_, cl) -> class_ ~f (cl.id :> Paths.Identifier.LabelParent.t) acc cl + | ClassType (_, clt) -> + class_type ~f (clt.id :> Paths.Identifier.LabelParent.t) acc clt | Include i -> include_ ~f id acc i | Comment d -> docs ~f id acc d @@ -49,8 +51,8 @@ and docs ~f id acc d = f acc (Doc (id, d)) and include_ ~f id acc inc = signature ~f id acc inc.expansion.content -and class_type ~f acc ct = - (* This check is important because [is_hidden] does not work on children of +and class_type ~f id acc ct = + (* This check is important because [is_internal] does not work on children of internal items. This means that if [Fold] did not make this check here, it would be difficult to filter for internal items afterwards. This also applies to the same check in functions bellow. *) @@ -59,8 +61,7 @@ and class_type ~f acc ct = let acc = f acc (ClassType ct) in match ct.expansion with | None -> acc - | Some cs -> - class_signature ~f (ct.id :> Paths.Identifier.LabelParent.t) acc cs + | Some cs -> class_signature ~f id acc cs and class_signature ~f id acc ct_expr = List.fold_left (class_signature_item ~f id) acc ct_expr.items @@ -73,16 +74,13 @@ and class_signature_item ~f id acc item = | Inherit _ -> acc | Comment d -> docs ~f id acc d -and class_ ~f acc cl = +and class_ ~f id acc cl = if Paths.Identifier.is_hidden cl.id then acc else let acc = f acc (Class cl) in match cl.expansion with | None -> acc - | Some cl_signature -> - class_signature ~f - (cl.id :> Paths.Identifier.LabelParent.t) - acc cl_signature + | Some cl_signature -> class_signature ~f id acc cl_signature and exception_ ~f acc exc = if Paths.Identifier.is_hidden exc.id then acc else f acc (Exception exc) @@ -92,30 +90,25 @@ and type_extension ~f acc te = f acc (Extension te) and value ~f acc v = if Paths.Identifier.is_hidden v.id then acc else f acc (Value v) -and module_ ~f acc m = +and module_ ~f id acc m = if Paths.Identifier.is_hidden m.id then acc else let acc = f acc (Module m) in match m.type_ with | Alias (_, None) -> acc - | Alias (_, Some s_e) -> - simple_expansion ~f (m.id :> Paths.Identifier.LabelParent.t) acc s_e - | ModuleType mte -> - module_type_expr ~f (m.id :> Paths.Identifier.LabelParent.t) acc mte + | Alias (_, Some s_e) -> simple_expansion ~f id acc s_e + | ModuleType mte -> module_type_expr ~f id acc mte and type_decl ~f acc td = if Paths.Identifier.is_hidden td.id then acc else f acc (TypeDecl td) -and module_type ~f acc mt = +and module_type ~f id acc mt = if Paths.Identifier.is_hidden mt.id then acc else let acc = f acc (ModuleType mt) in match mt.expr with | None -> acc - | Some mt_expr -> - module_type_expr ~f - (mt.id :> Paths.Identifier.LabelParent.t) - acc mt_expr + | Some mt_expr -> module_type_expr ~f id acc mt_expr and simple_expansion ~f id acc s_e = match s_e with diff --git a/src/model/fold.mli b/src/model/fold.mli index 1b6bd414b2..e5fc4a1473 100644 --- a/src/model/fold.mli +++ b/src/model/fold.mli @@ -28,18 +28,72 @@ type item = val unit : f:('a -> item -> 'a) -> 'a -> Compilation_unit.t -> 'a val page : f:('a -> item -> 'a) -> 'a -> Page.t -> 'a +val signature : + f:('a -> item -> 'a) -> + Paths.Identifier.LabelParent.t -> + 'a -> + Signature.t -> + 'a +val signature_item : + f:('a -> item -> 'a) -> + Paths.Identifier.LabelParent.t -> + 'a -> + Signature.item -> + 'a val docs : f:('a -> item -> 'a) -> Paths.Identifier.LabelParent.t -> 'a -> Comment.docs_or_stop -> 'a -val class_type : f:('a -> item -> 'a) -> 'a -> ClassType.t -> 'a -val class_ : f:('a -> item -> 'a) -> 'a -> Class.t -> 'a +val include_ : + f:('a -> item -> 'a) -> + Paths.Identifier.LabelParent.t -> + 'a -> + Include.t -> + 'a +val class_type : + f:('a -> item -> 'a) -> + Paths.Identifier.LabelParent.t -> + 'a -> + ClassType.t -> + 'a +val class_signature : + f:('a -> item -> 'a) -> + Paths.Identifier.LabelParent.t -> + 'a -> + ClassSignature.t -> + 'a +val class_signature_item : + f:('a -> item -> 'a) -> + Paths.Identifier.LabelParent.t -> + 'a -> + ClassSignature.item -> + 'a +val class_ : + f:('a -> item -> 'a) -> Paths.Identifier.LabelParent.t -> 'a -> Class.t -> 'a val exception_ : f:('a -> item -> 'a) -> 'a -> Exception.t -> 'a val type_extension : f:('a -> item -> 'a) -> 'a -> Extension.t -> 'a val value : f:('a -> item -> 'a) -> 'a -> Value.t -> 'a -val module_ : f:('a -> item -> 'a) -> 'a -> Module.t -> 'a +val module_ : + f:('a -> item -> 'a) -> Paths.Identifier.LabelParent.t -> 'a -> Module.t -> 'a val type_decl : f:('a -> item -> 'a) -> 'a -> TypeDecl.t -> 'a -val module_type : f:('a -> item -> 'a) -> 'a -> ModuleType.t -> 'a +val module_type : + f:('a -> item -> 'a) -> + Paths.Identifier.LabelParent.t -> + 'a -> + ModuleType.t -> + 'a +val simple_expansion : + f:('a -> item -> 'a) -> + Paths.Identifier.LabelParent.t -> + 'a -> + ModuleType.simple_expansion -> + 'a +val module_type_expr : + f:('a -> item -> 'a) -> + Paths.Identifier.LabelParent.t -> + 'a -> + ModuleType.expr -> + 'a val functor_parameter : f:('a -> item -> 'a) -> 'a -> FunctorParameter.t -> 'a diff --git a/test/search/html_search.t/run.t b/test/search/html_search.t/run.t index f41bb156a0..4da72cd74e 100644 --- a/test/search/html_search.t/run.t +++ b/test/search/html_search.t/run.t @@ -270,6 +270,7 @@ Passing a file which is not a correctly marshalled one: Warning: Error while unmarshalling "my_file": End_of_file + Passing no file: $ odoc compile-index From a50b66318aa9f0a8f4f49c322f7b9ed15f83e64d Mon Sep 17 00:00:00 2001 From: Paul-Elliot Date: Tue, 20 Feb 2024 15:39:33 +0100 Subject: [PATCH 2/6] Add a marshalled input/output format for indexes Signed-off-by: Paul-Elliot --- src/driver/cmd_outputs.ml | 20 +++++ src/driver/compile.ml | 80 ++++++++++++++++--- src/driver/compile.mli | 4 + src/driver/odoc.ml | 72 ++++++++--------- src/driver/odoc.mli | 13 ++-- src/driver/odoc_driver.ml | 2 + src/driver/packages.ml | 11 ++- src/driver/packages.mli | 1 - src/driver/sherlodoc.ml | 30 ++++++++ src/model/paths.ml | 4 + src/model/paths.mli | 4 + src/odoc/bin/main.ml | 55 +++++++++---- src/odoc/fs.mli | 5 ++ src/odoc/indexing.ml | 90 ++++++++++++++++++---- src/odoc/indexing.mli | 7 +- src/odoc/odoc_file.ml | 28 +++++-- src/odoc/odoc_file.mli | 8 ++ src/search/json_index/json_search.ml | 10 +++ src/search/json_index/json_search.mli | 4 + test/search/html_search.t/run.t | 80 +++++++++---------- test/search/id_standalone_comments.t/run.t | 6 +- test/search/module_aliases.t/run.t | 2 +- 22 files changed, 396 insertions(+), 140 deletions(-) create mode 100644 src/driver/cmd_outputs.ml create mode 100644 src/driver/sherlodoc.ml diff --git a/src/driver/cmd_outputs.ml b/src/driver/cmd_outputs.ml new file mode 100644 index 0000000000..f6bce2666e --- /dev/null +++ b/src/driver/cmd_outputs.ml @@ -0,0 +1,20 @@ +let submit desc cmd output_file = + match Worker_pool.submit desc cmd output_file with + | Ok x -> x + | Error exn -> raise exn + +let compile_output = ref [ "" ] + +let compile_src_output = ref [ "" ] + +let link_output = ref [ "" ] + +let generate_output = ref [ "" ] + +let source_tree_output = ref [ "" ] + +let add_prefixed_output cmd list prefix lines = + if List.length lines > 0 then + list := + !list + @ (Bos.Cmd.to_string cmd :: List.map (fun l -> prefix ^ ": " ^ l) lines) diff --git a/src/driver/compile.ml b/src/driver/compile.ml index 34c5220c5b..bfc004b1db 100644 --- a/src/driver/compile.ml +++ b/src/driver/compile.ml @@ -16,17 +16,17 @@ type compiled = { include_dirs : Fpath.Set.t; impl : impl option; pkg_args : pkg_args; - current_package : string; + pkgname : string; } let mk_byhash (pkgs : Packages.t Util.StringMap.t) = Util.StringMap.fold - (fun _pkg_name pkg acc -> + (fun pkg_name pkg acc -> List.fold_left (fun acc (lib : Packages.libty) -> List.fold_left (fun acc (m : Packages.modulety) -> - Util.StringMap.add m.m_intf.mif_hash m acc) + Util.StringMap.add m.m_intf.mif_hash (pkg_name, m) acc) acc lib.modules) acc pkg.Packages.libraries) pkgs Util.StringMap.empty @@ -95,7 +95,7 @@ let compile output_dir all = | None -> Logs.debug (fun m -> m "Error locating hash: %s" hash); Error Not_found - | Some modty -> + | Some (pkgname, modty) -> let deps = modty.m_intf.mif_deps in let output_file = Fpath.(output_dir // modty.m_intf.mif_odoc_file) in let fibers = @@ -146,7 +146,7 @@ let compile output_dir all = include_dirs = includes; impl; pkg_args; - current_package = modty.m_package; + pkgname; } in @@ -167,7 +167,7 @@ let compile output_dir all = List.filter_map (function Ok x -> Some x | Error _ -> None) mod_results in Util.StringMap.fold - (fun _ (pkg : Packages.t) acc -> + (fun pkgname (pkg : Packages.t) acc -> Logs.debug (fun m -> m "Package %s mlds: [%a]" pkg.name Fmt.(list ~sep:sp Packages.pp_mld) @@ -191,13 +191,13 @@ let compile output_dir all = include_dirs; impl = None; pkg_args; - current_package = pkg.name; + pkgname : string; } :: acc) acc pkg.mlds) all mods -type linked = { output_file : Fpath.t; src : Fpath.t option } +type linked = { output_file : Fpath.t; src : Fpath.t option; pkgname : string } let link : compiled list -> _ = fun compiled -> @@ -205,7 +205,7 @@ let link : compiled list -> _ = fun c -> let includes = Fpath.Set.add c.output_dir c.include_dirs in let link input_file = - let { pkg_args = { libs; docs }; current_package; _ } = c in + let { pkg_args = { libs; docs }; pkgname = current_package; _ } = c in Odoc.link ~input_file ~includes ~libs ~docs ~current_package () in let impl = @@ -214,7 +214,13 @@ let link : compiled list -> _ = Logs.debug (fun m -> m "Linking impl: %a" Fpath.pp impl); link impl; Atomic.incr Stats.stats.linked_impls; - [ { output_file = Fpath.(set_ext "odocl" impl); src = Some src } ] + [ + { + output_file = Fpath.(set_ext "odocl" impl); + src = Some src; + pkgname = c.pkgname; + }; + ] | None -> [] in match c.m with @@ -227,16 +233,66 @@ let link : compiled list -> _ = (match c.m with | Module _ -> Atomic.incr Stats.stats.linked_units | Mld _ -> Atomic.incr Stats.stats.linked_mlds); - { output_file = Fpath.(set_ext "odocl" c.output_file); src = None } + { + output_file = Fpath.(set_ext "odocl" c.output_file); + src = None; + pkgname = c.pkgname; + } :: impl in Fiber.List.map link compiled |> List.concat +let odoc_index_path ~odoc_dir pkgname = + Fpath.(odoc_dir / pkgname / "index.odoc-index") +let sherlodoc_js_index_path_relative_to_html pkgname = + Fpath.(v pkgname / "sherlodoc_db.js") + +let sherlodoc_js_path_relative_to_html = Fpath.v "sherlodoc.js" +let sherlodoc_js_index_path ~html_dir pkgname = + Fpath.(html_dir // sherlodoc_js_index_path_relative_to_html pkgname) + +let sherlodoc_js_path ~html_dir = + Fpath.(html_dir // sherlodoc_js_path_relative_to_html) + +let sherlodoc_marshall_path ~html_dir = + Fpath.(html_dir / "sherlodoc_db.marshal") +let index_one output_dir pkgname _pkg = + let dir = Fpath.(output_dir / pkgname) in + let dst = odoc_index_path ~odoc_dir:output_dir pkgname in + let include_rec = Fpath.Set.singleton dir in + Odoc.compile_index ~json:false ~dst ~include_rec () +let index odoc_dir pkgs = Util.StringMap.iter (index_one odoc_dir) pkgs + +let sherlodoc_index_one ~html_dir ~odoc_dir pkgname _pkg_content = + ignore @@ Bos.OS.Dir.create Fpath.(html_dir / pkgname); + let format = `js in + let inputs = [ odoc_index_path ~odoc_dir pkgname ] in + let dst = sherlodoc_js_index_path ~html_dir pkgname in + Sherlodoc.index ~format ~inputs ~dst () + +let sherlodoc ~html_dir ~odoc_dir pkgs = + ignore @@ Bos.OS.Dir.create html_dir; + Sherlodoc.js (sherlodoc_js_path ~html_dir); + Util.StringMap.iter (sherlodoc_index_one ~html_dir ~odoc_dir) pkgs; + let format = `marshal in + let dst = sherlodoc_marshall_path ~html_dir in + let inputs = + pkgs |> Util.StringMap.bindings + |> List.map (fun (pkgname, _pkg) -> odoc_index_path ~odoc_dir pkgname) + in + Sherlodoc.index ~format ~inputs ~dst () + let html_generate : Fpath.t -> linked list -> _ = fun output_dir linked -> let html_generate : linked -> unit = fun l -> - Odoc.html_generate + let search_uris = + [ + sherlodoc_js_index_path_relative_to_html l.pkgname; + sherlodoc_js_path_relative_to_html; + ] + in + Odoc.html_generate ~search_uris ~output_dir:(Fpath.to_string output_dir) ~input_file:l.output_file ?source:l.src (); Atomic.incr Stats.stats.generated_units diff --git a/src/driver/compile.mli b/src/driver/compile.mli index 33848c6cbe..07604683cf 100644 --- a/src/driver/compile.mli +++ b/src/driver/compile.mli @@ -8,4 +8,8 @@ type linked val link : compiled list -> linked list +val index : Fpath.t -> Packages.set -> unit + +val sherlodoc : html_dir:Fpath.t -> odoc_dir:Fpath.t -> Packages.set -> unit + val html_generate : Fpath.t -> linked list -> unit diff --git a/src/driver/odoc.ml b/src/driver/odoc.ml index ae6de665bb..e6733994e6 100644 --- a/src/driver/odoc.ml +++ b/src/driver/odoc.ml @@ -5,31 +5,10 @@ type compile_deps = { digest : Digest.t; deps : (string * Digest.t) list } let odoc = Cmd.v "./_build/default/src/odoc/bin/main.exe" (* This is the just-built odoc binary *) -let submit desc cmd output_file = - match Worker_pool.submit desc cmd output_file with - | Ok x -> x - | Error exn -> raise exn - -let compile_output = ref [ "" ] - -let compile_src_output = ref [ "" ] - -let link_output = ref [ "" ] - -let generate_output = ref [ "" ] - -let source_tree_output = ref [ "" ] - -let add_prefixed_output cmd list prefix lines = - if List.length lines > 0 then - list := - !list - @ (Bos.Cmd.to_string cmd :: List.map (fun l -> prefix ^ ": " ^ l) lines) - let compile_deps f = let cmd = Cmd.(odoc % "compile-deps" % Fpath.to_string f) in let desc = Printf.sprintf "Compile deps for %s" (Fpath.to_string f) in - let deps = submit desc cmd None in + let deps = Cmd_outputs.submit desc cmd None in let l = List.filter_map (Astring.String.cut ~sep:" ") deps in let basename = Fpath.(basename (f |> rem_ext)) |> String.capitalize_ascii in match List.partition (fun (n, _) -> basename = n) l with @@ -53,8 +32,9 @@ let compile ~output_dir ~input_file:file ~includes ~parent_id = in let cmd = cmd % "--parent-id" % parent_id in let desc = Printf.sprintf "Compiling %s" (Fpath.to_string file) in - let lines = submit desc cmd output_file in - add_prefixed_output cmd compile_output (Fpath.to_string file) lines + let lines = Cmd_outputs.submit desc cmd output_file in + Cmd_outputs.( + add_prefixed_output cmd compile_output (Fpath.to_string file) lines) let compile_impl ~output_dir ~input_file:file ~includes ~parent_id ~source_id = let open Cmd in @@ -78,8 +58,9 @@ let compile_impl ~output_dir ~input_file:file ~includes ~parent_id ~source_id = let desc = Printf.sprintf "Compiling implementation %s" (Fpath.to_string file) in - let lines = submit desc cmd output_file in - add_prefixed_output cmd compile_output (Fpath.to_string file) lines + let lines = Cmd_outputs.submit desc cmd output_file in + Cmd_outputs.( + add_prefixed_output cmd compile_output (Fpath.to_string file) lines) let link ?(ignore_output = false) ~input_file:file ~includes ~docs ~libs ~current_package () = @@ -113,9 +94,26 @@ let link ?(ignore_output = false) ~input_file:file ~includes ~docs ~libs in let desc = Printf.sprintf "Linking %s" (Fpath.to_string file) in - let lines = submit desc cmd (Some output_file) in + let lines = Cmd_outputs.submit desc cmd (Some output_file) in if not ignore_output then - add_prefixed_output cmd link_output (Fpath.to_string file) lines + Cmd_outputs.( + add_prefixed_output cmd link_output (Fpath.to_string file) lines) + +let compile_index ?(ignore_output = false) ~dst ~json ~include_rec () = + let include_rec = + Fpath.Set.fold + (fun path acc -> Cmd.(acc % "--include-rec" % p path)) + include_rec Cmd.empty + in + let json = if json then Cmd.v "--json" else Cmd.empty in + let cmd = + Cmd.(odoc % "compile-index" %% json %% v "-o" % p dst %% include_rec) + in + let desc = "Generating search index" in + let lines = Cmd_outputs.submit desc cmd (Some dst) in + if not ignore_output then + Cmd_outputs.( + add_prefixed_output cmd link_output (Fpath.to_string dst) lines) let html_generate ~output_dir ?(ignore_output = false) ?(assets = []) ?source ?(search_uris = []) ~input_file:file () = @@ -136,21 +134,22 @@ let html_generate ~output_dir ?(ignore_output = false) ?(assets = []) ?source % output_dir in let desc = Printf.sprintf "Generating HTML for %s" (Fpath.to_string file) in - let lines = submit desc cmd None in + let lines = Cmd_outputs.submit desc cmd None in if not ignore_output then - add_prefixed_output cmd generate_output (Fpath.to_string file) lines + Cmd_outputs.( + add_prefixed_output cmd generate_output (Fpath.to_string file) lines) let support_files path = let open Cmd in let cmd = odoc % "support-files" % "-o" % Fpath.to_string path in let desc = "Generating support files" in - submit desc cmd None + Cmd_outputs.submit desc cmd None let count_occurrences output = let open Cmd in let cmd = odoc % "count-occurrences" % "-I" % "." % "-o" % p output in let desc = "Counting occurrences" in - submit desc cmd None + Cmd_outputs.submit desc cmd None let source_tree ?(ignore_output = false) ~parent ~output file = let open Cmd in @@ -159,15 +158,18 @@ let source_tree ?(ignore_output = false) ~parent ~output file = odoc % "source-tree" % "-I" % "." %% parent % "-o" % p output % p file in let desc = Printf.sprintf "Source tree for %s" (Fpath.to_string file) in - let lines = submit desc cmd None in + let lines = Cmd_outputs.submit desc cmd None in if not ignore_output then - add_prefixed_output cmd source_tree_output (Fpath.to_string file) lines + Cmd_outputs.( + add_prefixed_output cmd source_tree_output (Fpath.to_string file) lines) let classify dir = let open Cmd in let cmd = odoc % "classify" % p dir in let desc = Printf.sprintf "Classifying %s" (Fpath.to_string dir) in - let lines = submit desc cmd None |> List.filter (fun l -> l <> "") in + let lines = + Cmd_outputs.submit desc cmd None |> List.filter (fun l -> l <> "") + in List.map (fun line -> match String.split_on_char ' ' line with diff --git a/src/driver/odoc.mli b/src/driver/odoc.mli index 77afc69aa4..2cc39abb86 100644 --- a/src/driver/odoc.mli +++ b/src/driver/odoc.mli @@ -25,6 +25,14 @@ val link : unit -> unit +val compile_index : + ?ignore_output:bool -> + dst:Fpath.t -> + json:bool -> + include_rec:Fpath.set -> + unit -> + unit + val html_generate : output_dir:string -> ?ignore_output:bool -> @@ -36,11 +44,6 @@ val html_generate : unit val support_files : Fpath.t -> string list -val compile_output : string list ref -val compile_src_output : string list ref -val link_output : string list ref -val generate_output : string list ref -val source_tree_output : string list ref val count_occurrences : Fpath.t -> string list val source_tree : ?ignore_output:bool -> parent:string -> output:Fpath.t -> Fpath.t -> unit diff --git a/src/driver/odoc_driver.ml b/src/driver/odoc_driver.ml index 97751d4245..be93511a94 100644 --- a/src/driver/odoc_driver.ml +++ b/src/driver/odoc_driver.ml @@ -514,6 +514,8 @@ let run libs verbose odoc_dir html_dir stats nb_workers = (fun () -> let compiled = Compile.compile odoc_dir all in let linked = Compile.link compiled in + let () = Compile.index odoc_dir all in + let () = Compile.sherlodoc ~html_dir ~odoc_dir all in let () = Compile.html_generate html_dir linked in let _ = Odoc.support_files html_dir in ()) diff --git a/src/driver/packages.ml b/src/driver/packages.ml index 2e6c5786a8..dd871c1e32 100644 --- a/src/driver/packages.ml +++ b/src/driver/packages.ml @@ -30,7 +30,6 @@ type modulety = { m_intf : intf; m_impl : impl option; m_hidden : bool; - m_package : string; } type mld = { @@ -68,7 +67,7 @@ module Module = struct let is_hidden name = Astring.String.is_infix ~affix:"__" name - let vs m_package lib_name dir modules = + let vs pkg_name lib_name dir modules = let mk m_name = let exists ext = let p = @@ -87,7 +86,7 @@ module Module = struct | _ -> None) in let mk_intf mif_path = - let mif_parent_id = Printf.sprintf "%s/lib/%s" m_package lib_name in + let mif_parent_id = Printf.sprintf "%s/lib/%s" pkg_name lib_name in let mif_odoc_file = Fpath.( v mif_parent_id @@ -107,7 +106,7 @@ module Module = struct | Error _ -> failwith "bad deps" in let mk_impl mip_path = - let mip_parent_id = Printf.sprintf "%s/lib/%s" m_package lib_name in + let mip_parent_id = Printf.sprintf "%s/lib/%s" pkg_name lib_name in let mip_odoc_file = Fpath.( v mip_parent_id @@ -124,7 +123,7 @@ module Module = struct m "Found source file %a for %s" Fpath.pp src_path m_name); let src_name = Fpath.filename src_path in let src_id = - Printf.sprintf "%s/src/%s/%s" m_package lib_name src_name + Printf.sprintf "%s/src/%s/%s" pkg_name lib_name src_name in Some { src_path; src_id } in @@ -143,7 +142,7 @@ module Module = struct Logs.err (fun m -> m "No files for module: %s" m_name); failwith "no files" in - Some { m_name; m_intf; m_impl; m_hidden; m_package } + Some { m_name; m_intf; m_impl; m_hidden } with _ -> Logs.err (fun m -> m "Error processing module %s. Ignoring." m_name); None diff --git a/src/driver/packages.mli b/src/driver/packages.mli index 62b86d2b69..45f1bca845 100644 --- a/src/driver/packages.mli +++ b/src/driver/packages.mli @@ -36,7 +36,6 @@ type modulety = { m_intf : intf; m_impl : impl option; m_hidden : bool; - m_package : string; } (** {1 Standalone pages units} *) diff --git a/src/driver/sherlodoc.ml b/src/driver/sherlodoc.ml new file mode 100644 index 0000000000..cde0448464 --- /dev/null +++ b/src/driver/sherlodoc.ml @@ -0,0 +1,30 @@ +open Bos +open Cmd_outputs + +let sherlodoc = Cmd.v "sherlodoc" + +let index ?(ignore_output = false) ~format ~inputs ~dst ?favored_prefixes () = + let desc = Printf.sprintf "Sherlodoc indexing at %s" (Fpath.to_string dst) in + let format = + Cmd.(v "--format" % match format with `marshal -> "marshal" | `js -> "js") + in + let favored_prefixes = + match favored_prefixes with + | None -> Cmd.empty + | Some favored_prefixes -> + Cmd.(v "--favoured_prefixes" % String.concat "," favored_prefixes) + in + let inputs = Cmd.(inputs |> List.map p |> of_list) in + let cmd = + Cmd.( + sherlodoc % "index" %% format %% favored_prefixes %% inputs % "-o" % p dst) + in + let lines = submit desc cmd (Some dst) in + if not ignore_output then + add_prefixed_output cmd link_output (Fpath.to_string dst) lines + +let js dst = + let cmd = Cmd.(sherlodoc % "js" % p dst) in + let desc = Printf.sprintf "Sherlodoc js at %s" (Fpath.to_string dst) in + let _lines = submit desc cmd (Some dst) in + () diff --git a/src/model/paths.ml b/src/model/paths.ml index d6dfa80613..ac7debcea5 100644 --- a/src/model/paths.ml +++ b/src/model/paths.ml @@ -643,6 +643,10 @@ module Identifier = struct mk_parent LocalName.to_string "sli" (fun (p, n) -> `SourceLocationInternal (p, n)) end + + module Hashtbl = struct + module Any = Hashtbl.Make (Any) + end end module Path = struct diff --git a/src/model/paths.mli b/src/model/paths.mli index 15a7bfcdec..98596a8f55 100644 --- a/src/model/paths.mli +++ b/src/model/paths.mli @@ -236,6 +236,10 @@ module Identifier : sig end end + module Hashtbl : sig + module Any : Hashtbl.S with type key = Any.t + end + module Mk : sig open Names diff --git a/src/odoc/bin/main.ml b/src/odoc/bin/main.ml index b6b1183f71..f0217ad4ae 100644 --- a/src/odoc/bin/main.ml +++ b/src/odoc/bin/main.ml @@ -478,26 +478,36 @@ module Compile_impl = struct end module Indexing = struct - let output_file ~dst = - match dst with - | Some file -> Fs.File.of_string file - | None -> Fs.File.of_string "index.json" + open Or_error - let index dst warnings_options inputs_in_file inputs = - let output = output_file ~dst in - match (inputs_in_file, inputs) with - | [], [] -> - Result.Error + let output_file ~dst marshall = + match (dst, marshall) with + | Some file, `JSON when not (Fpath.has_ext "json" (Fpath.v file)) -> + Error (`Msg - "At least one of --file-list or an .odocl file must be passed to \ - odoc compile-index") - | _ -> Indexing.compile ~output ~warnings_options inputs_in_file inputs - + "When generating a json index, the output must have a .json file \ + extension") + | Some file, `Marshall when not (Fpath.has_ext "odoc-index" (Fpath.v file)) + -> + Error + (`Msg + "When generating a binary index, the output must have a \ + .odoc-index file extension") + | Some file, _ -> Ok (Fs.File.of_string file) + | None, `JSON -> Ok (Fs.File.of_string "index.json") + | None, `Marshall -> Ok (Fs.File.of_string "index.odoc-index") + + let index dst json warnings_options includes_rec inputs_in_file inputs = + let marshall = if json then `JSON else `Marshall in + output_file ~dst marshall >>= fun output -> + Indexing.compile marshall ~output ~warnings_options ~includes_rec + ~inputs_in_file ~odocls:inputs let cmd = let dst = let doc = "Output file path. Non-existing intermediate directories are created. \ - Defaults to index.json" + Defaults to index.odoc-index, or index.json if --json is passed (in \ + which case, the .odoc-index file extension is mandatory)." in Arg.( value & opt (some string) None & info ~docs ~docv:"PATH" ~doc [ "o" ]) @@ -511,13 +521,28 @@ module Indexing = struct value & opt_all convert_fpath [] & info ~doc ~docv:"FILE" [ "file-list" ]) in + let include_rec = + let doc = + "Include all the .odocl files found recursively in DIR in the \ + generated index." + in + Arg.( + value + & opt_all (convert_directory ()) [] + & info ~doc ~docv:"DIR" [ "include-rec" ]) + in + let json = + let doc = "whether to output a json file, or a binary .odoc-index file" in + Arg.(value & flag & info ~doc [ "json" ]) + in let inputs = let doc = ".odocl file to index" in Arg.(value & pos_all convert_fpath [] & info ~doc ~docv:"FILE" []) in Term.( const handle_error - $ (const index $ dst $ warnings_options $ inputs_in_file $ inputs)) + $ (const index $ dst $ json $ warnings_options $ include_rec + $ inputs_in_file $ inputs)) let info ~docs = let doc = diff --git a/src/odoc/fs.mli b/src/odoc/fs.mli index aa30d1f18e..c7062848d5 100644 --- a/src/odoc/fs.mli +++ b/src/odoc/fs.mli @@ -44,6 +44,11 @@ module Directory : sig val to_fpath : t -> Fpath.t + val fold_files_rec : ?ext:string -> ('a -> file -> 'a) -> 'a -> t -> 'a + (** [fold_files_rec_result ~ext f acc d] recursively folds [f] over the files + with extension matching [ext] (defaults to [""]) contained in [d] + and its sub directories. *) + val fold_files_rec_result : ?ext:string -> ('a -> file -> ('a, msg) result) -> diff --git a/src/odoc/indexing.ml b/src/odoc/indexing.ml index 718f3b6365..b7a3a16186 100644 --- a/src/odoc/indexing.ml +++ b/src/odoc/indexing.ml @@ -3,18 +3,26 @@ open Odoc_json_index open Or_error open Odoc_model -let handle_file file ~unit ~page = - Odoc_file.load file >>= fun unit' -> - match unit' with - | { Odoc_file.content = Unit_content unit'; _ } when unit'.hidden -> - Error (`Msg "Hidden units are ignored when generating an index") - | { Odoc_file.content = Unit_content unit'; _ } (* when not unit'.hidden *) -> - Ok (unit unit') - | { Odoc_file.content = Page_content page'; _ } -> Ok (page page') - | _ -> - Error - (`Msg - "Only pages and unit are allowed as input when generating an index") +module H = Odoc_model.Paths.Identifier.Hashtbl.Any + +let handle_file file ~unit ~page ~occ = + match Fpath.basename file with + | s when String.is_prefix ~affix:"index-" s -> + Odoc_file.load_index file >>= fun index -> Ok (occ index) + | _ -> ( + Odoc_file.load file >>= fun unit' -> + match unit' with + | { Odoc_file.content = Unit_content unit'; _ } when unit'.hidden -> + Error (`Msg "Hidden units are ignored when generating an index") + | { Odoc_file.content = Unit_content unit'; _ } + (* when not unit'.hidden *) -> + Ok (unit unit') + | { Odoc_file.content = Page_content page'; _ } -> Ok (page page') + | _ -> + Error + (`Msg + "Only pages and unit are allowed as input when generating an \ + index")) let parse_input_file input = let is_sep = function '\n' | '\r' -> true | _ -> false in @@ -32,9 +40,7 @@ let parse_input_files input = (Ok []) input >>= fun files -> Ok (List.concat files) -let compile ~output ~warnings_options inputs_in_file inputs = - parse_input_files inputs_in_file >>= fun files -> - let files = List.rev_append inputs files in +let compile_to_json ~output ~warnings_options files = let output_channel = Fs.Directory.mkdir_p (Fs.File.dirname output); open_out_bin (Fs.File.to_string output) @@ -53,6 +59,7 @@ let compile ~output ~warnings_options inputs_in_file inputs = handle_file ~unit:(print Json_search.unit acc) ~page:(print Json_search.page acc) + ~occ:(print Json_search.index acc) file with | Ok acc -> acc @@ -66,3 +73,56 @@ let compile ~output ~warnings_options inputs_in_file inputs = result |> Error.handle_warnings ~warnings_options >>= fun (_ : bool) -> Format.fprintf output "]"; Ok () + +let compile_to_marshall ~output ~warnings_options files = + let final_index = H.create 10 in + let unit u = + Odoc_model.Fold.unit + ~f:(fun () item -> + let entries = Odoc_search.Entry.entries_of_item item in + List.iter + (fun entry -> H.add final_index entry.Odoc_search.Entry.id entry) + entries) + () u + in + let page p = + Odoc_model.Fold.page + ~f:(fun () item -> + let entries = Odoc_search.Entry.entries_of_item item in + List.iter + (fun entry -> H.add final_index entry.Odoc_search.Entry.id entry) + entries) + () p + in + let index i = H.iter (H.add final_index) i in + let index () = + List.fold_left + (fun acc file -> + match handle_file ~unit ~page ~occ:index file with + | Ok acc -> acc + | Error (`Msg m) -> + Error.raise_warning ~non_fatal:true + (Error.filename_only "%s" m (Fs.File.to_string file)); + acc) + () files + in + let result = Error.catch_warnings index in + result |> Error.handle_warnings ~warnings_options >>= fun () -> + Ok (Odoc_file.save_index output final_index) + +let compile out_format ~output ~warnings_options ~includes_rec ~inputs_in_file + ~odocls = + parse_input_files inputs_in_file >>= fun files -> + let files = List.rev_append odocls files in + let files = + List.rev_append files + (includes_rec + |> List.map (fun include_rec -> + Fs.Directory.fold_files_rec ~ext:"odocl" + (fun files file -> file :: files) + [] include_rec) + |> List.concat) + in + match out_format with + | `JSON -> compile_to_json ~output ~warnings_options files + | `Marshall -> compile_to_marshall ~output ~warnings_options files diff --git a/src/odoc/indexing.mli b/src/odoc/indexing.mli index ceb398f3f0..36b7483aa8 100644 --- a/src/odoc/indexing.mli +++ b/src/odoc/indexing.mli @@ -4,13 +4,16 @@ val handle_file : Fpath.t -> unit:(Odoc_model.Lang.Compilation_unit.t -> 'a) -> page:(Odoc_model.Lang.Page.t -> 'a) -> + occ:(Odoc_search.Entry.t Odoc_model.Paths.Identifier.Hashtbl.Any.t -> 'a) -> ('a, [> msg ]) result (** This function is exposed for custom indexers that uses [odoc] as a library to generate their search index *) val compile : + [ `JSON | `Marshall ] -> output:Fs.file -> warnings_options:Odoc_model.Error.warnings_options -> - Fs.file list -> - Fs.file list -> + includes_rec:Fs.directory list -> + inputs_in_file:Fs.file list -> + odocls:Fs.file list -> (unit, [> msg ]) result diff --git a/src/odoc/odoc_file.ml b/src/odoc/odoc_file.ml index f7f00fd79b..eb8a4c38ba 100644 --- a/src/odoc/odoc_file.ml +++ b/src/odoc/odoc_file.ml @@ -31,14 +31,18 @@ type t = { content : content; warnings : Odoc_model.Error.t list } let magic = "odoc-%%VERSION%%" (** Exceptions while saving are allowed to leak. *) -let save_unit file (root : Root.t) (t : t) = +let save_ file f = Fs.Directory.mkdir_p (Fs.File.dirname file); let oc = open_out_bin (Fs.File.to_string file) in output_string oc magic; - Marshal.to_channel oc root []; - Marshal.to_channel oc t []; + f oc; close_out oc +let save_unit file (root : Root.t) (t : t) = + save_ file (fun oc -> + Marshal.to_channel oc root []; + Marshal.to_channel oc t []) + let save_page file ~warnings page = let dir = Fs.File.dirname file in let base = Fs.File.(to_string @@ basename file) in @@ -81,9 +85,7 @@ let load_ file f = let res = try let actual_magic = really_input_string ic (String.length magic) in - if actual_magic = magic then - let root = Marshal.from_channel ic in - f ic root + if actual_magic = magic then f ic else let msg = Printf.sprintf "%s: invalid magic number %S, expected %S\n%!" file @@ -100,7 +102,17 @@ let load_ file f = close_in ic; res -let load file = load_ file (fun ic _ -> Ok (Marshal.from_channel ic)) +let load file = + load_ file (fun ic -> + let _root = Marshal.from_channel ic in + Ok (Marshal.from_channel ic)) (** The root is saved separately in the files to support this function. *) -let load_root file = load_ file (fun _ root -> Ok root) +let load_root file = + load_ file (fun ic -> + let root = Marshal.from_channel ic in + Ok root) + +let save_index dst idx = save_ dst (fun oc -> Marshal.to_channel oc idx []) + +let load_index file = load_ file (fun ic -> Ok (Marshal.from_channel ic)) diff --git a/src/odoc/odoc_file.mli b/src/odoc/odoc_file.mli index 956d26b8a9..9a07d55c84 100644 --- a/src/odoc/odoc_file.mli +++ b/src/odoc/odoc_file.mli @@ -55,3 +55,11 @@ val load : Fs.File.t -> (t, [> msg ]) result val load_root : Fs.File.t -> (Root.t, [> msg ]) result (** Only load the root. Faster than {!load}, used for looking up imports. *) + +val save_index : + Fs.File.t -> Odoc_search.Entry.t Paths.Identifier.Hashtbl.Any.t -> unit + +val load_index : + Fs.File.t -> + (Odoc_search.Entry.t Paths.Identifier.Hashtbl.Any.t, [> msg ]) result +(** Load a [.odoc-index] file. *) diff --git a/src/search/json_index/json_search.ml b/src/search/json_index/json_search.ml index a77952251e..f4f54fd34f 100644 --- a/src/search/json_index/json_search.ml +++ b/src/search/json_index/json_search.ml @@ -214,3 +214,13 @@ let page ppf (page : Odoc_model.Lang.Page.t) = in let _first = Odoc_model.Fold.page ~f true page in () + +let index ppf (index : Entry.t Odoc_model.Paths.Identifier.Hashtbl.Any.t) = + let _first = + Odoc_model.Paths.Identifier.Hashtbl.Any.fold + (fun _id entry first -> + let entry = (entry, Html.of_entry entry) in + output_json ppf first [ entry ]) + index true + in + () diff --git a/src/search/json_index/json_search.mli b/src/search/json_index/json_search.mli index 2b132af07c..018ab445a9 100644 --- a/src/search/json_index/json_search.mli +++ b/src/search/json_index/json_search.mli @@ -2,3 +2,7 @@ val unit : Format.formatter -> Odoc_model.Lang.Compilation_unit.t -> unit val page : Format.formatter -> Odoc_model.Lang.Page.t -> unit +val index : + Format.formatter -> + Odoc_search.Entry.t Odoc_model.Paths.Identifier.Hashtbl.Any.t -> + unit diff --git a/test/search/html_search.t/run.t b/test/search/html_search.t/run.t index 4da72cd74e..1354a36c2d 100644 --- a/test/search/html_search.t/run.t +++ b/test/search/html_search.t/run.t @@ -48,33 +48,28 @@ we will generate. $ odoc html-generate --search-uri fuse.js.js --search-uri index.js -o html page-page.odocl $ odoc support-files -o html -We now focus on how to generate the index.js file. There are mainly two ways: by -using odoc as a library, or by using the the `compile-index` command. This -command generates a json index containing all .odocl given as input, to be -consumed later by a search engine. If -o is not provided, the file is saved as -index.json. -Odocl files can be given either in a list (using --file-list, -passing a file with the list of line-separated files), or by passing directly -the name of the files. +We now focus on how to generate the index.js file. - $ printf "main.odocl\npage-page.odocl\nj.odocl\n" > index_map - $ odoc compile-index -o index1.json --file-list index_map - -Or equivalently: - - $ printf "main.odocl\npage-page.odocl\n" > index_map - $ odoc compile-index -o index2.json --file-list index_map j.odocl +For this, we compute an index of all the values contained in a given list of +odoc files, using the `compile-index` command. -Or equivalently: +This command generates has two output format: a json output for consumption by +external search engine, and an `odoc` specific extension. The odoc file is +meant to be consumed either by search engine written in OCaml, which would +depend on `odoc` as a library, or by `odoc` itself to build a global index +incrementally: the `compile-index` command can take indexes as input! - $ odoc compile-index main.odocl page-page.odocl j.odocl +If -o is not provided, the file is saved as index.json, or index-index.odoc if +the --marshall flag is passed. Odocl files can be given either in a list (using +--file-list, passing a file with the list of line-separated files), or by +passing directly the name of the files. -Let's check that the previous commands are indeed independent: + $ printf "main.odocl\npage-page.odocl\nj.odocl\n" > index_map + $ odoc compile-index --json -o index.json --include-rec . - $ diff index.json index1.json - $ diff index.json index2.json + $ odoc compile-index -o index-main.odoc-index --include-rec . -The index file contains a json array, each element of the array corresponding to +The json index file contains a json array, each element of the array corresponding to a search entry. An index entry contains: - an ID, @@ -247,32 +242,39 @@ Testing the warnings/errors for the `compile-index` command: Passing an inexistent file: - $ printf "inexistent.odocl\n" > index_map - $ odoc compile-index --file-list index_map - File "inexistent.odocl": - Warning: File does not exist + $ odoc compile-index --include-rec babar + $ odoc compile-index --file-list babar + odoc: option '--file-list': no 'babar' file or directory + Usage: odoc compile-index [--file-list=FILE] [--include-rec=DIR] [--json] [OPTION]… [FILE]… + Try 'odoc compile-index --help' or 'odoc --help' for more information. + [2] -Passing an odoc file which is neither a compilation unit nor a page: +Passing an empty folder is allowed: - $ odoc compile -c srctree-source page.mld - $ printf "a.ml\n" > source_tree.map - $ odoc source-tree -I . --parent page -o srctree-source.odoc source_tree.map + $ mkdir foo + $ odoc compile-index --include-rec foo - $ odoc compile-index srctree-source.odoc - File "srctree-source.odoc": - Warning: Only pages and unit are allowed as input when generating an index +Wrong file extensions: + + $ odoc compile-index -o index.odoc + ERROR: When generating a binary index, the output must have a .odoc-index file extension + [1] + $ odoc compile-index -o index.json + ERROR: When generating a binary index, the output must have a .odoc-index file extension + [1] + $ odoc compile-index --json -o index.odoc-index + ERROR: When generating a json index, the output must have a .json file extension + [1] Passing a file which is not a correctly marshalled one: - $ echo hello > my_file - $ odoc compile-index my_file - File "my_file": - Warning: Error while unmarshalling "my_file": End_of_file + $ echo hello > my_file.odocl + $ odoc compile-index --include-rec . + File "./my_file.odocl": + Warning: Error while unmarshalling "./my_file.odocl": End_of_file -Passing no file: +Passing no file is allowed, generating an empty index: $ odoc compile-index - ERROR: At least one of --file-list or an .odocl file must be passed to odoc compile-index - [1] diff --git a/test/search/id_standalone_comments.t/run.t b/test/search/id_standalone_comments.t/run.t index 2e16e73254..3ce9d4b545 100644 --- a/test/search/id_standalone_comments.t/run.t +++ b/test/search/id_standalone_comments.t/run.t @@ -7,7 +7,11 @@ Compile and link the documentation $ odoc compile -I . main.cmt $ odoc link -I . main.odoc - $ odoc compile-index main.odocl + $ odoc compile-index --json --include-rec . +We test that you can also pass a .odocl file directly. + $ odoc compile-index --json main.odocl -o index2.json +Indexes should be the same no matter how the inputs were passed. + $ diff index.json index2.json Let's have a look at the links generated for standalone comments search entries: diff --git a/test/search/module_aliases.t/run.t b/test/search/module_aliases.t/run.t index 404e605dad..045f7bc04d 100644 --- a/test/search/module_aliases.t/run.t +++ b/test/search/module_aliases.t/run.t @@ -6,7 +6,7 @@ Compile and link the documentation $ odoc compile main.cmt $ odoc link main.odoc - $ odoc compile-index main.odocl + $ odoc compile-index --json --include-rec . Search results only redirect to their definition point (not the expansions). Comments link to the expansion they are in. From c4dffa8c92ad2f5d7d3f7760458aac8f2d712df9 Mon Sep 17 00:00:00 2001 From: Emile Trotignon Date: Mon, 10 Jun 2024 14:34:27 +0200 Subject: [PATCH 3/6] add sherlodoc to the deps of the odoc-driver package --- odoc-driver.opam | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/odoc-driver.opam b/odoc-driver.opam index f6185ceb03..2f7bf25604 100644 --- a/odoc-driver.opam +++ b/odoc-driver.opam @@ -34,7 +34,7 @@ documentation for installed packages. depends: [ "odoc" {= version} - "bos" + "bos" "fpath" "yojson" "ocamlfind" @@ -43,6 +43,7 @@ depends: [ "eio_main" "progress" "cmdliner" + "sherlodoc" ] build: [ From 3de1a0220e574f6753178eaa413668fdccb53b11 Mon Sep 17 00:00:00 2001 From: Emile Trotignon Date: Mon, 8 Jul 2024 14:05:35 +0200 Subject: [PATCH 4/6] add pin depend to opam file --- odoc-driver.opam | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/odoc-driver.opam b/odoc-driver.opam index 2f7bf25604..cfbbb7a5dc 100644 --- a/odoc-driver.opam +++ b/odoc-driver.opam @@ -46,6 +46,10 @@ depends: [ "sherlodoc" ] +pin-depends: [ + ["sherlodoc.dev" "git+https://github.com/emiletrotignon/sherlodoc.git#076cc2b"] +] + build: [ ["dune" "subst"] {dev} [ From ee8628a0810804c84a6614ec643e3498c6d31df8 Mon Sep 17 00:00:00 2001 From: Emile Trotignon Date: Mon, 8 Jul 2024 15:53:50 +0200 Subject: [PATCH 5/6] remove sherlodoc from deps because of a bug in ocaml ci --- odoc-driver.opam | 5 ----- 1 file changed, 5 deletions(-) diff --git a/odoc-driver.opam b/odoc-driver.opam index cfbbb7a5dc..87ac2706ac 100644 --- a/odoc-driver.opam +++ b/odoc-driver.opam @@ -43,11 +43,6 @@ depends: [ "eio_main" "progress" "cmdliner" - "sherlodoc" -] - -pin-depends: [ - ["sherlodoc.dev" "git+https://github.com/emiletrotignon/sherlodoc.git#076cc2b"] ] build: [ From 906c96da51239123f985ace25e6943308e965e2c Mon Sep 17 00:00:00 2001 From: Emile Trotignon Date: Tue, 11 Jun 2024 12:18:32 +0200 Subject: [PATCH 6/6] update CHANGES.md --- CHANGES.md | 1 + 1 file changed, 1 insertion(+) diff --git a/CHANGES.md b/CHANGES.md index 37708b0d14..eb124df261 100644 --- a/CHANGES.md +++ b/CHANGES.md @@ -16,6 +16,7 @@ - Path-references to hierarchical pages and modules (@Julow, #1151) Absolute (`{!/foo}`), relative (`{!./foo}`) and package-local (`{!//foo}`) are added. +- Add a marshalled search index consumable by sherlodoc (@EmileTrotignon, @panglesd, #1084) ### Changed