Skip to content

Commit c67b183

Browse files
authored
Merge pull request ocaml#13850 from gasche/type-annotations-ghost
[internal] more debug printing, locations on "extra" AST nodes
2 parents 74d344b + 672b91b commit c67b183

File tree

2 files changed

+14
-18
lines changed

2 files changed

+14
-18
lines changed

parsing/printast.mli

+1
Original file line numberDiff line numberDiff line change
@@ -27,6 +27,7 @@ val interface : formatter -> signature_item list -> unit
2727
val implementation : formatter -> structure_item list -> unit
2828
val top_phrase : formatter -> toplevel_phrase -> unit
2929

30+
val pattern: int -> formatter -> pattern -> unit
3031
val expression: int -> formatter -> expression -> unit
3132
val structure: int -> formatter -> structure -> unit
3233
val payload: int -> formatter -> payload -> unit

typing/printtyped.ml

+13-18
Original file line numberDiff line numberDiff line change
@@ -235,12 +235,7 @@ and pattern : type k . _ -> _ -> k general_pattern -> unit = fun i ppf x ->
235235
line i ppf "pattern %a\n" fmt_location x.pat_loc;
236236
attributes i ppf x.pat_attributes;
237237
let i = i+1 in
238-
begin match x.pat_extra with
239-
| [] -> ()
240-
| extra ->
241-
line i ppf "extra\n";
242-
List.iter (pattern_extra (i+1) ppf) extra;
243-
end;
238+
List.iter (pattern_extra i ppf) x.pat_extra;
244239
match x.pat_desc with
245240
| Tpat_any -> line i ppf "Tpat_any\n";
246241
| Tpat_var (s,_,_) -> line i ppf "Tpat_var \"%a\"\n" fmt_ident s;
@@ -289,7 +284,9 @@ and labeled_pattern
289284
tuple_component_label i ppf label;
290285
pattern i ppf x
291286

292-
and pattern_extra i ppf (extra_pat, _, attrs) =
287+
and pattern_extra i ppf (extra_pat, loc, attrs) =
288+
line i ppf "extra %a\n" fmt_location loc;
289+
let i = i + 1 in
293290
match extra_pat with
294291
| Tpat_unpack ->
295292
line i ppf "Tpat_extra_unpack\n";
@@ -316,12 +313,15 @@ and function_body i ppf (body : function_body) =
316313
line i ppf "Tfunction_cases%a %a\n"
317314
fmt_partiality partial
318315
fmt_location loc;
319-
attributes (i+1) ppf attrs;
320-
Option.iter (fun e -> expression_extra (i+1) ppf e []) exp_extra;
321-
list (i+1) case ppf cases
316+
let i = i+1 in
317+
attributes i ppf attrs;
318+
Option.iter (fun e -> expression_extra i ppf (e, loc, [])) exp_extra;
319+
list i case ppf cases
322320

323-
and expression_extra i ppf x attrs =
324-
match x with
321+
and expression_extra i ppf (extra, loc, attrs) =
322+
line i ppf "extra %a\n" fmt_location loc;
323+
let i = i + 1 in
324+
match extra with
325325
| Texp_constraint ct ->
326326
line i ppf "Texp_constraint\n";
327327
attributes i ppf attrs;
@@ -343,12 +343,7 @@ and expression i ppf x =
343343
line i ppf "expression %a\n" fmt_location x.exp_loc;
344344
attributes i ppf x.exp_attributes;
345345
let i = i+1 in
346-
begin match x.exp_extra with
347-
| [] -> ()
348-
| extra ->
349-
line i ppf "extra\n";
350-
List.iter (fun (x, _, attrs) -> expression_extra (i+1) ppf x attrs) extra;
351-
end;
346+
List.iter (expression_extra i ppf) x.exp_extra;
352347
match x.exp_desc with
353348
| Texp_ident (li,_,_) -> line i ppf "Texp_ident %a\n" fmt_path li;
354349
| Texp_instvar (_, li,_) -> line i ppf "Texp_instvar %a\n" fmt_path li;

0 commit comments

Comments
 (0)