forked from ocaml/ocaml
-
Notifications
You must be signed in to change notification settings - Fork 6
/
Copy pathtypemod.ml
2036 lines (1919 loc) · 75.5 KB
/
typemod.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 *)
(* *)
(* Xavier Leroy, 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 Misc
open Longident
open Path
open Asttypes
open Parsetree
open Types
open Format
type error =
Cannot_apply of module_type
| Not_included of Includemod.error list
| Cannot_eliminate_dependency of module_type
| Signature_expected
| Structure_expected of module_type
| With_no_component of Longident.t
| With_mismatch of Longident.t * Includemod.error list
| With_makes_applicative_functor_ill_typed of
Longident.t * Path.t * Includemod.error list
| With_changes_module_alias of Longident.t * Ident.t * Path.t
| With_cannot_remove_constrained_type
| Repeated_name of string * string
| Non_generalizable of type_expr
| Non_generalizable_class of Ident.t * class_declaration
| Non_generalizable_module of module_type
| Implementation_is_required of string
| Interface_not_compiled of string
| Not_allowed_in_functor_body
| Not_a_packed_module of type_expr
| Incomplete_packed_module of type_expr
| Scoping_pack of Longident.t * type_expr
| Recursive_module_require_explicit_type
| Apply_generative
| Cannot_scrape_alias of Path.t
exception Error of Location.t * Env.t * error
exception Error_forward of Location.error
module ImplementationHooks = Misc.MakeHooks(struct
type t = Typedtree.structure * Typedtree.module_coercion
end)
module InterfaceHooks = Misc.MakeHooks(struct
type t = Typedtree.signature
end)
open Typedtree
let fst3 (x,_,_) = x
let rec path_concat head p =
match p with
Pident tail -> Pdot (Pident head, Ident.name tail, 0)
| Pdot (pre, s, pos) -> Pdot (path_concat head pre, s, pos)
| Papply _ -> assert false
(* Extract a signature from a module type *)
let extract_sig env loc mty =
match Env.scrape_alias env mty with
Mty_signature sg -> sg
| Mty_alias(_, path) ->
raise(Error(loc, env, Cannot_scrape_alias path))
| _ -> raise(Error(loc, env, Signature_expected))
let extract_sig_open env loc mty =
match Env.scrape_alias env mty with
Mty_signature sg -> sg
| Mty_alias(_, path) ->
raise(Error(loc, env, Cannot_scrape_alias path))
| mty -> raise(Error(loc, env, Structure_expected mty))
(* Compute the environment after opening a module *)
let type_open_ ?used_slot ?toplevel ovf env loc lid =
let path = Typetexp.lookup_module ~load:true env lid.loc lid.txt in
match Env.open_signature ~loc ?used_slot ?toplevel ovf path env with
| Some env -> path, env
| None ->
let md = Env.find_module path env in
ignore (extract_sig_open env lid.loc md.md_type);
assert false
let type_open ?toplevel env sod =
let (path, newenv) =
Builtin_attributes.warning_scope sod.popen_attributes
(fun () ->
type_open_ ?toplevel sod.popen_override env sod.popen_loc
sod.popen_lid
)
in
let od =
{
open_override = sod.popen_override;
open_path = path;
open_txt = sod.popen_lid;
open_attributes = sod.popen_attributes;
open_loc = sod.popen_loc;
}
in
(path, newenv, od)
(* Record a module type *)
let rm node =
Stypes.record (Stypes.Ti_mod node);
node
(* Forward declaration, to be filled in by type_module_type_of *)
let type_module_type_of_fwd :
(Env.t -> Parsetree.module_expr ->
Typedtree.module_expr * Types.module_type) ref
= ref (fun _env _m -> assert false)
(* Merge one "with" constraint in a signature *)
let rec add_rec_types env = function
Sig_type(id, decl, Trec_next) :: rem ->
add_rec_types (Env.add_type ~check:true id decl env) rem
| _ -> env
let check_type_decl env loc id row_id newdecl decl rs rem =
let env = Env.add_type ~check:true id newdecl env in
let env =
match row_id with
| None -> env
| Some id -> Env.add_type ~check:false id newdecl env
in
let env = if rs = Trec_not then env else add_rec_types env rem in
Includemod.type_declarations ~loc env id newdecl decl;
Typedecl.check_coherence env loc id newdecl
let update_rec_next rs rem =
match rs with
Trec_next -> rem
| Trec_first | Trec_not ->
match rem with
Sig_type (id, decl, Trec_next) :: rem ->
Sig_type (id, decl, rs) :: rem
| Sig_module (id, mty, Trec_next) :: rem ->
Sig_module (id, mty, rs) :: rem
| _ -> rem
let make p n i =
let open Variance in
set May_pos p (set May_neg n (set May_weak n (set Inj i null)))
let rec iter_path_apply p ~f =
match p with
| Pident _ -> ()
| Pdot (p, _, _) -> iter_path_apply p ~f
| Papply (p1, p2) ->
iter_path_apply p1 ~f;
iter_path_apply p2 ~f;
f p1 p2 (* after recursing, so we know both paths are well typed *)
let path_is_strict_prefix =
let rec list_is_strict_prefix l ~prefix =
match l, prefix with
| [], [] -> false
| _ :: _, [] -> true
| [], _ :: _ -> false
| s1 :: t1, s2 :: t2 ->
String.equal s1 s2 && list_is_strict_prefix t1 ~prefix:t2
in
fun path ~prefix ->
match Path.flatten path, Path.flatten prefix with
| `Contains_apply, _ | _, `Contains_apply -> false
| `Ok (ident1, l1), `Ok (ident2, l2) ->
Ident.same ident1 ident2
&& list_is_strict_prefix l1 ~prefix:l2
let iterator_with_env env =
let env = ref env in
let super = Btype.type_iterators in
env, { super with
Btype.it_signature = (fun self sg ->
(* add all items to the env before recursing down, to handle recursive
definitions *)
let env_before = !env in
List.iter (fun i -> env := Env.add_item i !env) sg;
super.Btype.it_signature self sg;
env := env_before
);
Btype.it_module_type = (fun self -> function
| Mty_functor (param, mty_arg, mty_body) ->
may (self.Btype.it_module_type self) mty_arg;
let env_before = !env in
env := Env.add_module ~arg:true param (Btype.default_mty mty_arg) !env;
self.Btype.it_module_type self mty_body;
env := env_before;
| mty ->
super.Btype.it_module_type self mty
)
}
let retype_applicative_functor_type ~loc env funct arg =
let mty_functor = (Env.find_module funct env).md_type in
let mty_arg = (Env.find_module arg env).md_type in
let mty_param =
match Env.scrape_alias env mty_functor with
| Mty_functor (_, Some mty_param, _) -> mty_param
| _ -> assert false (* could trigger due to MPR#7611 *)
in
let aliasable = not (Env.is_functor_arg arg env) in
ignore(Includemod.modtypes ~loc env
(Mtype.strengthen ~aliasable env mty_arg arg) mty_param)
(* When doing a deep destructive substitution with type M.N.t := .., we change M
and M.N and so we have to check that uses of the modules other than just
extracting components from them still make sense. There are only two such
kinds of uses:
- applicative functor types: F(M).t might not be well typed anymore
- aliases: module A = M still makes sense but it doesn't mean the same thing
anymore, so it's forbidden until it's clear what we should do with it.
This function would be called with M.N.t and N.t to check for these uses. *)
let check_usage_of_path_of_substituted_item paths env signature ~loc ~lid =
let iterator =
let env, super = iterator_with_env env in
{ super with
Btype.it_signature_item = (fun self -> function
| Sig_module (id, { md_type = Mty_alias (_, aliased_path); _ }, _)
when List.exists
(fun path -> path_is_strict_prefix path ~prefix:aliased_path)
paths
->
let e = With_changes_module_alias (lid.txt, id, aliased_path) in
raise(Error(loc, !env, e))
| sig_item ->
super.Btype.it_signature_item self sig_item
);
Btype.it_path = (fun referenced_path ->
iter_path_apply referenced_path ~f:(fun funct arg ->
if List.exists
(fun path -> path_is_strict_prefix path ~prefix:arg)
paths
then
let env = !env in
try retype_applicative_functor_type ~loc env funct arg
with Includemod.Error explanation ->
raise(Error(loc, env,
With_makes_applicative_functor_ill_typed
(lid.txt, referenced_path, explanation)))
)
);
}
in
iterator.Btype.it_signature iterator signature;
Btype.unmark_iterators.Btype.it_signature Btype.unmark_iterators signature
let type_decl_is_alias sdecl = (* assuming no explicit constraint *)
match sdecl.ptype_manifest with
| Some {ptyp_desc = Ptyp_constr (lid, stl)}
when List.length stl = List.length sdecl.ptype_params ->
begin
match
List.iter2 (fun x (y, _) ->
match x, y with
{ptyp_desc=Ptyp_var sx}, {ptyp_desc=Ptyp_var sy}
when sx = sy -> ()
| _, _ -> raise Exit)
stl sdecl.ptype_params;
with
| exception Exit -> None
| () -> Some lid
end
| _ -> None
;;
let params_are_constrained =
let rec loop = function
| [] -> false
| hd :: tl ->
match (Btype.repr hd).desc with
| Tvar _ -> List.memq hd tl || loop tl
| _ -> true
in
loop
;;
let merge_constraint initial_env loc sg constr =
let lid =
match constr with
| Pwith_type (lid, _) | Pwith_module (lid, _)
| Pwith_typesubst (lid, _) | Pwith_modsubst (lid, _) -> lid
in
let destructive_substitution =
match constr with
| Pwith_type _ | Pwith_module _ -> false
| Pwith_typesubst _ | Pwith_modsubst _ -> true
in
let real_ids = ref [] in
let rec merge env sg namelist row_id =
match (sg, namelist, constr) with
([], _, _) ->
raise(Error(loc, env, With_no_component lid.txt))
| (Sig_type(id, decl, rs) :: rem, [s],
Pwith_type (_, ({ptype_kind = Ptype_abstract} as sdecl)))
when Ident.name id = s && Typedecl.is_fixed_type sdecl ->
let decl_row =
{ type_params =
List.map (fun _ -> Btype.newgenvar()) sdecl.ptype_params;
type_arity = List.length sdecl.ptype_params;
type_kind = Type_abstract;
type_private = Private;
type_manifest = None;
type_variance =
List.map
(fun (_, v) ->
let (c, n) =
match v with
| Covariant -> true, false
| Contravariant -> false, true
| Invariant -> false, false
in
make (not n) (not c) false
)
sdecl.ptype_params;
type_loc = sdecl.ptype_loc;
type_newtype_level = None;
type_attributes = [];
type_immediate = false;
type_unboxed = unboxed_false_default_false;
}
and id_row = Ident.create (s^"#row") in
let initial_env =
Env.add_type ~check:false id_row decl_row initial_env
in
let tdecl = Typedecl.transl_with_constraint
initial_env id (Some(Pident id_row)) decl sdecl in
let newdecl = tdecl.typ_type in
check_type_decl env sdecl.ptype_loc id row_id newdecl decl rs rem;
let decl_row = {decl_row with type_params = newdecl.type_params} in
let rs' = if rs = Trec_first then Trec_not else rs in
(Pident id, lid, Twith_type tdecl),
Sig_type(id_row, decl_row, rs') :: Sig_type(id, newdecl, rs) :: rem
| (Sig_type(id, decl, rs) :: rem , [s], Pwith_type (_, sdecl))
when Ident.name id = s ->
let tdecl =
Typedecl.transl_with_constraint initial_env id None decl sdecl in
let newdecl = tdecl.typ_type in
check_type_decl env sdecl.ptype_loc id row_id newdecl decl rs rem;
(Pident id, lid, Twith_type tdecl), Sig_type(id, newdecl, rs) :: rem
| (Sig_type(id, _, _) :: rem, [s], (Pwith_type _ | Pwith_typesubst _))
when Ident.name id = s ^ "#row" ->
merge env rem namelist (Some id)
| (Sig_type(id, decl, rs) :: rem, [s], Pwith_typesubst (_, sdecl))
when Ident.name id = s ->
(* Check as for a normal with constraint, but discard definition *)
let tdecl =
Typedecl.transl_with_constraint initial_env id None decl sdecl in
let newdecl = tdecl.typ_type in
check_type_decl env sdecl.ptype_loc id row_id newdecl decl rs rem;
real_ids := [Pident id];
(Pident id, lid, Twith_typesubst tdecl),
update_rec_next rs rem
| (Sig_module(id, md, rs) :: rem, [s], Pwith_module (_, lid'))
when Ident.name id = s ->
let path, md' = Typetexp.find_module initial_env loc lid'.txt in
let md'' = {md' with md_type = Mtype.remove_aliases env md'.md_type} in
let newmd = Mtype.strengthen_decl ~aliasable:false env md'' path in
ignore(Includemod.modtypes ~loc env newmd.md_type md.md_type);
(Pident id, lid, Twith_module (path, lid')),
Sig_module(id, newmd, rs) :: rem
| (Sig_module(id, md, rs) :: rem, [s], Pwith_modsubst (_, lid'))
when Ident.name id = s ->
let path, md' = Typetexp.find_module initial_env loc lid'.txt in
let newmd = Mtype.strengthen_decl ~aliasable:false env md' path in
ignore(Includemod.modtypes ~loc env newmd.md_type md.md_type);
real_ids := [Pident id];
(Pident id, lid, Twith_modsubst (path, lid')),
update_rec_next rs rem
| (Sig_module(id, md, rs) :: rem, s :: namelist, _)
when Ident.name id = s ->
let ((path, _path_loc, tcstr), newsg) =
merge env (extract_sig env loc md.md_type) namelist None in
let path = path_concat id path in
real_ids := path :: !real_ids;
let item = Sig_module(id, {md with md_type=Mty_signature newsg}, rs) in
(path, lid, tcstr),
item :: rem
| (item :: rem, _, _) ->
let (cstr, items) = merge (Env.add_item item env) rem namelist row_id
in
cstr, item :: items
in
try
let names = Longident.flatten lid.txt in
let (tcstr, sg) = merge initial_env sg names None in
if destructive_substitution then (
match List.rev !real_ids with
| [] -> assert false
| last :: rest ->
(* The last item is the one that's removed. We don't need to check how
it's used since it's replaced by a more specific type/module. *)
assert (match last with Pident _ -> true | _ -> false);
match rest with
| [] -> ()
| _ :: _ ->
check_usage_of_path_of_substituted_item
rest initial_env sg ~loc ~lid;
);
let sg =
match tcstr with
| (_, _, Twith_typesubst tdecl) ->
let how_to_extend_subst =
let sdecl =
match constr with
| Pwith_typesubst (_, sdecl) -> sdecl
| _ -> assert false
in
match type_decl_is_alias sdecl with
| Some lid ->
let replacement =
try Env.lookup_type lid.txt initial_env
with Not_found -> assert false
in
fun s path -> Subst.add_type_path path replacement s
| None ->
let body =
match tdecl.typ_type.type_manifest with
| None -> assert false
| Some x -> x
in
let params = tdecl.typ_type.type_params in
if params_are_constrained params
then raise(Error(loc, initial_env, With_cannot_remove_constrained_type));
fun s path -> Subst.add_type_function path ~params ~body s
in
let sub = List.fold_left how_to_extend_subst Subst.identity !real_ids in
Subst.signature sub sg
| (_, _, Twith_modsubst (real_path, _)) ->
let sub =
List.fold_left
(fun s path -> Subst.add_module_path path real_path s)
Subst.identity
!real_ids
in
Subst.signature sub sg
| _ ->
sg
in
(tcstr, sg)
with Includemod.Error explanation ->
raise(Error(loc, initial_env, With_mismatch(lid.txt, explanation)))
(* Add recursion flags on declarations arising from a mutually recursive
block. *)
let map_rec fn decls rem =
match decls with
| [] -> rem
| d1 :: dl -> fn Trec_first d1 :: map_end (fn Trec_next) dl rem
let map_rec_type ~rec_flag fn decls rem =
match decls with
| [] -> rem
| d1 :: dl ->
let first =
match rec_flag with
| Recursive -> Trec_first
| Nonrecursive -> Trec_not
in
fn first d1 :: map_end (fn Trec_next) dl rem
let rec map_rec_type_with_row_types ~rec_flag fn decls rem =
match decls with
| [] -> rem
| d1 :: dl ->
if Btype.is_row_name (Ident.name d1.typ_id) then
fn Trec_not d1 :: map_rec_type_with_row_types ~rec_flag fn dl rem
else
map_rec_type ~rec_flag fn decls rem
(* Add type extension flags to extension constructors *)
let map_ext fn exts rem =
match exts with
| [] -> rem
| d1 :: dl -> fn Text_first d1 :: map_end (fn Text_next) dl rem
(* Auxiliary for translating recursively-defined module types.
Return a module type that approximates the shape of the given module
type AST. Retain only module, type, and module type
components of signatures. For types, retain only their arity,
making them abstract otherwise. *)
let rec approx_modtype env smty =
match smty.pmty_desc with
Pmty_ident lid ->
let (path, _info) = Typetexp.find_modtype env smty.pmty_loc lid.txt in
Mty_ident path
| Pmty_alias lid ->
let path = Typetexp.lookup_module env smty.pmty_loc lid.txt in
Mty_alias(Mta_absent, path)
| Pmty_signature ssg ->
Mty_signature(approx_sig env ssg)
| Pmty_functor(param, sarg, sres) ->
let arg = may_map (approx_modtype env) sarg in
let (id, newenv) =
Env.enter_module ~arg:true param.txt (Btype.default_mty arg) env in
let res = approx_modtype newenv sres in
Mty_functor(id, arg, res)
| Pmty_with(sbody, _constraints) ->
approx_modtype env sbody
| Pmty_typeof smod ->
let (_, mty) = !type_module_type_of_fwd env smod in
mty
| Pmty_extension ext ->
raise (Error_forward (Builtin_attributes.error_of_extension ext))
and approx_module_declaration env pmd =
{
Types.md_type = approx_modtype env pmd.pmd_type;
md_attributes = pmd.pmd_attributes;
md_loc = pmd.pmd_loc;
}
and approx_sig env ssg =
match ssg with
[] -> []
| item :: srem ->
match item.psig_desc with
| Psig_type (rec_flag, sdecls) ->
let decls = Typedecl.approx_type_decl sdecls in
let rem = approx_sig env srem in
map_rec_type ~rec_flag
(fun rs (id, info) -> Sig_type(id, info, rs)) decls rem
| Psig_module pmd ->
let id = Ident.create pmd.pmd_name.txt in
let md = approx_module_declaration env pmd in
let newenv = Env.enter_module_declaration id md env in
Sig_module(id, md, Trec_not) :: approx_sig newenv srem
| Psig_recmodule sdecls ->
let decls =
List.map
(fun pmd ->
(Ident.create pmd.pmd_name.txt,
approx_module_declaration env pmd)
)
sdecls
in
let newenv =
List.fold_left
(fun env (id, md) -> Env.add_module_declaration ~check:false
id md env)
env decls in
map_rec (fun rs (id, md) -> Sig_module(id, md, rs)) decls
(approx_sig newenv srem)
| Psig_modtype d ->
let info = approx_modtype_info env d in
let (id, newenv) = Env.enter_modtype d.pmtd_name.txt info env in
Sig_modtype(id, info) :: approx_sig newenv srem
| Psig_open sod ->
let (_path, mty, _od) = type_open env sod in
approx_sig mty srem
| Psig_include sincl ->
let smty = sincl.pincl_mod in
let mty = approx_modtype env smty in
let sg = Subst.signature Subst.identity
(extract_sig env smty.pmty_loc mty) in
let newenv = Env.add_signature sg env in
sg @ approx_sig newenv srem
| Psig_class sdecls | Psig_class_type sdecls ->
let decls = Typeclass.approx_class_declarations env sdecls in
let rem = approx_sig env srem in
List.flatten
(map_rec
(fun rs decl ->
let open Typeclass in
[Sig_class_type(decl.clsty_ty_id, decl.clsty_ty_decl, rs);
Sig_type(decl.clsty_obj_id, decl.clsty_obj_abbr, rs);
Sig_type(decl.clsty_typesharp_id, decl.clsty_abbr, rs)])
decls [rem])
| _ ->
approx_sig env srem
and approx_modtype_info env sinfo =
{
mtd_type = may_map (approx_modtype env) sinfo.pmtd_type;
mtd_attributes = sinfo.pmtd_attributes;
mtd_loc = sinfo.pmtd_loc;
}
let approx_modtype env smty =
Warnings.without_warnings
(fun () -> approx_modtype env smty)
(* Additional validity checks on type definitions arising from
recursive modules *)
let check_recmod_typedecls env sdecls decls =
let recmod_ids = List.map fst3 decls in
List.iter2
(fun pmd (id, _, mty) ->
let mty = mty.mty_type in
List.iter
(fun path ->
Typedecl.check_recmod_typedecl env pmd.pmd_type.pmty_loc recmod_ids
path (Env.find_type path env))
(Mtype.type_paths env (Pident id) mty))
sdecls decls
(* Auxiliaries for checking uniqueness of names in signatures and structures *)
module StringSet =
Set.Make(struct type t = string let compare (x:t) y = String.compare x y end)
let check cl loc set_ref name =
if StringSet.mem name !set_ref
then raise(Error(loc, Env.empty, Repeated_name(cl, name)))
else set_ref := StringSet.add name !set_ref
type names =
{
types: StringSet.t ref;
modules: StringSet.t ref;
modtypes: StringSet.t ref;
typexts: StringSet.t ref;
}
let new_names () =
{
types = ref StringSet.empty;
modules = ref StringSet.empty;
modtypes = ref StringSet.empty;
typexts = ref StringSet.empty;
}
let check_name check names name = check names name.loc name.txt
let check_type names loc s = check "type" loc names.types s
let check_module names loc s = check "module" loc names.modules s
let check_modtype names loc s = check "module type" loc names.modtypes s
let check_typext names loc s = check "extension constructor" loc names.typexts s
let check_sig_item names loc = function
| Sig_type(id, _, _) -> check_type names loc (Ident.name id)
| Sig_module(id, _, _) -> check_module names loc (Ident.name id)
| Sig_modtype(id, _) -> check_modtype names loc (Ident.name id)
| Sig_typext(id, _, _) -> check_typext names loc (Ident.name id)
| _ -> ()
(* Simplify multiple specifications of a value or an extension in a signature.
(Other signature components, e.g. types, modules, etc, are checked for
name uniqueness.) If multiple specifications with the same name,
keep only the last (rightmost) one. *)
let simplify_signature sg =
let rec aux = function
| [] -> [], StringSet.empty
| (Sig_value(id, _descr) as component) :: sg ->
let (sg, val_names) as k = aux sg in
let name = Ident.name id in
if StringSet.mem name val_names then k
else (component :: sg, StringSet.add name val_names)
| component :: sg ->
let (sg, val_names) = aux sg in
(component :: sg, val_names)
in
let (sg, _) = aux sg in
sg
(* Check and translate a module type expression *)
let transl_modtype_longident loc env lid =
let (path, _info) = Typetexp.find_modtype env loc lid in
path
let transl_module_alias loc env lid =
Typetexp.lookup_module env loc lid
let mkmty desc typ env loc attrs =
let mty = {
mty_desc = desc;
mty_type = typ;
mty_loc = loc;
mty_env = env;
mty_attributes = attrs;
} in
Cmt_format.add_saved_type (Cmt_format.Partial_module_type mty);
mty
let mksig desc env loc =
let sg = { sig_desc = desc; sig_loc = loc; sig_env = env } in
Cmt_format.add_saved_type (Cmt_format.Partial_signature_item sg);
sg
(* let signature sg = List.map (fun item -> item.sig_type) sg *)
let rec transl_modtype env smty =
Builtin_attributes.warning_scope smty.pmty_attributes
(fun () -> transl_modtype_aux env smty)
and transl_modtype_aux env smty =
let loc = smty.pmty_loc in
match smty.pmty_desc with
Pmty_ident lid ->
let path = transl_modtype_longident loc env lid.txt in
mkmty (Tmty_ident (path, lid)) (Mty_ident path) env loc
smty.pmty_attributes
| Pmty_alias lid ->
let path = transl_module_alias loc env lid.txt in
mkmty (Tmty_alias (path, lid)) (Mty_alias(Mta_absent, path)) env loc
smty.pmty_attributes
| Pmty_signature ssg ->
let sg = transl_signature env ssg in
mkmty (Tmty_signature sg) (Mty_signature sg.sig_type) env loc
smty.pmty_attributes
| Pmty_functor(param, sarg, sres) ->
let arg = Misc.may_map (transl_modtype env) sarg in
let ty_arg = Misc.may_map (fun m -> m.mty_type) arg in
let (id, newenv) =
Env.enter_module ~arg:true param.txt (Btype.default_mty ty_arg) env in
Ctype.init_def(Ident.current_time()); (* PR#6513 *)
let res = transl_modtype newenv sres in
mkmty (Tmty_functor (id, param, arg, res))
(Mty_functor(id, ty_arg, res.mty_type)) env loc
smty.pmty_attributes
| Pmty_with(sbody, constraints) ->
let body = transl_modtype env sbody in
let init_sg = extract_sig env sbody.pmty_loc body.mty_type in
let (rev_tcstrs, final_sg) =
List.fold_left
(fun (rev_tcstrs,sg) sdecl ->
let (tcstr, sg) = merge_constraint env smty.pmty_loc sg sdecl
in
(tcstr :: rev_tcstrs, sg)
)
([],init_sg) constraints in
mkmty (Tmty_with ( body, List.rev rev_tcstrs))
(Mtype.freshen (Mty_signature final_sg)) env loc
smty.pmty_attributes
| Pmty_typeof smod ->
let env = Env.in_signature false env in
let tmty, mty = !type_module_type_of_fwd env smod in
mkmty (Tmty_typeof tmty) mty env loc smty.pmty_attributes
| Pmty_extension ext ->
raise (Error_forward (Builtin_attributes.error_of_extension ext))
and transl_signature env sg =
let names = new_names () in
let rec transl_sig env sg =
Ctype.init_def(Ident.current_time());
match sg with
[] -> [], [], env
| item :: srem ->
let loc = item.psig_loc in
match item.psig_desc with
| Psig_value sdesc ->
let (tdesc, newenv) =
Typedecl.transl_value_decl env item.psig_loc sdesc
in
let (trem,rem, final_env) = transl_sig newenv srem in
mksig (Tsig_value tdesc) env loc :: trem,
Sig_value(tdesc.val_id, tdesc.val_val) :: rem,
final_env
| Psig_type (rec_flag, sdecls) ->
List.iter
(fun decl -> check_name check_type names decl.ptype_name)
sdecls;
let (decls, newenv) =
Typedecl.transl_type_decl env rec_flag sdecls
in
let (trem, rem, final_env) = transl_sig newenv srem in
mksig (Tsig_type (rec_flag, decls)) env loc :: trem,
map_rec_type_with_row_types ~rec_flag
(fun rs td -> Sig_type(td.typ_id, td.typ_type, rs)) decls rem,
final_env
| Psig_typext styext ->
List.iter
(fun pext -> check_name check_typext names pext.pext_name)
styext.ptyext_constructors;
let (tyext, newenv) =
Typedecl.transl_type_extension false env item.psig_loc styext
in
let (trem, rem, final_env) = transl_sig newenv srem in
let constructors = tyext.tyext_constructors in
mksig (Tsig_typext tyext) env loc :: trem,
map_ext (fun es ext ->
Sig_typext(ext.ext_id, ext.ext_type, es)) constructors rem,
final_env
| Psig_exception sext ->
check_name check_typext names sext.pext_name;
let (ext, newenv) = Typedecl.transl_exception env sext in
let (trem, rem, final_env) = transl_sig newenv srem in
mksig (Tsig_exception ext) env loc :: trem,
Sig_typext(ext.ext_id, ext.ext_type, Text_exception) :: rem,
final_env
| Psig_module pmd ->
check_name check_module names pmd.pmd_name;
let id = Ident.create pmd.pmd_name.txt in
let tmty =
Builtin_attributes.warning_scope pmd.pmd_attributes
(fun () -> transl_modtype env pmd.pmd_type)
in
let md = {
md_type=tmty.mty_type;
md_attributes=pmd.pmd_attributes;
md_loc=pmd.pmd_loc;
}
in
let newenv = Env.enter_module_declaration id md env in
let (trem, rem, final_env) = transl_sig newenv srem in
mksig (Tsig_module {md_id=id; md_name=pmd.pmd_name; md_type=tmty;
md_loc=pmd.pmd_loc;
md_attributes=pmd.pmd_attributes})
env loc :: trem,
Sig_module(id, md, Trec_not) :: rem,
final_env
| Psig_recmodule sdecls ->
List.iter
(fun pmd -> check_name check_module names pmd.pmd_name)
sdecls;
let (decls, newenv) =
transl_recmodule_modtypes env sdecls in
let (trem, rem, final_env) = transl_sig newenv srem in
mksig (Tsig_recmodule decls) env loc :: trem,
map_rec (fun rs md ->
let d = {Types.md_type = md.md_type.mty_type;
md_attributes = md.md_attributes;
md_loc = md.md_loc;
} in
Sig_module(md.md_id, d, rs))
decls rem,
final_env
| Psig_modtype pmtd ->
let newenv, mtd, sg =
transl_modtype_decl names env pmtd
in
let (trem, rem, final_env) = transl_sig newenv srem in
mksig (Tsig_modtype mtd) env loc :: trem,
sg :: rem,
final_env
| Psig_open sod ->
let (_path, newenv, od) = type_open env sod in
let (trem, rem, final_env) = transl_sig newenv srem in
mksig (Tsig_open od) env loc :: trem,
rem, final_env
| Psig_include sincl ->
let smty = sincl.pincl_mod in
let tmty =
Builtin_attributes.warning_scope sincl.pincl_attributes
(fun () -> transl_modtype env smty)
in
let mty = tmty.mty_type in
let sg = Subst.signature Subst.identity
(extract_sig env smty.pmty_loc mty) in
List.iter (check_sig_item names item.psig_loc) sg;
let newenv = Env.add_signature sg env in
let incl =
{ incl_mod = tmty;
incl_type = sg;
incl_attributes = sincl.pincl_attributes;
incl_loc = sincl.pincl_loc;
}
in
let (trem, rem, final_env) = transl_sig newenv srem in
mksig (Tsig_include incl) env loc :: trem,
sg @ rem,
final_env
| Psig_class cl ->
List.iter
(fun {pci_name} -> check_name check_type names pci_name)
cl;
let (classes, newenv) = Typeclass.class_descriptions env cl in
let (trem, rem, final_env) = transl_sig newenv srem in
mksig (Tsig_class
(List.map (fun decr ->
decr.Typeclass.cls_info) classes)) env loc
:: trem,
List.flatten
(map_rec
(fun rs cls ->
let open Typeclass in
[Sig_class(cls.cls_id, cls.cls_decl, rs);
Sig_class_type(cls.cls_ty_id, cls.cls_ty_decl, rs);
Sig_type(cls.cls_obj_id, cls.cls_obj_abbr, rs);
Sig_type(cls.cls_typesharp_id, cls.cls_abbr, rs)])
classes [rem]),
final_env
| Psig_class_type cl ->
List.iter
(fun {pci_name} -> check_name check_type names pci_name)
cl;
let (classes, newenv) = Typeclass.class_type_declarations env cl in
let (trem,rem, final_env) = transl_sig newenv srem in
mksig (Tsig_class_type
(List.map (fun decl -> decl.Typeclass.clsty_info) classes))
env loc :: trem,
List.flatten
(map_rec
(fun rs decl ->
let open Typeclass in
[Sig_class_type(decl.clsty_ty_id, decl.clsty_ty_decl, rs);
Sig_type(decl.clsty_obj_id, decl.clsty_obj_abbr, rs);
Sig_type(decl.clsty_typesharp_id, decl.clsty_abbr, rs)])
classes [rem]),
final_env
| Psig_attribute x ->
Builtin_attributes.warning_attribute x;
let (trem,rem, final_env) = transl_sig env srem in
mksig (Tsig_attribute x) env loc :: trem, rem, final_env
| Psig_extension (ext, _attrs) ->
raise (Error_forward (Builtin_attributes.error_of_extension ext))
in
let previous_saved_types = Cmt_format.get_saved_types () in
Builtin_attributes.warning_scope []
(fun () ->
let (trem, rem, final_env) = transl_sig (Env.in_signature true env) sg in
let rem = simplify_signature rem in
let sg = { sig_items = trem; sig_type = rem; sig_final_env = final_env } in
Cmt_format.set_saved_types
((Cmt_format.Partial_signature sg) :: previous_saved_types);
sg
)
and transl_modtype_decl names env pmtd =
Builtin_attributes.warning_scope pmtd.pmtd_attributes
(fun () -> transl_modtype_decl_aux names env pmtd)
and transl_modtype_decl_aux names env
{pmtd_name; pmtd_type; pmtd_attributes; pmtd_loc} =
check_name check_modtype names pmtd_name;
let tmty = Misc.may_map (transl_modtype env) pmtd_type in
let decl =
{
Types.mtd_type=may_map (fun t -> t.mty_type) tmty;
mtd_attributes=pmtd_attributes;
mtd_loc=pmtd_loc;
}
in
let (id, newenv) = Env.enter_modtype pmtd_name.txt decl env in
let mtd =
{
mtd_id=id;
mtd_name=pmtd_name;
mtd_type=tmty;
mtd_attributes=pmtd_attributes;
mtd_loc=pmtd_loc;
}
in
newenv, mtd, Sig_modtype(id, decl)
and transl_recmodule_modtypes env sdecls =
let make_env curr =
List.fold_left
(fun env (id, _, mty) -> Env.add_module ~arg:true id mty env)
env curr in
let make_env2 curr =
List.fold_left
(fun env (id, _, mty) -> Env.add_module ~arg:true id mty.mty_type env)
env curr in
let transition env_c curr =
List.map2
(fun pmd (id, id_loc, _mty) ->
let tmty =
Builtin_attributes.warning_scope pmd.pmd_attributes
(fun () -> transl_modtype env_c pmd.pmd_type)
in
(id, id_loc, tmty))
sdecls curr in
let ids = List.map (fun x -> Ident.create x.pmd_name.txt) sdecls in
let approx_env =
(*
cf #5965
We use a dummy module type in order to detect a reference to one
of the module being defined during the call to approx_modtype.
It will be detected in Env.lookup_module.
*)
List.fold_left
(fun env id ->
let dummy = Mty_ident (Path.Pident (Ident.create "#recmod#")) in
Env.add_module ~arg:true id dummy env
)
env ids
in
Ctype.init_def(Ident.current_time()); (* PR#7082 *)
let init =
List.map2
(fun id pmd ->
(id, pmd.pmd_name, approx_modtype approx_env pmd.pmd_type))
ids sdecls
in
let env0 = make_env init in
let dcl1 =
Warnings.without_warnings
(fun () -> transition env0 init)