Skip to content

Commit 7eba117

Browse files
alainfrischmshinwell
authored andcommitted
Remove spurious semicolons after non-unit expressions (ocaml#1305)
1 parent 82b3cdc commit 7eba117

File tree

6 files changed

+34
-34
lines changed

6 files changed

+34
-34
lines changed

bytecomp/matching.ml

+1-1
Original file line numberDiff line numberDiff line change
@@ -1787,7 +1787,7 @@ let rec do_make_string_test_tree loc arg sw delta d =
17871787
bind_sw
17881788
(Lprim
17891789
(prim_string_compare,
1790-
[arg; Lconst (Const_immstring s)], loc;))
1790+
[arg; Lconst (Const_immstring s)], loc))
17911791
(fun r ->
17921792
tree_way_test loc r
17931793
(do_make_string_test_tree loc arg lt delta d)

middle_end/inline_and_simplify_aux.ml

+1-1
Original file line numberDiff line numberDiff line change
@@ -293,7 +293,7 @@ module Env = struct
293293
try
294294
Set_of_closures_origin.Map.find origin t.actively_unrolling
295295
with Not_found ->
296-
Misc.fatal_error "Unexpected actively unrolled function";
296+
Misc.fatal_error "Unexpected actively unrolled function"
297297
in
298298
let actively_unrolling =
299299
Set_of_closures_origin.Map.add origin (unrolling - 1) t.actively_unrolling

parsing/lexer.mll

+2-2
Original file line numberDiff line numberDiff line change
@@ -530,15 +530,15 @@ and comment = parse
530530
"(*"
531531
{ comment_start_loc := (Location.curr lexbuf) :: !comment_start_loc;
532532
store_lexeme lexbuf;
533-
comment lexbuf;
533+
comment lexbuf
534534
}
535535
| "*)"
536536
{ match !comment_start_loc with
537537
| [] -> assert false
538538
| [_] -> comment_start_loc := []; Location.curr lexbuf
539539
| _ :: l -> comment_start_loc := l;
540540
store_lexeme lexbuf;
541-
comment lexbuf;
541+
comment lexbuf
542542
}
543543
| "\""
544544
{

stdlib/camlinternalFormat.ml

+8-8
Original file line numberDiff line numberDiff line change
@@ -2040,7 +2040,7 @@ let fmt_ebb_of_string ?legacy_behavior str =
20402040
let invalid_format_message str_ind msg =
20412041
failwith_message
20422042
"invalid format %S: at character number %d, %s"
2043-
str str_ind msg;
2043+
str str_ind msg
20442044
in
20452045

20462046
(* Used when the end of the format (or the current sub-format) was encountered
@@ -2688,14 +2688,14 @@ let fmt_ebb_of_string ?legacy_behavior str =
26882688
let fail_single_percent str_ind =
26892689
failwith_message
26902690
"invalid format %S: '%%' alone is not accepted in character sets, \
2691-
use %%%% instead at position %d." str str_ind;
2691+
use %%%% instead at position %d." str str_ind
26922692
in
26932693

26942694
(* Parse the first character of a char set. *)
26952695
let rec parse_char_set_start str_ind end_ind =
26962696
if str_ind = end_ind then unexpected_end_of_format end_ind;
26972697
let c = str.[str_ind] in
2698-
parse_char_set_after_char (str_ind + 1) end_ind c;
2698+
parse_char_set_after_char (str_ind + 1) end_ind c
26992699

27002700
(* Parse the content of a char set until the first ']'. *)
27012701
and parse_char_set_content str_ind end_ind =
@@ -2705,9 +2705,9 @@ let fmt_ebb_of_string ?legacy_behavior str =
27052705
str_ind + 1
27062706
| '-' ->
27072707
add_char '-';
2708-
parse_char_set_content (str_ind + 1) end_ind;
2708+
parse_char_set_content (str_ind + 1) end_ind
27092709
| c ->
2710-
parse_char_set_after_char (str_ind + 1) end_ind c;
2710+
parse_char_set_after_char (str_ind + 1) end_ind c
27112711

27122712
(* Test for range in char set. *)
27132713
and parse_char_set_after_char str_ind end_ind c =
@@ -2838,10 +2838,10 @@ let fmt_ebb_of_string ?legacy_behavior str =
28382838
search_subformat_end (sub_end + 2) end_ind c
28392839
| '}' ->
28402840
(* Error: %(...%}. *)
2841-
expected_character (str_ind + 1) "character ')'" '}';
2841+
expected_character (str_ind + 1) "character ')'" '}'
28422842
| ')' ->
28432843
(* Error: %{...%). *)
2844-
expected_character (str_ind + 1) "character '}'" ')';
2844+
expected_character (str_ind + 1) "character '}'" ')'
28452845
| _ ->
28462846
search_subformat_end (str_ind + 2) end_ind c
28472847
end
@@ -2931,7 +2931,7 @@ let fmt_ebb_of_string ?legacy_behavior str =
29312931
failwith_message
29322932
"invalid format %S: at character number %d, \
29332933
%s is incompatible with '%c' in sub-format %S"
2934-
str pct_ind option symb subfmt;
2934+
str pct_ind option symb subfmt
29352935

29362936
in parse 0 (String.length str)
29372937

tools/cmt2annot.ml

+1-1
Original file line numberDiff line numberDiff line change
@@ -29,7 +29,7 @@ let bind_variables scope =
2929
Annot.Idef scope))
3030
| _ -> ()
3131
end;
32-
super.pat sub p;
32+
super.pat sub p
3333
in
3434
{super with pat}
3535

typing/untypeast.ml

+21-21
Original file line numberDiff line numberDiff line change
@@ -187,7 +187,7 @@ let value_description sub v =
187187
(sub.typ sub v.val_desc)
188188

189189
let module_binding sub mb =
190-
let loc = sub.location sub mb.mb_loc; in
190+
let loc = sub.location sub mb.mb_loc in
191191
let attrs = sub.attributes sub mb.mb_attributes in
192192
Mb.mk ~loc ~attrs
193193
(map_loc sub mb.mb_name)
@@ -196,7 +196,7 @@ let module_binding sub mb =
196196
let type_parameter sub (ct, v) = (sub.typ sub ct, v)
197197

198198
let type_declaration sub decl =
199-
let loc = sub.location sub decl.typ_loc; in
199+
let loc = sub.location sub decl.typ_loc in
200200
let attrs = sub.attributes sub decl.typ_attributes in
201201
Type.mk ~loc ~attrs
202202
~params:(List.map (type_parameter sub) decl.typ_params)
@@ -223,15 +223,15 @@ let constructor_arguments sub = function
223223
| Cstr_record l -> Pcstr_record (List.map (sub.label_declaration sub) l)
224224

225225
let constructor_declaration sub cd =
226-
let loc = sub.location sub cd.cd_loc; in
226+
let loc = sub.location sub cd.cd_loc in
227227
let attrs = sub.attributes sub cd.cd_attributes in
228228
Type.constructor ~loc ~attrs
229229
~args:(constructor_arguments sub cd.cd_args)
230230
?res:(map_opt (sub.typ sub) cd.cd_res)
231231
(map_loc sub cd.cd_name)
232232

233233
let label_declaration sub ld =
234-
let loc = sub.location sub ld.ld_loc; in
234+
let loc = sub.location sub ld.ld_loc in
235235
let attrs = sub.attributes sub ld.ld_attributes in
236236
Type.field ~loc ~attrs
237237
~mut:ld.ld_mutable
@@ -247,7 +247,7 @@ let type_extension sub tyext =
247247
(List.map (sub.extension_constructor sub) tyext.tyext_constructors)
248248

249249
let extension_constructor sub ext =
250-
let loc = sub.location sub ext.ext_loc; in
250+
let loc = sub.location sub ext.ext_loc in
251251
let attrs = sub.attributes sub ext.ext_attributes in
252252
Te.constructor ~loc ~attrs
253253
(map_loc sub ext.ext_name)
@@ -259,7 +259,7 @@ let extension_constructor sub ext =
259259
)
260260

