Skip to content

Commit c19e8b2

Browse files
committed
Refactor environment lookup functions
1 parent 27f621d commit c19e8b2

34 files changed

+2133
-1737
lines changed

debugger/eval.ml

Lines changed: 21 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -75,24 +75,27 @@ let value_path event env path =
7575
fatal_error ("Cannot find address for: " ^ (Path.name path))
7676

7777
let rec expression event env = function
78-
E_ident lid ->
79-
begin try
80-
let (p, valdesc) = Env.lookup_value lid env in
81-
(begin match valdesc.val_kind with
82-
Val_ivar (_, cl_num) ->
83-
let (p0, _) =
84-
Env.lookup_value (Longident.Lident ("self-" ^ cl_num)) env
85-
in
86-
let v = value_path event env p0 in
87-
let i = value_path event env p in
88-
Debugcom.Remote_value.field v (Debugcom.Remote_value.obj i)
89-
| _ ->
90-
value_path event env p
91-
end,
92-
Ctype.correct_levels valdesc.val_type)
93-
with Not_found ->
94-
raise(Error(Unbound_long_identifier lid))
95-
end
78+
| E_ident lid -> begin
79+
match Env.find_value_by_name lid env with
80+
| (p, valdesc) ->
81+
let v =
82+
match valdesc.val_kind with
83+
| Val_ivar (_, cl_num) ->
84+
let (p0, _) =
85+
Env.find_value_by_name
86+
(Longident.Lident ("self-" ^ cl_num)) env
87+
in
88+
let v = value_path event env p0 in
89+
let i = value_path event env p in
90+
Debugcom.Remote_value.field v (Debugcom.Remote_value.obj i)
91+
| _ ->
92+
value_path event env p
93+
in
94+
let typ = Ctype.correct_levels valdesc.val_type in
95+
v, typ
96+
| exception Not_found ->
97+
raise(Error(Unbound_long_identifier lid))
98+
end
9699
| E_result ->
97100
begin match event with
98101
Some {ev_ev = {ev_kind = Event_after ty; ev_typsubst = subst}}

debugger/loadprinter.ml

Lines changed: 20 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -99,10 +99,14 @@ let init () =
9999

100100
let match_printer_type desc typename =
101101
let printer_type =
102-
try
103-
Env.lookup_type (Ldot(Lident "Topdirs", typename)) Env.empty
104-
with Not_found ->
105-
raise (Error(Unbound_identifier(Ldot(Lident "Topdirs", typename)))) in
102+
match
103+
Env.find_type_by_name
104+
(Ldot(Lident "Topdirs", typename)) Env.empty
105+
with
106+
| path, _ -> path
107+
| exception Not_found ->
108+
raise (Error(Unbound_identifier(Ldot(Lident "Topdirs", typename))))
109+
in
106110
Ctype.begin_def();
107111
let ty_arg = Ctype.newvar() in
108112
Ctype.unify Env.empty
@@ -113,17 +117,18 @@ let match_printer_type desc typename =
113117
ty_arg
114118

115119
let find_printer_type lid =
116-
try
117-
let (path, desc) = Env.lookup_value lid Env.empty in
118-
let (ty_arg, is_old_style) =
119-
try
120-
(match_printer_type desc "printer_type_new", false)
121-
with Ctype.Unify _ ->
122-
(match_printer_type desc "printer_type_old", true) in
123-
(ty_arg, path, is_old_style)
124-
with
125-
| Not_found -> raise(Error(Unbound_identifier lid))
126-
| Ctype.Unify _ -> raise(Error(Wrong_type lid))
120+
match Env.find_value_by_name lid Env.empty with
121+
| (path, desc) -> begin
122+
match match_printer_type desc "printer_type_new" with
123+
| ty_arg -> (ty_arg, path, false)
124+
| exception Ctype.Unify _ -> begin
125+
match match_printer_type desc "printer_type_old" with
126+
| ty_arg -> (ty_arg, path, true)
127+
| exception Ctype.Unify _ -> raise(Error(Wrong_type lid))
128+
end
129+
end
130+
| exception Not_found ->
131+
raise(Error(Unbound_identifier lid))
127132

128133
let install_printer ppf lid =
129134
let (ty_arg, path, is_old_style) = find_printer_type lid in

