Skip to content

Commit 6095df9

Browse files
committed
Rename parsetree constants.
PConst -> Pconst int -> integer
1 parent 6bb1c73 commit 6095df9

9 files changed

+65
-65
lines changed

parsing/ast_mapper.ml

+5-5
Original file line numberDiff line numberDiff line change
@@ -626,13 +626,13 @@ let default_mapper =
626626

627627
let rec extension_of_error {loc; msg; if_highlight; sub} =
628628
{ loc; txt = "ocaml.error" },
629-
PStr ([Str.eval (Exp.constant (PConst_string (msg, None)));
630-
Str.eval (Exp.constant (PConst_string (if_highlight, None)))] @
629+
PStr ([Str.eval (Exp.constant (Pconst_string (msg, None)));
630+
Str.eval (Exp.constant (Pconst_string (if_highlight, None)))] @
631631
(List.map (fun ext -> Str.extension (extension_of_error ext)) sub))
632632

633633
let attribute_of_warning loc s =
634634
{ loc; txt = "ocaml.ppwarning" },
635-
PStr ([Str.eval ~loc (Exp.constant (PConst_string (s, None)))])
635+
PStr ([Str.eval ~loc (Exp.constant (Pconst_string (s, None)))])
636636

637637
module StringMap = Map.Make(struct
638638
type t = string
@@ -660,7 +660,7 @@ module PpxContext = struct
660660

661661
let lid name = { txt = Lident name; loc = Location.none }
662662

663-
let make_string x = Exp.constant (PConst_string (x, None))
663+
let make_string x = Exp.constant (Pconst_string (x, None))
664664

665665
let make_bool x =
666666
if x
@@ -715,7 +715,7 @@ module PpxContext = struct
715715
let restore fields =
716716
let field name payload =
717717
let rec get_string = function
718-
| { pexp_desc = Pexp_constant (PConst_string (str, None)) } -> str
718+
| { pexp_desc = Pexp_constant (Pconst_string (str, None)) } -> str
719719
| _ -> raise_errorf "Internal error: invalid [@@@ocaml.ppx.context \
720720
{ %s }] string syntax" name
721721
and get_bool pexp =

parsing/builtin_attributes.ml

+5-5
Original file line numberDiff line numberDiff line change
@@ -14,7 +14,7 @@ open Asttypes
1414
open Parsetree
1515

1616
let string_of_cst = function
17-
| PConst_string(s, _) -> Some s
17+
| Pconst_string(s, _) -> Some s
1818
| _ -> None
1919

2020
let string_of_payload = function
@@ -37,13 +37,13 @@ let rec error_of_extension ext =
3737
in
3838
begin match p with
3939
| PStr({pstr_desc=Pstr_eval
40-
({pexp_desc=Pexp_constant(PConst_string(msg,_))}, _)}::
40+
({pexp_desc=Pexp_constant(Pconst_string(msg,_))}, _)}::
4141
{pstr_desc=Pstr_eval
42-
({pexp_desc=Pexp_constant(PConst_string(if_highlight,_))}, _)}::
42+
({pexp_desc=Pexp_constant(Pconst_string(if_highlight,_))}, _)}::
4343
inner) ->
4444
Location.error ~loc ~if_highlight ~sub:(sub_from inner) msg
4545
| PStr({pstr_desc=Pstr_eval
46-
({pexp_desc=Pexp_constant(PConst_string(msg,_))}, _)}::inner) ->
46+
({pexp_desc=Pexp_constant(Pconst_string(msg,_))}, _)}::inner) ->
4747
Location.error ~loc ~sub:(sub_from inner) msg
4848
| _ -> Location.errorf ~loc "Invalid syntax for extension '%s'." txt
4949
end
@@ -113,7 +113,7 @@ let emit_external_warnings =
113113
begin match a with
114114
| {txt="ocaml.ppwarning"|"ppwarning"},
115115
PStr[{pstr_desc=Pstr_eval({pexp_desc=Pexp_constant
116-
(PConst_string (s, _))},_);
116+
(Pconst_string (s, _))},_);
117117
pstr_loc}] ->
118118
Location.prerr_warning pstr_loc (Warnings.Preprocessor s)
119119
| _ -> ()

parsing/docstrings.ml

