Skip to content

Commit dc6cbe7

Browse files
authored
Merge pull request ocaml#13837 from Octachron/aligned_spellchecking_hints
error messages: align spellchecking hints
2 parents 2f39689 + 40ae152 commit dc6cbe7

File tree

22 files changed

+313
-160
lines changed

22 files changed

+313
-160
lines changed

Changes

+5
Original file line numberDiff line numberDiff line change
@@ -336,6 +336,11 @@ Working version
336336
occurences of `'a`
337337
(Samuel Vivien, review by Florian Angeletti)
338338

339+
- #13817: align spellchecking hints with the possibly misspelled identifier/
340+
Error: Unbound type constructor "aray"
341+
Hint: Did you mean "array"?
342+
(Florian Angeletti, suggestion by Daniel Bünzli, review by Gabriel Scherer)
343+
339344
### Internal/compiler-libs changes:
340345

341346
- #13314: Comment the code of Translclass

testsuite/tests/messages/highlight_tabs.ml

+1-1
Original file line numberDiff line numberDiff line change
@@ -9,5 +9,5 @@ Line 1, characters 10-13:
99
1 | let x = abc
1010
^^^
1111
Error: Unbound value "abc"
12-
Hint: Did you mean "abs"?
12+
Hint: Did you mean "abs"?
1313
|}];;

testsuite/tests/messages/spellcheck.ml

+21-21
Original file line numberDiff line numberDiff line change
@@ -9,7 +9,7 @@
99

1010
#directery "foo/";;
1111
[%%expect {|
12-
Unknown directive "directery".
12+
Unknown directive "directery".
1313
Hint: Did you mean "directory"?
1414
|}];;
1515

@@ -22,7 +22,7 @@ Line 1, characters 8-19:
2222
1 | let _ = Fun.pratect
2323
^^^^^^^^^^^
2424
Error: Unbound value "Fun.pratect"
25-
Hint: Did you mean "Fun.protect"?
25+
Hint: Did you mean "Fun.protect"?
2626
|}];;
2727

2828
type 'a t = 'a aray
@@ -31,7 +31,7 @@ Line 1, characters 15-19:
3131
1 | type 'a t = 'a aray
3232
^^^^
3333
Error: Unbound type constructor "aray"
34-
Hint: Did you mean "array"?
34+
Hint: Did you mean "array"?
3535
|}];;
3636

3737
module _ = Stdlib.Aray
@@ -40,7 +40,7 @@ Line 1, characters 11-22:
4040
1 | module _ = Stdlib.Aray
4141
^^^^^^^^^^^
4242
Error: Unbound module "Stdlib.Aray"
43-
Hint: Did you mean "Stdlib.Array"?
43+
Hint: Did you mean "Stdlib.Array"?
4444
|}];;
4545

4646
let x = Same 42
@@ -49,7 +49,7 @@ Line 1, characters 8-12:
4949
1 | let x = Same 42
5050
^^^^
5151
Error: Unbound constructor "Same"
52-
Hint: Did you mean "Some"?
52+
Hint: Did you mean "Some"?
5353
|}];;
5454

5555
let x : int option = Same 42
@@ -59,7 +59,7 @@ Line 1, characters 21-25:
5959
^^^^
6060
Error: This variant expression is expected to have type "int option"
6161
There is no constructor "Same" within type "option"
62-
Hint: Did you mean "Some"?
62+
Hint: Did you mean "Some"?
6363
|}];;
6464

6565
let x = { content = 42 }
@@ -68,7 +68,7 @@ Line 1, characters 10-17:
6868
1 | let x = { content = 42 }
6969
^^^^^^^
7070
Error: Unbound record field "content"
71-
Hint: Did you mean "contents"?
71+
Hint: Did you mean "contents"?
7272
|}];;
7373

7474
let x : int ref = { content = 42 }
@@ -78,7 +78,7 @@ Line 1, characters 20-27:
7878
^^^^^^^
7979
Error: This record expression is expected to have type "int ref"
8080
There is no field "content" within type "ref"
81-
Hint: Did you mean "contents"?
81+
Hint: Did you mean "contents"?
8282
|}];;
8383

8484
class foobar = object end
@@ -89,7 +89,7 @@ Line 2, characters 23-29:
8989
2 | let _ = object inherit foobaz end
9090
^^^^^^
9191
Error: Unbound class "foobaz"
92-
Hint: Did you mean "foobar"?
92+
Hint: Did you mean "foobar"?
9393
|}];;
9494