lambda/lambda.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -656,7 +656,7 @@ let transl_prim mod_name name =
656656
let pers = Ident.create_persistent mod_name in
657657
let env = Env.add_persistent_structure pers Env.empty in
658658
let lid = Longident.Ldot (Longident.Lident mod_name, name) in
659-
match Env.lookup_value lid env with
659+
match Env.find_value_by_name lid env with
660660
| path, _ -> transl_value_path Location.none env path
661661
| exception Not_found ->
662662
fatal_error ("Primitive " ^ name ^ " not found.")

lambda/matching.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1766,7 +1766,7 @@ let get_mod_field modname field =
17661766
| exception Not_found ->
17671767
fatal_error ("Module " ^ modname ^ " unavailable.")
17681768
| env -> (
1769-
match Env.lookup_value (Longident.Lident field) env with
1769+
match Env.find_value_by_name (Longident.Lident field) env with
17701770
| exception Not_found ->
17711771
fatal_error ("Primitive " ^ modname ^ "." ^ field ^ " not found.")
17721772
| path, _ -> transl_value_path Location.none env path

testsuite/tests/basic/patmatch_split_no_or.ml

Lines changed: 26 additions & 26 deletions
Original file line numberDiff line numberDiff line change
@@ -16,10 +16,10 @@ let last_is_anys = function
1616
[%%expect{|
1717
(let
1818
(last_is_anys/10 =
19-
(function param/11 : int
19+
(function param/12 : int
2020
(catch
21-
(if (field 0 param/11) (if (field 1 param/11) (exit 1) 1)
22-
(if (field 1 param/11) (exit 1) 2))
21+
(if (field 0 param/12) (if (field 1 param/12) (exit 1) 1)
22+
(if (field 1 param/12) (exit 1) 2))
2323
with (1) 3)))
2424
(apply (field 1 (global Toploop!)) "last_is_anys" last_is_anys/10))
2525
val last_is_anys : bool * bool -> int = <fun>
@@ -32,13 +32,13 @@ let last_is_vars = function
3232
;;
3333
[%%expect{|
3434
(let
35-
(last_is_vars/16 =
36-
(function param/19 : int
35+
(last_is_vars/17 =
36+
(function param/21 : int
3737
(catch
38-
(if (field 0 param/19) (if (field 1 param/19) (exit 3) 1)
39-
(if (field 1 param/19) (exit 3) 2))
38+
(if (field 0 param/21) (if (field 1 param/21) (exit 3) 1)
39+
(if (field 1 param/21) (exit 3) 2))
4040
with (3) 3)))
41-
(apply (field 1 (global Toploop!)) "last_is_vars" last_is_vars/16))
41+
(apply (field 1 (global Toploop!)) "last_is_vars" last_is_vars/17))
4242
val last_is_vars : bool * bool -> int = <fun>
4343
|}]
4444

@@ -52,12 +52,12 @@ type t += A | B of unit | C of bool * int;;
5252
0a
5353
type t = ..
5454
(let
55-
(A/23 = (makeblock 248 "A" (caml_fresh_oo_id 0))
56-
B/24 = (makeblock 248 "B" (caml_fresh_oo_id 0))
57-
C/25 = (makeblock 248 "C" (caml_fresh_oo_id 0)))
58-
(seq (apply (field 1 (global Toploop!)) "A/23" A/23)
59-
(apply (field 1 (global Toploop!)) "B/24" B/24)
60-
(apply (field 1 (global Toploop!)) "C/25" C/25)))
55+
(A/25 = (makeblock 248 "A" (caml_fresh_oo_id 0))
56+
B/26 = (makeblock 248 "B" (caml_fresh_oo_id 0))
57+
C/27 = (makeblock 248 "C" (caml_fresh_oo_id 0)))
58+
(seq (apply (field 1 (global Toploop!)) "A/25" A/25)
59+
(apply (field 1 (global Toploop!)) "B/26" B/26)
60+
(apply (field 1 (global Toploop!)) "C/27" C/27)))
6161
type t += A | B of unit | C of bool * int
6262
|}]
6363

@@ -71,20 +71,20 @@ let f = function
7171
;;
7272
[%%expect{|
7373
(let
74-
(C/25 = (apply (field 0 (global Toploop!)) "C/25")
75-
B/24 = (apply (field 0 (global Toploop!)) "B/24")
76-
A/23 = (apply (field 0 (global Toploop!)) "A/23")
77-
f/26 =
78-
(function param/27 : int
79-
(let (*match*/28 =a (field 0 param/27))
74+
(C/27 = (apply (field 0 (global Toploop!)) "C/27")
75+
B/26 = (apply (field 0 (global Toploop!)) "B/26")
76+
A/25 = (apply (field 0 (global Toploop!)) "A/25")
77+
f/28 =
78+
(function param/30 : int
79+
(let (*match*/31 =a (field 0 param/30))
8080
(catch
81-
(if (== *match*/28 A/23) (if (field 1 param/27) 1 (exit 8))
81+
(if (== *match*/31 A/25) (if (field 1 param/30) 1 (exit 8))
8282
(exit 8))
8383
with (8)
84-
(if (field 1 param/27)
85-
(if (== (field 0 *match*/28) B/24) 2
86-
(if (== (field 0 *match*/28) C/25) 3 4))
87-
(if (field 2 param/27) 12 11))))))
88-
(apply (field 1 (global Toploop!)) "f" f/26))
84+
(if (field 1 param/30)
85+
(if (== (field 0 *match*/31) B/26) 2
86+
(if (== (field 0 *match*/31) C/27) 3 4))
87+
(if (field 2 param/30) 12 11))))))
88+
(apply (field 1 (global Toploop!)) "f" f/28))
8989
val f : t * bool * bool -> int = <fun>
9090
|}]

testsuite/tests/generalized-open/gpr1506.ml

Lines changed: 6 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -100,9 +100,9 @@ include struct open struct type t = T end let x = T end
100100
Line 1, characters 15-41:
101101
1 | include struct open struct type t = T end let x = T end
102102
^^^^^^^^^^^^^^^^^^^^^^^^^^
103-
Error: The type t/143 introduced by this open appears in the signature
103+
Error: The type t/150 introduced by this open appears in the signature
104104
Line 1, characters 46-47:
105-
The value x has no valid type if t/143 is hidden
105+
The value x has no valid type if t/150 is hidden
106106
|}];;
107107

