Skip to content

Commit 0149366

Browse files
panglesdjonludlam
authored andcommitted
Never add links from ghost locations
Signed-off-by: Paul-Elliot <[email protected]>
1 parent 0646170 commit 0149366

File tree

1 file changed

+20
-17
lines changed

1 file changed

+20
-17
lines changed

src/loader/implementation.ml

Lines changed: 20 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -156,17 +156,18 @@ module Analysis = struct
156156

157157
and expression env = function
158158
| { exp_desc = Texp_ident (p, _, value_description); exp_loc; _ } -> (
159-
(* Only generate anchor if the uid is in the location table. We don't
160-
link to modules outside of the compilation unit. *)
161-
match
162-
Shape.Uid.Tbl.find_opt (get_uid_to_loc env) value_description.val_uid
163-
with
164-
| Some _ -> [ (DefJmp value_description.val_uid, pos_of_loc exp_loc) ]
165-
| None when not exp_loc.loc_ghost -> (
166-
match p with
167-
| Pident id -> [ (LocalValue id, pos_of_loc exp_loc) ]
168-
| _ -> [])
169-
| None -> [])
159+
if exp_loc.loc_ghost then []
160+
else
161+
(* Only generate anchor if the uid is in the location table. We don't
162+
link to modules outside of the compilation unit. *)
163+
match
164+
Shape.Uid.Tbl.find_opt (get_uid_to_loc env) value_description.val_uid
165+
with
166+
| Some _ -> [ (DefJmp value_description.val_uid, pos_of_loc exp_loc) ]
167+
| None -> (
168+
match p with
169+
| Pident id -> [ (LocalValue id, pos_of_loc exp_loc) ]
170+
| _ -> []))
170171
| { exp_desc = Texp_constant _; _ } -> []
171172
| { exp_desc = Texp_let (_, vbs, e); _ } ->
172173
List.concat_map (value_binding env) vbs @ expression env e
@@ -178,13 +179,15 @@ module Analysis = struct
178179
| { exp_desc = Texp_tuple es; _ } -> List.concat_map (expression env) es
179180
| { exp_desc = Texp_construct (_, cons_description, es); exp_loc; _ } ->
180181
let x =
181-
match
182-
Shape.Uid.Tbl.find_opt (get_uid_to_loc env) cons_description.cstr_uid
183-
with
184-
| Some _ -> [ (DefJmp cons_description.cstr_uid, pos_of_loc exp_loc) ]
185-
| None -> []
182+
if exp_loc.loc_ghost then []
183+
else
184+
match
185+
Shape.Uid.Tbl.find_opt (get_uid_to_loc env) cons_description.cstr_uid
186+
with
187+
| Some _ -> [ (DefJmp cons_description.cstr_uid, pos_of_loc exp_loc) ]
188+
| None -> []
186189
in
187-
x @ List.concat_map (expression env) es
190+
x @ List.concat_map (expression env) es
188191
| { exp_desc = Texp_variant (_, Some e); _ } -> expression env e
189192
| { exp_desc = Texp_variant (_, None); _ } -> []
190193
| { exp_desc = Texp_record { fields; extended_expression; _ }; _ } ->

0 commit comments

Comments
 (0)