Skip to content

Commit

Permalink
Add simplified index output for ocaml.org
Browse files Browse the repository at this point in the history
  • Loading branch information
jonludlam committed Jan 22, 2025
1 parent 7e76186 commit f0dba28
Show file tree
Hide file tree
Showing 11 changed files with 2,465 additions and 11 deletions.
26 changes: 22 additions & 4 deletions src/odoc/bin/main.ml
Original file line number Diff line number Diff line change
Expand Up @@ -478,7 +478,10 @@ module Indexing = struct

let output_file ~dst marshall =
match (dst, marshall) with
| Some file, `JSON when not (Fpath.has_ext "json" (Fpath.v file)) ->
| Some file, `JSON
when not
(Fpath.has_ext "json" (Fpath.v file)
|| Fpath.has_ext "js" (Fpath.v file)) ->
Error
(`Msg
"When generating a json index, the output must have a .json file \
Expand All @@ -493,11 +496,12 @@ module Indexing = struct
| 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 roots inputs_in_file inputs occurrences =
let index dst json warnings_options roots inputs_in_file inputs occurrences
simplified_json wrap_json =
let marshall = if json then `JSON else `Marshall in
output_file ~dst marshall >>= fun output ->
Indexing.compile marshall ~output ~warnings_options ~roots ~occurrences
~inputs_in_file ~odocls:inputs
~inputs_in_file ~simplified_json ~wrap_json ~odocls:inputs

let cmd =
let dst =
Expand Down Expand Up @@ -529,6 +533,20 @@ module Indexing = struct
let doc = "whether to output a json file, or a binary .odoc-index file" in
Arg.(value & flag & info ~doc [ "json" ])
in
let simplified_json =
let doc =
"whether to simplify the json file. Only has an effect in json output \
mode."
in
Arg.(value & flag & info ~doc [ "simplified-json" ])
in
let wrap_json =
let doc =
"whether to wrap the json file. Only has an effect in json output mode."
in
Arg.(value & flag & info ~doc [ "wrap-json" ])
in

let inputs =
let doc = ".odocl file to index" in
Arg.(value & pos_all convert_fpath [] & info ~doc ~docv:"FILE" [])
Expand All @@ -546,7 +564,7 @@ module Indexing = struct
Term.(
const handle_error
$ (const index $ dst $ json $ warnings_options $ roots $ inputs_in_file
$ inputs $ occurrences))
$ inputs $ occurrences $ simplified_json $ wrap_json))

let info ~docs =
let doc =
Expand Down
17 changes: 13 additions & 4 deletions src/odoc/indexing.ml
Original file line number Diff line number Diff line change
Expand Up @@ -23,21 +23,28 @@ let parse_input_files input =
(Ok []) input
>>= fun files -> Ok (List.concat files)

let compile_to_json ~output ~occurrences hierarchies =
let compile_to_json ~output ~occurrences ~wrap ~simplified hierarchies =
let output_channel =
Fs.Directory.mkdir_p (Fs.File.dirname output);
open_out_bin (Fs.File.to_string output)
in
let output = Format.formatter_of_out_channel output_channel in
if wrap then Format.fprintf output "let documents = ";
let all =
List.fold_left
(fun acc hierarchy ->
Tree.fold_left
~f:(fun acc entry -> Json_search.of_entry ?occurrences entry :: acc)
~f:(fun acc entry ->
Json_search.of_entry ~simplified ?occurrences entry :: acc)
acc hierarchy)
[] hierarchies
in
Format.fprintf output "%s" (Odoc_utils.Json.to_string (`Array (List.rev all)));
if wrap then
Format.fprintf output
";\n\
const options = { keys: ['name', 'comment'] };\n\
var idx_fuse = new Fuse(documents, options);\n";
Ok ()

let read_occurrences file =
Expand All @@ -52,7 +59,7 @@ let absolute_normalization p =
Fpath.normalize p

let compile out_format ~output ~warnings_options ~occurrences ~roots
~inputs_in_file ~odocls =
~inputs_in_file ~simplified_json ~wrap_json ~odocls =
let handle_warnings f =
let res = Error.catch_warnings f in
Error.handle_warnings ~warnings_options res |> Result.join
Expand Down Expand Up @@ -126,5 +133,7 @@ let compile out_format ~output ~warnings_options ~occurrences ~roots
List.map hierarchy_of_group root_groups
in
match out_format with
| `JSON -> compile_to_json ~output ~occurrences hierarchies
| `JSON ->
compile_to_json ~output ~occurrences ~simplified:simplified_json
~wrap:wrap_json hierarchies
| `Marshall -> Ok (Odoc_file.save_index output hierarchies)
2 changes: 2 additions & 0 deletions src/odoc/indexing.mli
Original file line number Diff line number Diff line change
Expand Up @@ -7,5 +7,7 @@ val compile :
occurrences:Fs.file option ->
roots:Fs.Directory.t list ->
inputs_in_file:Fs.file list ->
simplified_json:bool ->
wrap_json:bool ->
odocls:Fs.file list ->
(unit, [> msg ]) result
75 changes: 73 additions & 2 deletions src/search/json_index/json_search.ml
Original file line number Diff line number Diff line change
Expand Up @@ -81,6 +81,56 @@ let rec of_id x =

let of_id n = `Array (List.rev @@ of_id (n :> Odoc_model.Paths.Identifier.t))

