Skip to content

Commit 6d8cc9a

Browse files
committed
Occurrences: don't expose sub in occurrence table
Signed-off-by: Paul-Elliot <peada@free.fr>
1 parent fd15b16 commit 6d8cc9a

File tree

3 files changed

+15
-6
lines changed

3 files changed

+15
-6
lines changed

src/occurrences/table.ml

Lines changed: 11 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,9 +1,14 @@
11
module H = Hashtbl.Make (Odoc_model.Paths.Identifier)
22

3-
type t = item H.t
4-
and item = { direct : int; indirect : int; sub : item H.t }
3+
type t = internal_item H.t
4+
and internal_item = { direct : int; indirect : int; sub : t }
55
type key = Odoc_model.Paths.Identifier.t
66

7+
type item = { direct : int; indirect : int }
8+
9+
let internal_to_item : internal_item -> item =
10+
fun { direct; indirect; _ } -> { direct; indirect }
11+
712
let v_item () = { direct = 0; indirect = 0; sub = H.create 0 }
813

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

86+
let get t id =
87+
match get t id with None -> None | Some i -> Some (internal_to_item i)
88+
8189
let rec iter f tbl =
8290
H.iter
8391
(fun id v ->
8492
iter f v.sub;
93+
let v = internal_to_item v in
8594
f id v)
8695
tbl

src/occurrences/table.mli

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,5 @@
11
type t
2-
type item = { direct : int; indirect : int; sub : t }
2+
type item = { direct : int; indirect : int }
33
type key = Odoc_model.Paths.Identifier.t
44

55
val v : unit -> t

src/search/json_index/json_search.ml

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -169,7 +169,7 @@ let of_entry ({ Entry.id; doc; kind } as entry) html occurrences =
169169
in
170170
let occurrences =
171171
match occurrences with
172-
| Some (`Direct direct, `Indirect indirect) ->
172+
| Some { Odoc_occurrences.Table.direct; indirect } ->
173173
[
174174
( "occurrences",
175175
`Object
@@ -215,8 +215,8 @@ let unit ?occurrences ppf u =
215215
a "polymorphic record" to avoid defining a type, but still get named
216216
fields! *)
217217
match Odoc_occurrences.Table.get occurrences id with
218-
| Some x -> Some (`Direct x.direct, `Indirect x.indirect)
219-
| None -> Some (`Direct 0, `Indirect 0))
218+
| Some x -> Some x
219+
| None -> Some { direct = 0; indirect = 0 })
220220
in
221221
let f first i =
222222
let entries = Entry.entries_of_item i in

0 commit comments

Comments
 (0)