forked from ocaml/ocaml
-
Notifications
You must be signed in to change notification settings - Fork 0
/
Copy pathout_type.ml
1971 lines (1742 loc) · 63.4 KB
/
out_type.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 and 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. *)
(* *)
(**************************************************************************)
(* Compute a spanning tree representation of types *)
open Misc
open Ctype
open Longident
open Path
open Asttypes
open Types
open Btype
open Outcometree
module String = Misc.Stdlib.String
module Sig_component_kind = Shape.Sig_component_kind
module Style = Misc.Style
(* Print a long identifier *)
module Fmt = Format_doc
open Format_doc
(* Print an identifier avoiding name collisions *)
module Out_name = struct
let create x = { printed_name = x }
let print x = x.printed_name
end
(** Some identifiers may require hiding when printing *)
type bound_ident = { hide:bool; ident:Ident.t }
(* printing environment for path shortening and naming *)
let printing_env = ref Env.empty
(* When printing, it is important to only observe the
current printing environment, without reading any new
cmi present on the file system *)
let in_printing_env f = Env.without_cmis f !printing_env
type namespace = Sig_component_kind.t =
| Value
| Type
| Constructor
| Label
| Module
| Module_type
| Extension_constructor
| Class
| Class_type
module Namespace = struct
let id = function
| Type -> 0
| Module -> 1
| Module_type -> 2
| Class -> 3
| Class_type -> 4
| Extension_constructor | Value | Constructor | Label -> 5
(* we do not handle those component *)
let size = 1 + id Value
let pp ppf x =
Fmt.pp_print_string ppf (Shape.Sig_component_kind.to_string x)
(** The two functions below should never access the filesystem,
and thus use {!in_printing_env} rather than directly
accessing the printing environment *)
let lookup =
let to_lookup f lid = fst @@ in_printing_env (f (Lident lid)) in
function
| Some Type -> to_lookup Env.find_type_by_name
| Some Module -> to_lookup Env.find_module_by_name
| Some Module_type -> to_lookup Env.find_modtype_by_name
| Some Class -> to_lookup Env.find_class_by_name
| Some Class_type -> to_lookup Env.find_cltype_by_name
| None | Some(Value|Extension_constructor|Constructor|Label) ->
fun _ -> raise Not_found
let location namespace id =
let path = Path.Pident id in
try Some (
match namespace with
| Some Type -> (in_printing_env @@ Env.find_type path).type_loc
| Some Module -> (in_printing_env @@ Env.find_module path).md_loc
| Some Module_type -> (in_printing_env @@ Env.find_modtype path).mtd_loc
| Some Class -> (in_printing_env @@ Env.find_class path).cty_loc
| Some Class_type -> (in_printing_env @@ Env.find_cltype path).clty_loc
| Some (Extension_constructor|Value|Constructor|Label) | None ->
Location.none
) with Not_found -> None
let best_class_namespace = function
| Papply _ | Pdot _ -> Some Module
| Pextra_ty _ -> assert false (* Only in type path *)
| Pident c ->
match location (Some Class) c with
| Some _ -> Some Class
| None -> Some Class_type
end
(** {2 Ident conflicts printing}
Ident conflicts arise when multiple {!Ident.t}s are attributed the same name.
The following module stores the global conflict references and provides the
printing functions for explaining the source of the conflicts.
*)
module Ident_conflicts = struct
module M = String.Map
type explanation =
{ kind: namespace; name:string; root_name:string; location:Location.t}
let explanations = ref M.empty
let add namespace name id =
match Namespace.location (Some namespace) id with
| None -> ()
| Some location ->
let explanation =
{ kind = namespace; location; name; root_name=Ident.name id}
in
explanations := M.add name explanation !explanations
let collect_explanation namespace id ~name =
let root_name = Ident.name id in
(* if [name] is of the form "root_name/%d", we register both
[id] and the identifier in scope for [root_name].
*)
if root_name <> name && not (M.mem name !explanations) then
begin
add namespace name id;
if not (M.mem root_name !explanations) then
(* lookup the identifier in scope with name [root_name] and
add it too
*)
match Namespace.lookup (Some namespace) root_name with
| Pident root_id -> add namespace root_name root_id
| exception Not_found | _ -> ()
end
let pp_explanation ppf r=
Fmt.fprintf ppf "@[<v 2>%a:@,Definition of %s %a@]"
Location.Doc.loc r.location (Sig_component_kind.to_string r.kind)
Style.inline_code r.name
let print_located_explanations ppf l =
Fmt.fprintf ppf "@[<v>%a@]"
(Fmt.pp_print_list pp_explanation) l
let reset () = explanations := M.empty
let list_explanations () =
let c = !explanations in
reset ();
c |> M.bindings |> List.map snd |> List.sort Stdlib.compare
let print_toplevel_hint ppf l =
let conj ppf () = Fmt.fprintf ppf " and@ " in
let pp_namespace_plural ppf n = Fmt.fprintf ppf "%as" Namespace.pp n in
let root_names = List.map (fun r -> r.kind, r.root_name) l in
let unique_root_names = List.sort_uniq Stdlib.compare root_names in
let submsgs = Array.make Namespace.size [] in
let () = List.iter (fun (n,_ as x) ->
submsgs.(Namespace.id n) <- x :: submsgs.(Namespace.id n)
) unique_root_names in
let pp_submsg ppf names =
match names with
| [] -> ()
| [namespace, a] ->
Fmt.fprintf ppf
"@,\
@[<2>@{<hint>Hint@}: The %a %a has been defined multiple times@ \
in@ this@ toplevel@ session.@ \
Some toplevel values still refer to@ old@ versions@ of@ this@ %a.\
@ Did you try to redefine them?@]"
Namespace.pp namespace
Style.inline_code a Namespace.pp namespace
| (namespace, _) :: _ :: _ ->
Fmt.fprintf ppf
"@,\
@[<2>@{<hint>Hint@}: The %a %a have been defined multiple times@ \
in@ this@ toplevel@ session.@ \
Some toplevel values still refer to@ old@ versions@ of@ those@ %a.\
@ Did you try to redefine them?@]"
pp_namespace_plural namespace
Fmt.(pp_print_list ~pp_sep:conj Style.inline_code)
(List.map snd names)
pp_namespace_plural namespace in
Array.iter (pp_submsg ppf) submsgs
let err_msg () =
let ltop, l =
(* isolate toplevel locations, since they are too imprecise *)
let from_toplevel a =
a.location.Location.loc_start.Lexing.pos_fname = "//toplevel//" in
List.partition from_toplevel (list_explanations ())
in
match l, ltop with
| [], [] -> None
| _ ->
Some
(Fmt.doc_printf "%a%a"
print_located_explanations l
print_toplevel_hint ltop
)
let err_print ppf = Option.iter Fmt.(fprintf ppf "@,%a" pp_doc) (err_msg ())
let exists () = M.cardinal !explanations >0
end
module Ident_names = struct
module M = String.Map
module S = String.Set
let enabled = ref true
let enable b = enabled := b
(* Names bound in recursive definitions should be considered as bound
in the environment when printing identifiers but not when trying
to find shortest path.
For instance, if we define
[{
module Avoid__me = struct
type t = A
end
type t = X
type u = [` A of t * t ]
module M = struct
type t = A of [ u | `B ]
type r = Avoid__me.t
end
}]
It is is important that in the definition of [t] that the outer type [t] is
printed as [t/2] reserving the name [t] to the type being defined in the
current recursive definition.
Contrarily, in the definition of [r], one should not shorten the
path [Avoid__me.t] to [r] until the end of the definition of [r].
The [bound_in_recursion] bridges the gap between those two slightly different
notions of printing environment.
*)
let bound_in_recursion = ref M.empty
(* When dealing with functor arguments, identity becomes fuzzy because the same
syntactic argument may be represented by different identifiers during the
error processing, we are thus disabling disambiguation on the argument name
*)
let fuzzy = ref S.empty
let with_fuzzy id f =
protect_refs [ R(fuzzy, S.add (Ident.name id) !fuzzy) ] f
let fuzzy_id namespace id = namespace = Module && S.mem (Ident.name id) !fuzzy
let with_hidden ids f =
let update m id = M.add (Ident.name id.ident) id.ident m in
let updated = List.fold_left update !bound_in_recursion ids in
protect_refs [ R(bound_in_recursion, updated )] f
let human_id id index =
(* The identifier with index [k] is the (k+1)-th most recent identifier in
the printing environment. We print them as [name/(k+1)] except for [k=0]
which is printed as [name] rather than [name/1].
*)
if index = 0 then
Ident.name id
else
let ordinal = index + 1 in
String.concat "/" [Ident.name id; string_of_int ordinal]
let indexed_name namespace id =
let find namespace id env = match namespace with
| Type -> Env.find_type_index id env
| Module -> Env.find_module_index id env
| Module_type -> Env.find_modtype_index id env
| Class -> Env.find_class_index id env
| Class_type-> Env.find_cltype_index id env
| Value | Extension_constructor | Constructor | Label -> None
in
let index =
match M.find_opt (Ident.name id) !bound_in_recursion with
| Some rec_bound_id ->
(* the identifier name appears in the current group of recursive
definition *)
if Ident.same rec_bound_id id then
Some 0
else
(* the current recursive definition shadows one more time the
previously existing identifier with the same name *)
Option.map succ (in_printing_env (find namespace id))
| None ->
in_printing_env (find namespace id)
in
let index =
(* If [index] is [None] at this point, it might indicate that
the identifier id is not defined in the environment, while there
are other identifiers in scope that share the same name.
Currently, this kind of partially incoherent environment happens
within functor error messages where the left and right hand side
have a different views of the environment at the source level.
Printing the source-level by using a default index of `0`
seems like a reasonable compromise in this situation however.*)
Option.value index ~default:0
in
human_id id index
let ident_name namespace id =
match namespace, !enabled with
| None, _ | _, false -> Out_name.create (Ident.name id)
| Some namespace, true ->
if fuzzy_id namespace id then Out_name.create (Ident.name id)
else
let name = indexed_name namespace id in
Ident_conflicts.collect_explanation namespace id ~name;
Out_name.create name
end
let ident_name = Ident_names.ident_name
(* Print a path *)
let ident_stdlib = Ident.create_persistent "Stdlib"
let non_shadowed_stdlib namespace = function
| Pdot(Pident id, s) as path ->
Ident.same id ident_stdlib &&
(match Namespace.lookup namespace s with
| path' -> Path.same path path'
| exception Not_found -> true)
| _ -> false
let find_double_underscore s =
let len = String.length s in
let rec loop i =
if i + 1 >= len then
None
else if s.[i] = '_' && s.[i + 1] = '_' then
Some i
else
loop (i + 1)
in
loop 0
let rec module_path_is_an_alias_of env path ~alias_of =
match Env.find_module path env with
| { md_type = Mty_alias path'; _ } ->
Path.same path' alias_of ||
module_path_is_an_alias_of env path' ~alias_of
| _ -> false
| exception Not_found -> false
(* Simple heuristic to print Foo__bar.* as Foo.Bar.* when Foo.Bar is an alias
for Foo__bar. This pattern is used by the stdlib. *)
let rec rewrite_double_underscore_paths env p =
match p with
| Pdot (p, s) ->
Pdot (rewrite_double_underscore_paths env p, s)
| Papply (a, b) ->
Papply (rewrite_double_underscore_paths env a,
rewrite_double_underscore_paths env b)
| Pextra_ty (p, extra) ->
Pextra_ty (rewrite_double_underscore_paths env p, extra)
| Pident id ->
let name = Ident.name id in
match find_double_underscore name with
| None -> p
| Some i ->
let better_lid =
Ldot
(Lident (String.sub name 0 i),
Unit_info.modulize
(String.sub name (i + 2) (String.length name - i - 2)))
in
match Env.find_module_by_name better_lid env with
| exception Not_found -> p
| p', _ ->
if module_path_is_an_alias_of env p' ~alias_of:p then
p'
else
p
let rewrite_double_underscore_paths env p =
if env == Env.empty then
p
else
rewrite_double_underscore_paths env p
let rec tree_of_path ?(disambiguation=true) namespace p =
let tree_of_path namespace p = tree_of_path ~disambiguation namespace p in
let namespace = if disambiguation then namespace else None in
match p with
| Pident id ->
Oide_ident (ident_name namespace id)
| Pdot(_, s) as path when non_shadowed_stdlib namespace path ->
Oide_ident (Out_name.create s)
| Pdot(p, s) ->
Oide_dot (tree_of_path (Some Module) p, s)
| Papply(p1, p2) ->
let t1 = tree_of_path (Some Module) p1 in
let t2 = tree_of_path (Some Module) p2 in
Oide_apply (t1, t2)
| Pextra_ty (p, extra) -> begin
(* inline record types are syntactically prevented from escaping their
binding scope, and are never shown to users. *)
match extra with
Pcstr_ty s ->
Oide_dot (tree_of_path (Some Type) p, s)
| Pext_ty ->
tree_of_path None p
end
let tree_of_path ?disambiguation namespace p =
tree_of_path ?disambiguation namespace
(rewrite_double_underscore_paths !printing_env p)
(* Print a recursive annotation *)
let tree_of_rec = function
| Trec_not -> Orec_not
| Trec_first -> Orec_first
| Trec_next -> Orec_next
(* Normalize paths *)
type param_subst = Id | Nth of int | Map of int list
let is_nth = function
Nth _ -> true
| _ -> false
let compose l1 = function
| Id -> Map l1
| Map l2 -> Map (List.map (List.nth l1) l2)
| Nth n -> Nth (List.nth l1 n)
let apply_subst s1 tyl =
if tyl = [] then []
(* cf. PR#7543: Typemod.type_package doesn't respect type constructor arity *)
else
match s1 with
Nth n1 -> [List.nth tyl n1]
| Map l1 -> List.map (List.nth tyl) l1
| Id -> tyl
type best_path = Paths of Path.t list | Best of Path.t
(** Short-paths cache: the five mutable variables below implement a one-slot
cache for short-paths
*)
let printing_old = ref Env.empty
let printing_pers = ref String.Set.empty
(** {!printing_old} and {!printing_pers} are the keys of the one-slot cache *)
let printing_depth = ref 0
let printing_cont = ref ([] : Env.iter_cont list)
let printing_map = ref Path.Map.empty
(**
- {!printing_map} is the main value stored in the cache.
Note that it is evaluated lazily and its value is updated during printing.
- {!printing_dep} is the current exploration depth of the environment,
it is used to determine whenever the {!printing_map} should be evaluated
further before completing a request.
- {!printing_cont} is the list of continuations needed to evaluate
the {!printing_map} one level further (see also {!Env.run_iter_cont})
*)
let rec index l x =
match l with
[] -> raise Not_found
| a :: l -> if eq_type x a then 0 else 1 + index l x
let rec uniq = function
[] -> true
| a :: l -> not (List.memq (a : int) l) && uniq l
let rec normalize_type_path ?(cache=false) env p =
try
let (params, ty, _) = Env.find_type_expansion p env in
match get_desc ty with
Tconstr (p1, tyl, _) ->
if List.length params = List.length tyl
&& List.for_all2 eq_type params tyl
then normalize_type_path ~cache env p1
else if cache || List.length params <= List.length tyl
|| not (uniq (List.map get_id tyl)) then (p, Id)
else
let l1 = List.map (index params) tyl in
let (p2, s2) = normalize_type_path ~cache env p1 in
(p2, compose l1 s2)
| _ ->
(p, Nth (index params ty))
with
Not_found ->
(Env.normalize_type_path None env p, Id)
let penalty s =
if s <> "" && s.[0] = '_' then
10
else
match find_double_underscore s with
| None -> 1
| Some _ -> 10
let rec path_size = function
Pident id ->
penalty (Ident.name id), -Ident.scope id
| Pdot (p, _) | Pextra_ty (p, Pcstr_ty _) ->
let (l, b) = path_size p in (1+l, b)
| Papply (p1, p2) ->
let (l, b) = path_size p1 in
(l + fst (path_size p2), b)
| Pextra_ty (p, _) -> path_size p
let same_printing_env env =
let used_pers = Env.used_persistent () in
Env.same_types !printing_old env && String.Set.equal !printing_pers used_pers
let set_printing_env env =
printing_env := env;
if !Clflags.real_paths ||
!printing_env == Env.empty ||
same_printing_env env then
()
else begin
(* printf "Reset printing_map@."; *)
printing_old := env;
printing_pers := Env.used_persistent ();
printing_map := Path.Map.empty;
printing_depth := 0;
(* printf "Recompute printing_map.@."; *)
let cont =
Env.iter_types
(fun p (p', _decl) ->
let (p1, s1) = normalize_type_path env p' ~cache:true in
(* Format.eprintf "%a -> %a = %a@." path p path p' path p1 *)
if s1 = Id then
try
let r = Path.Map.find p1 !printing_map in
match !r with
Paths l -> r := Paths (p :: l)
| Best p' -> r := Paths [p; p'] (* assert false *)
with Not_found ->
printing_map := Path.Map.add p1 (ref (Paths [p])) !printing_map)
env in
printing_cont := [cont];
end
let wrap_printing_env env f =
set_printing_env env;
try_finally f ~always:(fun () -> set_printing_env Env.empty)
let wrap_printing_env ~error env f =
if error then Env.without_cmis (wrap_printing_env env) f
else wrap_printing_env env f
let rec lid_of_path = function
Path.Pident id ->
Longident.Lident (Ident.name id)
| Path.Pdot (p1, s) | Path.Pextra_ty (p1, Pcstr_ty s) ->
Longident.Ldot (lid_of_path p1, s)
| Path.Papply (p1, p2) ->
Longident.Lapply (lid_of_path p1, lid_of_path p2)
| Path.Pextra_ty (p, Pext_ty) -> lid_of_path p
let is_unambiguous path env =
let l = Env.find_shadowed_types path env in
List.exists (Path.same path) l || (* concrete paths are ok *)
match l with
[] -> true
| p :: rem ->
(* allow also coherent paths: *)
let normalize p = fst (normalize_type_path ~cache:true env p) in
let p' = normalize p in
List.for_all (fun p -> Path.same (normalize p) p') rem ||
(* also allow repeatedly defining and opening (for toplevel) *)
let id = lid_of_path p in
List.for_all (fun p -> lid_of_path p = id) rem &&
Path.same p (fst (Env.find_type_by_name id env))
let rec get_best_path r =
match !r with
Best p' -> p'
| Paths [] -> raise Not_found
| Paths l ->
r := Paths [];
List.iter
(fun p ->
(* Format.eprintf "evaluating %a@." path p; *)
match !r with
Best p' when path_size p >= path_size p' -> ()
| _ -> if is_unambiguous p !printing_env then r := Best p)
(* else Format.eprintf "%a ignored as ambiguous@." path p *)
l;
get_best_path r
let best_type_path p =
if !printing_env == Env.empty
then (p, Id)
else if !Clflags.real_paths
then (p, Id)
else
let (p', s) = normalize_type_path !printing_env p in
let get_path () = get_best_path (Path.Map.find p' !printing_map) in
while !printing_cont <> [] &&
try fst (path_size (get_path ())) > !printing_depth with Not_found -> true
do
printing_cont := List.map snd (Env.run_iter_cont !printing_cont);
incr printing_depth;
done;
let p'' = try get_path () with Not_found -> p' in
(* Format.eprintf "%a = %a -> %a@." path p path p' path p''; *)
(p'', s)
(* When building a tree for a best type path, we should not disambiguate
identifiers whenever the short-path algorithm detected a better path than
the original one.*)
let tree_of_best_type_path p p' =
if Path.same p p' then tree_of_path (Some Type) p'
else tree_of_path ~disambiguation:false None p'
(* Print a type expression *)
let proxy ty = Transient_expr.repr (proxy ty)
(* When printing a type scheme, we print weak names. When printing a plain
type, we do not. This type controls that behavior *)
type type_or_scheme = Type | Type_scheme
let is_non_gen mode ty =
match mode with
| Type_scheme -> is_Tvar ty && get_level ty <> generic_level
| Type -> false
let nameable_row row =
row_name row <> None &&
List.for_all
(fun (_, f) ->
match row_field_repr f with
| Reither(c, l, _) ->
row_closed row && if c then l = [] else List.length l = 1
| _ -> true)
(row_fields row)
(* This specialized version of [Btype.iter_type_expr] normalizes and
short-circuits the traversal of the [type_expr], so that it covers only the
subterms that would be printed by the type printer. *)
let printer_iter_type_expr f ty =
match get_desc ty with
| Tconstr(p, tyl, _) ->
let (_p', s) = best_type_path p in
List.iter f (apply_subst s tyl)
| Tvariant row -> begin
match row_name row with
| Some(_p, tyl) when nameable_row row ->
List.iter f tyl
| _ ->
iter_row f row
end
| Tobject (fi, nm) -> begin
match !nm with
| None ->
let fields, _ = flatten_fields fi in
List.iter
(fun (_, kind, ty) ->
if field_kind_repr kind = Fpublic then
f ty)
fields
| Some (_, l) ->
List.iter f (List.tl l)
end
| Tfield(_, kind, ty1, ty2) ->
if field_kind_repr kind = Fpublic then
f ty1;
f ty2
| _ ->
Btype.iter_type_expr f ty
let quoted_ident ppf x =
Style.as_inline_code !Oprint.out_ident ppf x
module Internal_names : sig
val reset : unit -> unit
val add : Path.t -> unit
val print_explanations : Env.t -> Fmt.formatter -> unit
end = struct
let names = ref Ident.Set.empty
let reset () =
names := Ident.Set.empty
let add p =
match p with
| Pident id ->
let name = Ident.name id in
if String.length name > 0 && name.[0] = '$' then begin
names := Ident.Set.add id !names
end
| Pdot _ | Papply _ | Pextra_ty _ -> ()
let print_explanations env ppf =
let constrs =
Ident.Set.fold
(fun id acc ->
let p = Pident id in
match Env.find_type p env with
| exception Not_found -> acc
| decl ->
match type_origin decl with
| Existential constr ->
let prev = String.Map.find_opt constr acc in
let prev = Option.value ~default:[] prev in
String.Map.add constr (tree_of_path None p :: prev) acc
| Definition | Rec_check_regularity -> acc)
!names String.Map.empty
in
String.Map.iter
(fun constr out_idents ->
match out_idents with
| [] -> ()
| [out_ident] ->
fprintf ppf
"@ @[<2>@{<hint>Hint@}:@ %a@ is an existential type@ \
bound by the constructor@ %a.@]"
quoted_ident out_ident
Style.inline_code constr
| out_ident :: out_idents ->
fprintf ppf
"@ @[<2>@{<hint>Hint@}:@ %a@ and %a@ are existential types@ \
bound by the constructor@ %a.@]"
(Fmt.pp_print_list
~pp_sep:(fun ppf () -> fprintf ppf ",@ ")
quoted_ident)
(List.rev out_idents)
quoted_ident out_ident
Style.inline_code constr)
constrs
end
module Variable_names : sig
val reset_names : unit -> unit
val add_subst : (type_expr * type_expr) list -> unit
val new_name : unit -> string
val new_var_name : non_gen:bool -> type_expr -> unit -> string
val name_of_type : (unit -> string) -> transient_expr -> string
val check_name_of_type : non_gen:bool -> transient_expr -> unit
val reserve: type_expr -> unit
val remove_names : transient_expr list -> unit
val with_local_names : (unit -> 'a) -> 'a
(* Refresh the weak variable map in the toplevel; for [print_items], which is
itself for the toplevel *)
val refresh_weak : unit -> unit
end = struct
(* We map from types to names, but not directly; we also store a substitution,
which maps from types to types. The lookup process is
"type -> apply substitution -> find name". The substitution is presumed to
be one-shot. *)
let names = ref ([] : (transient_expr * string) list)
let name_subst = ref ([] : (transient_expr * transient_expr) list)
let name_counter = ref 0
let named_vars = ref ([] : string list)
let visited_for_named_vars = ref ([] : transient_expr list)
let weak_counter = ref 1
let weak_var_map = ref TypeMap.empty
let named_weak_vars = ref String.Set.empty
let reset_names () =
names := [];
name_subst := [];
name_counter := 0;
named_vars := [];
visited_for_named_vars := []
let add_named_var tty =
match tty.desc with
Tvar (Some name) | Tunivar (Some name) ->
if List.mem name !named_vars then () else
named_vars := name :: !named_vars
| _ -> ()
let rec add_named_vars ty =
let tty = Transient_expr.repr ty in
let px = proxy ty in
if not (List.memq px !visited_for_named_vars) then begin
visited_for_named_vars := px :: !visited_for_named_vars;
match tty.desc with
| Tvar _ | Tunivar _ ->
add_named_var tty
| _ ->
printer_iter_type_expr add_named_vars ty
end
let substitute ty =
match List.assq ty !name_subst with
| ty' -> ty'
| exception Not_found -> ty
let add_subst subst =
name_subst :=
List.map (fun (t1,t2) -> Transient_expr.repr t1, Transient_expr.repr t2)
subst
@ !name_subst
let name_is_already_used name =
List.mem name !named_vars
|| List.exists (fun (_, name') -> name = name') !names
|| String.Set.mem name !named_weak_vars
let rec new_name () =
let name = Misc.letter_of_int !name_counter in
incr name_counter;
if name_is_already_used name then new_name () else name
let rec new_weak_name ty () =
let name = "weak" ^ Int.to_string !weak_counter in
incr weak_counter;
if name_is_already_used name then new_weak_name ty ()
else begin
named_weak_vars := String.Set.add name !named_weak_vars;
weak_var_map := TypeMap.add ty name !weak_var_map;
name
end
let new_var_name ~non_gen ty () =
if non_gen then new_weak_name ty ()
else new_name ()
let name_of_type name_generator t =
(* We've already been through repr at this stage, so t is our representative
of the union-find class. *)
let t = substitute t in
try List.assq t !names with Not_found ->
try TransientTypeMap.find t !weak_var_map with Not_found ->
let name =
match t.desc with
Tvar (Some name) | Tunivar (Some name) ->
(* Some part of the type we've already printed has assigned another
* unification variable to that name. We want to keep the name, so
* try adding a number until we find a name that's not taken. *)
let available name =
List.for_all
(fun (_, name') -> name <> name')
!names
in
if available name then name
else
let suffixed i = name ^ Int.to_string i in
let i = Misc.find_first_mono (fun i -> available (suffixed i)) in
suffixed i
| _ ->
(* No name available, create a new one *)
name_generator ()
in
(* Exception for type declarations *)
if name <> "_" then names := (t, name) :: !names;
name
let check_name_of_type ~non_gen px =
let name_gen = new_var_name ~non_gen (Transient_expr.type_expr px) in
ignore(name_of_type name_gen px)
let remove_names tyl =
let tyl = List.map substitute tyl in
names := List.filter (fun (ty,_) -> not (List.memq ty tyl)) !names
let with_local_names f =
let old_names = !names in
let old_subst = !name_subst in
names := [];
name_subst := [];
try_finally
~always:(fun () ->
names := old_names;
name_subst := old_subst)
f
let refresh_weak () =
let refresh t name (m,s) =
if is_non_gen Type_scheme t then
begin
TypeMap.add t name m,
String.Set.add name s
end
else m, s in
let m, s =
TypeMap.fold refresh !weak_var_map (TypeMap.empty ,String.Set.empty) in
named_weak_vars := s;
weak_var_map := m
let reserve ty =
normalize_type ty;
add_named_vars ty
end
module Aliases = struct
let visited_objects = ref ([] : transient_expr list)
let aliased = ref ([] : transient_expr list)
let delayed = ref ([] : transient_expr list)
let printed_aliases = ref ([] : transient_expr list)
(* [printed_aliases] is a subset of [aliased] that records only those aliased
types that have actually been printed; this allows us to avoid naming loops
that the user will never see. *)
let is_delayed t = List.memq t !delayed
let remove_delay t =
if is_delayed t then
delayed := List.filter ((!=) t) !delayed
let add_delayed t =
if not (is_delayed t) then delayed := t :: !delayed
let is_aliased_proxy px = List.memq px !aliased
let is_printed_proxy px = List.memq px !printed_aliases
let add_proxy px =
if not (is_aliased_proxy px) then
aliased := px :: !aliased
let add ty = add_proxy (proxy ty)
let add_printed_proxy ~non_gen px =
Variable_names.check_name_of_type ~non_gen px;
printed_aliases := px :: !printed_aliases
let mark_as_printed px =
if is_aliased_proxy px then (add_printed_proxy ~non_gen:false) px
let add_printed ty = add_printed_proxy (proxy ty)
let aliasable ty =
match get_desc ty with
Tvar _ | Tunivar _ | Tpoly _ -> false
| Tconstr (p, _, _) ->
not (is_nth (snd (best_type_path p)))
| _ -> true
let should_visit_object ty =
match get_desc ty with
| Tvariant row -> not (static_row row)
| Tobject _ -> opened_object ty
| _ -> false
let rec mark_loops_rec visited ty =
let px = proxy ty in
if List.memq px visited && aliasable ty then add_proxy px else
let tty = Transient_expr.repr ty in
let visited = px :: visited in
match tty.desc with
| Tvariant _ | Tobject _ ->
if List.memq px !visited_objects then add_proxy px else begin
if should_visit_object ty then
visited_objects := px :: !visited_objects;
printer_iter_type_expr (mark_loops_rec visited) ty
end
| Tpoly(ty, tyl) ->
List.iter add tyl;
mark_loops_rec visited ty
| _ ->
printer_iter_type_expr (mark_loops_rec visited) ty
let mark_loops ty =
mark_loops_rec [] ty
let reset () =
visited_objects := []; aliased := []; delayed := []; printed_aliases := []
end
let prepare_type ty =