261261
let pattern sub pat =
262-
let loc = sub.location sub pat.pat_loc; in
262+
let loc = sub.location sub pat.pat_loc in
263263
(* todo: fix attributes on extras *)
264264
let attrs = sub.attributes sub pat.pat_attributes in
265265
let desc =
@@ -319,7 +319,7 @@ let pattern sub pat =
319319
Pat.mk ~loc ~attrs desc
320320

321321
let exp_extra sub (extra, loc, attrs) sexp =
322-
let loc = sub.location sub loc; in
322+
let loc = sub.location sub loc in
323323
let attrs = sub.attributes sub attrs in
324324
let desc =
325325
match extra with
@@ -346,14 +346,14 @@ let case sub {c_lhs; c_guard; c_rhs} =
346346
}
347347

348348
let value_binding sub vb =
349-
let loc = sub.location sub vb.vb_loc; in
349+
let loc = sub.location sub vb.vb_loc in
350350
let attrs = sub.attributes sub vb.vb_attributes in
351351
Vb.mk ~loc ~attrs
352352
(sub.pat sub vb.vb_pat)
353353
(sub.expr sub vb.vb_expr)
354354

355355
let expression sub exp =
356-
let loc = sub.location sub exp.exp_loc; in
356+
let loc = sub.location sub exp.exp_loc in
357357
let attrs = sub.attributes sub exp.exp_attributes in
358358
let desc =
359359
match exp.exp_desc with
@@ -481,7 +481,7 @@ let package_type sub pack =
481481
(s, sub.typ sub ct)) pack.pack_fields)
482482

483483
let module_type_declaration sub mtd =
484-
let loc = sub.location sub mtd.mtd_loc; in
484+
let loc = sub.location sub mtd.mtd_loc in
485485
let attrs = sub.attributes sub mtd.mtd_attributes in
486486
Mtd.mk ~loc ~attrs
487487
?typ:(map_opt (sub.module_type sub) mtd.mtd_type)
@@ -491,7 +491,7 @@ let signature sub sg =
491491
List.map (sub.signature_item sub) sg.sig_items
492492

