forked from let-def/ocaml
-
Notifications
You must be signed in to change notification settings - Fork 0
/
typeclass.ml
2126 lines (1987 loc) · 75.5 KB
/
typeclass.ml
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
335
336
337
338
339
340
341
342
343
344
345
346
347
348
349
350
351
352
353
354
355
356
357
358
359
360
361
362
363
364
365
366
367
368
369
370
371
372
373
374
375
376
377
378
379
380
381
382
383
384
385
386
387
388
389
390
391
392
393
394
395
396
397
398
399
400
401
402
403
404
405
406
407
408
409
410
411
412
413
414
415
416
417
418
419
420
421
422
423
424
425
426
427
428
429
430
431
432
433
434
435
436
437
438
439
440
441
442
443
444
445
446
447
448
449
450
451
452
453
454
455
456
457
458
459
460
461
462
463
464
465
466
467
468
469
470
471
472
473
474
475
476
477
478
479
480
481
482
483
484
485
486
487
488
489
490
491
492
493
494
495
496
497
498
499
500
501
502
503
504
505
506
507
508
509
510
511
512
513
514
515
516
517
518
519
520
521
522
523
524
525
526
527
528
529
530
531
532
533
534
535
536
537
538
539
540
541
542
543
544
545
546
547
548
549
550
551
552
553
554
555
556
557
558
559
560
561
562
563
564
565
566
567
568
569
570
571
572
573
574
575
576
577
578
579
580
581
582
583
584
585
586
587
588
589
590
591
592
593
594
595
596
597
598
599
600
601
602
603
604
605
606
607
608
609
610
611
612
613
614
615
616
617
618
619
620
621
622
623
624
625
626
627
628
629
630
631
632
633
634
635
636
637
638
639
640
641
642
643
644
645
646
647
648
649
650
651
652
653
654
655
656
657
658
659
660
661
662
663
664
665
666
667
668
669
670
671
672
673
674
675
676
677
678
679
680
681
682
683
684
685
686
687
688
689
690
691
692
693
694
695
696
697
698
699
700
701
702
703
704
705
706
707
708
709
710
711
712
713
714
715
716
717
718
719
720
721
722
723
724
725
726
727
728
729
730
731
732
733
734
735
736
737
738
739
740
741
742
743
744
745
746
747
748
749
750
751
752
753
754
755
756
757
758
759
760
761
762
763
764
765
766
767
768
769
770
771
772
773
774
775
776
777
778
779
780
781
782
783
784
785
786
787
788
789
790
791
792
793
794
795
796
797
798
799
800
801
802
803
804
805
806
807
808
809
810
811
812
813
814
815
816
817
818
819
820
821
822
823
824
825
826
827
828
829
830
831
832
833
834
835
836
837
838
839
840
841
842
843
844
845
846
847
848
849
850
851
852
853
854
855
856
857
858
859
860
861
862
863
864
865
866
867
868
869
870
871
872
873
874
875
876
877
878
879
880
881
882
883
884
885
886
887
888
889
890
891
892
893
894
895
896
897
898
899
900
901
902
903
904
905
906
907
908
909
910
911
912
913
914
915
916
917
918
919
920
921
922
923
924
925
926
927
928
929
930
931
932
933
934
935
936
937
938
939
940
941
942
943
944
945
946
947
948
949
950
951
952
953
954
955
956
957
958
959
960
961
962
963
964
965
966
967
968
969
970
971
972
973
974
975
976
977
978
979
980
981
982
983
984
985
986
987
988
989
990
991
992
993
994
995
996
997
998
999
1000
(**************************************************************************)
(* *)
(* OCaml *)
(* *)
(* Jerome Vouillon, projet Cristal, INRIA Rocquencourt *)
(* *)
(* Copyright 1996 Institut National de Recherche en Informatique et *)
(* en Automatique. *)
(* *)
(* All rights reserved. This file is distributed under the terms of *)
(* the GNU Lesser General Public License version 2.1, with the *)
(* special exception on linking described in the file LICENSE. *)
(* *)
(**************************************************************************)
open Parsetree
open Asttypes
open Path
open Types
open Typecore
open Typetexp
open Format
type 'a class_info = {
cls_id : Ident.t;
cls_id_loc : string loc;
cls_decl : class_declaration;
cls_ty_id : Ident.t;
cls_ty_decl : class_type_declaration;
cls_obj_id : Ident.t;
cls_obj_abbr : type_declaration;
cls_typesharp_id : Ident.t;
cls_abbr : type_declaration;
cls_arity : int;
cls_pub_methods : string list;
cls_info : 'a;
}
type class_type_info = {
clsty_ty_id : Ident.t;
clsty_id_loc : string loc;
clsty_ty_decl : class_type_declaration;
clsty_obj_id : Ident.t;
clsty_obj_abbr : type_declaration;
clsty_typesharp_id : Ident.t;
clsty_abbr : type_declaration;
clsty_info : Typedtree.class_type_declaration;
}
type 'a full_class = {
id : Ident.t;
id_loc : tag loc;
clty: class_declaration;
ty_id: Ident.t;
cltydef: class_type_declaration;
obj_id: Ident.t;
obj_abbr: type_declaration;
cl_id: Ident.t;
cl_abbr: type_declaration;
arity: int;
pub_meths: string list;
coe: Warnings.loc list;
req: 'a Typedtree.class_infos;
}
type kind =
| Object
| Class
| Class_type
type final =
| Final
| Not_final
let kind_of_final = function
| Final -> Object
| Not_final -> Class
type error =
| Unconsistent_constraint of Errortrace.unification_error
| Field_type_mismatch of string * string * Errortrace.unification_error
| Unexpected_field of type_expr * string
| Structure_expected of class_type
| Cannot_apply of class_type
| Apply_wrong_label of arg_label
| Pattern_type_clash of type_expr
| Repeated_parameter
| Unbound_class_2 of Longident.t
| Unbound_class_type_2 of Longident.t
| Abbrev_type_clash of type_expr * type_expr * type_expr
| Constructor_type_mismatch of string * Errortrace.unification_error
| Virtual_class of kind * string list * string list
| Undeclared_methods of kind * string list
| Parameter_arity_mismatch of Longident.t * int * int
| Parameter_mismatch of Errortrace.unification_error
| Bad_parameters of Ident.t * type_expr * type_expr
| Class_match_failure of Ctype.class_match_failure list
| Unbound_val of string
| Unbound_type_var of
(formatter -> unit) * (type_expr * bool * string * type_expr)
| Non_generalizable_class of Ident.t * Types.class_declaration
| Cannot_coerce_self of type_expr
| Non_collapsable_conjunction of
Ident.t * Types.class_declaration * Errortrace.unification_error
| Self_clash of Errortrace.unification_error
| Mutability_mismatch of string * mutable_flag
| No_overriding of string * string
| Duplicate of string * string
| Closing_self_type of class_signature
exception Error of Location.t * Env.t * error
exception Error_forward of Location.error
open Typedtree
let type_open_descr :
(?used_slot:bool ref -> Env.t -> Parsetree.open_description
-> open_description * Env.t) ref =
ref (fun ?used_slot:_ _ -> assert false)
let ctyp desc typ env loc =
{ ctyp_desc = desc; ctyp_type = typ; ctyp_loc = loc; ctyp_env = env;
ctyp_attributes = [] }
(*
Path associated to the temporary class type of a class being typed
(its constructor is not available).
*)
let unbound_class =
Path.Pident (Ident.create_local "*undef*")
(************************************)
(* Some operations on class types *)
(************************************)
let extract_constraints cty =
let sign = Btype.signature_of_class_type cty in
(Btype.instance_vars sign,
Btype.methods sign,
Btype.concrete_methods sign)
(* Record a class type *)
let rc node =
Cmt_format.add_saved_type (Cmt_format.Partial_class_expr node);
node
let update_class_signature loc env ~warn_implicit_public virt kind sign =
let implicit_public, implicit_declared =
Ctype.update_class_signature env sign
in
if implicit_declared <> [] then begin
match virt with
| Virtual -> () (* Should perhaps emit warning 17 here *)
| Concrete ->
raise (Error(loc, env, Undeclared_methods(kind, implicit_declared)))
end;
if warn_implicit_public && implicit_public <> [] then begin
Location.prerr_warning
loc (Warnings.Implicit_public_methods implicit_public)
end
let complete_class_signature loc env virt kind sign =
update_class_signature loc env ~warn_implicit_public:false virt kind sign;
Ctype.hide_private_methods env sign
let complete_class_type loc env virt kind typ =
let sign = Btype.signature_of_class_type typ in
complete_class_signature loc env virt kind sign
let check_virtual loc env virt kind sign =
match virt with
| Virtual -> ()
| Concrete ->
match Btype.virtual_methods sign, Btype.virtual_instance_vars sign with
| [], [] -> ()
| meths, vars ->
raise(Error(loc, env, Virtual_class(kind, meths, vars)))
(* Return the constructor type associated to a class type *)
let rec constructor_type constr cty =
match cty with
Cty_constr (_, _, cty) ->
constructor_type constr cty
| Cty_signature _ ->
constr
| Cty_arrow (l, ty, cty) ->
Ctype.newty (Tarrow (l, ty, constructor_type constr cty, commu_ok))
(***********************************)
(* Primitives for typing classes *)
(***********************************)
let raise_add_method_failure loc env label sign failure =
match (failure : Ctype.add_method_failure) with
| Ctype.Unexpected_method ->
raise(Error(loc, env, Unexpected_field (sign.Types.csig_self, label)))
| Ctype.Type_mismatch trace ->
raise(Error(loc, env, Field_type_mismatch ("method", label, trace)))
let raise_add_instance_variable_failure loc env label failure =
match (failure : Ctype.add_instance_variable_failure) with
| Ctype.Mutability_mismatch mut ->
raise (Error(loc, env, Mutability_mismatch(label, mut)))
| Ctype.Type_mismatch trace ->
raise (Error(loc, env,
Field_type_mismatch("instance variable", label, trace)))
let raise_inherit_class_signature_failure loc env sign = function
| Ctype.Self_type_mismatch trace ->
raise(Error(loc, env, Self_clash trace))
| Ctype.Method(label, failure) ->
raise_add_method_failure loc env label sign failure
| Ctype.Instance_variable(label, failure) ->
raise_add_instance_variable_failure loc env label failure
let add_method loc env label priv virt ty sign =
match Ctype.add_method env label priv virt ty sign with
| () -> ()
| exception Ctype.Add_method_failed failure ->
raise_add_method_failure loc env label sign failure
let add_instance_variable ~strict loc env label mut virt ty sign =
match Ctype.add_instance_variable ~strict env label mut virt ty sign with
| () -> ()
| exception Ctype.Add_instance_variable_failed failure ->
raise_add_instance_variable_failure loc env label failure
let inherit_class_signature ~strict loc env sign1 sign2 =
match Ctype.inherit_class_signature ~strict env sign1 sign2 with
| () -> ()
| exception Ctype.Inherit_class_signature_failed failure ->
raise_inherit_class_signature_failure loc env sign1 failure
let inherit_class_type ~strict loc env sign1 cty2 =
let sign2 =
match Btype.scrape_class_type cty2 with
| Cty_signature sign2 -> sign2
| _ ->
raise(Error(loc, env, Structure_expected cty2))
in
inherit_class_signature ~strict loc env sign1 sign2
let unify_delayed_method_type loc env label ty expected_ty=
match Ctype.unify env ty expected_ty with
| () -> ()
| exception Ctype.Unify trace ->
raise(Error(loc, env, Field_type_mismatch ("method", label, trace)))
let type_constraint val_env sty sty' loc =
let cty = transl_simple_type val_env false sty in
let ty = cty.ctyp_type in
let cty' = transl_simple_type val_env false sty' in
let ty' = cty'.ctyp_type in
begin
try Ctype.unify val_env ty ty' with Ctype.Unify err ->
raise(Error(loc, val_env, Unconsistent_constraint err));
end;
(cty, cty')
let make_method loc cl_num expr =
let open Ast_helper in
let mkid s = mkloc s loc in
Exp.fun_ ~loc:expr.pexp_loc Nolabel None
(Pat.alias ~loc (Pat.var ~loc (mkid "self-*")) (mkid ("self-" ^ cl_num)))
expr
(*******************************)
let delayed_meth_specs = ref []
let rec class_type_field env sign self_scope ctf =
let loc = ctf.pctf_loc in
let mkctf desc =
{ ctf_desc = desc; ctf_loc = loc; ctf_attributes = ctf.pctf_attributes }
in
let mkctf_with_attrs f =
Builtin_attributes.warning_scope ctf.pctf_attributes
(fun () -> mkctf (f ()))
in
match ctf.pctf_desc with
| Pctf_inherit sparent ->
mkctf_with_attrs
(fun () ->
let parent = class_type env Virtual self_scope sparent in
complete_class_type parent.cltyp_loc
env Virtual Class_type parent.cltyp_type;
inherit_class_type ~strict:false loc env sign parent.cltyp_type;
Tctf_inherit parent)
| Pctf_val ({txt=lab}, mut, virt, sty) ->
mkctf_with_attrs
(fun () ->
let cty = transl_simple_type env false sty in
let ty = cty.ctyp_type in
add_instance_variable ~strict:false loc env lab mut virt ty sign;
Tctf_val (lab, mut, virt, cty))
| Pctf_method ({txt=lab}, priv, virt, sty) ->
mkctf_with_attrs
(fun () ->
let sty = Ast_helper.Typ.force_poly sty in
match sty.ptyp_desc, priv with
| Ptyp_poly ([],sty'), Public ->
let expected_ty = Ctype.newvar () in
add_method loc env lab priv virt expected_ty sign;
let returned_cty = ctyp Ttyp_any (Ctype.newty Tnil) env loc in
delayed_meth_specs :=
Warnings.mk_lazy (fun () ->
let cty = transl_simple_type_univars env sty' in
let ty = cty.ctyp_type in
unify_delayed_method_type loc env lab ty expected_ty;
returned_cty.ctyp_desc <- Ttyp_poly ([], cty);
returned_cty.ctyp_type <- ty;
) :: !delayed_meth_specs;
Tctf_method (lab, priv, virt, returned_cty)
| _ ->
let cty = transl_simple_type env false sty in
let ty = cty.ctyp_type in
add_method loc env lab priv virt ty sign;
Tctf_method (lab, priv, virt, cty))
| Pctf_constraint (sty, sty') ->
mkctf_with_attrs
(fun () ->
let (cty, cty') = type_constraint env sty sty' ctf.pctf_loc in
Tctf_constraint (cty, cty'))
| Pctf_attribute x ->
Builtin_attributes.warning_attribute x;
mkctf (Tctf_attribute x)
| Pctf_extension ext ->
raise (Error_forward (Builtin_attributes.error_of_extension ext))
and class_signature virt env pcsig self_scope loc =
let {pcsig_self=sty; pcsig_fields=psign} = pcsig in
let sign = Ctype.new_class_signature () in
(* Introduce a dummy method preventing self type from being closed. *)
Ctype.add_dummy_method env ~scope:self_scope sign;
let self_cty = transl_simple_type env false sty in
let self_type = self_cty.ctyp_type in
begin try
Ctype.unify env self_type sign.csig_self
with Ctype.Unify _ ->
raise(Error(sty.ptyp_loc, env, Pattern_type_clash self_type))
end;
(* Class type fields *)
let fields =
Builtin_attributes.warning_scope []
(fun () -> List.map (class_type_field env sign self_scope) psign)
in
check_virtual loc env virt Class_type sign;
{ csig_self = self_cty;
csig_fields = fields;
csig_type = sign; }
and class_type env virt self_scope scty =
Builtin_attributes.warning_scope scty.pcty_attributes
(fun () -> class_type_aux env virt self_scope scty)
and class_type_aux env virt self_scope scty =
let cltyp desc typ =
{
cltyp_desc = desc;
cltyp_type = typ;
cltyp_loc = scty.pcty_loc;
cltyp_env = env;
cltyp_attributes = scty.pcty_attributes;
}
in
match scty.pcty_desc with
| Pcty_constr (lid, styl) ->
let (path, decl) = Env.lookup_cltype ~loc:scty.pcty_loc lid.txt env in
if Path.same decl.clty_path unbound_class then
raise(Error(scty.pcty_loc, env, Unbound_class_type_2 lid.txt));
let (params, clty) =
Ctype.instance_class decl.clty_params decl.clty_type
in
(* Adding a dummy method to the self type prevents it from being closed /
escaping. *)
Ctype.add_dummy_method env ~scope:self_scope
(Btype.signature_of_class_type clty);
if List.length params <> List.length styl then
raise(Error(scty.pcty_loc, env,
Parameter_arity_mismatch (lid.txt, List.length params,
List.length styl)));
let ctys = List.map2
(fun sty ty ->
let cty' = transl_simple_type env false sty in
let ty' = cty'.ctyp_type in
begin
try Ctype.unify env ty' ty with Ctype.Unify err ->
raise(Error(sty.ptyp_loc, env, Parameter_mismatch err))
end;
cty'
) styl params
in
let typ = Cty_constr (path, params, clty) in
cltyp (Tcty_constr ( path, lid , ctys)) typ
| Pcty_signature pcsig ->
let clsig = class_signature virt env pcsig self_scope scty.pcty_loc in
let typ = Cty_signature clsig.csig_type in
cltyp (Tcty_signature clsig) typ
| Pcty_arrow (l, sty, scty) ->
let cty = transl_simple_type env false sty in
let ty = cty.ctyp_type in
let ty =
if Btype.is_optional l
then Ctype.newty (Tconstr(Predef.path_option,[ty], ref Mnil))
else ty in
let clty = class_type env virt self_scope scty in
let typ = Cty_arrow (l, ty, clty.cltyp_type) in
cltyp (Tcty_arrow (l, cty, clty)) typ
| Pcty_open (od, e) ->
let (od, newenv) = !type_open_descr env od in
let clty = class_type newenv virt self_scope e in
cltyp (Tcty_open (od, clty)) clty.cltyp_type
| Pcty_extension ext ->
raise (Error_forward (Builtin_attributes.error_of_extension ext))
let class_type env virt self_scope scty =
delayed_meth_specs := [];
let cty = class_type env virt self_scope scty in
List.iter Lazy.force (List.rev !delayed_meth_specs);
delayed_meth_specs := [];
cty
(*******************************)
let enter_ancestor_val name val_env =
Env.enter_unbound_value name Val_unbound_ancestor val_env
let enter_self_val name val_env =
Env.enter_unbound_value name Val_unbound_self val_env
let enter_instance_var_val name val_env =
Env.enter_unbound_value name Val_unbound_instance_variable val_env
let enter_ancestor_met ~loc name ~sign ~meths ~cl_num ~ty ~attrs met_env =
let check s = Warnings.Unused_ancestor s in
let kind = Val_anc (sign, meths, cl_num) in
let desc =
{ val_type = ty; val_kind = kind;
val_attributes = attrs;
Types.val_loc = loc;
val_uid = Uid.mk ~current_unit:(Env.get_unit_name ()) }
in
Env.enter_value ~check name desc met_env
let add_self_met loc id sign self_var_kind vars cl_num
as_var ty attrs met_env =
let check =
if as_var then (fun s -> Warnings.Unused_var s)
else (fun s -> Warnings.Unused_var_strict s)
in
let kind = Val_self (sign, self_var_kind, vars, cl_num) in
let desc =
{ val_type = ty; val_kind = kind;
val_attributes = attrs;
Types.val_loc = loc;
val_uid = Uid.mk ~current_unit:(Env.get_unit_name ()) }
in
Env.add_value ~check id desc met_env
let add_instance_var_met loc label id sign cl_num attrs met_env =
let mut, ty =
match Vars.find label sign.csig_vars with
| (mut, _, ty) -> mut, ty
| exception Not_found -> assert false
in
let kind = Val_ivar (mut, cl_num) in
let desc =
{ val_type = ty; val_kind = kind;
val_attributes = attrs;
Types.val_loc = loc;
val_uid = Uid.mk ~current_unit:(Env.get_unit_name ()) }
in
Env.add_value id desc met_env
let add_instance_vars_met loc vars sign cl_num met_env =
List.fold_left
(fun met_env (label, id) ->
add_instance_var_met loc label id sign cl_num [] met_env)
met_env vars
type intermediate_class_field =
| Inherit of
{ override : override_flag;
parent : class_expr;
super : string option;
inherited_vars : (string * Ident.t) list;
super_meths : (string * Ident.t) list;
loc : Location.t;
attributes : attribute list; }
| Virtual_val of
{ label : string loc;
mut : mutable_flag;
id : Ident.t;
cty : core_type;
already_declared : bool;
loc : Location.t;
attributes : attribute list; }
| Concrete_val of
{ label : string loc;
mut : mutable_flag;
id : Ident.t;
override : override_flag;
definition : expression;
already_declared : bool;
loc : Location.t;
attributes : attribute list; }
| Virtual_method of
{ label : string loc;
priv : private_flag;
cty : core_type;
loc : Location.t;
attributes : attribute list; }
| Concrete_method of
{ label : string loc;
priv : private_flag;
override : override_flag;
sdefinition : Parsetree.expression;
warning_state : Warnings.state;
loc : Location.t;
attributes : attribute list; }
| Constraint of
{ cty1 : core_type;
cty2 : core_type;
loc : Location.t;
attributes : attribute list; }
| Initializer of
{ sexpr : Parsetree.expression;
warning_state : Warnings.state;
loc : Location.t;
attributes : attribute list; }
| Attribute of
{ attribute : attribute;
loc : Location.t;
attributes : attribute list; }
type first_pass_accummulater =
{ rev_fields : intermediate_class_field list;
val_env : Env.t;
par_env : Env.t;
concrete_meths : MethSet.t;
concrete_vals : VarSet.t;
local_meths : MethSet.t;
local_vals : VarSet.t;
vars : Ident.t Vars.t; }
let rec class_field_first_pass self_loc cl_num sign self_scope acc cf =
let { rev_fields; val_env; par_env; concrete_meths; concrete_vals;
local_meths; local_vals; vars } = acc
in
let loc = cf.pcf_loc in
let attributes = cf.pcf_attributes in
let with_attrs f = Builtin_attributes.warning_scope attributes f in
match cf.pcf_desc with
| Pcf_inherit (override, sparent, super) ->
with_attrs
(fun () ->
let parent =
class_expr cl_num val_env par_env
Virtual self_scope sparent
in
complete_class_type parent.cl_loc
par_env Virtual Class parent.cl_type;
inherit_class_type ~strict:true loc val_env sign parent.cl_type;
let parent_sign = Btype.signature_of_class_type parent.cl_type in
let new_concrete_meths = Btype.concrete_methods parent_sign in
let new_concrete_vals = Btype.concrete_instance_vars parent_sign in
let over_meths = MethSet.inter new_concrete_meths concrete_meths in
let over_vals = VarSet.inter new_concrete_vals concrete_vals in
begin match override with
| Fresh ->
let cname =
match parent.cl_type with
| Cty_constr (p, _, _) -> Path.name p
| _ -> "inherited"
in
if not (MethSet.is_empty over_meths) then
Location.prerr_warning loc
(Warnings.Method_override
(cname :: MethSet.elements over_meths));
if not (VarSet.is_empty over_vals) then
Location.prerr_warning loc
(Warnings.Instance_variable_override
(cname :: VarSet.elements over_vals));
| Override ->
if MethSet.is_empty over_meths && VarSet.is_empty over_vals then
raise (Error(loc, val_env, No_overriding ("","")))
end;
let concrete_vals = VarSet.union new_concrete_vals concrete_vals in
let concrete_meths =
MethSet.union new_concrete_meths concrete_meths
in
let val_env, par_env, inherited_vars, vars =
Vars.fold
(fun label _ (val_env, par_env, inherited_vars, vars) ->
let val_env = enter_instance_var_val label val_env in
let par_env = enter_instance_var_val label par_env in
let id = Ident.create_local label in
let inherited_vars = (label, id) :: inherited_vars in
let vars = Vars.add label id vars in
(val_env, par_env, inherited_vars, vars))
parent_sign.csig_vars (val_env, par_env, [], vars)
in
(* Methods available through super *)
let super_meths =
MethSet.fold
(fun label acc -> (label, Ident.create_local label) :: acc)
new_concrete_meths []
in
(* Super *)
let (val_env, par_env, super) =
match super with
| None -> (val_env, par_env, None)
| Some {txt=name} ->
let val_env = enter_ancestor_val name val_env in
let par_env = enter_ancestor_val name par_env in
(val_env, par_env, Some name)
in
let field =
Inherit
{ override; parent; super; inherited_vars;
super_meths; loc; attributes }
in
let rev_fields = field :: rev_fields in
{ acc with rev_fields; val_env; par_env;
concrete_meths; concrete_vals; vars })
| Pcf_val (label, mut, Cfk_virtual styp) ->
with_attrs
(fun () ->
if !Clflags.principal then Ctype.begin_def ();
let cty = Typetexp.transl_simple_type val_env false styp in
let ty = cty.ctyp_type in
if !Clflags.principal then begin
Ctype.end_def ();
Ctype.generalize_structure ty
end;
add_instance_variable ~strict:true loc val_env
label.txt mut Virtual ty sign;
let already_declared, val_env, par_env, id, vars =
match Vars.find label.txt vars with
| id -> true, val_env, par_env, id, vars
| exception Not_found ->
let name = label.txt in
let val_env = enter_instance_var_val name val_env in
let par_env = enter_instance_var_val name par_env in
let id = Ident.create_local name in
let vars = Vars.add label.txt id vars in
false, val_env, par_env, id, vars
in
let field =
Virtual_val
{ label; mut; id; cty; already_declared; loc; attributes }
in
let rev_fields = field :: rev_fields in
{ acc with rev_fields; val_env; par_env; vars })
| Pcf_val (label, mut, Cfk_concrete (override, sdefinition)) ->
with_attrs
(fun () ->
if VarSet.mem label.txt local_vals then
raise(Error(loc, val_env,
Duplicate ("instance variable", label.txt)));
if VarSet.mem label.txt concrete_vals then begin
if override = Fresh then
Location.prerr_warning label.loc
(Warnings.Instance_variable_override[label.txt])
end else begin
if override = Override then
raise(Error(loc, val_env,
No_overriding ("instance variable", label.txt)))
end;
if !Clflags.principal then Ctype.begin_def ();
let definition = type_exp val_env sdefinition in
if !Clflags.principal then begin
Ctype.end_def ();
Ctype.generalize_structure definition.exp_type
end;
add_instance_variable ~strict:true loc val_env
label.txt mut Concrete definition.exp_type sign;
let already_declared, val_env, par_env, id, vars =
match Vars.find label.txt vars with
| id -> true, val_env, par_env, id, vars
| exception Not_found ->
let name = label.txt in
let val_env = enter_instance_var_val name val_env in
let par_env = enter_instance_var_val name par_env in
let id = Ident.create_local name in
let vars = Vars.add label.txt id vars in
false, val_env, par_env, id, vars
in
let field =
Concrete_val
{ label; mut; id; override; definition;
already_declared; loc; attributes }
in
let rev_fields = field :: rev_fields in
let concrete_vals = VarSet.add label.txt concrete_vals in
let local_vals = VarSet.add label.txt local_vals in
{ acc with rev_fields; val_env; par_env;
concrete_vals; local_vals; vars })
| Pcf_method (label, priv, Cfk_virtual sty) ->
with_attrs
(fun () ->
let sty = Ast_helper.Typ.force_poly sty in
let cty = transl_simple_type val_env false sty in
let ty = cty.ctyp_type in
add_method loc val_env label.txt priv Virtual ty sign;
let field =
Virtual_method { label; priv; cty; loc; attributes }
in
let rev_fields = field :: rev_fields in
{ acc with rev_fields })
| Pcf_method (label, priv, Cfk_concrete (override, expr)) ->
with_attrs
(fun () ->
if MethSet.mem label.txt local_meths then
raise(Error(loc, val_env, Duplicate ("method", label.txt)));
if MethSet.mem label.txt concrete_meths then begin
if override = Fresh then begin
Location.prerr_warning loc
(Warnings.Method_override [label.txt])
end
end else begin
if override = Override then begin
raise(Error(loc, val_env, No_overriding("method", label.txt)))
end
end;
let expr =
match expr.pexp_desc with
| Pexp_poly _ -> expr
| _ -> Ast_helper.Exp.poly ~loc:expr.pexp_loc expr None
in
let sbody, sty =
match expr.pexp_desc with
| Pexp_poly (sbody, sty) -> sbody, sty
| _ -> assert false
in
let ty =
match sty with
| None -> Ctype.newvar ()
| Some sty ->
let sty = Ast_helper.Typ.force_poly sty in
let cty' =
Typetexp.transl_simple_type val_env false sty
in
cty'.ctyp_type
in
add_method loc val_env label.txt priv Concrete ty sign;
begin
try
match get_desc ty with
| Tvar _ ->
let ty' = Ctype.newvar () in
Ctype.unify val_env (Ctype.newty (Tpoly (ty', []))) ty;
Ctype.unify val_env (type_approx val_env sbody) ty'
| Tpoly (ty1, tl) ->
let _, ty1' = Ctype.instance_poly false tl ty1 in
let ty2 = type_approx val_env sbody in
Ctype.unify val_env ty2 ty1'
| _ -> assert false
with Ctype.Unify err ->
raise(Error(loc, val_env,
Field_type_mismatch ("method", label.txt, err)))
end;
let sdefinition = make_method self_loc cl_num expr in
let warning_state = Warnings.backup () in
let field =
Concrete_method
{ label; priv; override; sdefinition;
warning_state; loc; attributes }
in
let rev_fields = field :: rev_fields in
let concrete_meths = MethSet.add label.txt concrete_meths in
let local_meths = MethSet.add label.txt local_meths in
{ acc with rev_fields; concrete_meths; local_meths })
| Pcf_constraint (sty1, sty2) ->
with_attrs
(fun () ->
let (cty1, cty2) = type_constraint val_env sty1 sty2 loc in
let field =
Constraint { cty1; cty2; loc; attributes }
in
let rev_fields = field :: rev_fields in
{ acc with rev_fields })
| Pcf_initializer sexpr ->
with_attrs
(fun () ->
let sexpr = make_method self_loc cl_num sexpr in
let warning_state = Warnings.backup () in
let field =
Initializer { sexpr; warning_state; loc; attributes }
in
let rev_fields = field :: rev_fields in
{ acc with rev_fields })
| Pcf_attribute attribute ->
Builtin_attributes.warning_attribute attribute;
let field = Attribute { attribute; loc; attributes } in
let rev_fields = field :: rev_fields in
{ acc with rev_fields }
| Pcf_extension ext ->
raise (Error_forward (Builtin_attributes.error_of_extension ext))
and class_fields_first_pass self_loc cl_num sign self_scope
val_env par_env cfs =
let rev_fields = [] in
let concrete_meths = MethSet.empty in
let concrete_vals = VarSet.empty in
let local_meths = MethSet.empty in
let local_vals = VarSet.empty in
let vars = Vars.empty in
let init_acc =
{ rev_fields; val_env; par_env;
concrete_meths; concrete_vals;
local_meths; local_vals; vars }
in
let acc =
Builtin_attributes.warning_scope []
(fun () ->
List.fold_left
(class_field_first_pass self_loc cl_num sign self_scope)
init_acc cfs)
in
List.rev acc.rev_fields, acc.vars
and class_field_second_pass cl_num sign met_env field =
let mkcf desc loc attrs =
{ cf_desc = desc; cf_loc = loc; cf_attributes = attrs }
in
match field with
| Inherit { override; parent; super;
inherited_vars; super_meths; loc; attributes } ->
let met_env =
add_instance_vars_met loc inherited_vars sign cl_num met_env
in
let met_env =
match super with
| None -> met_env
| Some name ->
let meths =
List.fold_left
(fun acc (label, id) -> Meths.add label id acc)
Meths.empty super_meths
in
let ty = Btype.self_type parent.cl_type in
let attrs = [] in
let _id, met_env =
enter_ancestor_met ~loc name ~sign ~meths
~cl_num ~ty ~attrs met_env
in
met_env
in
let desc =
Tcf_inherit(override, parent, super, inherited_vars, super_meths)
in
met_env, mkcf desc loc attributes
| Virtual_val { label; mut; id; cty; already_declared; loc; attributes } ->
let met_env =
if already_declared then met_env
else begin
add_instance_var_met loc label.txt id sign cl_num attributes met_env
end
in
let kind = Tcfk_virtual cty in
let desc = Tcf_val(label, mut, id, kind, already_declared) in
met_env, mkcf desc loc attributes
| Concrete_val { label; mut; id; override;
definition; already_declared; loc; attributes } ->
let met_env =
if already_declared then met_env
else begin
add_instance_var_met loc label.txt id sign cl_num attributes met_env
end
in
let kind = Tcfk_concrete(override, definition) in
let desc = Tcf_val(label, mut, id, kind, already_declared) in
met_env, mkcf desc loc attributes
| Virtual_method { label; priv; cty; loc; attributes } ->
let kind = Tcfk_virtual cty in
let desc = Tcf_method(label, priv, kind) in
met_env, mkcf desc loc attributes
| Concrete_method { label; priv; override;
sdefinition; warning_state; loc; attributes } ->
Warnings.with_state warning_state
(fun () ->
let ty = Btype.method_type label.txt sign in
let self_type = sign.Types.csig_self in
let meth_type =
mk_expected
(Btype.newgenty (Tarrow(Nolabel, self_type, ty, commu_ok)))
in
Ctype.raise_nongen_level ();
let texp = type_expect met_env sdefinition meth_type in
Ctype.end_def ();
let kind = Tcfk_concrete (override, texp) in
let desc = Tcf_method(label, priv, kind) in
met_env, mkcf desc loc attributes)
| Constraint { cty1; cty2; loc; attributes } ->
let desc = Tcf_constraint(cty1, cty2) in
met_env, mkcf desc loc attributes
| Initializer { sexpr; warning_state; loc; attributes } ->
Warnings.with_state warning_state
(fun () ->
Ctype.raise_nongen_level ();
let unit_type = Ctype.instance Predef.type_unit in
let self_type = sign.Types.csig_self in
let meth_type =
mk_expected
(Ctype.newty (Tarrow (Nolabel, self_type, unit_type, commu_ok)))
in
let texp = type_expect met_env sexpr meth_type in
Ctype.end_def ();
let desc = Tcf_initializer texp in
met_env, mkcf desc loc attributes)
| Attribute { attribute; loc; attributes; } ->
let desc = Tcf_attribute attribute in
met_env, mkcf desc loc attributes
and class_fields_second_pass cl_num sign met_env fields =
let _, rev_cfs =
List.fold_left
(fun (met_env, cfs) field ->
let met_env, cf =
class_field_second_pass cl_num sign met_env field
in
met_env, cf :: cfs)
(met_env, []) fields
in
List.rev rev_cfs
(* N.B. the self type of a final object type doesn't contain a dummy method in
the beginning.
We only explicitly add a dummy method to class definitions (and class (type)
declarations)), which are later removed (made absent) by [final_decl].
If we ever find a dummy method in a final object self type, it means that
somehow we've unified the self type of the object with the self type of a not
yet finished class.
When this happens, we cannot close the object type and must error. *)
and class_structure cl_num virt self_scope final val_env met_env loc
{ pcstr_self = spat; pcstr_fields = str } =
(* Environment for substructures *)
let par_env = met_env in
(* Location of self. Used for locations of self arguments *)
let self_loc = {spat.ppat_loc with Location.loc_ghost = true} in
let sign = Ctype.new_class_signature () in
(* Adding a dummy method to the signature prevents it from being closed /
escaping. That isn't needed for objects though. *)
begin match final with
| Not_final -> Ctype.add_dummy_method val_env ~scope:self_scope sign;
| Final -> ()
end;
(* Self binder *)
let (self_pat, self_pat_vars) = type_self_pattern val_env spat in
let val_env, par_env =
List.fold_right
(fun {pv_id; _} (val_env, par_env) ->
let name = Ident.name pv_id in
let val_env = enter_self_val name val_env in
let par_env = enter_self_val name par_env in
val_env, par_env)
self_pat_vars (val_env, par_env)
in
(* Check that the binder has a correct type *)
begin try Ctype.unify val_env self_pat.pat_type sign.csig_self with
Ctype.Unify _ ->
raise(Error(spat.ppat_loc, val_env,
Pattern_type_clash self_pat.pat_type))
end;
(* Typing of class fields *)
let (fields, vars) =
class_fields_first_pass self_loc cl_num sign self_scope
val_env par_env str
in
let kind = kind_of_final final in
(* Check for unexpected virtual methods *)
check_virtual loc val_env virt kind sign;
(* Update the class signature *)
update_class_signature loc val_env
~warn_implicit_public:false virt kind sign;