9595
module type Foobar = sig end
@@ -100,7 +100,7 @@ Line 2, characters 13-19:
100100
2 | module Foo : Foobaz = struct end
101101
^^^^^^
102102
Error: Unbound module type "Foobaz"
103-
Hint: Did you mean "Foobar"?
103+
Hint: Did you mean "Foobar"?
104104
|}];;
105105

106106
class type foobar = object end
@@ -111,7 +111,7 @@ Line 2, characters 9-15:
111111
2 | let _ : #foobaz = object end
112112
^^^^^^
113113
Error: Unbound class type "foobaz"
114-
Hint: Did you mean "foobar"?
114+
Hint: Did you mean "foobar"?
115115
|}];;
116116

117117
let _ =
@@ -124,7 +124,7 @@ let _ =
124124
Line 5, characters 22-33:
125125
5 | method update n = foobaz <- n
126126
^^^^^^^^^^^
127-
Error: The value "foobaz" is not an instance variable
127+
Error: The value "foobaz" is not an instance variable
128128
Hint: Did you mean "foobar"?
129129
|}];;
130130

@@ -136,7 +136,7 @@ let _ = function (foobar | foobaz) -> ()
136136
Line 1, characters 17-34:
137137
1 | let _ = function (foobar | foobaz) -> ()
138138
^^^^^^^^^^^^^^^^^
139-
Error: Variable "foobar" must occur on both sides of this "|" pattern
139+
Error: Variable "foobar" must occur on both sides of this "|" pattern
140140
Hint: Did you mean "foobaz"?
141141
|}];;
142142

@@ -148,23 +148,23 @@ Line 2, characters 13-19:
148148
2 | let _ = fun {foobaz} -> ()
149149
^^^^^^
150150
Error: Unbound record field "foobaz"
151-
Hint: Did you mean "foobar"?
151+
Hint: Did you mean "foobar"?
152152
|}];;
153153
let _ = { foobaz = 42 }
154154
[%%expect {|
155155
Line 1, characters 10-16:
156156
1 | let _ = { foobaz = 42 }
157157
^^^^^^
158158
Error: Unbound record field "foobaz"
159-
Hint: Did you mean "foobar"?
159+
Hint: Did you mean "foobar"?
160160
|}];;
161161
let _ = fun x -> x.foobaz
162162
[%%expect {|
163163
Line 1, characters 19-25:
164164
1 | let _ = fun x -> x.foobaz
165165
^^^^^^
166166
Error: Unbound record field "foobaz"
167-
Hint: Did you mean "foobar"?
167+
Hint: Did you mean "foobar"?
168168
|}];;
169169

170170
type bar = Foobar of int
@@ -175,7 +175,7 @@ Line 2, characters 8-14:
175175
2 | let _ = Foobaz 42
176176
^^^^^^
177177
Error: Unbound constructor "Foobaz"
178-
Hint: Did you mean "Foobar"?
178+
Hint: Did you mean "Foobar"?
179179
|}];;
180180

181181
type baz = K of { foobar : int }
@@ -185,7 +185,7 @@ type baz = K of { foobar : int; }
185185
Line 2, characters 12-18:
186186
2 | let _ = K { foobaz = 42 }
187187
^^^^^^
188-
Error: The field "foobaz" is not part of the record argument for the "baz.K" constructor
188+
Error: The field "foobaz" is not part of the record argument for the "baz.K" constructor
189189
Hint: Did you mean "foobar"?
190190
|}];;
191191

@@ -198,7 +198,7 @@ Line 3, characters 17-21:
198198
3 | method other = self#foobaz
199199
^^^^
200200
Error: This expression has no method "foobaz"
201-
Hint: Did you mean "foobar"?
201+
Hint: Did you mean "foobar"?
202202
|}];;
203203

204204

@@ -211,7 +211,7 @@ Line 3, characters 18-35:
211211
3 | method myself = {< foobaz = 42 >}
212212
^^^^^^^^^^^^^^^^^
213213
Error: Unbound instance variable "foobaz"
214-
Hint: Did you mean "foobar"?
214+
Hint: Did you mean "foobar"?
215215
|}];;
216216

217217
let closely = ()
@@ -226,5 +226,5 @@ Line 5, characters 9-17:
226226
5 | let () = M.closer
227227
^^^^^^^^
228228
Error: Unbound value "M.closer"
229-
Hint: Did you mean "M.close"?
229+
Hint: Did you mean "M.close"?
230230
|}]

testsuite/tests/typing-core-bugs/missing_rec_hint.ml

