@@ -169,34 +169,32 @@ let report_type_mismatch0 first second decl ppf err =
169
169
" uses unboxed representation"
170
170
| Immediate -> pr " %s is not an immediate type" first
171
171
172
- let report_type_mismatch first second decl ppf =
173
- List. iter
174
- (fun err ->
175
- if err = Manifest then () else
176
- Format. fprintf ppf " @ %a." (report_type_mismatch0 first second decl) err)
172
+ let report_type_mismatch first second decl ppf err =
173
+ if err = Manifest then () else
174
+ Format. fprintf ppf " @ %a." (report_type_mismatch0 first second decl) err
177
175
178
176
let rec compare_constructor_arguments ~loc env cstr params1 params2 arg1 arg2 =
179
177
match arg1, arg2 with
180
178
| Types. Cstr_tuple arg1 , Types. Cstr_tuple arg2 ->
181
- if List. length arg1 <> List. length arg2 then [ Field_arity cstr]
179
+ if List. length arg1 <> List. length arg2 then Some ( Field_arity cstr)
182
180
else if
183
181
(* Ctype.equal must be called on all arguments at once, cf. PR#7378 *)
184
182
Ctype. equal env true (params1 @ arg1) (params2 @ arg2)
185
- then [] else [ Field_type cstr]
183
+ then None else Some ( Field_type cstr)
186
184
| Types. Cstr_record l1 , Types. Cstr_record l2 ->
187
185
compare_records env ~loc params1 params2 0 l1 l2
188
- | _ -> [ Field_type cstr]
186
+ | _ -> Some ( Field_type cstr)
189
187
190
188
and compare_variants ~loc env params1 params2 n
191
189
(cstrs1 : Types.constructor_declaration list )
192
190
(cstrs2 : Types.constructor_declaration list ) =
193
191
match cstrs1, cstrs2 with
194
- [] , [] -> []
195
- | [] , c ::_ -> [ Field_missing (true , c.Types. cd_id)]
196
- | c ::_ , [] -> [ Field_missing (false , c.Types. cd_id)]
192
+ [] , [] -> None
193
+ | [] , c ::_ -> Some ( Field_missing (true , c.Types. cd_id))
194
+ | c ::_ , [] -> Some ( Field_missing (false , c.Types. cd_id))
197
195
| cd1 ::rem1 , cd2 ::rem2 ->
198
196
if Ident. name cd1.cd_id <> Ident. name cd2.cd_id then
199
- [ Field_names (n, cd1.cd_id, cd2.cd_id)]
197
+ Some ( Field_names (n, cd1.cd_id, cd2.cd_id))
200
198
else begin
201
199
Builtin_attributes. check_deprecated_inclusion
202
200
~def: cd1.cd_loc
@@ -210,14 +208,14 @@ and compare_variants ~loc env params1 params2 n
210
208
if Ctype. equal env true [r1] [r2] then
211
209
compare_constructor_arguments ~loc env cd1.cd_id [r1] [r2]
212
210
cd1.cd_args cd2.cd_args
213
- else [ Field_type cd1.cd_id]
211
+ else Some ( Field_type cd1.cd_id)
214
212
| Some _ , None | None , Some _ ->
215
- [ Field_type cd1.cd_id]
213
+ Some ( Field_type cd1.cd_id)
216
214
| _ ->
217
215
compare_constructor_arguments ~loc env cd1.cd_id
218
216
params1 params2 cd1.cd_args cd2.cd_args
219
217
in
220
- if r <> [] then r
218
+ if r <> None then r
221
219
else compare_variants ~loc env params1 params2 (n+ 1 ) rem1 rem2
222
220
end
223
221
@@ -226,14 +224,14 @@ and compare_records ~loc env params1 params2 n
226
224
(labels1 : Types.label_declaration list )
227
225
(labels2 : Types.label_declaration list ) =
228
226
match labels1, labels2 with
229
- [] , [] -> []
230
- | [] , l ::_ -> [ Field_missing (true , l.Types. ld_id)]
231
- | l ::_ , [] -> [ Field_missing (false , l.Types. ld_id)]
227
+ [] , [] -> None
228
+ | [] , l ::_ -> Some ( Field_missing (true , l.Types. ld_id))
229
+ | l ::_ , [] -> Some ( Field_missing (false , l.Types. ld_id))
232
230
| ld1 ::rem1 , ld2 ::rem2 ->
233
231
if Ident. name ld1.ld_id <> Ident. name ld2.ld_id
234
- then [ Field_names (n, ld1.ld_id, ld2.ld_id)]
232
+ then Some ( Field_names (n, ld1.ld_id, ld2.ld_id))
235
233
else if ld1.ld_mutable <> ld2.ld_mutable then
236
- [ Field_mutable ld1.ld_id]
234
+ Some ( Field_mutable ld1.ld_id)
237
235
else begin
238
236
Builtin_attributes. check_deprecated_mutable_inclusion
239
237
~def: ld1.ld_loc
@@ -248,7 +246,7 @@ and compare_records ~loc env params1 params2 n
248
246
(n+ 1 )
249
247
rem1 rem2
250
248
else
251
- [ Field_type ld1.ld_id]
249
+ Some ( Field_type ld1.ld_id)
252
250
end
253
251
254
252
let type_declarations ?(equality = false ) ~loc env ~mark name decl1 id decl2 =
@@ -258,37 +256,37 @@ let type_declarations ?(equality = false) ~loc env ~mark name decl1 id decl2 =
258
256
loc
259
257
decl1.type_attributes decl2.type_attributes
260
258
name;
261
- if decl1.type_arity <> decl2.type_arity then [ Arity ] else
262
- if not (private_flags decl1 decl2) then [ Privacy ] else
259
+ if decl1.type_arity <> decl2.type_arity then Some Arity else
260
+ if not (private_flags decl1 decl2) then Some Privacy else
263
261
let err = match (decl1.type_manifest, decl2.type_manifest) with
264
262
(_ , None) ->
265
263
if Ctype. equal env true decl1.type_params decl2.type_params
266
- then [] else [ Constraint ]
264
+ then None else Some Constraint
267
265
| (Some ty1 , Some ty2 ) ->
268
266
if type_manifest env ty1 decl1.type_params ty2 decl2.type_params
269
267
decl2.type_private
270
- then [] else [ Manifest ]
268
+ then None else Some Manifest
271
269
| (None, Some ty2 ) ->
272
270
let ty1 =
273
271
Btype. newgenty (Tconstr (Pident id, decl2.type_params, ref Mnil ))
274
272
in
275
273
if Ctype. equal env true decl1.type_params decl2.type_params then
276
- if Ctype. equal env false [ty1] [ty2] then []
277
- else [ Manifest ]
278
- else [ Constraint ]
274
+ if Ctype. equal env false [ty1] [ty2] then None
275
+ else Some Manifest
276
+ else Some Constraint
279
277
in
280
- if err <> [] then err else
278
+ if err <> None then err else
281
279
let err =
282
280
match (decl2.type_kind, decl1.type_unboxed.unboxed,
283
281
decl2.type_unboxed.unboxed) with
284
- | Type_abstract , _ , _ -> []
285
- | _ , true , false -> [ Unboxed_representation false ]
286
- | _ , false , true -> [ Unboxed_representation true ]
287
- | _ -> []
282
+ | Type_abstract , _ , _ -> None
283
+ | _ , true , false -> Some ( Unboxed_representation false )
284
+ | _ , false , true -> Some ( Unboxed_representation true )
285
+ | _ -> None
288
286
in
289
- if err <> [] then err else
287
+ if err <> None then err else
290
288
let err = match (decl1.type_kind, decl2.type_kind) with
291
- (_ , Type_abstract) -> []
289
+ (_ , Type_abstract) -> None
292
290
| (Type_variant cstrs1 , Type_variant cstrs2 ) ->
293
291
if mark then begin
294
292
let mark cstrs usage name decl =
@@ -312,26 +310,26 @@ let type_declarations ?(equality = false) ~loc env ~mark name decl1 id decl2 =
312
310
compare_records ~loc env decl1.type_params
313
311
decl2.type_params 1 labels1 labels2
314
312
in
315
- if err <> [] || rep1 = rep2 then err else
316
- [ Record_representation (rep2 = Record_float )]
317
- | (Type_open, Type_open) -> []
318
- | (_ , _ ) -> [ Kind ]
313
+ if err <> None || rep1 = rep2 then err else
314
+ Some ( Record_representation (rep2 = Record_float ))
315
+ | (Type_open, Type_open) -> None
316
+ | (_ , _ ) -> Some Kind
319
317
in
320
- if err <> [] then err else
318
+ if err <> None then err else
321
319
let abstr = decl2.type_kind = Type_abstract && decl2.type_manifest = None in
322
320
(* If attempt to assign a non-immediate type (e.g. string) to a type that
323
321
* must be immediate, then we error *)
324
322
let err =
325
323
if abstr &&
326
324
not decl1.type_immediate &&
327
325
decl2.type_immediate then
328
- [ Immediate ]
329
- else []
326
+ Some Immediate
327
+ else None
330
328
in
331
- if err <> [] then err else
329
+ if err <> None then err else
332
330
let need_variance =
333
331
abstr || decl1.type_private = Private || decl1.type_kind = Type_open in
334
- if not need_variance then [] else
332
+ if not need_variance then None else
335
333
let abstr = abstr || decl2.type_private = Private in
336
334
let opn = decl2.type_kind = Type_open && decl2.type_manifest = None in
337
335
let constrained ty = not (Btype. (is_Tvar (repr ty))) in
@@ -346,7 +344,7 @@ let type_declarations ?(equality = false) ~loc env ~mark name decl1 id decl2 =
346
344
let (p1,n1,i1,j1) = get_lower v1 and (p2,n2,i2,j2) = get_lower v2 in
347
345
imp abstr (imp p2 p1 && imp n2 n1 && imp i2 i1 && imp j2 j1))
348
346
decl2.type_params (List. combine decl1.type_variance decl2.type_variance)
349
- then [] else [ Variance ]
347
+ then None else Some Variance
350
348
351
349
(* Inclusion between extension constructors *)
352
350
@@ -364,21 +362,22 @@ let extension_constructors ~loc env ~mark id ext1 ext2 =
364
362
let ty2 =
365
363
Btype. newgenty (Tconstr (ext2.ext_type_path, ext2.ext_type_params, ref Mnil ))
366
364
in
367
- if Ctype. equal env true
368
- (ty1 :: ext1.ext_type_params)
369
- (ty2 :: ext2.ext_type_params)
370
- then
371
- if compare_constructor_arguments ~loc env (Ident. create " " )
365
+ if not (Ctype. equal env true (ty1 :: ext1.ext_type_params)
366
+ (ty2 :: ext2.ext_type_params))
367
+ then Some (Field_type id)
368
+ else
369
+ let r =
370
+ compare_constructor_arguments ~loc env id
372
371
ext1.ext_type_params ext2.ext_type_params
373
- ext1.ext_args ext2.ext_args = [] then
374
- if match ext1.ext_ret_type, ext2.ext_ret_type with
375
- Some r1 , Some r2 when not (Ctype. equal env true [r1] [r2]) -> false
376
- | Some _ , None | None , Some _ -> false
377
- | _ -> true
378
- then
372
+ ext1.ext_args ext2.ext_args
373
+ in
374
+ if r <> None then r else
375
+ match ext1.ext_ret_type, ext2.ext_ret_type with
376
+ Some r1 , Some r2 when not (Ctype. equal env true [r1] [r2]) ->
377
+ Some (Field_type id)
378
+ | Some _ , None | None , Some _ ->
379
+ Some (Field_type id)
380
+ | _ ->
379
381
match ext1.ext_private, ext2.ext_private with
380
- Private , Public -> false
381
- | _ , _ -> true
382
- else false
383
- else false
384
- else false
382
+ Private , Public -> Some Privacy
383
+ | _ , _ -> None
0 commit comments