Skip to content

Commit 314a9dd

Browse files
committed
Revert "update locations for destructive substitutions"
This reverts commit f8a8070.
1 parent 26c4cab commit 314a9dd

File tree

3 files changed

+3
-19
lines changed

3 files changed

+3
-19
lines changed

typing/subst.ml

Lines changed: 1 addition & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -29,15 +29,13 @@ type t =
2929
modules: Path.t Path.Map.t;
3030
modtypes: module_type Ident.Map.t;
3131
for_saving: bool;
32-
loc: Location.t option;
3332
}
3433

3534
let identity =
3635
{ types = Path.Map.empty;
3736
modules = Path.Map.empty;
3837
modtypes = Ident.Map.empty;
3938
for_saving = false;
40-
loc = None;
4139
}
4240

4341
let add_type_path id p s = { s with types = Path.Map.add id (Path p) s.types }
@@ -53,13 +51,8 @@ let add_modtype id ty s = { s with modtypes = Ident.Map.add id ty s.modtypes }
5351

5452
let for_saving s = { s with for_saving = true }
5553

56-
let change_locs s loc = { s with loc = Some loc }
57-
5854
let loc s x =
59-
match s.loc with
60-
| Some l -> l
61-
| None ->
62-
if s.for_saving && not !Clflags.keep_locs then Location.none else x
55+
if s.for_saving && not !Clflags.keep_locs then Location.none else x
6356

6457
let remove_loc =
6558
let open Ast_mapper in
@@ -502,11 +495,6 @@ let merge_tbls f m1 m2 =
502495
let merge_path_maps f m1 m2 =
503496
Path.Map.fold (fun k d accu -> Path.Map.add k (f d) accu) m1 m2
504497

505-
let keep_latest_loc l1 l2 =
506-
match l2 with
507-
| None -> l1
508-
| Some _ -> l2
509-
510498
let type_replacement s = function
511499
| Path p -> Path (type_path s p)
512500
| Type_function { params; body } ->
@@ -522,5 +510,4 @@ let compose s1 s2 =
522510
modules = merge_path_maps (module_path s2) s1.modules s2.modules;
523511
modtypes = merge_tbls (modtype s2) s1.modtypes s2.modtypes;
524512
for_saving = s1.for_saving || s2.for_saving;
525-
loc = keep_latest_loc s1.loc s2.loc;
526513
}

typing/subst.mli

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -42,7 +42,6 @@ val add_module_path: Path.t -> Path.t -> t -> t
4242
val add_modtype: Ident.t -> module_type -> t -> t
4343
val for_saving: t -> t
4444
val reset_for_saving: unit -> unit
45-
val change_locs: t -> Location.t -> t
4645

4746
val module_path: t -> Path.t -> Path.t
4847
val type_path: t -> Path.t -> Path.t

typing/typemod.ml

Lines changed: 2 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -589,15 +589,13 @@ let merge_constraint initial_env remove_aliases loc sg constr =
589589
With_cannot_remove_constrained_type));
590590
fun s path -> Subst.add_type_function path ~params ~body s
591591
in
592-
let sub = Subst.change_locs Subst.identity loc in
593-
let sub = List.fold_left how_to_extend_subst sub !real_ids in
592+
let sub = List.fold_left how_to_extend_subst Subst.identity !real_ids in
594593
Subst.signature sub sg
595594
| (_, _, Twith_modsubst (real_path, _)) ->
596-
let sub = Subst.change_locs Subst.identity loc in
597595
let sub =
598596
List.fold_left
599597
(fun s path -> Subst.add_module_path path real_path s)
600-
sub
598+
Subst.identity
601599
!real_ids
602600
in
603601
Subst.signature sub sg

0 commit comments

Comments
 (0)