108108
module A = struct
@@ -120,9 +120,9 @@ Lines 3-6, characters 4-7:
120120
4 | type t = T
121121
5 | let x = T
122122
6 | end
123-
Error: The type t/149 introduced by this open appears in the signature
123+
Error: The type t/156 introduced by this open appears in the signature
124124
Line 7, characters 8-9:
125-
The value y has no valid type if t/149 is hidden
125+
The value y has no valid type if t/156 is hidden
126126
|}];;
127127

128128
module A = struct
@@ -139,9 +139,9 @@ Lines 3-5, characters 4-7:
139139
3 | ....open struct
140140
4 | type t = T
141141
5 | end
142-
Error: The type t/155 introduced by this open appears in the signature
142+
Error: The type t/162 introduced by this open appears in the signature
143143
Line 6, characters 8-9:
144-
The value y has no valid type if t/155 is hidden
144+
The value y has no valid type if t/162 is hidden
145145
|}]
146146

147147
(* It was decided to not allow this anymore. *)

testsuite/tests/messages/precise_locations.ml

Lines changed: 6 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -48,21 +48,21 @@ type t =
4848
#warnings "@3";;
4949
let x =
5050
Foo ();;
51-
(* "Foo ()": the whole construct, with arguments, is deprecated *)
51+
5252
[%%expect{|
5353
type t = Foo of unit | Bar
54-
Line 6, characters 0-6:
54+
Line 6, characters 0-3:
5555
6 | Foo ();;
56-
^^^^^^
56+
^^^
5757
Error (alert deprecated): Foo
5858
|}];;
5959
function
6060
Foo _ -> () | Bar -> ();;
61-
(* "Foo _", the whole construct is deprecated *)
61+
6262
[%%expect{|
63-
Line 2, characters 0-5:
63+
Line 2, characters 0-3:
6464
2 | Foo _ -> () | Bar -> ();;
65-
^^^^^
65+
^^^
6666
Error (alert deprecated): Foo
6767
|}];;
6868

