Skip to content

Commit bb0d859

Browse files
panglesdjonludlam
authored andcommitted
fmt
Signed-off-by: Paul-Elliot <[email protected]>
1 parent cf0880e commit bb0d859

File tree

1 file changed

+65
-52
lines changed

1 file changed

+65
-52
lines changed

src/loader/implementation.ml

Lines changed: 65 additions & 52 deletions
Original file line numberDiff line numberDiff line change
@@ -144,7 +144,8 @@ module IdentHashtbl = Hashtbl.Make (struct
144144
end)
145145

146146
module AnnotHashtbl = Hashtbl.Make (struct
147-
type t = Odoc_model.Lang.Source_info.annotation Odoc_model.Lang.Source_info.with_pos
147+
type t =
148+
Odoc_model.Lang.Source_info.annotation Odoc_model.Lang.Source_info.with_pos
148149
let equal l1 l2 = l1 = l2
149150
let hash = Hashtbl.hash
150151
end)
@@ -162,14 +163,14 @@ let populate_local_defs source_id poses loc_to_id local_ident_to_loc =
162163
(Printf.sprintf "local_%s_%d" (Ident.name id) (counter ()))
163164
in
164165
(match source_id with
165-
Some source_id ->
166+
| Some source_id ->
166167
let identifier =
167-
Odoc_model.Paths.Identifier.Mk.source_location_int (source_id, name)
168+
Odoc_model.Paths.Identifier.Mk.source_location_int
169+
(source_id, name)
168170
in
169171
LocHashtbl.add loc_to_id loc identifier
170-
| None -> ()
171-
);
172-
IdentHashtbl.add local_ident_to_loc id loc;
172+
| None -> ());
173+
IdentHashtbl.add local_ident_to_loc id loc
173174
| _ -> ())
174175
poses
175176

@@ -255,39 +256,44 @@ let anchor_of_identifier id =
255256
(* Adds the global definitions, found in the [uid_to_loc], to the [loc_to_id]
256257
and [uid_to_id] tables. *)
257258
let populate_global_defs env source_id loc_to_id uid_to_loc uid_to_id =
258-
match source_id with None -> () | Some source_id ->
259-
let mk_src_id id =
260-
let name = Odoc_model.Names.DefName.make_std (anchor_of_identifier id) in
261-
(Odoc_model.Paths.Identifier.Mk.source_location (source_id, name)
262-
:> Odoc_model.Paths.Identifier.SourceLocation.t)
263-
in
264-
let () =
265-
Ident_env.iter_located_identifier env @@ fun loc id ->
266-
LocHashtbl.add loc_to_id loc (mk_src_id id)
267-
in
268-
let mk_src_id () =
269-
let name =
270-
Odoc_model.Names.DefName.make_std (Printf.sprintf "def_%d" (counter ()))
271-
in
272-
(Odoc_model.Paths.Identifier.Mk.source_location (source_id, name)
273-
:> Odoc_model.Paths.Identifier.SourceLocation.t)
274-
in
275-
Shape.Uid.Tbl.iter
276-
(fun uid loc ->
277-
if loc.Location.loc_ghost then ()
278-
else
279-
match LocHashtbl.find_opt loc_to_id loc with
280-
| Some id -> UidHashtbl.add uid_to_id uid id
281-
| None -> (
282-
(* In case there is no entry for the location of the uid, we add one. *)
283-
match uid with
284-
| Item _ ->
285-
let id = mk_src_id () in
286-
LocHashtbl.add loc_to_id loc id;
287-
UidHashtbl.add uid_to_id uid id
288-
| Compilation_unit _ -> ()
289-
| _ -> ()))
290-
uid_to_loc
259+
match source_id with
260+
| None -> ()
261+
| Some source_id ->
262+
let mk_src_id id =
263+
let name =
264+
Odoc_model.Names.DefName.make_std (anchor_of_identifier id)
265+
in
266+
(Odoc_model.Paths.Identifier.Mk.source_location (source_id, name)
267+
:> Odoc_model.Paths.Identifier.SourceLocation.t)
268+
in
269+
let () =
270+
Ident_env.iter_located_identifier env @@ fun loc id ->
271+
LocHashtbl.add loc_to_id loc (mk_src_id id)
272+
in
273+
let mk_src_id () =
274+
let name =
275+
Odoc_model.Names.DefName.make_std
276+
(Printf.sprintf "def_%d" (counter ()))
277+
in
278+
(Odoc_model.Paths.Identifier.Mk.source_location (source_id, name)
279+
:> Odoc_model.Paths.Identifier.SourceLocation.t)
280+
in
281+
Shape.Uid.Tbl.iter
282+
(fun uid loc ->
283+
if loc.Location.loc_ghost then ()
284+
else
285+
match LocHashtbl.find_opt loc_to_id loc with
286+
| Some id -> UidHashtbl.add uid_to_id uid id
287+
| None -> (
288+
(* In case there is no entry for the location of the uid, we add one. *)
289+
match uid with
290+
| Item _ ->
291+
let id = mk_src_id () in
292+
LocHashtbl.add loc_to_id loc id;
293+
UidHashtbl.add uid_to_id uid id
294+
| Compilation_unit _ -> ()
295+
| _ -> ()))
296+
uid_to_loc
291297