+2-2
Original file line numberDiff line numberDiff line change
@@ -49,7 +49,7 @@ Line 2, characters 13-19:
4949
2 | let value2 = value2 (* typo: should be value1 *) + 1 in
5050
^^^^^^
5151
Error: Unbound value "value2"
52-
Hint: Did you mean "value1"?
52+
Hint: Did you mean "value1"?
5353
|}];;
5454

5555
let foobar1 () = () in
@@ -61,7 +61,7 @@ Line 2, characters 17-24:
6161
2 | let foobar2 () = foobar2 () (* typo? or missing "rec"? *) in
6262
^^^^^^^
6363
Error: Unbound value "foobar2"
64-
Hint: Did you mean "foobar1"?
64+
Hint: Did you mean "foobar1"?
6565
Hint: If this is a recursive definition,
6666
you should add the "rec" keyword on line 2
6767
|}];;

testsuite/tests/typing-core-bugs/repeated_did_you_mean.ml

+1-1
Original file line numberDiff line numberDiff line change
@@ -18,5 +18,5 @@ Line 7, characters 8-11:
1818
7 | let _ = fox;;
1919
^^^
2020
Error: Unbound value "fox"
21-
Hint: Did you mean "foo"?
21+
Hint: Did you mean "foo"?
2222
|}]

testsuite/tests/typing-extensions/disambiguation.ml

+7-7
Original file line numberDiff line numberDiff line change
@@ -30,7 +30,7 @@ Line 1, characters 11-15:
3030
^^^^
3131
Error: This variant expression is expected to have type "t"
3232
There is no constructor "Alph" within type "t"
33-
Hint: Did you mean "Aleph" or "Alpha"?
33+
Hint: Did you mean "Aleph" or "Alpha"?
3434
|}]
3535

3636
open M;;
@@ -41,7 +41,7 @@ Line 2, characters 12-16:
4141
^^^^
4242
Error: This variant expression is expected to have type "M.w"
4343
There is no constructor "Alha" within type "M.w"
44-
Hint: Did you mean "Alpha"?
44+
Hint: Did you mean "Alpha"?
4545
|}]
4646

4747
let z: t = Bet;;
@@ -51,7 +51,7 @@ Line 1, characters 11-14:
5151
^^^
5252
Error: This variant expression is expected to have type "t"
5353
There is no constructor "Bet" within type "t"
54-
Hint: Did you mean "Beth"?
54+
Hint: Did you mean "Beth"?
5555
|}]
5656

5757

@@ -65,7 +65,7 @@ Line 3, characters 9-13:
6565
^^^^
6666
Error: This variant expression is expected to have type "t"
6767
There is no constructor "Gamm" within type "t"
68-
Hint: Did you mean "Gamma"?
68+
Hint: Did you mean "Gamma"?
6969
|}];;
7070

7171
raise Not_Found;;
@@ -75,7 +75,7 @@ Line 1, characters 6-15:
7575
^^^^^^^^^
7676
Error: This variant expression is expected to have type "exn"
7777
There is no constructor "Not_Found" within type "exn"
78-
Hint: Did you mean "Not_found"?
78+
Hint: Did you mean "Not_found"?
7979
|}]
8080

8181
(** Aliasing *)
@@ -156,7 +156,7 @@ Line 7, characters 13-17:
156156
^^^^
157157
Error: This variant expression is expected to have type "P.p"
158158
There is no constructor "Alha" within type "x"
159-
Hint: Did you mean "Alpha"?
159+
Hint: Did you mean "Alpha"?
160160
|}]
161161

162162
module M = struct type t = .. type t += T end
@@ -197,7 +197,7 @@ Line 3, characters 8-12:
197197
^^^^
198198
Error: This variant expression is expected to have type "exn"
199199
There is no constructor "Locl" within type "exn"
200-
Hint: Did you mean "Local"?
200+
Hint: Did you mean "Local"?
201201
|}]
202202

203203
let x =

testsuite/tests/typing-labeled-tuples/labeled_tuples.ml

+1-1
Original file line numberDiff line numberDiff line change
@@ -296,7 +296,7 @@ Line 1, characters 22-30:
296296
1 | type bad_t = {x : lbl:bad_type * int}
297297
^^^^^^^^
298298
Error: Unbound type constructor "bad_type"
299-
Hint: Did you mean "bad_t"?
299+
Hint: Did you mean "bad_t"?
300300
|}]
301301
302302
type tx = { x : foo:int * bar:int }

testsuite/tests/typing-misc/polyvars.ml

