Skip to content

Commit 895a7f4

Browse files
committed
Continue + expect test.
1 parent 7fa6a8c commit 895a7f4

File tree

6 files changed

+372
-47
lines changed

6 files changed

+372
-47
lines changed
+18
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,18 @@
1+
#**************************************************************************
2+
#* *
3+
#* OCaml *
4+
#* *
5+
#* Xavier Clerc, SED, INRIA Rocquencourt *
6+
#* *
7+
#* Copyright 2010 Institut National de Recherche en Informatique et *
8+
#* en Automatique. *
9+
#* *
10+
#* All rights reserved. This file is distributed under the terms of *
11+
#* the GNU Lesser General Public License version 2.1, with the *
12+
#* special exception on linking described in the file LICENSE. *
13+
#* *
14+
#**************************************************************************
15+
16+
BASEDIR=../..
17+
include $(BASEDIR)/makefiles/Makefile.expect
18+
include $(BASEDIR)/makefiles/Makefile.common
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,300 @@
1+
[@@@ocaml.warning "+3"];;
2+
3+
module X: sig
4+
type t [@@ocaml.deprecated]
5+
type s [@@ocaml.deprecated]
6+
val x: t [@@ocaml.deprecated]
7+
end = struct
8+
type t = int
9+
type s
10+
let x = 0
11+
end;;
12+
[%%expect{|
13+
Line _, characters 9-10:
14+
Warning 3: deprecated: t
15+
module X : sig type t type s val x : t end
16+
|}]
17+
18+
type t = X.t
19+
;;
20+
[%%expect{|
21+
Line _, characters 9-12:
22+
Warning 3: deprecated: X.t
23+
type t = X.t
24+
|}]
25+
26+
let x = X.x
27+
;;
28+
[%%expect{|
29+
Line _, characters 8-11:
30+
Warning 3: deprecated: X.x
31+
val x : X.t = <abstr>
32+
|}]
33+
34+
(* Warning control on type declaration *)
35+
36+
type t = X.t * X.s
37+
;;
38+
[%%expect{|
39+
Line _, characters 9-12:
40+
Warning 3: deprecated: X.t
41+
Line _, characters 15-18:
42+
Warning 3: deprecated: X.s
43+
type t = X.t * X.s
44+
|}]
45+
46+
type t = X.t * X.s [@@ocaml.warning "-3"]
47+
;;
48+
[%%expect{|
49+
type t = X.t * X.s
50+
|}]
51+
52+
type t1 = X.t [@@ocaml.warning "-3"]
53+
and t2 = X.s
54+
;;
55+
[%%expect{|
56+
Line _, characters 9-12:
57+
Warning 3: deprecated: X.s
58+
type t1 = X.t
59+
and t2 = X.s
60+
|}]
61+
62+
type t = A of t [@@ocaml.deprecated]
63+
;;
64+
[%%expect{|
65+
Line _, characters 14-15:
66+
Warning 3: deprecated: t
67+
type t = A of t
68+
|}]
69+
70+
type t = A of t
71+
[@@ocaml.deprecated]
72+
[@@ocaml.warning "-3"]
73+
;;
74+
[%%expect{|
75+
type t = A of t
76+
|}]
77+
78+
(* Warning control on type expressions *)
79+
80+
type t = (X.t * X.s) [@ocaml.warning "-3"]
81+
;;
82+
[%%expect{|
83+
type t = X.t * X.s
84+
|}]
85+
86+
type t = (X.t [@ocaml.warning "-3"]) * X.s
87+
;;
88+
[%%expect{|
89+
Line _, characters 39-42:
90+
Warning 3: deprecated: X.s
91+
type t = X.t * X.s
92+
|}]
93+
94+
95+
type t = A of (t [@ocaml.warning "-3"])
96+
[@@ocaml.deprecated]
97+
;;
98+
[%%expect{|
99+
type t = A of t
100+
|}]
101+
102+
(* Warning control on pattern expressions *)
103+
104+
let _ = function (_ : X.t) -> ()
105+
;;
106+
[%%expect{|
107+
Line _, characters 22-25:
108+
Warning 3: deprecated: X.t
109+
- : X.t -> unit = <fun>
110+
|}]
111+
112+
let _ = function (_ : X.t)[@ocaml.warning "-3"] -> ()
113+
;;
114+
[%%expect{|
115+
- : X.t -> unit = <fun>
116+
|}]
117+
118+
119+
(* Warning control on module expression and module declaration *)
120+
121+
module M = struct let x = X.x end
122+
;;
123+
[%%expect{|
124+
Line _, characters 26-29:
125+
Warning 3: deprecated: X.x
126+
module M : sig val x : X.t end
127+
|}]
128+
129+
module M = (struct let x = X.x end)[@ocaml.warning "-3"]
130+
;;
131+
[%%expect{|
132+
module M : sig val x : X.t end
133+
|}]
134+
135+
module M = struct let x = X.x end [@@ocaml.warning "-3"]
136+
;;
137+
[%%expect{|
138+
module M : sig val x : X.t end
139+
|}]
140+
141+
142+
module rec M : sig val x: X.t end = struct let x = X.x end
143+
[%%expect{|
144+
Line _, characters 26-29:
145+
Warning 3: deprecated: X.t
146+
Line _, characters 26-29:
147+
Warning 3: deprecated: X.t
148+
Line _, characters 51-54:
149+
Warning 3: deprecated: X.x
150+
module rec M : sig val x : X.t end
151+
|}]
152+
153+
module rec M : sig val x: X.t end = struct let x = X.x end [@@ocaml.warning "-3"]
154+
[%%expect{|
155+
module rec M : sig val x : X.t end
156+
|}]
157+
158+
module rec M :
159+
(sig val x: X.t end)[@ocaml.warning "-3"] =
160+
(struct let x = X.x end)[@ocaml.warning "-3"]
161+
[%%expect{|
162+
module rec M : sig val x : X.t end
163+
|}]
164+
165+
module rec M :
166+
(sig val x: X.t end)[@ocaml.warning "-3"] =
167+
struct let x = X.x end
168+
[%%expect{|
169+
Line _, characters 17-20:
170+
Warning 3: deprecated: X.x
171+
module rec M : sig val x : X.t end
172+
|}]
173+
174+
(* Warning control on module type expression and module type declaration *)
175+
176+
module type S = sig type t = X.t end
177+
;;
178+
[%%expect{|
179+
Line _, characters 29-32:
180+
Warning 3: deprecated: X.t
181+
module type S = sig type t = X.t end
182+
|}]
183+
184+
module type S = (sig type t = X.t end)[@ocaml.warning "-3"]
185+
;;
186+
[%%expect{|
187+
module type S = sig type t = X.t end
188+
|}]
189+
190+
module type S = sig type t = X.t end[@@ocaml.warning "-3"]
191+
;;
192+
[%%expect{|
193+
module type S = sig type t = X.t end
194+
|}]
195+
196+
197+
(* Warning control on class expressions, class declarations and class fields *)
198+
199+
class c = object method x = X.x end
200+
;;
201+
[%%expect{|
202+
Line _, characters 28-31:
203+
Warning 3: deprecated: X.x
204+
class c : object method x : X.t end
205+
|}]
206+
207+
class c = object method x = X.x end[@@ocaml.warning "-3"]
208+
;;
209+
[%%expect{|
210+
class c : object method x : X.t end
211+
|}]
212+
213+
class c = (object method x = X.x end)[@ocaml.warning "-3"]
214+
;;
215+
[%%expect{|
216+
class c : object method x : X.t end
217+
|}]
218+
219+
class c = object method x = X.x [@@ocaml.warning "-3"] end
220+
;;
221+
[%%expect{|
222+
class c : object method x : X.t end
223+
|}]
224+
225+
(* Warning control on class type expressions, class type declarations
226+
and class type fields *)
227+
228+
class type c = object method x : X.t end
229+
;;
230+
[%%expect{|
231+
Line _, characters 33-36:
232+
Warning 3: deprecated: X.t
233+
class type c = object method x : X.t end
234+
|}]
235+
236+
class type c = object method x : X.t end[@@ocaml.warning "-3"]
237+
;;
238+
[%%expect{|
239+
class type c = object method x : X.t end
240+
|}]
241+
242+
class type c = object method x : X.t end[@ocaml.warning "-3"]
243+
;;
244+
[%%expect{|
245+
class type c = object method x : X.t end
246+
|}]
247+
248+
class type c = object method x : X.t [@@ocaml.warning "-3"] end
249+
;;
250+
[%%expect{|
251+
class type c = object method x : X.t end
252+
|}]
253+
254+
255+
256+
(* External declarations *)
257+
258+
external foo: unit -> X.t = "foo"
259+
;;
260+
[%%expect{|
261+
Line _, characters 22-25:
262+
Warning 3: deprecated: X.t
263+
external foo : unit -> X.t = "foo"
264+
|}]
265+
266+
external foo: unit -> X.t = "foo"[@@ocaml.warning "-3"]
267+
;;
268+
[%%expect{|
269+
external foo : unit -> X.t = "foo"
270+
|}]
271+
272+
273+
(* open / include *)
274+
275+
module D = struct end[@@ocaml.deprecated]
276+
277+
open D
278+
;;
279+
[%%expect{|
280+
module D : sig end
281+
Line _, characters 5-6:
282+
Warning 3: deprecated: module D
283+
|}]
284+
285+
open D [@@ocaml.warning "-3"]
286+
;;
287+
[%%expect{|
288+
|}]
289+
290+
include D
291+
;;
292+
[%%expect{|
293+
Line _, characters 8-9:
294+
Warning 3: deprecated: module D
295+
|}]
296+
297+
include D [@@ocaml.warning "-3"]
298+
;;
299+
[%%expect{|
300+
|}]

testsuite/tests/warnings/w03.ml

-29
This file was deleted.

0 commit comments

Comments
 (0)