Skip to content

Commit 981b159

Browse files
panglesdjonludlam
authored andcommitted
Occurrences: Rename Definition to LocalDefinition when applicable
Signed-off-by: Paul-Elliot <[email protected]>
1 parent b9f3c09 commit 981b159

File tree

2 files changed

+12
-12
lines changed

2 files changed

+12
-12
lines changed

src/loader/implementation.ml

Lines changed: 10 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -141,10 +141,10 @@ module UidHashtbl = Shape.Uid.Tbl
141141

142142
(* Adds the local definitions found in traverse infos to the [loc_to_id] and
143143
[ident_to_id] tables. *)
144-
let populate_local_defs source_id poses loc_to_id ident_to_loc =
144+
let populate_local_defs source_id poses loc_to_id local_ident_to_loc =
145145
List.iter
146146
(function
147-
| Typedtree_traverse.Analysis.Definition id, loc ->
147+
| Typedtree_traverse.Analysis.LocalDefinition id, loc ->
148148
let name =
149149
Odoc_model.Names.LocalName.make_std
150150
(Printf.sprintf "local_%s_%d" (Ident.name id) (counter ()))
@@ -157,7 +157,7 @@ let populate_local_defs source_id poses loc_to_id ident_to_loc =
157157
LocHashtbl.add loc_to_id loc identifier
158158
| None -> ()
159159
);
160-
IdentHashtbl.add ident_to_loc id loc;
160+
IdentHashtbl.add local_ident_to_loc id loc;
161161
| _ -> ())
162162
poses
163163

@@ -281,13 +281,13 @@ let (>>=) a b = Option.map b a
281281

282282
(* Extract [Typedtree_traverse] occurrence information and turn them into proper
283283
source infos *)
284-
let process_occurrences env poses loc_to_id ident_to_loc =
284+
let process_occurrences env poses loc_to_id local_ident_to_loc =
285285
let open Odoc_model.Lang.Source_info in
286286
let process p find_in_env =
287287
match p with
288-
| Path.Pident id when IdentHashtbl.mem ident_to_loc id -> (
288+
| Path.Pident id when IdentHashtbl.mem local_ident_to_loc id -> (
289289
match
290-
LocHashtbl.find_opt loc_to_id (IdentHashtbl.find ident_to_loc id)
290+
LocHashtbl.find_opt loc_to_id (IdentHashtbl.find local_ident_to_loc id)
291291
with
292292
| None -> None
293293
| Some id ->
@@ -321,7 +321,7 @@ let process_occurrences env poses loc_to_id ident_to_loc =
321321
| Constructor _p, loc ->
322322
(* process p Ident_env.Path.read_constructor *) None >>= fun l ->
323323
(Constructor l, pos_of_loc loc)
324-
| Definition _, _ -> None)
324+
| LocalDefinition _, _ -> None)
325325
poses
326326

327327

@@ -348,15 +348,15 @@ let read_cmt_infos source_id_opt id cmt_info ~count_occurrences =
348348
not modify the anchors for existing anchors. *)
349349
in
350350
let loc_to_id = LocHashtbl.create 10
351-
and ident_to_loc = IdentHashtbl.create 10
351+
and local_ident_to_loc = IdentHashtbl.create 10
352352
and uid_to_id = UidHashtbl.create 10 in
353353
let () =
354354
(* populate [loc_to_id], [ident_to_id] and [uid_to_id] *)
355-
populate_local_defs source_id traverse_infos loc_to_id ident_to_loc;
355+
populate_local_defs source_id traverse_infos loc_to_id local_ident_to_loc;
356356
populate_global_defs env source_id loc_to_id uid_to_loc uid_to_id
357357
in
358358
let source_infos =
359-
process_occurrences env traverse_infos loc_to_id ident_to_loc
359+
process_occurrences env traverse_infos loc_to_id local_ident_to_loc
360360
|> add_definitions loc_to_id
361361
in
362362
( Some (shape, Shape.Uid.Tbl.to_map uid_to_id),

src/loader/typedtree_traverse.ml

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -2,7 +2,7 @@
22

33
module Analysis = struct
44
type annotation =
5-
| Definition of Ident.t
5+
| LocalDefinition of Ident.t
66
| Value of Path.t
77
| Module of Path.t
88
| ClassType of Path.t
@@ -38,7 +38,7 @@ module Analysis = struct
3838
in
3939
let maybe_localvalue id loc =
4040
match Ident_env.identifier_of_loc env loc with
41-
| None -> Some (Definition id, loc)
41+
| None -> Some (LocalDefinition id, loc)
4242
| Some _ -> None
4343
in
4444
let () =

0 commit comments

Comments
 (0)