forked from ocaml/ocaml
-
Notifications
You must be signed in to change notification settings - Fork 0
/
Copy pathmatching.ml
3240 lines (2790 loc) · 99.6 KB
/
matching.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. *)
(* *)
(**************************************************************************)
(* Compilation of pattern matching *)
open Misc
open Asttypes
open Types
open Typedtree
open Lambda
open Parmatch
open Printf
open Printpat
let dbg = false
(* See Peyton-Jones, ``The Implementation of functional programming
languages'', chapter 5. *)
(*
Well, it was true at the beginning of the world.
Now, see Lefessant-Maranget ``Optimizing Pattern-Matching'' ICFP'2001
*)
(*
Compatibility predicate that considers potential rebindings of constructors
of an extension type.
"may_compat p q" returns false when p and q never admit a common instance;
returns true when they may have a common instance.
*)
module MayCompat =
Parmatch.Compat (struct let equal = Types.may_equal_constr end)
let may_compat = MayCompat.compat
and may_compats = MayCompat.compats
(*
Many functions on the various data structures of the algorithm :
- Pattern matrices.
- Default environments: mapping from matrices to exit numbers.
- Contexts: matrices whose column are partitioned into
left and right.
- Jump summaries: mapping from exit numbers to contexts
*)
let string_of_lam lam =
Printlambda.lambda Format.str_formatter lam ;
Format.flush_str_formatter ()
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"
type matrix = pattern list list
let add_omega_column pss = List.map (fun ps -> omega::ps) pss
type ctx = {left:pattern list ; right:pattern list}
let pretty_ctx ctx =
List.iter
(fun {left=left ; right=right} ->
Format.eprintf "LEFT:%a RIGHT:%a\n" pretty_line left pretty_line right)
ctx
let le_ctx c1 c2 =
le_pats c1.left c2.left &&
le_pats c1.right c2.right
let lshift {left=left ; right=right} = match right with
| x::xs -> {left=x::left ; right=xs}
| _ -> assert false
let lforget {left=left ; right=right} = match right with
| _::xs -> {left=omega::left ; right=xs}
| _ -> assert false
let rec small_enough n = function
| [] -> true
| _::rem ->
if n <= 0 then false
else small_enough (n-1) rem
let ctx_lshift ctx =
if small_enough (!Clflags.match_context_rows - 1) ctx then
List.map lshift ctx
else (* Context pruning *) begin
get_mins le_ctx (List.map lforget ctx)
end
let rshift {left=left ; right=right} = match left with
| p::ps -> {left=ps ; right=p::right}
| _ -> assert false
let ctx_rshift ctx = List.map rshift ctx
let rec nchars n ps =
if n <= 0 then [],ps
else match ps with
| p::rem ->
let chars, cdrs = nchars (n-1) rem in
p::chars,cdrs
| _ -> assert false
let rshift_num n {left=left ; right=right} =
let shifted,left = nchars n left in
{left=left ; right = shifted@right}
let ctx_rshift_num n ctx = List.map (rshift_num n) ctx
(* Recombination of contexts (eg: (_,_)::p1::p2::rem -> (p1,p2)::rem)
All mutable fields are replaced by '_', since side-effects in
guards can alter these fields *)
let combine {left=left ; right=right} = match left with
| p::ps -> {left=ps ; right=set_args_erase_mutable p right}
| _ -> assert false
let ctx_combine ctx = List.map combine ctx
let ncols = function
| [] -> 0
| ps::_ -> List.length ps
exception NoMatch
exception OrPat
let filter_matrix matcher pss =
let rec filter_rec = function
| (p::ps)::rem ->
begin match p.pat_desc with
| Tpat_alias (p,_,_) ->
filter_rec ((p::ps)::rem)
| Tpat_var _ ->
filter_rec ((omega::ps)::rem)
| _ ->
begin
let rem = filter_rec rem in
try
matcher p ps::rem
with
| NoMatch -> rem
| OrPat ->
match p.pat_desc with
| Tpat_or (p1,p2,_) -> filter_rec [(p1::ps) ;(p2::ps)]@rem
| _ -> assert false
end
end
| [] -> []
| _ ->
pretty_matrix Format.err_formatter pss ;
fatal_error "Matching.filter_matrix" in
filter_rec pss
let make_default matcher env =
let rec make_rec = function
| [] -> []
| ([[]],i)::_ -> [[[]],i]
| (pss,i)::rem ->
let rem = make_rec rem in
match filter_matrix matcher pss with
| [] -> rem
| ([]::_) -> ([[]],i)::rem
| pss -> (pss,i)::rem in
make_rec env
let ctx_matcher p =
let p = normalize_pat p in
match p.pat_desc with
| Tpat_construct (_, cstr,omegas) ->
(fun q rem -> match q.pat_desc with
| Tpat_construct (_, cstr',args)
(* NB: may_constr_equal considers (potential) constructor rebinding *)
when Types.may_equal_constr cstr cstr' ->
p,args@rem
| Tpat_any -> p,omegas @ rem
| _ -> raise NoMatch)
| Tpat_constant cst ->
(fun q rem -> match q.pat_desc with
| Tpat_constant cst' when const_compare cst cst' = 0 ->
p,rem
| Tpat_any -> p,rem
| _ -> raise NoMatch)
| Tpat_variant (lab,Some omega,_) ->
(fun q rem -> match q.pat_desc with
| Tpat_variant (lab',Some arg,_) when lab=lab' ->
p,arg::rem
| Tpat_any -> p,omega::rem
| _ -> raise NoMatch)
| Tpat_variant (lab,None,_) ->
(fun q rem -> match q.pat_desc with
| Tpat_variant (lab',None,_) when lab=lab' ->
p,rem
| Tpat_any -> p,rem
| _ -> raise NoMatch)
| Tpat_array omegas ->
let len = List.length omegas in
(fun q rem -> match q.pat_desc with
| Tpat_array args when List.length args = len -> p,args @ rem
| Tpat_any -> p, omegas @ rem
| _ -> raise NoMatch)
| Tpat_tuple omegas ->
let len = List.length omegas in
(fun q rem -> match q.pat_desc with
| Tpat_tuple args when List.length args = len -> p,args @ rem
| Tpat_any -> p, omegas @ rem
| _ -> raise NoMatch)
| Tpat_record (((_, lbl, _) :: _) as l,_) -> (* Records are normalized *)
let len = Array.length lbl.lbl_all in
(fun q rem -> match q.pat_desc with
| Tpat_record (((_, lbl', _) :: _) as l',_)
when Array.length lbl'.lbl_all = len ->
let l' = all_record_args l' in
p, List.fold_right (fun (_, _,p) r -> p::r) l' rem
| Tpat_any -> p,List.fold_right (fun (_, _,p) r -> p::r) l rem
| _ -> raise NoMatch)
| Tpat_lazy omega ->
(fun q rem -> match q.pat_desc with
| Tpat_lazy arg -> p, (arg::rem)
| Tpat_any -> p, (omega::rem)
| _ -> raise NoMatch)
| _ -> fatal_error "Matching.ctx_matcher"
let filter_ctx q ctx =
let matcher = ctx_matcher q in
let rec filter_rec = function
| ({right=p::ps} as l)::rem ->
begin match p.pat_desc with
| Tpat_or (p1,p2,_) ->
filter_rec ({l with right=p1::ps}::{l with right=p2::ps}::rem)
| Tpat_alias (p,_,_) ->
filter_rec ({l with right=p::ps}::rem)
| Tpat_var _ ->
filter_rec ({l with right=omega::ps}::rem)
| _ ->
begin let rem = filter_rec rem in
try
let to_left, right = matcher p ps in
{left=to_left::l.left ; right=right}::rem
with
| NoMatch -> rem
end
end
| [] -> []
| _ -> fatal_error "Matching.filter_ctx" in
filter_rec ctx
let select_columns pss ctx =
let n = ncols pss in
List.fold_right
(fun ps r ->
List.fold_right
(fun {left=left ; right=right} r ->
let transfert, right = nchars n right in
try
{left = lubs transfert ps @ left ; right=right}::r
with
| Empty -> r)
ctx r)
pss []
let ctx_lub p ctx =
List.fold_right
(fun {left=left ; right=right} r ->
match right with
| q::rem ->
begin try
{left=left ; right = lub p q::rem}::r
with
| Empty -> r
end
| _ -> fatal_error "Matching.ctx_lub")
ctx []
let ctx_match ctx pss =
List.exists
(fun {right=qs} -> List.exists (fun ps -> may_compats qs ps) pss)
ctx
type jumps = (int * ctx list) list
let pretty_jumps (env : jumps) = match env with
| [] -> ()
| _ ->
List.iter
(fun (i,ctx) ->
Printf.fprintf stderr "jump for %d\n" i ;
pretty_ctx ctx)
env
let rec jumps_extract i = function
| [] -> [],[]
| (j,pss) as x::rem as all ->
if i=j then pss,rem
else if j < i then [],all
else
let r,rem = jumps_extract i rem in
r,(x::rem)
let rec jumps_remove i = function
| [] -> []
| (j,_)::rem when i=j -> rem
| x::rem -> x::jumps_remove i rem
let jumps_empty = []
and jumps_is_empty = function
| [] -> true
| _ -> false
let jumps_singleton i = function
| [] -> []
| ctx -> [i,ctx]
let jumps_add i pss jumps = match pss with
| [] -> jumps
| _ ->
let rec add = function
| [] -> [i,pss]
| (j,qss) as x::rem as all ->
if j > i then x::add rem
else if j < i then (i,pss)::all
else (i,(get_mins le_ctx (pss@qss)))::rem in
add jumps
let rec jumps_union (env1:(int*ctx list)list) env2 = match env1,env2 with
| [],_ -> env2
| _,[] -> env1
| ((i1,pss1) as x1::rem1), ((i2,pss2) as x2::rem2) ->
if i1=i2 then
(i1,get_mins le_ctx (pss1@pss2))::jumps_union rem1 rem2
else if i1 > i2 then
x1::jumps_union rem1 env2
else
x2::jumps_union env1 rem2
let rec merge = function
| env1::env2::rem -> jumps_union env1 env2::merge rem
| envs -> envs
let rec jumps_unions envs = match envs with
| [] -> []
| [env] -> env
| _ -> jumps_unions (merge envs)
let jumps_map f env =
List.map
(fun (i,pss) -> i,f pss)
env
(* Pattern matching before any compilation *)
type pattern_matching =
{ mutable cases : (pattern list * lambda) list;
args : (lambda * let_kind) list ;
default : (matrix * int) list}
(* Pattern matching after application of both the or-pat rule and the
mixture rule *)
type pm_or_compiled =
{body : pattern_matching ;
handlers :
(matrix * int * (Ident.t * Lambda.value_kind) list * pattern_matching)
list;
or_matrix : matrix ; }
type pm_half_compiled =
| PmOr of pm_or_compiled
| PmVar of pm_var_compiled
| Pm of pattern_matching
and pm_var_compiled =
{inside : pm_half_compiled ; var_arg : lambda ; }
type pm_half_compiled_info =
{me : pm_half_compiled ;
matrix : matrix ;
top_default : (matrix * int) list ; }
let pretty_cases cases =
List.iter
(fun (ps,_l) ->
List.iter
(fun p -> Format.eprintf " %a%!" top_pretty p)
ps ;
Format.eprintf "\n")
cases
let pretty_def def =
Format.eprintf "+++++ Defaults +++++\n" ;
List.iter
(fun (pss,i) -> Format.eprintf "Matrix for %d\n%a" i pretty_matrix pss)
def ;
Format.eprintf "+++++++++++++++++++++\n"
let pretty_pm pm =
pretty_cases pm.cases ;
if pm.default <> [] then
pretty_def pm.default
let rec pretty_precompiled = function
| Pm pm ->
Format.eprintf "++++ PM ++++\n" ;
pretty_pm pm
| PmVar x ->
Format.eprintf "++++ VAR ++++\n" ;
pretty_precompiled x.inside
| PmOr x ->
Format.eprintf "++++ OR ++++\n" ;
pretty_pm x.body ;
pretty_matrix Format.err_formatter x.or_matrix ;
List.iter
(fun (_,i,_,pm) ->
eprintf "++ Handler %d ++\n" i ;
pretty_pm pm)
x.handlers
let pretty_precompiled_res first nexts =
pretty_precompiled first ;
List.iter
(fun (e, pmh) ->
eprintf "** DEFAULT %d **\n" e ;
pretty_precompiled pmh)
nexts
(* Identifying some semantically equivalent lambda-expressions,
Our goal here is also to
find alpha-equivalent (simple) terms *)
(* However, as shown by PR#6359 such sharing may hinders the
lambda-code invariant that all bound idents are unique,
when switches are compiled to test sequences.
The definitive fix is the systematic introduction of exit/catch
in case action sharing is present.
*)
module StoreExp =
Switch.Store
(struct
type t = lambda
type key = lambda
let compare_key = Stdlib.compare
let make_key = Lambda.make_key
end)
let make_exit i = Lstaticraise (i,[])
(* Introduce a catch, if worth it *)
let make_catch d k = match d with
| Lstaticraise (_,[]) -> k d
| _ ->
let e = next_raise_count () in
Lstaticcatch (k (make_exit e),(e,[]),d)
(* Introduce a catch, if worth it, delayed version *)
let rec as_simple_exit = function
| Lstaticraise (i,[]) -> Some i
| Llet (Alias,_k,_,_,e) -> as_simple_exit e
| _ -> None
let make_catch_delayed handler = match as_simple_exit handler with
| Some i -> i,(fun act -> act)
| None ->
let i = next_raise_count () in
(*
Printf.eprintf "SHARE LAMBDA: %i\n%s\n" i (string_of_lam handler);
*)
i,
(fun body -> match body with
| Lstaticraise (j,_) ->
if i=j then handler else body
| _ -> Lstaticcatch (body,(i,[]),handler))
let raw_action l =
match make_key l with | Some l -> l | None -> l
let tr_raw act = match make_key act with
| Some act -> act
| None -> raise Exit
let same_actions = function
| [] -> None
| [_,act] -> Some act
| (_,act0) :: rem ->
try
let raw_act0 = tr_raw act0 in
let rec s_rec = function
| [] -> Some act0
| (_,act)::rem ->
if raw_act0 = tr_raw act then
s_rec rem
else
None in
s_rec rem
with
| Exit -> None
(* Test for swapping two clauses *)
let up_ok_action act1 act2 =
try
let raw1 = tr_raw act1
and raw2 = tr_raw act2 in
raw1 = raw2
with
| Exit -> false
let up_ok (ps,act_p) l =
List.for_all
(fun (qs,act_q) ->
up_ok_action act_p act_q || not (may_compats ps qs))
l
(*
The simplify function normalizes the first column of the match
- records are expanded so that they possess all fields
- aliases are removed and replaced by bindings in actions.
However or-patterns are simplified differently,
- aliases are not removed
- or-patterns (_|p) are changed into _
*)
exception Var of pattern
let simplify_or p =
let rec simpl_rec p = match p with
| {pat_desc = Tpat_any|Tpat_var _} -> raise (Var p)
| {pat_desc = Tpat_alias (q,id,s)} ->
begin try
{p with pat_desc = Tpat_alias (simpl_rec q,id,s)}
with
| Var q -> raise (Var {p with pat_desc = Tpat_alias (q,id,s)})
end
| {pat_desc = Tpat_or (p1,p2,o)} ->
let q1 = simpl_rec p1 in
begin try
let q2 = simpl_rec p2 in
{p with pat_desc = Tpat_or (q1, q2, o)}
with
| Var q2 -> raise (Var {p with pat_desc = Tpat_or (q1, q2, o)})
end
| {pat_desc = Tpat_record (lbls,closed)} ->
let all_lbls = all_record_args lbls in
{p with pat_desc=Tpat_record (all_lbls, closed)}
| _ -> p in
try
simpl_rec p
with
| Var p -> p
let simplify_cases args cls = match args with
| [] -> assert false
| (arg,_)::_ ->
let rec simplify = function
| [] -> []
| ((pat :: patl, action) as cl) :: rem ->
begin match pat.pat_desc with
| Tpat_var (id, _) ->
let k = Typeopt.value_kind pat.pat_env pat.pat_type in
(omega :: patl, bind_with_value_kind Alias (id, k) arg action) ::
simplify rem
| Tpat_any ->
cl :: simplify rem
| Tpat_alias(p, id,_) ->
let k = Typeopt.value_kind pat.pat_env pat.pat_type in
simplify ((p :: patl,
bind_with_value_kind Alias (id, k) arg action) :: rem)
| Tpat_record ([],_) ->
(omega :: patl, action)::
simplify rem
| Tpat_record (lbls, closed) ->
let all_lbls = all_record_args lbls in
let full_pat =
{pat with pat_desc=Tpat_record (all_lbls, closed)} in
(full_pat::patl,action)::
simplify rem
| Tpat_or _ ->
let pat_simple = simplify_or pat in
begin match pat_simple.pat_desc with
| Tpat_or _ ->
(pat_simple :: patl, action) ::
simplify rem
| _ ->
simplify ((pat_simple::patl,action) :: rem)
end
| _ -> cl :: simplify rem
end
| _ -> assert false in
simplify cls
(* Once matchings are simplified one can easily find
their nature *)
let rec what_is_cases cases = match cases with
| ({pat_desc=Tpat_any} :: _, _) :: rem -> what_is_cases rem
| (({pat_desc=(Tpat_var _|Tpat_or (_,_,_)|Tpat_alias (_,_,_))}::_),_)::_
-> assert false (* applies to simplified matchings only *)
| (p::_,_)::_ -> p
| [] -> omega
| _ -> assert false
(* A few operations on default environments *)
let as_matrix cases = get_mins le_pats (List.map (fun (ps,_) -> ps) cases)
let cons_default matrix raise_num default =
match matrix with
| [] -> default
| _ -> (matrix,raise_num)::default
let default_compat p def =
List.fold_right
(fun (pss,i) r ->
let qss =
List.fold_right
(fun qs r -> match qs with
| q::rem when may_compat p q -> rem::r
| _ -> r)
pss [] in
match qss with
| [] -> r
| _ -> (qss,i)::r)
def []
(* Or-pattern expansion, variables are a complication w.r.t. the article *)
exception Cannot_flatten
let mk_alpha_env arg aliases ids =
List.map
(fun id -> id,
if List.mem id aliases then
match arg with
| Some v -> v
| _ -> raise Cannot_flatten
else
Ident.create_local (Ident.name id))
ids
let rec explode_or_pat arg patl mk_action rem vars aliases = function
| {pat_desc = Tpat_or (p1,p2,_)} ->
explode_or_pat
arg patl mk_action
(explode_or_pat arg patl mk_action rem vars aliases p2)
vars aliases p1
| {pat_desc = Tpat_alias (p,id, _)} ->
explode_or_pat arg patl mk_action rem vars (id::aliases) p
| {pat_desc = Tpat_var (x, _)} ->
let env = mk_alpha_env arg (x::aliases) vars in
(omega::patl,mk_action (List.map snd env))::rem
| p ->
let env = mk_alpha_env arg aliases vars in
(alpha_pat env p::patl,mk_action (List.map snd env))::rem
let pm_free_variables {cases=cases} =
List.fold_right
(fun (_,act) r -> Ident.Set.union (free_variables act) r)
cases Ident.Set.empty
(* Basic grouping predicates *)
let pat_as_constr = function
| {pat_desc=Tpat_construct (_, cstr,_)} -> cstr
| _ -> fatal_error "Matching.pat_as_constr"
let group_const_int = function
| {pat_desc= Tpat_constant Const_int _ } -> true
| _ -> false
let group_const_char = function
| {pat_desc= Tpat_constant Const_char _ } -> true
| _ -> false
let group_const_string = function
| {pat_desc= Tpat_constant Const_string _ } -> true
| _ -> false
let group_const_float = function
| {pat_desc= Tpat_constant Const_float _ } -> true
| _ -> false
let group_const_int32 = function
| {pat_desc= Tpat_constant Const_int32 _ } -> true
| _ -> false
let group_const_int64 = function
| {pat_desc= Tpat_constant Const_int64 _ } -> true
| _ -> false
let group_const_nativeint = function
| {pat_desc= Tpat_constant Const_nativeint _ } -> true
| _ -> false
and group_constructor = function
| {pat_desc = Tpat_construct (_,_,_)} -> true
| _ -> false
and group_variant = function
| {pat_desc = Tpat_variant (_, _, _)} -> true
| _ -> false
and group_var = function
| {pat_desc=Tpat_any} -> true
| _ -> false
and group_tuple = function
| {pat_desc = (Tpat_tuple _|Tpat_any)} -> true
| _ -> false
and group_record = function
| {pat_desc = (Tpat_record _|Tpat_any)} -> true
| _ -> false
and group_array = function
| {pat_desc=Tpat_array _} -> true
| _ -> false
and group_lazy = function
| {pat_desc = Tpat_lazy _} -> true
| _ -> false
let get_group p = match p.pat_desc with
| Tpat_any -> group_var
| Tpat_constant Const_int _ -> group_const_int
| Tpat_constant Const_char _ -> group_const_char
| Tpat_constant Const_string _ -> group_const_string
| Tpat_constant Const_float _ -> group_const_float
| Tpat_constant Const_int32 _ -> group_const_int32
| Tpat_constant Const_int64 _ -> group_const_int64
| Tpat_constant Const_nativeint _ -> group_const_nativeint
| Tpat_construct _ -> group_constructor
| Tpat_tuple _ -> group_tuple
| Tpat_record _ -> group_record
| Tpat_array _ -> group_array
| Tpat_variant (_,_,_) -> group_variant
| Tpat_lazy _ -> group_lazy
| _ -> fatal_error "Matching.get_group"
let is_or p = match p.pat_desc with
| Tpat_or _ -> true
| _ -> false
(* Conditions for appending to the Or matrix *)
let conda p q = not (may_compat p q)
and condb act ps qs = not (is_guarded act) && Parmatch.le_pats qs ps
let or_ok p ps l =
List.for_all
(function
| ({pat_desc=Tpat_or _} as q::qs,act) ->
conda p q || condb act ps qs
| _ -> true)
l
(* Insert or append a pattern in the Or matrix *)
let equiv_pat p q = le_pat p q && le_pat q p
let rec get_equiv p l = match l with
| (q::_,_) as cl::rem ->
if equiv_pat p q then
let others,rem = get_equiv p rem in
cl::others,rem
else
[],l
| _ -> [],l
let insert_or_append p ps act ors no =
let rec attempt seen = function
| (q::qs,act_q) as cl::rem ->
if is_or q then begin
if may_compat p q then
if
Typedtree.pat_bound_idents p = [] &&
Typedtree.pat_bound_idents q = [] &&
equiv_pat p q
then (* attempt insert, for equivalent orpats with no variables *)
let _, not_e = get_equiv q rem in
if
or_ok p ps not_e && (* check append condition for head of O *)
List.for_all (* check insert condition for tail of O *)
(fun cl -> match cl with
| (q::_,_) -> not (may_compat p q)
| _ -> assert false)
seen
then (* insert *)
List.rev_append seen ((p::ps,act)::cl::rem), no
else (* fail to insert or append *)
ors,(p::ps,act)::no
else if condb act_q ps qs then (* check condition (b) for append *)
attempt (cl::seen) rem
else
ors,(p::ps,act)::no
else (* p # q, go on with append/insert *)
attempt (cl::seen) rem
end else (* q is not an or-pat, go on with append/insert *)
attempt (cl::seen) rem
| _ -> (* [] in fact *)
(p::ps,act)::ors,no in (* success in appending *)
attempt [] ors
(* Reconstruct default information from half_compiled pm list *)
let rec rebuild_matrix pmh = match pmh with
| Pm pm -> as_matrix pm.cases
| PmOr {or_matrix=m} -> m
| PmVar x -> add_omega_column (rebuild_matrix x.inside)
let rec rebuild_default nexts def = match nexts with
| [] -> def
| (e, pmh)::rem ->
(add_omega_column (rebuild_matrix pmh), e)::
rebuild_default rem def
let rebuild_nexts arg nexts k =
List.fold_right
(fun (e, pm) k -> (e, PmVar {inside=pm ; var_arg=arg})::k)
nexts k
(*
Split a matching.
Splitting is first directed by or-patterns, then by
tests (e.g. constructors)/variable transitions.
The approach is greedy, every split function attempts to
raise rows as much as possible in the top matrix,
then splitting applies again to the remaining rows.
Some precompilation of or-patterns and
variable pattern occurs. Mostly this means that bindings
are performed now, being replaced by let-bindings
in actions (cf. simplify_cases).
Additionally, if the match argument is a variable, matchings whose
first column is made of variables only are split further
(cf. precompile_var).
*)
let rec split_or argo cls args def =
let cls = simplify_cases args cls in
let rec do_split before ors no = function
| [] ->
cons_next
(List.rev before) (List.rev ors) (List.rev no)
| ((p::ps,act) as cl)::rem ->
if up_ok cl no then
if is_or p then
let ors, no = insert_or_append p ps act ors no in
do_split before ors no rem
else begin
if up_ok cl ors then
do_split (cl::before) ors no rem
else if or_ok p ps ors then
do_split before (cl::ors) no rem
else
do_split before ors (cl::no) rem
end
else
do_split before ors (cl::no) rem
| _ -> assert false
and cons_next yes yesor = function
| [] ->
precompile_or argo yes yesor args def []
| rem ->
let {me=next ; matrix=matrix ; top_default=def},nexts =
do_split [] [] [] rem in
let idef = next_raise_count () in
precompile_or
argo yes yesor args
(cons_default matrix idef def)
((idef,next)::nexts) in
do_split [] [] [] cls
(* Ultra-naive splitting, close to semantics, used for extension,
as potential rebind prevents any kind of optimisation *)
and split_naive cls args def k =
let rec split_exc cstr0 yes = function
| [] ->
let yes = List.rev yes in
{ me = Pm {cases=yes; args=args; default=def;} ;
matrix = as_matrix yes ;
top_default=def},
k
| (p::_,_ as cl)::rem ->
if group_constructor p then
let cstr = pat_as_constr p in
if cstr = cstr0 then split_exc cstr0 (cl::yes) rem
else
let yes = List.rev yes in
let {me=next ; matrix=matrix ; top_default=def}, nexts =
split_exc cstr [cl] rem in
let idef = next_raise_count () in
let def = cons_default matrix idef def in
{ me = Pm {cases=yes; args=args; default=def} ;
matrix = as_matrix yes ;
top_default = def; },
(idef,next)::nexts
else
let yes = List.rev yes in
let {me=next ; matrix=matrix ; top_default=def}, nexts =
split_noexc [cl] rem in
let idef = next_raise_count () in
let def = cons_default matrix idef def in
{ me = Pm {cases=yes; args=args; default=def} ;
matrix = as_matrix yes ;
top_default = def; },
(idef,next)::nexts
| _ -> assert false
and split_noexc yes = function
| [] -> precompile_var args (List.rev yes) def k
| (p::_,_ as cl)::rem ->
if group_constructor p then
let yes= List.rev yes in
let {me=next; matrix=matrix; top_default=def;},nexts =
split_exc (pat_as_constr p) [cl] rem in
let idef = next_raise_count () in
precompile_var
args yes
(cons_default matrix idef def)
((idef,next)::nexts)
else split_noexc (cl::yes) rem
| _ -> assert false in
match cls with
| [] -> assert false
| (p::_,_ as cl)::rem ->
if group_constructor p then
split_exc (pat_as_constr p) [cl] rem
else
split_noexc [cl] rem
| _ -> assert false
and split_constr cls args def k =
let ex_pat = what_is_cases cls in
match ex_pat.pat_desc with
| Tpat_any -> precompile_var args cls def k
| Tpat_construct (_,{cstr_tag=Cstr_extension _},_) ->
split_naive cls args def k
| _ ->
let group = get_group ex_pat in