+1-1
Original file line numberDiff line numberDiff line change
@@ -124,7 +124,7 @@ let f (x : [`A | `B] as 'a) (y : [> 'a]) = ();;
124124
Line 1, characters 61-63:
125125
1 | let f : ([`A | `B ] as 'a) -> [> 'a] -> unit = fun x (y : [> 'a]) -> ();;
126126
^^
127-
Error: The type "'a" does not expand to a polymorphic variant type
127+
Error: The type "'a" does not expand to a polymorphic variant type
128128
Hint: Did you mean "`a"?
129129
|}]
130130

testsuite/tests/typing-misc/printing.ml

+1-1
Original file line numberDiff line numberDiff line change
@@ -9,7 +9,7 @@ type t = [ 'A_name | `Hi ];;
99
Line 1, characters 11-18:
1010
1 | type t = [ 'A_name | `Hi ];;
1111
^^^^^^^
12-
Error: The type "'A_name" does not expand to a polymorphic variant type
12+
Error: The type "'A_name" does not expand to a polymorphic variant type
1313
Hint: Did you mean "`A_name"?
1414
|}];;
1515

testsuite/tests/typing-misc/records.ml

+1-1
Original file line numberDiff line numberDiff line change
@@ -298,5 +298,5 @@ Line 6, characters 13-20:
298298
6 | ; Coq__10.f2 = 0
299299
^^^^^^^
300300
Error: Unbound module "Coq__10"
301-
Hint: Did you mean "Coq__11"?
301+
Hint: Did you mean "Coq__11"?
302302
|}]

testsuite/tests/typing-misc/typetexp_errors.ml

+1-1
Original file line numberDiff line numberDiff line change
@@ -8,7 +8,7 @@ Line 1, characters 32-35:
88
1 | type ('a,'at,'any,'en) t = A of 'an
99
^^^
1010
Error: The type variable "'an" is unbound in this type declaration.
11-
Hint: Did you mean "'a", "'any", "'at" or "'en"?
11+
Hint: Did you mean "'a", "'any", "'at" or "'en"?
1212
|}
1313
]
1414

testsuite/tests/typing-modules/pr6633.ml

+1-1
Original file line numberDiff line numberDiff line change
@@ -26,7 +26,7 @@ Line 2, characters 26-32:
2626
2 | module Foo = functor (E : EqualF) -> struct end;;
2727
^^^^^^
2828
Error: Unbound module type "EqualF"
29-
Hint: Did you mean "Equals"?
29+
Hint: Did you mean "Equals"?
3030
|}]
3131

3232
(* If a module is used as a module type it should trigger the hint

testsuite/tests/typing-sigsubst/sig_local_aliases.ml

+1-1
Original file line numberDiff line numberDiff line change
@@ -50,7 +50,7 @@ Line 2, characters 14-22:
5050
2 | module M := Funct(M)
5151
^^^^^^^^
5252
Error: Unbound module "Funct"
53-
Hint: Did you mean "Fun"?
53+
Hint: Did you mean "Fun"?
5454
|}]
5555

5656
module type Reject2 = sig

testsuite/tests/typing-warnings/records.ml

+1-1
Original file line numberDiff line numberDiff line change
@@ -523,7 +523,7 @@ Line 3, characters 19-22:
523523
^^^
524524
Error: This record expression is expected to have type "t"
525525
There is no field "yyz" within type "t"
526-
Hint: Did you mean "yyy"?
526+
Hint: Did you mean "yyy"?
527527
|}]
528528

529529
(* PR#6004 *)

toplevel/topcommon.ml

+8-5
Original file line numberDiff line numberDiff line change
@@ -358,11 +358,14 @@ let inline_code = Format_doc.compat Style.inline_code
358358
let try_run_directive ppf dir_name pdir_arg =
359359
begin match get_directive dir_name with
360360
| None ->
361-
fprintf ppf "Unknown directive %a." inline_code dir_name;
362-
let directives = all_directive_names () in
363-
Format_doc.compat Misc.did_you_mean ppf
364-
(fun () -> Misc.spellcheck directives dir_name);
365-
fprintf ppf "@.";
361+
let print ppf () =
362+
let directives = all_directive_names () in
363+
Misc.aligned_hint ~prefix:"" ppf
364+
"@{<ralign>Unknown directive @}%a."
365+
Style.inline_code dir_name
366+
(Misc.did_you_mean (Misc.spellcheck directives dir_name))
367+
in
368+
fprintf ppf "%a@." (Format_doc.compat print) ();
366369
false
367370
| Some d ->
368371
match d, pdir_arg with

0 commit comments

Comments
 (0)