Skip to content

Commit

Permalink
Occurrences: don't expose sub in occurrence table
Browse files Browse the repository at this point in the history
Signed-off-by: Paul-Elliot <[email protected]>
  • Loading branch information
panglesd committed Jul 15, 2024
1 parent fd15b16 commit 447e6ac
Show file tree
Hide file tree
Showing 3 changed files with 15 additions and 9 deletions.
13 changes: 11 additions & 2 deletions src/occurrences/table.ml
Original file line number Diff line number Diff line change
@@ -1,9 +1,14 @@
module H = Hashtbl.Make (Odoc_model.Paths.Identifier)

type t = item H.t
and item = { direct : int; indirect : int; sub : item H.t }
type t = internal_item H.t
and internal_item = { direct : int; indirect : int; sub : t }
type key = Odoc_model.Paths.Identifier.t

type item = { direct : int; indirect : int }

let internal_to_item : internal_item -> item =
fun { direct; indirect; _ } -> { direct; indirect }

let v_item () = { direct = 0; indirect = 0; sub = H.create 0 }

let v () = H.create 0
Expand Down Expand Up @@ -78,9 +83,13 @@ let rec get t id =
| `AssetFile _ | `SourceDir _ | `SourceLocationInternal _ ->
None

let get t id =
match get t id with None -> None | Some i -> Some (internal_to_item i)

let rec iter f tbl =
H.iter
(fun id v ->
iter f v.sub;
let v = internal_to_item v in
f id v)
tbl
2 changes: 1 addition & 1 deletion src/occurrences/table.mli
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
type t
type item = { direct : int; indirect : int; sub : t }
type item = { direct : int; indirect : int }
type key = Odoc_model.Paths.Identifier.t

val v : unit -> t
Expand Down
9 changes: 3 additions & 6 deletions src/search/json_index/json_search.ml
Original file line number Diff line number Diff line change
Expand Up @@ -169,7 +169,7 @@ let of_entry ({ Entry.id; doc; kind } as entry) html occurrences =
in
let occurrences =
match occurrences with
| Some (`Direct direct, `Indirect indirect) ->
| Some { Odoc_occurrences.Table.direct; indirect } ->
[
( "occurrences",
`Object
Expand Down Expand Up @@ -211,12 +211,9 @@ let unit ?occurrences ppf u =
match occurrences with
| None -> None
| Some occurrences -> (
(* We don't want to include the [sub] field of occurrence tables. We use
a "polymorphic record" to avoid defining a type, but still get named
fields! *)
match Odoc_occurrences.Table.get occurrences id with
| Some x -> Some (`Direct x.direct, `Indirect x.indirect)
| None -> Some (`Direct 0, `Indirect 0))
| Some x -> Some x
| None -> Some { direct = 0; indirect = 0 })
in
let f first i =
let entries = Entry.entries_of_item i in
Expand Down

0 comments on commit 447e6ac

Please sign in to comment.