Skip to content

Commit 11b5424

Browse files
committed
Avoid printing double spaces in function argument lists
1 parent 7751faa commit 11b5424

File tree

2 files changed

+11
-14
lines changed

2 files changed

+11
-14
lines changed

parsing/pprintast.ml

Lines changed: 10 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -518,26 +518,26 @@ and label_exp ctxt f (l,opt,p) =
518518
match l with
519519
| Nolabel ->
520520
(* single case pattern parens needed here *)
521-
pp f "%a@ " (simple_pattern ctxt) p
521+
pp f "%a" (simple_pattern ctxt) p
522522
| Optional rest ->
523523
begin match p with
524524
| {ppat_desc = Ppat_var {txt;_}; ppat_attributes = []}
525525
when txt = rest ->
526526
(match opt with
527-
| Some o -> pp f "?(%s=@;%a)@;" rest (expression ctxt) o
528-
| None -> pp f "?%s@ " rest)
527+
| Some o -> pp f "?(%s=@;%a)" rest (expression ctxt) o
528+
| None -> pp f "?%s" rest)
529529
| _ ->
530530
(match opt with
531531
| Some o ->
532-
pp f "?%s:(%a=@;%a)@;"
532+
pp f "?%s:(%a=@;%a)"
533533
rest (pattern1 ctxt) p (expression ctxt) o
534-
| None -> pp f "?%s:%a@;" rest (simple_pattern ctxt) p)
534+
| None -> pp f "?%s:%a" rest (simple_pattern ctxt) p)
535535
end
536536
| Labelled l -> match p with
537537
| {ppat_desc = Ppat_var {txt;_}; ppat_attributes = []}
538538
when txt = l ->
539-
pp f "~%s@;" l
540-
| _ -> pp f "~%s:%a@;" l (simple_pattern ctxt) p
539+
pp f "~%s" l
540+
| _ -> pp f "~%s:%a" l (simple_pattern ctxt) p
541541

542542
and sugar_expr ctxt f e =
543543
if e.pexp_attributes <> [] then false
@@ -1242,11 +1242,8 @@ and pp_print_pexp_function ctxt sep f x =
12421242
if x.pexp_attributes <> [] then pp f "%s@;%a" sep (expression ctxt) x
12431243
else match x.pexp_desc with
12441244
| Pexp_fun (label, eo, p, e) ->
1245-
if label=Nolabel then
1246-
pp f "%a@ %a" (simple_pattern ctxt) p (pp_print_pexp_function ctxt sep) e
1247-
else
1248-
pp f "%a@ %a"
1249-
(label_exp ctxt) (label,eo,p) (pp_print_pexp_function ctxt sep) e
1245+
pp f "%a@ %a"
1246+
(label_exp ctxt) (label,eo,p) (pp_print_pexp_function ctxt sep) e
12501247
| Pexp_newtype (str,e) ->
12511248
pp f "(type@ %s)@ %a" str.txt (pp_print_pexp_function ctxt sep) e
12521249
| _ -> pp f "%s@;%a" sep (expression ctxt) x
@@ -1414,7 +1411,7 @@ and structure_item ctxt f x =
14141411
pp f "@[<2>%s %a%a%s %a%a=@;%a@]%a" kwd
14151412
virtual_flag x.pci_virt
14161413
(class_params_def ctxt) ls txt
1417-
(list (label_exp ctxt)) args
1414+
(list (label_exp ctxt) ~last:"@ ") args
14181415
(option class_constraint) constr
14191416
(class_expr ctxt) cl
14201417
(item_attributes ctxt) x.pci_attributes

testsuite/tests/parsing/multi_indices.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -35,7 +35,7 @@ val ( .![;..]<- ) : ('a, 'b, 'c) A.t -> int array -> 'a -> unit = <fun>
3535

3636
let (.![;..]) a n =
3737
Format.printf "indices: @[[|%a|]@]@."
38-
(Format.pp_print_list ~pp_sep:(fun ppf () -> Format.fprintf ppf ";@ ")
38+
(Format.pp_print_list ~pp_sep:(fun ppf () -> Format.fprintf ppf ";@ ")
3939
Format.pp_print_int) (Array.to_list n);
4040
A.get a n;;
4141
val ( .![;..] ) : ('a, 'b, 'c) A.t -> int array -> 'a = <fun>

0 commit comments

Comments
 (0)