Skip to content

Commit b29813f

Browse files
committed
remove warnings which don't make sense in JS context
1 parent 1aa4e14 commit b29813f

File tree

1 file changed

+67
-16
lines changed

1 file changed

+67
-16
lines changed

utils/warnings.ml

Lines changed: 67 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -57,7 +57,9 @@ type t =
5757
| Wildcard_arg_to_constant_constr (* 28 *)
5858
| Eol_in_string (* 29 *)
5959
| Duplicate_definitions of string * string * string * string (*30 *)
60+
#if undefined BS_ONLY then
6061
| Multiple_definition of string * string * string (* 31 *)
62+
#end
6163
| Unused_value_declaration of string (* 32 *)
6264
| Unused_open of string (* 33 *)
6365
| Unused_type_declaration of string (* 34 *)
@@ -77,14 +79,18 @@ type t =
7779
| Eliminated_optional_arguments of string list (* 48 *)
7880
| No_cmi_file of string * string option (* 49 *)
7981
| Bad_docstring of bool (* 50 *)
82+
#if undefined BS_ONLY then
8083
| Expect_tailcall (* 51 *)
84+
#end
8185
| Fragile_literal_pattern (* 52 *)
8286
| Misplaced_attribute of string (* 53 *)
8387
| Duplicated_attribute of string (* 54 *)
8488
| Inlining_impossible of string (* 55 *)
8589
| Unreachable_case (* 56 *)
8690
| Ambiguous_pattern of string list (* 57 *)
91+
#if undefined BS_ONLY then
8792
| No_cmx_file of string (* 58 *)
93+
#end
8894
| Assignment_to_non_mutable_value (* 59 *)
8995
| Unused_module of string (* 60 *)
9096
| Unboxable_type_in_prim_decl of string (* 61 *)
@@ -139,7 +145,9 @@ let number = function
139145
| Wildcard_arg_to_constant_constr -> 28
140146
| Eol_in_string -> 29
141147
| Duplicate_definitions _ -> 30
148+
#if undefined BS_ONLY then
142149
| Multiple_definition _ -> 31
150+
#end
143151
| Unused_value_declaration _ -> 32
144152
| Unused_open _ -> 33
145153
| Unused_type_declaration _ -> 34
@@ -159,14 +167,18 @@ let number = function
159167
| Eliminated_optional_arguments _ -> 48
160168
| No_cmi_file _ -> 49
161169
| Bad_docstring _ -> 50
170+
#if undefined BS_ONLY then
162171
| Expect_tailcall -> 51
172+
#end
163173
| Fragile_literal_pattern -> 52
164174
| Misplaced_attribute _ -> 53
165175
| Duplicated_attribute _ -> 54
166176
| Inlining_impossible _ -> 55
167177
| Unreachable_case -> 56
168178
| Ambiguous_pattern _ -> 57
179+
#if undefined BS_ONLY then
169180
| No_cmx_file _ -> 58
181+
#end
170182
| Assignment_to_non_mutable_value -> 59
171183
| Unused_module _ -> 60
172184
| Unboxable_type_in_prim_decl _ -> 61
@@ -360,15 +372,27 @@ let message = function
360372
("the following methods are overridden by the class"
361373
:: cname :: ":\n " :: slist)
362374
| Method_override [] -> assert false
375+
#if true then
376+
| Partial_match "" ->
377+
"You forgot to handle a possible case here, though we don't have more information on the value."
378+
| Partial_match s ->
379+
"You forgot to handle a possible case here, for example: \n " ^ s
380+
#else
363381
| Partial_match "" -> "this pattern-matching is not exhaustive."
364382
| Partial_match s ->
365383
"this pattern-matching is not exhaustive.\n\
366384
Here is an example of a case that is not matched:\n" ^ s
385+
#end
367386
| Non_closed_record_pattern s ->
368387
"the following labels are not bound in this record pattern:\n" ^ s ^
369388
"\nEither bind these labels explicitly or add '; _' to the pattern."
389+
#if true then
390+
| Statement_type ->
391+
"This expression returns a value, but you're not doing anything with it. If this is on purpose, wrap it with `ignore`."
392+
#else
370393
| Statement_type ->
371394
"this expression should have type unit."
395+
#end
372396
| Unused_match -> "this match case is unused."
373397
| Unused_pat -> "this sub-pattern is unused."
374398
| Instance_variable_override [lab] ->
@@ -384,7 +408,17 @@ let message = function
384408
| Implicit_public_methods l ->
385409
"the following private methods were made public implicitly:\n "
386410
^ String.concat " " l ^ "."
411+
#if true then
412+
| Unerasable_optional_argument ->
413+
String.concat ""
414+
["This optional parameter in final position will, in practice, not be optional.\n";
415+
" Reorder the parameters so that at least one non-optional one is in final position or, if all parameters are optional, insert a final ().\n\n";
416+
" Explanation: If the final parameter is optional, it'd be unclear whether a function application that omits it should be considered fully applied, or partially applied. Imagine writing `let title = display(\"hello!\")`, only to realize `title` isn't your desired result, but a curried call that takes a final optional argument, e.g. `~showDate`.\n\n";
417+
" Formal rule: an optional argument is considered intentionally omitted when the 1st positional (i.e. neither labeled nor optional) argument defined after it is passed in."
418+
]
419+
#else
387420
| Unerasable_optional_argument -> "this optional argument cannot be erased."
421+
#end
388422
| Undeclared_virtual_method m -> "the virtual method "^m^" is not declared."
389423
| Not_principal s -> s^" is not principal."
390424
| Without_principality s -> s^" without principality."
@@ -393,10 +427,21 @@ let message = function
393427
"this statement never returns (or has an unsound type.)"
394428
| Preprocessor s -> s
395429
| Useless_record_with ->
430+
begin match !Config.syntax_kind with
431+
| `ml ->
396432
"all the fields are explicitly listed in this record:\n\
397433
the 'with' clause is useless."
434+
| `reason | `rescript ->
435+
"All the fields are already explicitly listed in this record. You can remove the `...` spread."
436+
end
437+
#if true then
398438
| Bad_module_name (modname) ->
439+
"This file's name is potentially invalid. The build systems conventionally turn a file name into a module name by upper-casing the first letter. " ^ modname ^ " isn't a valid module name.\n" ^
440+
"Note: some build systems might e.g. turn kebab-case into CamelCase module, which is why this isn't a hard error."
441+
#else
442+
| Bad_module_name (modname) ->
399443
"bad source file name: \"" ^ modname ^ "\" is not a valid module name."
444+
#end
400445
| All_clauses_guarded ->
401446
"this pattern-matching is not exhaustive.\n\
402447
All clauses in this pattern-matching are guarded."
@@ -408,10 +453,12 @@ let message = function
408453
| Duplicate_definitions (kind, cname, tc1, tc2) ->
409454
Printf.sprintf "the %s %s is defined in both types %s and %s."
410455
kind cname tc1 tc2
456+
#if undefined BS_ONLY then
411457
| Multiple_definition(modname, file1, file2) ->
412458
Printf.sprintf
413459
"files %s and %s both define a module named %s"
414460
file1 file2 modname
461+
#end
415462
| Unused_value_declaration v -> "unused value " ^ v ^ "."
416463
| Unused_open s -> "unused open " ^ s ^ "."
417464
| Unused_type_declaration s -> "unused type " ^ s ^ "."
@@ -491,8 +538,10 @@ let message = function
491538
| Bad_docstring unattached ->
492539
if unattached then "unattached documentation comment (ignored)"
493540
else "ambiguous documentation comment"
541+
#if undefined BS_ONLY then
494542
| Expect_tailcall ->
495543
Printf.sprintf "expected tailcall"
544+
#end
496545
| Fragile_literal_pattern ->
497546
Printf.sprintf
498547
"Code should not depend on the actual values of\n\
@@ -521,10 +570,12 @@ let message = function
521570
"Ambiguous or-pattern variables under guard;\n\
522571
%s may match different arguments. (See manual section 8.5)"
523572
msg
573+
#if undefined BS_ONLY then
524574
| No_cmx_file name ->
525575
Printf.sprintf
526576
"no cmx file was found in path for module %s, \
527577
and its interface was not compiled with -opaque" name
578+
#end
528579
| Assignment_to_non_mutable_value ->
529580
"A potential assignment to a non-mutable value was detected \n\
530581
in this source file. Such assignments may generate incorrect code \n\
@@ -541,23 +592,23 @@ let message = function
541592

542593
#if true then
543594
| Bs_unused_attribute s ->
544-
"Unused BuckleScript attribute: " ^ s ^ "\n\
595+
"Unused attribute: " ^ s ^ "\n\
545596
This means such annotation is not annotated properly. \n\
546597
for example, some annotations is only meaningful in externals \n"
547598
| Bs_polymorphic_comparison ->
548-
"polymorphic comparison introduced (maybe unsafe)"
599+
"Polymorphic comparison introduced (maybe unsafe)"
549600
| Bs_ffi_warning s ->
550-
"BuckleScript FFI warning: " ^ s
601+
"FFI warning: " ^ s
551602
| Bs_derive_warning s ->
552-
"BuckleScript bs.deriving warning: " ^ s
603+
"bs.deriving warning: " ^ s
553604
| Bs_fragile_external s ->
554-
"BuckleScript warning: " ^ s ^" : the external name is inferred from val name is unsafe from refactoring when changing value name"
605+
s ^ " : the external name is inferred from val name is unsafe from refactoring when changing value name"
555606
| Bs_unimplemented_primitive s ->
556-
"BuckleScript warning: Unimplemented primitive used:" ^ s
607+
"Unimplemented primitive used:" ^ s
557608
| Bs_integer_literal_overflow ->
558-
"BuckleScript warning: Integer literal exceeds the range of representable integers of type int"
609+
"Integer literal exceeds the range of representable integers of type int"
559610
| Bs_uninterpreted_delimiters s ->
560-
"BuckleScript warning: Uninterpreted delimiters " ^ s
611+
"Uninterpreted delimiters " ^ s
561612
#end
562613
;;
563614

@@ -694,14 +745,14 @@ let descriptions =
694745
62, "Type constraint on GADT type declaration";
695746

696747
#if true then
697-
101, "BuckleScript warning: Unused bs attributes";
698-
102, "BuckleScript warning: polymorphic comparison introduced (maybe unsafe)";
699-
103, "BuckleScript warning: about fragile FFI definitions" ;
700-
104, "BuckleScript warning: bs.deriving warning with customized message ";
701-
105, "BuckleScript warning: the external name is inferred from val name is unsafe from refactoring when changing value name";
702-
106, "BuckleScript warning: Unimplemented primitive used:";
703-
107, "BuckleScript warning: Integer literal exceeds the range of representable integers of type int";
704-
108, "BuckleScript warning: Uninterpreted delimiters (for unicode)"
748+
101, "Unused bs attributes";
749+
102, "Polymorphic comparison introduced (maybe unsafe)";
750+
103, "Fragile FFI definitions" ;
751+
104, "bs.deriving warning with customized message ";
752+
105, "External name is inferred from val name is unsafe from refactoring when changing value name";
753+
106, "Unimplemented primitive used:";
754+
107, "Integer literal exceeds the range of representable integers of type int";
755+
108, "Uninterpreted delimiters (for unicode)"
705756
#end
706757
]
707758
;;

0 commit comments

Comments
 (0)