@@ -265,31 +265,31 @@ let type_constant = function
265
265
| Const_nativeint _ -> instance_def Predef. type_nativeint
266
266
267
267
let constant : Parsetree.constant -> (Asttypes.constant, error) result = function
268
- | PConst_int (i ,None) ->
268
+ | Pconst_integer (i ,None) ->
269
269
begin
270
270
try Ok (Const_int (Misc.Int_literal_converter. int i))
271
271
with Failure _ -> Error (Literal_overflow " int" )
272
272
end
273
- | PConst_int (i ,Some 'l' ) ->
273
+ | Pconst_integer (i ,Some 'l' ) ->
274
274
begin
275
275
try Ok (Const_int32 (Misc.Int_literal_converter. int32 i))
276
276
with Failure _ -> Error (Literal_overflow " int32" )
277
277
end
278
- | PConst_int (i ,Some 'L' ) ->
278
+ | Pconst_integer (i ,Some 'L' ) ->
279
279
begin
280
280
try Ok (Const_int64 (Misc.Int_literal_converter. int64 i))
281
281
with Failure _ -> Error (Literal_overflow " int64" )
282
282
end
283
- | PConst_int (i ,Some 'n' ) ->
283
+ | Pconst_integer (i ,Some 'n' ) ->
284
284
begin
285
285
try Ok (Const_nativeint (Misc.Int_literal_converter. nativeint i))
286
286
with Failure _ -> Error (Literal_overflow " nativeint" )
287
287
end
288
- | PConst_int (i ,Some c ) -> Error (Unknown_literal (i, c))
289
- | PConst_char c -> Ok (Const_char c)
290
- | PConst_string (s ,d ) -> Ok (Const_string (s,d))
291
- | PConst_float (f ,None)-> Ok (Const_float f)
292
- | PConst_float (f ,Some c ) -> Error (Unknown_literal (f, c))
288
+ | Pconst_integer (i ,Some c ) -> Error (Unknown_literal (i, c))
289
+ | Pconst_char c -> Ok (Const_char c)
290
+ | Pconst_string (s ,d ) -> Ok (Const_string (s,d))
291
+ | Pconst_float (f ,None)-> Ok (Const_float f)
292
+ | Pconst_float (f ,Some c ) -> Error (Unknown_literal (f, c))
293
293
294
294
let constant_or_raise env loc cst =
295
295
match constant cst with
@@ -1070,14 +1070,14 @@ let rec type_pat ~constrs ~labels ~no_existentials ~mode ~explode ~env
1070
1070
pat_type = expected_ty;
1071
1071
pat_attributes = sp.ppat_attributes;
1072
1072
pat_env = ! env }
1073
- | Ppat_interval (PConst_char c1 , PConst_char c2 ) ->
1073
+ | Ppat_interval (Pconst_char c1 , Pconst_char c2 ) ->
1074
1074
let open Ast_helper.Pat in
1075
1075
let gloc = {loc with Location. loc_ghost= true } in
1076
1076
let rec loop c1 c2 =
1077
- if c1 = c2 then constant ~loc: gloc (PConst_char c1)
1077
+ if c1 = c2 then constant ~loc: gloc (Pconst_char c1)
1078
1078
else
1079
1079
or_ ~loc: gloc
1080
- (constant ~loc: gloc (PConst_char c1))
1080
+ (constant ~loc: gloc (Pconst_char c1))
1081
1081
(loop (Char. chr(Char. code c1 + 1 )) c2)
1082
1082
in
1083
1083
let p = if c1 < = c2 then loop c1 c2 else loop c2 c1 in
@@ -1948,7 +1948,7 @@ and type_expect_ ?in_function ?(recarg=Rejected) env sexp ty_expected =
1948
1948
exp_attributes = sexp.pexp_attributes;
1949
1949
exp_env = env }
1950
1950
end
1951
- | Pexp_constant (PConst_string (str , _ ) as cst ) -> (
1951
+ | Pexp_constant (Pconst_string (str , _ ) as cst ) -> (
1952
1952
let cst = constant_or_raise env loc cst in
1953
1953
(* Terrible hack for format strings *)
1954
1954
let ty_exp = expand_head env ty_expected in
@@ -2990,9 +2990,9 @@ and type_format loc str env =
2990
2990
| _ :: _ :: _ -> Some (mk_exp_loc (Pexp_tuple args)) in
2991
2991
mk_exp_loc (Pexp_construct (mk_lid_loc lid, arg)) in
2992
2992
let mk_cst cst = mk_exp_loc (Pexp_constant cst) in
2993
- let mk_int n = mk_cst (PConst_int (string_of_int n, None ))
2994
- and mk_string str = mk_cst (PConst_string (str, None ))
2995
- and mk_char chr = mk_cst (PConst_char chr) in
2993
+ let mk_int n = mk_cst (Pconst_integer (string_of_int n, None ))
2994
+ and mk_string str = mk_cst (Pconst_string (str, None ))
2995
+ and mk_char chr = mk_cst (Pconst_char chr) in
2996
2996
let rec mk_formatting_lit fmting = match fmting with
2997
2997
| Close_box ->
2998
2998
mk_constr " Close_box" []
0 commit comments