forked from rescript-lang/rescript
-
Notifications
You must be signed in to change notification settings - Fork 0
/
Copy pathparmatch.ml
2613 lines (2301 loc) · 83.1 KB
/
parmatch.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. *)
(* *)
(**************************************************************************)
(* Detection of partial matches and unused match cases. *)
open Misc
open Asttypes
open Types
open Typedtree
(*************************************)
(* Utilities for building patterns *)
(*************************************)
let make_pat desc ty tenv =
{pat_desc = desc; pat_loc = Location.none; pat_extra = [];
pat_type = ty ; pat_env = tenv;
pat_attributes = [];
}
let omega = make_pat Tpat_any Ctype.none Env.empty
let extra_pat =
make_pat
(Tpat_var (Ident.create "+", mknoloc "+"))
Ctype.none Env.empty
let rec omegas i =
if i <= 0 then [] else omega :: omegas (i-1)
let omega_list l = List.map (fun _ -> omega) l
let zero = make_pat (Tpat_constant (Const_int 0)) Ctype.none Env.empty
(*******************)
(* Coherence check *)
(*******************)
(* For some of the operations we do in this module, we would like (because it
simplifies matters) to assume that patterns appearing on a given column in a
pattern matrix are /coherent/ (think "of the same type").
Unfortunately that is not always true.
Consider the following (well-typed) example:
{[
type _ t = S : string t | U : unit t
let f (type a) (t1 : a t) (t2 : a t) (a : a) =
match t1, t2, a with
| U, _, () -> ()
| _, S, "" -> ()
]}
Clearly the 3rd column contains incoherent patterns.
On the example above, most of the algorithms will explore the pattern matrix
as illustrated by the following tree:
{v
S
-------> | "" |
U | S, "" | __/ | () |
--------> | _, () | \ ¬ S
| U, _, () | __/ -------> | () |
| _, S, "" | \
---------> | S, "" | ----------> | "" |
¬ U S
v}
where following an edge labelled by a pattern P means "assuming the value I
am matching on is filtered by [P] on the column I am currently looking at,
then the following submatrix is still reachable".
Notice that at any point of that tree, if the first column of a matrix is
incoherent, then the branch leading to it can only be taken if the scrutinee
is ill-typed.
In the example above the only case where we have a matrix with an incoherent
first column is when we consider [t1, t2, a] to be [U, S, ...]. However such
a value would be ill-typed, so we can never actually get there.
Checking the first column at each step of the recursion and making the
concious decision of "aborting" the algorithm whenever the first column
becomes incoherent, allows us to retain the initial assumption in later
stages of the algorithms.
---
N.B. two patterns can be considered coherent even though they might not be of
the same type.
That's in part because we only care about the "head" of patterns and leave
checking coherence of subpatterns for the next steps of the algorithm:
('a', 'b') and (1, ()) will be deemed coherent because they are both a tuples
of arity 2 (we'll notice at a later stage the incoherence of 'a' and 1).
But also because it can be hard/costly to determine exactly whether two
patterns are of the same type or not (eg. in the example above with _ and S,
but see also the module [Coherence_illustration] in
testsuite/tests/basic-more/robustmatch.ml).
For the moment our weak, loosely-syntactic, coherence check seems to be
enough and we leave it to each user to consider (and document!) what happens
when an "incoherence" is not detected by this check.
*)
let simplify_head_pat p k =
let rec simplify_head_pat p k =
match p.pat_desc with
| Tpat_alias (p,_,_) -> simplify_head_pat p k
| Tpat_var (_,_) -> omega :: k
| Tpat_or (p1,p2,_) -> simplify_head_pat p1 (simplify_head_pat p2 k)
| _ -> p :: k
in simplify_head_pat p k
let rec simplified_first_col = function
| [] -> []
| [] :: _ -> assert false (* the rows are non-empty! *)
| (p::_) :: rows ->
simplify_head_pat p (simplified_first_col rows)
(* Given the simplified first column of a matrix, this function first looks for
a "discriminating" pattern on that column (i.e. a non-omega one) and then
check that every other head pattern in the column is coherent with that one.
*)
let all_coherent column =
let coherent_heads hp1 hp2 =
match hp1.pat_desc, hp2.pat_desc with
| (Tpat_var _ | Tpat_alias _ | Tpat_or _), _
| _, (Tpat_var _ | Tpat_alias _ | Tpat_or _) ->
assert false
| Tpat_construct (_, c, _), Tpat_construct (_, c', _) ->
c.cstr_consts = c'.cstr_consts
&& c.cstr_nonconsts = c'.cstr_nonconsts
| Tpat_constant c1, Tpat_constant c2 -> begin
match c1, c2 with
| Const_char _, Const_char _
| Const_int _, Const_int _
| Const_int32 _, Const_int32 _
| Const_int64 _, Const_int64 _
| Const_nativeint _, Const_nativeint _
| Const_float _, Const_float _
| Const_string _, Const_string _ -> true
| ( Const_char _
| Const_int _
| Const_int32 _
| Const_int64 _
| Const_nativeint _
| Const_float _
| Const_string _), _ -> false
end
| Tpat_tuple l1, Tpat_tuple l2 -> List.length l1 = List.length l2
| Tpat_record ((_, lbl1, _) :: _, _), Tpat_record ((_, lbl2, _) :: _, _) ->
Array.length lbl1.lbl_all = Array.length lbl2.lbl_all
| Tpat_any, _
| _, Tpat_any
| Tpat_record ([], _), Tpat_record (_, _)
| Tpat_record (_, _), Tpat_record ([], _)
| Tpat_variant _, Tpat_variant _
| Tpat_array _, Tpat_array _
| Tpat_lazy _, Tpat_lazy _ -> true
| _, _ -> false
in
match
List.find (fun head_pat ->
match head_pat.pat_desc with
| Tpat_var _ | Tpat_alias _ | Tpat_or _ -> assert false
| Tpat_any -> false
| _ -> true
) column
with
| exception Not_found ->
(* only omegas on the column: the column is coherent. *)
true
| discr_pat ->
List.for_all (coherent_heads discr_pat) column
let first_column simplified_matrix =
List.map fst simplified_matrix
(***********************)
(* Compatibility check *)
(***********************)
(* Patterns p and q compatible means:
there exists value V that matches both, However....
The case of extension types is dubious, as constructor rebind permits
that different constructors are the same (and are thus compatible).
Compilation must take this into account, consider:
type t = ..
type t += A|B
type t += C=A
let f x y = match x,y with
| true,A -> '1'
| _,C -> '2'
| false,A -> '3'
| _,_ -> '_'
As C is bound to A the value of f false A is '2' (and not '3' as it would
be in the absence of rebinding).
Not considering rebinding, patterns "false,A" and "_,C" are incompatible
and the compiler can swap the second and third clause, resulting in the
(more efficiently compiled) matching
match x,y with
| true,A -> '1'
| false,A -> '3'
| _,C -> '2'
| _,_ -> '_'
This is not correct: when C is bound to A, "f false A" returns '2' (not '3')
However, diagnostics do not take constructor rebinding into account.
Notice, that due to module abstraction constructor rebinding is hidden.
module X : sig type t = .. type t += A|B end = struct
type t = ..
type t += A
type t += B=A
end
open X
let f x = match x with
| A -> '1'
| B -> '2'
| _ -> '_'
The second clause above will NOT (and cannot) be flagged as useless.
Finally, there are two compatibility fonction
compat p q ---> 'syntactic compatibility, used for diagnostics.
may_compat p q ---> a safe approximation of possible compat,
for compilation
*)
let is_absent tag row = Btype.row_field tag !row = Rabsent
let is_absent_pat p = match p.pat_desc with
| Tpat_variant (tag, _, row) -> is_absent tag row
| _ -> false
let const_compare x y =
match x,y with
| Const_float f1, Const_float f2 ->
Pervasives.compare (float_of_string f1) (float_of_string f2)
| Const_string (s1, _), Const_string (s2, _) ->
String.compare s1 s2
| _, _ -> Pervasives.compare x y
let records_args l1 l2 =
(* Invariant: fields are already sorted by Typecore.type_label_a_list *)
let rec combine r1 r2 l1 l2 = match l1,l2 with
| [],[] -> List.rev r1, List.rev r2
| [],(_,_,p2)::rem2 -> combine (omega::r1) (p2::r2) [] rem2
| (_,_,p1)::rem1,[] -> combine (p1::r1) (omega::r2) rem1 []
| (_,lbl1,p1)::rem1, ( _,lbl2,p2)::rem2 ->
if lbl1.lbl_pos < lbl2.lbl_pos then
combine (p1::r1) (omega::r2) rem1 l2
else if lbl1.lbl_pos > lbl2.lbl_pos then
combine (omega::r1) (p2::r2) l1 rem2
else (* same label on both sides *)
combine (p1::r1) (p2::r2) rem1 rem2 in
combine [] [] l1 l2
module Compat
(Constr:sig
val equal :
Types.constructor_description ->
Types.constructor_description ->
bool
end) = struct
let rec compat p q = match p.pat_desc,q.pat_desc with
(* Variables match any value *)
| ((Tpat_any|Tpat_var _),_)
| (_,(Tpat_any|Tpat_var _)) -> true
(* Structural induction *)
| Tpat_alias (p,_,_),_ -> compat p q
| _,Tpat_alias (q,_,_) -> compat p q
| Tpat_or (p1,p2,_),_ ->
(compat p1 q || compat p2 q)
| _,Tpat_or (q1,q2,_) ->
(compat p q1 || compat p q2)
(* Constructors, with special case for extension *)
| Tpat_construct (_, c1,ps1), Tpat_construct (_, c2,ps2) ->
Constr.equal c1 c2 && compats ps1 ps2
(* More standard stuff *)
| Tpat_variant(l1,op1, _), Tpat_variant(l2,op2,_) ->
l1=l2 && ocompat op1 op2
| Tpat_constant c1, Tpat_constant c2 ->
const_compare c1 c2 = 0
| Tpat_tuple ps, Tpat_tuple qs -> compats ps qs
| Tpat_lazy p, Tpat_lazy q -> compat p q
| Tpat_record (l1,_),Tpat_record (l2,_) ->
let ps,qs = records_args l1 l2 in
compats ps qs
| Tpat_array ps, Tpat_array qs ->
List.length ps = List.length qs &&
compats ps qs
| _,_ -> false
and ocompat op oq = match op,oq with
| None,None -> true
| Some p,Some q -> compat p q
| (None,Some _)|(Some _,None) -> false
and compats ps qs = match ps,qs with
| [], [] -> true
| p::ps, q::qs -> compat p q && compats ps qs
| _,_ -> false
end
module SyntacticCompat =
Compat
(struct
let equal c1 c2 = Types.equal_tag c1.cstr_tag c2.cstr_tag
end)
let compat = SyntacticCompat.compat
and compats = SyntacticCompat.compats
(* Due to (potential) rebinding, two extension constructors
of the same arity type may equal *)
exception Empty (* Empty pattern *)
(****************************************)
(* Utilities for retrieving type paths *)
(****************************************)
(* May need a clean copy, cf. PR#4745 *)
let clean_copy ty =
if ty.level = Btype.generic_level then ty
else Subst.type_expr Subst.identity ty
let get_type_path ty tenv =
let ty = Ctype.repr (Ctype.expand_head tenv (clean_copy ty)) in
match ty.desc with
| Tconstr (path,_,_) -> path
| _ -> fatal_error "Parmatch.get_type_path"
(*************************************)
(* Values as patterns pretty printer *)
(*************************************)
open Format
;;
let is_cons = function
| {cstr_name = "::"} -> true
| _ -> false
let pretty_const c = match c with
| Const_int i -> Printf.sprintf "%d" i
| Const_char c -> Printf.sprintf "%C" c
| Const_string (s, _) -> Printf.sprintf "%S" s
| Const_float f -> Printf.sprintf "%s" f
| Const_int32 i -> Printf.sprintf "%ldl" i
| Const_int64 i -> Printf.sprintf "%LdL" i
| Const_nativeint i -> Printf.sprintf "%ndn" i
let rec pretty_val ppf v =
match v.pat_extra with
(cstr, _loc, _attrs) :: rem ->
begin match cstr with
| Tpat_unpack ->
fprintf ppf "@[(module %a)@]" pretty_val { v with pat_extra = rem }
| Tpat_constraint _ ->
fprintf ppf "@[(%a : _)@]" pretty_val { v with pat_extra = rem }
| Tpat_type _ ->
fprintf ppf "@[(# %a)@]" pretty_val { v with pat_extra = rem }
| Tpat_open _ ->
fprintf ppf "@[(# %a)@]" pretty_val { v with pat_extra = rem }
end
| [] ->
match v.pat_desc with
| Tpat_any -> fprintf ppf "_"
| Tpat_var (x,_) -> fprintf ppf "%s" (Ident.name x)
| Tpat_constant c -> fprintf ppf "%s" (pretty_const c)
| Tpat_tuple vs ->
fprintf ppf "@[(%a)@]" (pretty_vals ",") vs
| Tpat_construct (_, cstr, []) ->
fprintf ppf "%s" cstr.cstr_name
| Tpat_construct (_, cstr, [w]) ->
fprintf ppf "@[<2>%s@ %a@]" cstr.cstr_name pretty_arg w
| Tpat_construct (_, cstr, vs) ->
let name = cstr.cstr_name in
begin match (name, vs) with
("::", [v1;v2]) ->
fprintf ppf "@[%a::@,%a@]" pretty_car v1 pretty_cdr v2
| _ ->
fprintf ppf "@[<2>%s@ @[(%a)@]@]" name (pretty_vals ",") vs
end
| Tpat_variant (l, None, _) ->
fprintf ppf "`%s" l
| Tpat_variant (l, Some w, _) ->
fprintf ppf "@[<2>`%s@ %a@]" l pretty_arg w
| Tpat_record (lvs,_) ->
let filtered_lvs = Ext_list.filter lvs
(function
| (_,_,{pat_desc=Tpat_any}) -> false (* do not show lbl=_ *)
| _ -> true) in
begin match filtered_lvs with
| [] -> fprintf ppf "_"
| (_, lbl, _) :: q ->
let elision_mark ppf =
(* we assume that there is no label repetitions here *)
if Array.length lbl.lbl_all > 1 + List.length q then
fprintf ppf ";@ _@ "
else () in
fprintf ppf "@[{%a%t}@]"
pretty_lvals filtered_lvs elision_mark
end
| Tpat_array vs ->
fprintf ppf "@[[| %a |]@]" (pretty_vals " ;") vs
| Tpat_lazy v ->
fprintf ppf "@[<2>lazy@ %a@]" pretty_arg v
| Tpat_alias (v, x,_) ->
fprintf ppf "@[(%a@ as %a)@]" pretty_val v Ident.print x
| Tpat_or (v,w,_) ->
fprintf ppf "@[(%a|@,%a)@]" pretty_or v pretty_or w
and pretty_car ppf v = match v.pat_desc with
| Tpat_construct (_,cstr, [_ ; _])
when is_cons cstr ->
fprintf ppf "(%a)" pretty_val v
| _ -> pretty_val ppf v
and pretty_cdr ppf v = match v.pat_desc with
| Tpat_construct (_,cstr, [v1 ; v2])
when is_cons cstr ->
fprintf ppf "%a::@,%a" pretty_car v1 pretty_cdr v2
| _ -> pretty_val ppf v
and pretty_arg ppf v = match v.pat_desc with
| Tpat_construct (_,_,_::_)
| Tpat_variant (_, Some _, _) -> fprintf ppf "(%a)" pretty_val v
| _ -> pretty_val ppf v
and pretty_or ppf v = match v.pat_desc with
| Tpat_or (v,w,_) ->
fprintf ppf "%a|@,%a" pretty_or v pretty_or w
| _ -> pretty_val ppf v
and pretty_vals sep ppf = function
| [] -> ()
| [v] -> pretty_val ppf v
| v::vs ->
fprintf ppf "%a%s@ %a" pretty_val v sep (pretty_vals sep) vs
and pretty_lvals ppf = function
| [] -> ()
| [_,lbl,v] ->
fprintf ppf "%s=%a" lbl.lbl_name pretty_val v
| (_, lbl,v)::rest ->
fprintf ppf "%s=%a;@ %a"
lbl.lbl_name pretty_val v pretty_lvals rest
let top_pretty ppf v =
fprintf ppf "@[%a@]@?" pretty_val v
let pretty_pat p =
top_pretty Format.str_formatter p ;
prerr_string (Format.flush_str_formatter ())
type matrix = pattern list list
let pretty_line ps =
List.iter
(fun p ->
top_pretty Format.str_formatter p ;
prerr_string " <" ;
prerr_string (Format.flush_str_formatter ()) ;
prerr_string ">")
ps
let pretty_matrix (pss : matrix) =
prerr_endline "begin matrix" ;
List.iter
(fun ps ->
pretty_line ps ;
prerr_endline "")
pss ;
prerr_endline "end matrix"
(****************************)
(* Utilities for matching *)
(****************************)
(* Check top matching *)
let simple_match p1 p2 =
match p1.pat_desc, p2.pat_desc with
| Tpat_construct(_, c1, _), Tpat_construct(_, c2, _) ->
Types.equal_tag c1.cstr_tag c2.cstr_tag
| Tpat_variant(l1, _, _), Tpat_variant(l2, _, _) ->
l1 = l2
| Tpat_constant(c1), Tpat_constant(c2) -> const_compare c1 c2 = 0
| Tpat_lazy _, Tpat_lazy _ -> true
| Tpat_record _ , Tpat_record _ -> true
| Tpat_tuple p1s, Tpat_tuple p2s
| Tpat_array p1s, Tpat_array p2s -> List.length p1s = List.length p2s
| _, (Tpat_any | Tpat_var(_)) -> true
| _, _ -> false
(* extract record fields as a whole *)
let record_arg p = match p.pat_desc with
| Tpat_any -> []
| Tpat_record (args,_) -> args
| _ -> fatal_error "Parmatch.as_record"
(* Raise Not_found when pos is not present in arg *)
let get_field pos arg =
let _,_, p = List.find (fun (_,lbl,_) -> pos = lbl.lbl_pos) arg in
p
let extract_fields omegas arg =
List.map
(fun (_,lbl,_) ->
try
get_field lbl.lbl_pos arg
with Not_found -> omega)
omegas
let all_record_args lbls = match lbls with
| (_,{lbl_all=lbl_all},_)::_ ->
let t =
Array.map
(fun lbl -> mknoloc (Longident.Lident "?temp?"), lbl,omega)
lbl_all in
List.iter
(fun ((_, lbl,_) as x) -> t.(lbl.lbl_pos) <- x)
lbls ;
Array.to_list t
| _ -> fatal_error "Parmatch.all_record_args"
(* Build argument list when p2 >= p1, where p1 is a simple pattern *)
let rec simple_match_args p1 p2 = match p2.pat_desc with
| Tpat_alias (p2,_,_) -> simple_match_args p1 p2
| Tpat_construct(_, _, args) -> args
| Tpat_variant(_, Some arg, _) -> [arg]
| Tpat_tuple(args) -> args
| Tpat_record(args,_) -> extract_fields (record_arg p1) args
| Tpat_array(args) -> args
| Tpat_lazy arg -> [arg]
| (Tpat_any | Tpat_var(_)) ->
begin match p1.pat_desc with
Tpat_construct(_, _,args) -> omega_list args
| Tpat_variant(_, Some _, _) -> [omega]
| Tpat_tuple(args) -> omega_list args
| Tpat_record(args,_) -> omega_list args
| Tpat_array(args) -> omega_list args
| Tpat_lazy _ -> [omega]
| _ -> []
end
| _ -> []
(*
Normalize a pattern ->
all arguments are omega (simple pattern) and no more variables
*)
let rec normalize_pat q = match q.pat_desc with
| Tpat_any | Tpat_constant _ -> q
| Tpat_var _ -> make_pat Tpat_any q.pat_type q.pat_env
| Tpat_alias (p,_,_) -> normalize_pat p
| Tpat_tuple (args) ->
make_pat (Tpat_tuple (omega_list args)) q.pat_type q.pat_env
| Tpat_construct (lid, c,args) ->
make_pat
(Tpat_construct (lid, c,omega_list args))
q.pat_type q.pat_env
| Tpat_variant (l, arg, row) ->
make_pat (Tpat_variant (l, may_map (fun _ -> omega) arg, row))
q.pat_type q.pat_env
| Tpat_array (args) ->
make_pat (Tpat_array (omega_list args)) q.pat_type q.pat_env
| Tpat_record (largs, closed) ->
make_pat
(Tpat_record (List.map (fun (lid,lbl,_) ->
lid, lbl,omega) largs, closed))
q.pat_type q.pat_env
| Tpat_lazy _ ->
make_pat (Tpat_lazy omega) q.pat_type q.pat_env
| Tpat_or _ -> fatal_error "Parmatch.normalize_pat"
(*
Build normalized (cf. supra) discriminating pattern,
in the non-data type case
*)
let discr_pat q pss =
let rec acc_pat acc pss = match pss with
({pat_desc = Tpat_alias (p,_,_)}::ps)::pss ->
acc_pat acc ((p::ps)::pss)
| ({pat_desc = Tpat_or (p1,p2,_)}::ps)::pss ->
acc_pat acc ((p1::ps)::(p2::ps)::pss)
| ({pat_desc = (Tpat_any | Tpat_var _)}::_)::pss ->
acc_pat acc pss
| (({pat_desc = Tpat_tuple _} as p)::_)::_ -> normalize_pat p
| (({pat_desc = Tpat_lazy _} as p)::_)::_ -> normalize_pat p
| (({pat_desc = Tpat_record (largs,closed)} as p)::_)::pss ->
let new_omegas =
List.fold_right
(fun (lid, lbl,_) r ->
try
let _ = get_field lbl.lbl_pos r in
r
with Not_found ->
(lid, lbl,omega)::r)
largs (record_arg acc)
in
acc_pat
(make_pat (Tpat_record (new_omegas, closed)) p.pat_type p.pat_env)
pss
| _ -> acc in
match normalize_pat q with
| {pat_desc= (Tpat_any | Tpat_record _)} as q -> acc_pat q pss
| q -> q
(*
In case a matching value is found, set actual arguments
of the matching pattern.
*)
let rec read_args xs r = match xs,r with
| [],_ -> [],r
| _::xs, arg::rest ->
let args,rest = read_args xs rest in
arg::args,rest
| _,_ ->
fatal_error "Parmatch.read_args"
let do_set_args erase_mutable q r = match q with
| {pat_desc = Tpat_tuple omegas} ->
let args,rest = read_args omegas r in
make_pat (Tpat_tuple args) q.pat_type q.pat_env::rest
| {pat_desc = Tpat_record (omegas,closed)} ->
let args,rest = read_args omegas r in
make_pat
(Tpat_record
(List.map2 (fun (lid, lbl,_) arg ->
if
erase_mutable &&
(match lbl.lbl_mut with
| Mutable -> true | Immutable -> false)
then
lid, lbl, omega
else
lid, lbl, arg)
omegas args, closed))
q.pat_type q.pat_env::
rest
| {pat_desc = Tpat_construct (lid, c,omegas)} ->
let args,rest = read_args omegas r in
make_pat
(Tpat_construct (lid, c,args))
q.pat_type q.pat_env::
rest
| {pat_desc = Tpat_variant (l, omega, row)} ->
let arg, rest =
match omega, r with
Some _, a::r -> Some a, r
| None, r -> None, r
| _ -> assert false
in
make_pat
(Tpat_variant (l, arg, row)) q.pat_type q.pat_env::
rest
| {pat_desc = Tpat_lazy _omega} ->
begin match r with
arg::rest ->
make_pat (Tpat_lazy arg) q.pat_type q.pat_env::rest
| _ -> fatal_error "Parmatch.do_set_args (lazy)"
end
| {pat_desc = Tpat_array omegas} ->
let args,rest = read_args omegas r in
make_pat
(Tpat_array args) q.pat_type q.pat_env::
rest
| {pat_desc=Tpat_constant _|Tpat_any} ->
q::r (* case any is used in matching.ml *)
| _ -> fatal_error "Parmatch.set_args"
let set_args q r = do_set_args false q r
and set_args_erase_mutable q r = do_set_args true q r
(* filter pss according to pattern q *)
let filter_one q pss =
let rec filter_rec = function
({pat_desc = Tpat_alias(p,_,_)}::ps)::pss ->
filter_rec ((p::ps)::pss)
| ({pat_desc = Tpat_or(p1,p2,_)}::ps)::pss ->
filter_rec ((p1::ps)::(p2::ps)::pss)
| (p::ps)::pss ->
if simple_match q p
then (simple_match_args q p @ ps) :: filter_rec pss
else filter_rec pss
| _ -> [] in
filter_rec pss
(*
Filter pss in the ``extra case''. This applies :
- According to an extra constructor (datatype case, non-complete signature).
- According to anything (all-variables case).
*)
let filter_extra pss =
let rec filter_rec = function
({pat_desc = Tpat_alias(p,_,_)}::ps)::pss ->
filter_rec ((p::ps)::pss)
| ({pat_desc = Tpat_or(p1,p2,_)}::ps)::pss ->
filter_rec ((p1::ps)::(p2::ps)::pss)
| ({pat_desc = (Tpat_any | Tpat_var(_))} :: qs) :: pss ->
qs :: filter_rec pss
| _::pss -> filter_rec pss
| [] -> [] in
filter_rec pss
(*
Pattern p0 is the discriminating pattern,
returns [(q0,pss0) ; ... ; (qn,pssn)]
where the qi's are simple patterns and the pssi's are
matched matrices.
NOTES
* (qi,[]) is impossible.
* In the case when matching is useless (all-variable case),
returns []
*)
let filter_all pat0 pss =
let rec insert q qs env =
match env with
[] ->
let q0 = normalize_pat q in
[q0, [simple_match_args q0 q @ qs]]
| ((q0,pss) as c)::env ->
if simple_match q0 q
then (q0, ((simple_match_args q0 q @ qs) :: pss)) :: env
else c :: insert q qs env in
let rec filter_rec env = function
({pat_desc = Tpat_alias(p,_,_)}::ps)::pss ->
filter_rec env ((p::ps)::pss)
| ({pat_desc = Tpat_or(p1,p2,_)}::ps)::pss ->
filter_rec env ((p1::ps)::(p2::ps)::pss)
| ({pat_desc = (Tpat_any | Tpat_var(_))}::_)::pss ->
filter_rec env pss
| (p::ps)::pss ->
filter_rec (insert p ps env) pss
| _ -> env
and filter_omega env = function
({pat_desc = Tpat_alias(p,_,_)}::ps)::pss ->
filter_omega env ((p::ps)::pss)
| ({pat_desc = Tpat_or(p1,p2,_)}::ps)::pss ->
filter_omega env ((p1::ps)::(p2::ps)::pss)
| ({pat_desc = (Tpat_any | Tpat_var(_))}::ps)::pss ->
filter_omega
(List.map (fun (q,qss) -> (q,(simple_match_args q omega @ ps) :: qss))
env)
pss
| _::pss -> filter_omega env pss
| [] -> env in
filter_omega
(filter_rec
(match pat0.pat_desc with
(Tpat_record(_) | Tpat_tuple(_) | Tpat_lazy(_)) -> [pat0,[]]
| _ -> [])
pss)
pss
(* Variant related functions *)
let rec set_last a = function
[] -> []
| [_] -> [a]
| x::l -> x :: set_last a l
(* mark constructor lines for failure when they are incomplete *)
let rec mark_partial = function
({pat_desc = Tpat_alias(p,_,_)}::ps)::pss ->
mark_partial ((p::ps)::pss)
| ({pat_desc = Tpat_or(p1,p2,_)}::ps)::pss ->
mark_partial ((p1::ps)::(p2::ps)::pss)
| ({pat_desc = (Tpat_any | Tpat_var(_))} :: _ as ps) :: pss ->
ps :: mark_partial pss
| ps::pss ->
(set_last zero ps) :: mark_partial pss
| [] -> []
let close_variant env row =
let row = Btype.row_repr row in
let nm =
List.fold_left
(fun nm (_tag,f) ->
match Btype.row_field_repr f with
| Reither(_, _, false, e) ->
(* m=false means that this tag is not explicitly matched *)
Btype.set_row_field e Rabsent;
None
| Rabsent | Reither (_, _, true, _) | Rpresent _ -> nm)
row.row_name row.row_fields in
if not row.row_closed || nm != row.row_name then begin
(* this unification cannot fail *)
Ctype.unify env row.row_more
(Btype.newgenty
(Tvariant {row with row_fields = []; row_more = Btype.newgenvar();
row_closed = true; row_name = nm}))
end
let row_of_pat pat =
match Ctype.expand_head pat.pat_env pat.pat_type with
{desc = Tvariant row} -> Btype.row_repr row
| _ -> assert false
(*
Check whether the first column of env makes up a complete signature or
not.
*)
let full_match closing env = match env with
| ({pat_desc = Tpat_construct(_,c,_)},_) :: _ ->
if c.cstr_consts < 0 then false (* extensions *)
else List.length env = c.cstr_consts + c.cstr_nonconsts
| ({pat_desc = Tpat_variant _} as p,_) :: _ ->
let fields =
List.map
(function ({pat_desc = Tpat_variant (tag, _, _)}, _) -> tag
| _ -> assert false)
env
in
let row = row_of_pat p in
if closing && not (Btype.row_fixed row) then
(* closing=true, we are considering the variant as closed *)
List.for_all
(fun (tag,f) ->
match Btype.row_field_repr f with
Rabsent | Reither(_, _, false, _) -> true
| Reither (_, _, true, _)
(* m=true, do not discard matched tags, rather warn *)
| Rpresent _ -> List.mem tag fields)
row.row_fields
else
row.row_closed &&
List.for_all
(fun (tag,f) ->
Btype.row_field_repr f = Rabsent || List.mem tag fields)
row.row_fields
| ({pat_desc = Tpat_constant(_)},_) :: _ -> false
| ({pat_desc = Tpat_tuple(_)},_) :: _ -> true
| ({pat_desc = Tpat_record(_)},_) :: _ -> true
| ({pat_desc = Tpat_array(_)},_) :: _ -> false
| ({pat_desc = Tpat_lazy(_)},_) :: _ -> true
| ({pat_desc = (Tpat_any|Tpat_var _|Tpat_alias _|Tpat_or _)},_) :: _
| []
->
assert false
(* Written as a non-fragile matching, PR#7451 originated from a fragile matching below. *)
let should_extend ext env = match ext with
| None -> false
| Some ext -> begin match env with
| [] -> assert false
| (p,_)::_ ->
begin match p.pat_desc with
| Tpat_construct
(_, {cstr_tag=(Cstr_constant _|Cstr_block _|Cstr_unboxed)},_) ->
let path = get_type_path p.pat_type p.pat_env in
Path.same path ext
| Tpat_construct
(_, {cstr_tag=(Cstr_extension _)},_) -> false
| Tpat_constant _|Tpat_tuple _|Tpat_variant _
| Tpat_record _|Tpat_array _ | Tpat_lazy _
-> false
| Tpat_any|Tpat_var _|Tpat_alias _|Tpat_or _
-> assert false
end
end
module ConstructorTagHashtbl = Hashtbl.Make(
struct
type t = Types.constructor_tag
let hash = Hashtbl.hash
let equal = Types.equal_tag
end
)
(* complement constructor tags *)
let complete_tags nconsts nconstrs tags =
let seen_const = Array.make nconsts false
and seen_constr = Array.make nconstrs false in
List.iter
(function
| Cstr_constant i -> seen_const.(i) <- true
| Cstr_block i -> seen_constr.(i) <- true
| _ -> assert false)
tags ;
let r = ConstructorTagHashtbl.create (nconsts+nconstrs) in
for i = 0 to nconsts-1 do
if not seen_const.(i) then
ConstructorTagHashtbl.add r (Cstr_constant i) ()
done ;
for i = 0 to nconstrs-1 do
if not seen_constr.(i) then
ConstructorTagHashtbl.add r (Cstr_block i) ()
done ;
r
(* build a pattern from a constructor list *)
let pat_of_constr ex_pat cstr =
{ex_pat with pat_desc =
Tpat_construct (mknoloc (Longident.Lident "?pat_of_constr?"),
cstr, omegas cstr.cstr_arity)}
let orify x y = make_pat (Tpat_or (x, y, None)) x.pat_type x.pat_env
let rec orify_many = function
| [] -> assert false
| [x] -> x
| x :: xs -> orify x (orify_many xs)
let pat_of_constrs ex_pat cstrs =
if cstrs = [] then raise Empty else
orify_many (List.map (pat_of_constr ex_pat) cstrs)
let pats_of_type ?(always=false) env ty =
let ty' = Ctype.expand_head env ty in
match ty'.desc with
| Tconstr (path, _, _) ->
begin try match (Env.find_type path env).type_kind with
| Type_variant cl when always || List.length cl = 1 ||
List.for_all (fun cd -> cd.Types.cd_res <> None) cl ->
let cstrs = fst (Env.find_type_descrs path env) in
List.map (pat_of_constr (make_pat Tpat_any ty env)) cstrs
| Type_record _ ->
let labels = snd (Env.find_type_descrs path env) in
let fields =
List.map (fun ld ->
mknoloc (Longident.Lident "?pat_of_label?"), ld, omega)
labels
in
[make_pat (Tpat_record (fields, Closed)) ty env]
| _ -> [omega]
with Not_found -> [omega]
end
| Ttuple tl ->
[make_pat (Tpat_tuple (omegas (List.length tl))) ty env]
| _ -> [omega]
let rec get_variant_constructors env ty =
match (Ctype.repr ty).desc with
| Tconstr (path,_,_) -> begin
try match Env.find_type path env with
| {type_kind=Type_variant _} ->
fst (Env.find_type_descrs path env)
| {type_manifest = Some _} ->
get_variant_constructors env
(Ctype.expand_head_once env (clean_copy ty))
| _ -> fatal_error "Parmatch.get_variant_constructors"
with Not_found ->
fatal_error "Parmatch.get_variant_constructors"
end
| _ -> fatal_error "Parmatch.get_variant_constructors"
(* Sends back a pattern that complements constructor tags all_tag *)