292298
(* Extract [Typedtree_traverse] occurrence information and turn them into proper
293299
source infos *)
@@ -317,24 +323,30 @@ let process_occurrences env poses loc_to_id local_ident_to_loc =
317323
List.iter
318324
(function
319325
| Typedtree_traverse.Analysis.Value p, loc ->
320-
process p Ident_env.Path.read_value |> Option.iter @@ fun l ->
321-
AnnotHashtbl.replace occ_tbl (Value l, pos_of_loc loc) ()
326+
process p Ident_env.Path.read_value
327+
|> Option.iter @@ fun l ->
328+
AnnotHashtbl.replace occ_tbl (Value l, pos_of_loc loc) ()
322329
| Module p, loc ->
323-
process p Ident_env.Path.read_module |> Option.iter @@ fun l ->
324-
AnnotHashtbl.replace occ_tbl (Module l, pos_of_loc loc) ()
330+
process p Ident_env.Path.read_module
331+
|> Option.iter @@ fun l ->
332+
AnnotHashtbl.replace occ_tbl (Module l, pos_of_loc loc) ()
325333
| ClassType p, loc ->
326-
process p Ident_env.Path.read_class_type |> Option.iter @@ fun l ->
327-
AnnotHashtbl.replace occ_tbl (ClassType l, pos_of_loc loc) ()
334+
process p Ident_env.Path.read_class_type
335+
|> Option.iter @@ fun l ->
336+
AnnotHashtbl.replace occ_tbl (ClassType l, pos_of_loc loc) ()
328337
| ModuleType p, loc ->
329-
process p Ident_env.Path.read_module_type |> Option.iter @@ fun l ->
330-
AnnotHashtbl.replace occ_tbl (ModuleType l, pos_of_loc loc) ()
338+
process p Ident_env.Path.read_module_type
339+
|> Option.iter @@ fun l ->
340+
AnnotHashtbl.replace occ_tbl (ModuleType l, pos_of_loc loc) ()
331341
| Type p, loc ->
332-
process p Ident_env.Path.read_type |> Option.iter @@ fun l ->
333-
AnnotHashtbl.replace occ_tbl (Type l, pos_of_loc loc) ()
342+
process p Ident_env.Path.read_type
343+
|> Option.iter @@ fun l ->
344+
AnnotHashtbl.replace occ_tbl (Type l, pos_of_loc loc) ()
334345
| Constructor _p, loc ->
335346
(* process p Ident_env.Path.read_constructor *)
336-
None |> Option.iter @@ fun l ->
337-
AnnotHashtbl.replace occ_tbl (Constructor l, pos_of_loc loc) ()
347+
None
348+
|> Option.iter @@ fun l ->
349+
AnnotHashtbl.replace occ_tbl (Constructor l, pos_of_loc loc) ()
338350
| LocalDefinition _, _ -> ())
339351
poses;
340352
AnnotHashtbl.fold (fun k () acc -> k :: acc) occ_tbl []
@@ -366,7 +378,8 @@ let read_cmt_infos source_id_opt id cmt_info ~count_occurrences =
366378
and uid_to_id = UidHashtbl.create 10 in
367379
let () =
368380
(* populate [loc_to_id], [ident_to_id] and [uid_to_id] *)
369-
populate_local_defs source_id traverse_infos loc_to_id local_ident_to_loc;
381+
populate_local_defs source_id traverse_infos loc_to_id
382+
local_ident_to_loc;
370383
populate_global_defs env source_id loc_to_id uid_to_loc uid_to_id
371384
in
372385
let source_infos =

0 commit comments

Comments
 (0)