File tree Expand file tree Collapse file tree 3 files changed +15
-9
lines changed Expand file tree Collapse file tree 3 files changed +15
-9
lines changed Original file line number Diff line number Diff line change 11module 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 }
55type 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+
712let v_item () = { direct = 0 ; indirect = 0 ; sub = H. create 0 }
813
914let 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+
8189let 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
Original file line number Diff line number Diff line change 11type t
2- type item = { direct : int ; indirect : int ; sub : t }
2+ type item = { direct : int ; indirect : int }
33type key = Odoc_model.Paths.Identifier .t
44
55val v : unit -> t
Original file line number Diff line number Diff 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
@@ -211,12 +211,9 @@ let unit ?occurrences ppf u =
211211 match occurrences with
212212 | None -> None
213213 | Some occurrences -> (
214- (* We don't want to include the [sub] field of occurrence tables. We use
215- a "polymorphic record" to avoid defining a type, but still get named
216- fields! *)
217214 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 ) )
215+ | Some x -> Some x
216+ | None -> Some { direct = 0 ; indirect = 0 } )
220217 in
221218 let f first i =
222219 let entries = Entry. entries_of_item i in
You can’t perform that action at this time.
0 commit comments