testsuite/tests/typing-objects/Tests.ml

Lines changed: 4 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -931,8 +931,8 @@ class a = object (self) val x = self#m method m = 3 end;;
931931
Line 1, characters 32-36:
932932
1 | class a = object (self) val x = self#m method m = 3 end;;
933933
^^^^
934-
Error: The instance variable self
935-
cannot be accessed from the definition of another instance variable
934+
Error: The self variable self
935+
cannot be accessed from the definition of an instance variable
936936
|}];;
937937

938938
class a = object method m = 3 end
@@ -942,8 +942,6 @@ class a : object method m : int end
942942
Line 2, characters 44-49:
943943
2 | class b = object inherit a as super val x = super#m end;;
944944
^^^^^
945-
Error: The instance variable super
946-
cannot be accessed from the definition of another instance variable
945+
Error: The ancestor variable super
946+
cannot be accessed from the definition of an instance variable
947947
|}];;
948-
949-

testsuite/tests/typing-warnings/open_warnings.ml

Lines changed: 12 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -43,9 +43,9 @@ Line 2, characters 2-13:
4343
2 | type t0 = A (* unused type and constructor *)
4444
^^^^^^^^^^^
4545
Warning 34: unused type t0.
46-
Line 2, characters 2-13:
46+
Line 2, characters 12-13:
4747
2 | type t0 = A (* unused type and constructor *)
48-
^^^^^^^^^^^
48+
^
4949
Warning 37: unused constructor A.
5050
module T3 : sig end
5151
|}]
@@ -61,9 +61,9 @@ Line 3, characters 20-30:
6161
3 | module M = struct type t = A end (* unused type and constructor *)
6262
^^^^^^^^^^
6363
Warning 34: unused type t.
64-
Line 3, characters 20-30:
64+
Line 3, characters 29-30:
6565
3 | module M = struct type t = A end (* unused type and constructor *)
66-
^^^^^^^^^^
66+
^
6767
Warning 37: unused constructor A.
6868
Line 4, characters 2-8:
6969
4 | open M (* unused open; no shadowing (A below refers to the one in t0) *)
@@ -87,9 +87,9 @@ Line 2, characters 2-13:
8787
2 | type t0 = A (* unused type and constructor *)
8888
^^^^^^^^^^^
8989
Warning 34: unused type t0.
90-
Line 2, characters 2-13:
90+
Line 2, characters 12-13:
9191
2 | type t0 = A (* unused type and constructor *)
92-
^^^^^^^^^^^
92+
^
9393
Warning 37: unused constructor A.
9494
module T5 : sig end
9595
|}]
@@ -131,9 +131,9 @@ Line 2, characters 2-13:
131131
2 | type t0 = A (* unused type and constructor *)
132132
^^^^^^^^^^^
133133
Warning 34: unused type t0.
134-
Line 2, characters 2-13:
134+
Line 2, characters 12-13:
135135
2 | type t0 = A (* unused type and constructor *)
136-
^^^^^^^^^^^
136+
^
137137
Warning 37: unused constructor A.
138138
module T3_bis : sig end
139139
|}]
@@ -149,9 +149,9 @@ Line 3, characters 20-30:
149149
3 | module M = struct type t = A end (* unused type and constructor *)
150150
^^^^^^^^^^
151151
Warning 34: unused type t.
152-
Line 3, characters 20-30:
152+
Line 3, characters 29-30:
153153
3 | module M = struct type t = A end (* unused type and constructor *)
154-
^^^^^^^^^^
154+
^
155155
Warning 37: unused constructor A.
156156
Line 4, characters 2-9:
157157
4 | open! M (* unused open; no shadowing (A below refers to the one in t0) *)
@@ -171,9 +171,9 @@ Line 2, characters 2-13:
171171
2 | type t0 = A (* unused type and constructor *)
172172
^^^^^^^^^^^
173173
Warning 34: unused type t0.
174-
Line 2, characters 2-13:
174+
Line 2, characters 12-13:
175175
2 | type t0 = A (* unused type and constructor *)
176-
^^^^^^^^^^^
176+
^
177177
Warning 37: unused constructor A.
178178
module T5_bis : sig end
179179
|}]

0 commit comments

Comments
 (0)