+2-2
Original file line numberDiff line numberDiff line change
@@ -85,7 +85,7 @@ let doc_loc = {txt = "ocaml.doc"; loc = Location.none}
8585
let docs_attr ds =
8686
let open Parsetree in
8787
let exp =
88-
{ pexp_desc = Pexp_constant (PConst_string(ds.ds_body, None));
88+
{ pexp_desc = Pexp_constant (Pconst_string(ds.ds_body, None));
8989
pexp_loc = ds.ds_loc;
9090
pexp_attributes = []; }
9191
in
@@ -134,7 +134,7 @@ let text_loc = {txt = "ocaml.text"; loc = Location.none}
134134
let text_attr ds =
135135
let open Parsetree in
136136
let exp =
137-
{ pexp_desc = Pexp_constant (PConst_string(ds.ds_body, None));
137+
{ pexp_desc = Pexp_constant (Pconst_string(ds.ds_body, None));
138138
pexp_loc = ds.ds_loc;
139139
pexp_attributes = []; }
140140
in

parsing/parser.mly

+14-14
Original file line numberDiff line numberDiff line change
@@ -79,18 +79,18 @@ let neg_string f =
7979

8080
let mkuminus name arg =
8181
match name, arg.pexp_desc with
82-
| "-", Pexp_constant(PConst_int (n,m)) ->
83-
mkexp(Pexp_constant(PConst_int(neg_string n,m)))
84-
| ("-" | "-."), Pexp_constant(PConst_float (f, m)) ->
85-
mkexp(Pexp_constant(PConst_float(neg_string f, m)))
82+
| "-", Pexp_constant(Pconst_integer (n,m)) ->
83+
mkexp(Pexp_constant(Pconst_integer(neg_string n,m)))
84+
| ("-" | "-."), Pexp_constant(Pconst_float (f, m)) ->
85+
mkexp(Pexp_constant(Pconst_float(neg_string f, m)))
8686
| _ ->
8787
mkexp(Pexp_apply(mkoperator ("~" ^ name) 1, [Nolabel, arg]))
8888

8989
let mkuplus name arg =
9090
let desc = arg.pexp_desc in
9191
match name, desc with
92-
| "+", Pexp_constant(PConst_int _)
93-
| ("+" | "+."), Pexp_constant(PConst_float _) -> mkexp desc
92+
| "+", Pexp_constant(Pconst_integer _)
93+
| ("+" | "+."), Pexp_constant(Pconst_float _) -> mkexp desc
9494
| _ ->
9595
mkexp(Pexp_apply(mkoperator ("~" ^ name) 1, [Nolabel, arg]))
9696

@@ -2169,17 +2169,17 @@ label:
21692169
/* Constants */
21702170
21712171
constant:
2172-
| INT { let (n, m) = $1 in PConst_int (n, m) }
2173-
| CHAR { PConst_char $1 }
2174-
| STRING { let (s, d) = $1 in PConst_string (s, d) }
2175-
| FLOAT { let (f, m) = $1 in PConst_float (f, m) }
2172+
| INT { let (n, m) = $1 in Pconst_integer (n, m) }
2173+
| CHAR { Pconst_char $1 }
2174+
| STRING { let (s, d) = $1 in Pconst_string (s, d) }
2175+
| FLOAT { let (f, m) = $1 in Pconst_float (f, m) }
21762176
;
21772177
signed_constant:
21782178
constant { $1 }
2179-
| MINUS INT { let (n, m) = $2 in PConst_int("-" ^ n, m) }
2180-
| MINUS FLOAT { let (f, m) = $2 in PConst_float("-" ^ f, m) }
2181-
| PLUS INT { let (n, m) = $2 in PConst_int (n, m) }
2182-
| PLUS FLOAT { let (f, m) = $2 in PConst_float(f, m) }
2179+
| MINUS INT { let (n, m) = $2 in Pconst_integer("-" ^ n, m) }
2180+
| MINUS FLOAT { let (f, m) = $2 in Pconst_float("-" ^ f, m) }
2181+
| PLUS INT { let (n, m) = $2 in Pconst_integer (n, m) }
2182+
| PLUS FLOAT { let (f, m) = $2 in Pconst_float(f, m) }
21832183
;
21842184
21852185
/* Identifiers and long identifiers */

parsing/parsetree.mli

+4-4
Original file line numberDiff line numberDiff line change
@@ -15,19 +15,19 @@
1515
open Asttypes
1616

1717
type constant =
18-
PConst_int of string * char option
18+
Pconst_integer of string * char option
1919
(* 3 3l 3L 3n
2020
2121
Suffixes [g-z][G-Z] are accepted by the parser.
2222
Suffixes except 'l', 'L' and 'n' are rejected by the typechecker
2323
*)
24-
| PConst_char of char
24+
| Pconst_char of char
2525
(* 'c' *)
26-
| PConst_string of string * string option
26+
| Pconst_string of string * string option
2727
(* "constant"
2828
{delim|other constant|delim}
2929
*)
30-
| PConst_float of string * char option
30+
| Pconst_float of string * char option
3131
(* 3.4 2e5 1.4e-4
3232
3333
Suffixes [g-z][G-Z] are accepted by the parser.

parsing/pprintast.ml

+7-7
Original file line numberDiff line numberDiff line change
@@ -168,13 +168,13 @@ class printer ()= object(self:'self)
168168
pp f "%a(%a)" self#longident y self#longident s
169169
method longident_loc f x = pp f "%a" self#longident x.txt
170170
method constant f = function
171-
| PConst_char i -> pp f "%C" i
172-
| PConst_string (i, None) -> pp f "%S" i
173-
| PConst_string (i, Some delim) -> pp f "{%s|%s|%s}" delim i delim
174-
| PConst_int (i,None) -> self#paren (i.[0]='-') (fun f -> pp f "%s") f i
175-
| PConst_int (i,Some m) -> self#paren (i.[0]='-') (fun f (i,m) -> pp f "%s%c" i m) f (i,m)
176-
| PConst_float (i,None) -> self#paren (i.[0]='-') (fun f -> pp f "%s") f i
177-
| PConst_float (i, Some m) -> self#paren (i.[0]='-') (fun f (i,m) -> pp f "%s%c" i m) f (i,m)
171+
| Pconst_char i -> pp f "%C" i
172+
| Pconst_string (i, None) -> pp f "%S" i
173+
| Pconst_string (i, Some delim) -> pp f "{%s|%s|%s}" delim i delim
174+
| Pconst_integer (i,None) -> self#paren (i.[0]='-') (fun f -> pp f "%s") f i
175+
| Pconst_integer (i,Some m) -> self#paren (i.[0]='-') (fun f (i,m) -> pp f "%s%c" i m) f (i,m)
176+
| Pconst_float (i,None) -> self#paren (i.[0]='-') (fun f -> pp f "%s") f i
177+
| Pconst_float (i, Some m) -> self#paren (i.[0]='-') (fun f (i,m) -> pp f "%s%c" i m) f (i,m)
178178

179179
(* trailing space*)
180180
method mutable_flag f = function

parsing/printast.ml

+5-5
Original file line numberDiff line numberDiff line change
@@ -55,12 +55,12 @@ let fmt_char_option f = function
5555

5656
let fmt_constant f x =
5757
match x with
58-
| PConst_int (i,m) -> fprintf f "PConst_int (%s,%a)" i fmt_char_option m;
59-
| PConst_char (c) -> fprintf f "PConst_char %02x" (Char.code c);
60-
| PConst_string (s, None) -> fprintf f "PConst_string(%S,None)" s;
61-
| PConst_string (s, Some delim) ->
58+
| Pconst_integer (i,m) -> fprintf f "PConst_int (%s,%a)" i fmt_char_option m;
59+
| Pconst_char (c) -> fprintf f "PConst_char %02x" (Char.code c);
60+
| Pconst_string (s, None) -> fprintf f "PConst_string(%S,None)" s;
61+
| Pconst_string (s, Some delim) ->
6262
fprintf f "PConst_string (%S,Some %S)" s delim;
63-
| PConst_float (s,m) -> fprintf f "PConst_float (%s,%a)" s fmt_char_option m;
63+
| Pconst_float (s,m) -> fprintf f "PConst_float (%s,%a)" s fmt_char_option m;
6464
;;
6565

6666
let fmt_mutable_flag f x =

typing/typecore.ml

+16-16
Original file line numberDiff line numberDiff line change
@@ -265,31 +265,31 @@ let type_constant = function
265265
| Const_nativeint _ -> instance_def Predef.type_nativeint
266266

267267
let constant : Parsetree.constant -> (Asttypes.constant, error) result = function
268-
| PConst_int (i,None) ->
268+
| Pconst_integer (i,None) ->
269269
begin
270270
try Ok (Const_int (Misc.Int_literal_converter.int i))
271271
with Failure _ -> Error (Literal_overflow "int")
272272
end
273-
| PConst_int (i,Some 'l') ->
273+
| Pconst_integer (i,Some 'l') ->
274274
begin
275275
try Ok (Const_int32 (Misc.Int_literal_converter.int32 i))
276276
with Failure _ -> Error (Literal_overflow "int32")
277277
end
278-
| PConst_int (i,Some 'L') ->
278+
| Pconst_integer (i,Some 'L') ->
279279
begin
280280
try Ok (Const_int64 (Misc.Int_literal_converter.int64 i))
281281
with Failure _ -> Error (Literal_overflow "int64")
282282
end
283-
| PConst_int (i,Some 'n') ->
283+
| Pconst_integer (i,Some 'n') ->
284284
begin
285285
try Ok (Const_nativeint (Misc.Int_literal_converter.nativeint i))
286286
with Failure _ -> Error (Literal_overflow "nativeint")
287287
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))
293293

294294
let constant_or_raise env loc cst =
295295
match constant cst with
@@ -1070,14 +1070,14 @@ let rec type_pat ~constrs ~labels ~no_existentials ~mode ~explode ~env
10701070
pat_type = expected_ty;
10711071
pat_attributes = sp.ppat_attributes;
10721072
pat_env = !env }
1073-
| Ppat_interval (PConst_char c1, PConst_char c2) ->
1073+
| Ppat_interval (Pconst_char c1, Pconst_char c2) ->
10741074
let open Ast_helper.Pat in
10751075
let gloc = {loc with Location.loc_ghost=true} in
10761076
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)
10781078
else
10791079
or_ ~loc:gloc
1080-
(constant ~loc:gloc (PConst_char c1))
1080+
(constant ~loc:gloc (Pconst_char c1))
10811081
(loop (Char.chr(Char.code c1 + 1)) c2)
10821082
in
10831083
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 =
19481948
exp_attributes = sexp.pexp_attributes;
19491949
exp_env = env }
19501950
end
1951-
| Pexp_constant(PConst_string (str, _) as cst) -> (
1951+
| Pexp_constant(Pconst_string (str, _) as cst) -> (
19521952
let cst = constant_or_raise env loc cst in
19531953
(* Terrible hack for format strings *)
19541954
let ty_exp = expand_head env ty_expected in
@@ -2990,9 +2990,9 @@ and type_format loc str env =
29902990
| _ :: _ :: _ -> Some (mk_exp_loc (Pexp_tuple args)) in
29912991
mk_exp_loc (Pexp_construct (mk_lid_loc lid, arg)) in
29922992
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
29962996
let rec mk_formatting_lit fmting = match fmting with
29972997
| Close_box ->
29982998
mk_constr "Close_box" []

typing/untypeast.ml

+7-7
Original file line numberDiff line numberDiff line change
@@ -113,13 +113,13 @@ let fresh_name s env =
113113
(** Mapping functions. *)
114114

115115
let constant = function
116-
| Const_char c -> PConst_char c
117-
| Const_string (s,d) -> PConst_string (s,d)
118-
| Const_int i -> PConst_int (string_of_int i, None)
119-
| Const_int32 i -> PConst_int (Int32.to_string i, Some 'l')
120-
| Const_int64 i -> PConst_int (Int64.to_string i, Some 'L')
121-
| Const_nativeint i -> PConst_int (Nativeint.to_string i, Some 'n')
122-
| Const_float f -> PConst_float (f,None)
116+
| Const_char c -> Pconst_char c
117+
| Const_string (s,d) -> Pconst_string (s,d)
118+
| Const_int i -> Pconst_integer (string_of_int i, None)
119+
| Const_int32 i -> Pconst_integer (Int32.to_string i, Some 'l')
120+
| Const_int64 i -> Pconst_integer (Int64.to_string i, Some 'L')
121+
| Const_nativeint i -> Pconst_integer (Nativeint.to_string i, Some 'n')
122+
| Const_float f -> Pconst_float (f,None)
123123

124124
let attribute sub (s, p) = (map_loc sub s, p)
125125
let attributes sub l = List.map (sub.attribute sub) l

0 commit comments

Comments
 (0)