493493
let signature_item sub item =
494-
let loc = sub.location sub item.sig_loc; in
494+
let loc = sub.location sub item.sig_loc in
495495
let desc =
496496
match item.sig_desc with
497497
Tsig_value v ->
@@ -522,14 +522,14 @@ let signature_item sub item =
522522
Sig.mk ~loc desc
523523

524524
let module_declaration sub md =
525-
let loc = sub.location sub md.md_loc; in
525+
let loc = sub.location sub md.md_loc in
526526
let attrs = sub.attributes sub md.md_attributes in
527527
Md.mk ~loc ~attrs
528528
(map_loc sub md.md_name)
529529
(sub.module_type sub md.md_type)
530530

531531
let include_infos f sub incl =
532-
let loc = sub.location sub incl.incl_loc; in
532+
let loc = sub.location sub incl.incl_loc in
533533
let attrs = sub.attributes sub incl.incl_attributes in
534534
Incl.mk ~loc ~attrs
535535
(f sub incl.incl_mod)
@@ -538,7 +538,7 @@ let include_declaration sub = include_infos sub.module_expr sub
538538
let include_description sub = include_infos sub.module_type sub
539539

540540
let class_infos f sub ci =
541-
let loc = sub.location sub ci.ci_loc; in
541+
let loc = sub.location sub ci.ci_loc in
542542
let attrs = sub.attributes sub ci.ci_attributes in
543543
Ci.mk ~loc ~attrs
544544
~virt:ci.ci_virt
@@ -551,7 +551,7 @@ let class_description sub = class_infos sub.class_type sub
551551
let class_type_declaration sub = class_infos sub.class_type sub
552552

553553
let module_type sub mty =
554-
let loc = sub.location sub mty.mty_loc; in
554+
let loc = sub.location sub mty.mty_loc in
555555
let attrs = sub.attributes sub mty.mty_attributes in
556556
let desc = match mty.mty_desc with
557557
Tmty_ident (_path, lid) -> Pmty_ident (map_loc sub lid)
@@ -581,7 +581,7 @@ let with_constraint sub (_path, lid, cstr) =
581581
map_loc sub lid2)
582582

583583
let module_expr sub mexpr =
584-
let loc = sub.location sub mexpr.mod_loc; in
584+
let loc = sub.location sub mexpr.mod_loc in
585585
let attrs = sub.attributes sub mexpr.mod_attributes in
586586
match mexpr.mod_desc with
587587
Tmod_constraint (m, _, Tmodtype_implicit, _ ) ->
@@ -607,7 +607,7 @@ let module_expr sub mexpr =
607607
Mod.mk ~loc ~attrs desc
608608

609609
let class_expr sub cexpr =
610-
let loc = sub.location sub cexpr.cl_loc; in
610+
let loc = sub.location sub cexpr.cl_loc in
611611
let attrs = sub.attributes sub cexpr.cl_attributes in
612612
let desc = match cexpr.cl_desc with
613613
| Tcl_constraint ( { cl_desc = Tcl_ident (_path, lid, tyl); _ },
@@ -644,7 +644,7 @@ let class_expr sub cexpr =
644644
Cl.mk ~loc ~attrs desc
645645

646646
let class_type sub ct =
647-
let loc = sub.location sub ct.cltyp_loc; in
647+
let loc = sub.location sub ct.cltyp_loc in
648648
let attrs = sub.attributes sub ct.cltyp_attributes in
649649
let desc = match ct.cltyp_desc with
650650
Tcty_signature csg -> Pcty_signature (sub.class_signature sub csg)
@@ -664,7 +664,7 @@ let class_signature sub cs =
664664
}
665665

666666
let class_type_field sub ctf =
667-
let loc = sub.location sub ctf.ctf_loc; in
667+
let loc = sub.location sub ctf.ctf_loc in
668668
let attrs = sub.attributes sub ctf.ctf_attributes in
669669
let desc = match ctf.ctf_desc with
670670
Tctf_inherit ct -> Pctf_inherit (sub.class_type sub ct)
@@ -679,7 +679,7 @@ let class_type_field sub ctf =
679679
Ctf.mk ~loc ~attrs desc
680680

681681
let core_type sub ct =
682-
let loc = sub.location sub ct.ctyp_loc; in
682+
let loc = sub.location sub ct.ctyp_loc in
683683
let attrs = sub.attributes sub ct.ctyp_attributes in
684684
let desc = match ct.ctyp_desc with
685685
Ttyp_any -> Ptyp_any
@@ -735,7 +735,7 @@ and is_self_pat = function
735735
| _ -> false
736736

737737
let class_field sub cf =
738-
let loc = sub.location sub cf.cf_loc; in
738+
let loc = sub.location sub cf.cf_loc in
739739
let attrs = sub.attributes sub cf.cf_attributes in
740740
let desc = match cf.cf_desc with
741741
Tcf_inherit (ovf, cl, super, _vals, _meths) ->

0 commit comments

Comments
 (0)