let rec prefix_name_kind_of_id (n : Odoc_model.Paths.Identifier.t) =
let open Odoc_model.Names in
let prefix_of_parent parent =
let prefix, pname, _kind =
prefix_name_kind_of_id (parent :> Odoc_model.Paths.Identifier.t)
in
if prefix = "" then pname else prefix ^ "." ^ pname
in
match n.iv with
| `Root (_, name) -> ("", ModuleName.to_string name, "module")
| `Page (_, name) -> ("", PageName.to_string name, "page")
| `AssetFile (_, name) -> ("", AssetName.to_string name, "asset")
| `LeafPage (_, name) -> ("", PageName.to_string name, "page")
| `Module (parent, name) ->
(prefix_of_parent parent, ModuleName.to_string name, "module")
| `Parameter (parent, name) ->
(prefix_of_parent parent, ModuleName.to_string name, "parameter")
| `Result x -> prefix_name_kind_of_id (x :> Odoc_model.Paths.Identifier.t)
| `ModuleType (parent, name) ->
(prefix_of_parent parent, ModuleTypeName.to_string name, "module_type")
| `Type (parent, name) ->
(prefix_of_parent parent, TypeName.to_string name, "type")
| `Constructor (parent, name) ->
(prefix_of_parent parent, ConstructorName.to_string name, "constructor")
| `Field (parent, name) ->
(prefix_of_parent parent, FieldName.to_string name, "field")
| `Extension (parent, name) ->
(prefix_of_parent parent, ExtensionName.to_string name, "extension")
| `ExtensionDecl (parent, _, name) ->
(prefix_of_parent parent, ExtensionName.to_string name, "extension_decl")
| `Exception (parent, name) ->
(prefix_of_parent parent, ExceptionName.to_string name, "exception")
| `Value (parent, name) ->
(prefix_of_parent parent, ValueName.to_string name, "value")
| `Class (parent, name) ->
(prefix_of_parent parent, TypeName.to_string name, "class")
| `ClassType (parent, name) ->
(prefix_of_parent parent, TypeName.to_string name, "class_type")
| `Method (parent, name) ->
(prefix_of_parent parent, MethodName.to_string name, "method")
| `InstanceVariable (parent, name) ->
( prefix_of_parent parent,
InstanceVariableName.to_string name,
"instance_variable" )
| `Label (parent, name) ->
(prefix_of_parent parent, LabelName.to_string name, "label")
| `SourceLocationMod _ | `SourceLocation _ | `SourcePage _
| `SourceLocationInternal _ ->
("", "", "")

let of_doc (doc : Odoc_model.Comment.elements) =
let txt = Text.of_doc doc in
`String txt
Expand Down Expand Up @@ -183,7 +233,27 @@ let of_entry ({ Entry.id; doc; kind } as entry) html occurrences =
([ ("id", j_id); ("doc", doc); ("kind", kind); ("display", display) ]
@ occurrences)

let of_entry ?occurrences entry =
let simplified_of_entry { Entry.id; doc; _ } =
let prefix, name, kind = prefix_name_kind_of_id id in
let config =
Odoc_html.Config.v ~flat:false ~semantic_uris:false ~indent:false
~open_details:false ~as_json:false ~remap:[] ()
in
let url =
Odoc_html.Link.href ~config ~resolve:(Base "/")
(Odoc_document.Url.from_identifier ~stop_before:false id)
in
let doc = of_doc doc in
`Object
[
("name", `String name);
("prefixname", `String prefix);
("kind", `String kind);
("url", `String url);
("comment", doc);
]

let of_entry ~simplified ?occurrences entry =
let get_occ id =
match occurrences with
| None -> None
Expand All @@ -196,4 +266,5 @@ let of_entry ?occurrences entry =
let occ = get_occ entry.Entry.id in
(entry, Html.of_entry entry, occ)
in
of_entry entry html occurrences
if simplified then simplified_of_entry entry
else of_entry entry html occurrences
1 change: 1 addition & 0 deletions src/search/json_index/json_search.mli
Original file line number Diff line number Diff line change
@@ -1,6 +1,7 @@
(** This module generates json intended to be consumed by search engines. *)

val of_entry :
simplified:bool ->
?occurrences:Odoc_occurrences.Table.t ->
Odoc_index.Entry.t ->
Odoc_utils.Json.json
2 changes: 1 addition & 1 deletion test/search/html_search.t/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -217,7 +217,7 @@ Passing an inexistent file:
$ odoc compile-index --root babar
$ odoc compile-index --file-list babar
odoc: option '--file-list': no 'babar' file or directory
Usage: odoc compile-index [--file-list=FILE] [--json] [OPTION]… [FILE]…
Usage: odoc compile-index [OPTION]… [FILE]…
Try 'odoc compile-index --help' or 'odoc --help' for more information.
[2]
Expand Down
Loading

0 comments on commit f0dba28

Please sign in to comment.