1 (***********************************************************************)
5 (* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
7 (* Copyright 1996 Institut National de Recherche en Informatique et *)
8 (* en Automatique. All rights reserved. This file is distributed *)
9 (* under the terms of the Q Public License version 1.0. *)
11 (***********************************************************************)
15 (* Detection of partial matches and unused match cases. *)
22 (*************************************)
23 (* Utilities for building patterns *)
24 (*************************************)
26 let make_pat desc ty tenv
=
27 {pat_desc
= desc
; pat_loc
= Location.none
;
28 pat_type
= ty
; pat_env
= tenv
}
30 let omega = make_pat Tpat_any
Ctype.none
Env.empty
33 make_pat (Tpat_var
(Ident.create
"+")) Ctype.none
Env.empty
36 if i
<= 0 then [] else omega :: omegas (i
-1)
38 let omega_list l
= List.map
(fun _
-> omega) l
40 let zero = make_pat (Tpat_constant
(Const_int
0)) Ctype.none
Env.empty
42 (***********************)
43 (* Compatibility check *)
44 (***********************)
46 (* p and q compatible means, there exists V that matches both *)
48 let is_absent tag row
= Btype.row_field tag
!row
= Rabsent
50 let is_absent_pat p
= match p
.pat_desc
with
51 | Tpat_variant
(tag
, _
, row
) -> is_absent tag row
54 let sort_fields args
=
56 (fun (lbl1
,_
) (lbl2
,_
) -> lbl1
.lbl_pos
<= lbl2
.lbl_pos
)
59 let records_args l1 l2
=
60 let l1 = sort_fields l1
61 and l2
= sort_fields l2
in
62 let rec combine r1 r2
l1 l2
= match l1,l2
with
64 | [],(_
,p2
)::rem2
-> combine (omega::r1
) (p2
::r2
) [] rem2
65 | (_
,p1
)::rem1
,[] -> combine (p1
::r1
) (omega::r2
) rem1
[]
66 | (lbl1
,p1
)::rem1
, (lbl2
,p2
)::rem2
->
67 if lbl1
.lbl_pos
< lbl2
.lbl_pos
then
68 combine (p1
::r1
) (omega::r2
) rem1 l2
69 else if lbl1
.lbl_pos
> lbl2
.lbl_pos
then
70 combine (omega::r1
) (p2
::r2
) l1 rem2
71 else (* same label on both sides *)
72 combine (p1
::r1
) (p2
::r2
) rem1 rem2
in
77 match p
.pat_desc
,q
.pat_desc
with
78 | Tpat_alias
(p
,_
),_
-> compat p q
79 | _
,Tpat_alias
(q
,_
) -> compat p q
80 | (Tpat_any
|Tpat_var _
),_
-> true
81 | _
,(Tpat_any
|Tpat_var _
) -> true
82 | Tpat_or
(p1
,p2
,_
),_
-> compat p1 q
|| compat p2 q
83 | _
,Tpat_or
(q1
,q2
,_
) -> compat p q1
|| compat p q2
84 | Tpat_constant c1
, Tpat_constant c2
-> c1
=c2
85 | Tpat_tuple ps
, Tpat_tuple qs
-> compats ps qs
86 | Tpat_construct
(c1
,ps1
), Tpat_construct
(c2
,ps2
) ->
87 c1
.cstr_tag
= c2
.cstr_tag
&& compats ps1 ps2
88 | Tpat_variant
(l1,Some p1
, r1
), Tpat_variant
(l2
,Some p2
,_
) ->
90 | Tpat_variant
(l1,None
,r1
), Tpat_variant
(l2
,None
,_
) ->
92 | Tpat_variant
(_
, None
, _
), Tpat_variant
(_
,Some _
, _
) -> false
93 | Tpat_variant
(_
, Some _
, _
), Tpat_variant
(_
, None
, _
) -> false
94 | Tpat_record
l1,Tpat_record l2
->
95 let ps,qs
= records_args l1 l2
in
97 | Tpat_array
ps, Tpat_array qs
->
98 List.length
ps = List.length qs
&&
103 and compats
ps qs
= match ps,qs
with
105 | p
::ps, q
::qs
-> compat p q
&& compats
ps qs
106 | _
,_
-> assert false
108 (****************************************)
109 (* Utilities for retrieving constructor *)
110 (* and record label names *)
111 (****************************************)
113 exception Empty
(* Empty pattern *)
115 let get_type_path ty tenv
=
116 let ty = Ctype.repr
(Ctype.expand_head tenv
ty) in
118 | Tconstr
(path
,_
,_
) -> path
119 | _
-> fatal_error
"Parmatch.get_type_path"
121 let get_type_descr ty tenv
=
122 match (Ctype.repr
ty).desc
with
123 | Tconstr
(path
,_
,_
) -> Env.find_type path tenv
124 | _
-> fatal_error
"Parmatch.get_type_descr"
126 let rec get_constr tag
ty tenv
=
127 match get_type_descr ty tenv
with
128 | {type_kind
=Type_variant
(constr_list
, priv
)} ->
129 Datarepr.find_constr_by_tag tag constr_list
130 | {type_manifest
= Some _
} ->
131 get_constr tag
(Ctype.expand_head_once tenv
ty) tenv
132 | _
-> fatal_error
"Parmatch.get_constr"
134 let find_label lbl lbls
=
136 let name,_
,_
= List.nth lbls lbl
.lbl_pos
in
138 with Failure
"nth" -> "*Unkown label*"
140 let rec get_record_labels ty tenv
=
141 match get_type_descr ty tenv
with
142 | {type_kind
= Type_record
(lbls
, rep
, priv
)} -> lbls
143 | {type_manifest
= Some _
} ->
144 get_record_labels (Ctype.expand_head_once tenv
ty) tenv
145 | _
-> fatal_error
"Parmatch.get_record_labels"
148 (*************************************)
149 (* Values as patterns pretty printer *)
150 (*************************************)
155 let get_constr_name tag
ty tenv
= match tag
with
156 | Cstr_exception path
-> Path.name path
159 let name,_
= get_constr tag
ty tenv
in name
161 | Datarepr.Constr_not_found
-> "*Unknown constructor*"
163 let is_cons tag v
= match get_constr_name tag v
.pat_type v
.pat_env
with
168 let rec pretty_val ppf v
= match v
.pat_desc
with
169 | Tpat_any
-> fprintf ppf
"_"
170 | Tpat_var x
-> Ident.print ppf x
171 | Tpat_constant
(Const_int i
) -> fprintf ppf
"%d" i
172 | Tpat_constant
(Const_char c
) -> fprintf ppf
"%C" c
173 | Tpat_constant
(Const_string s
) -> fprintf ppf
"%S" s
174 | Tpat_constant
(Const_float f
) -> fprintf ppf
"%s" f
175 | Tpat_constant
(Const_int32 i
) -> fprintf ppf
"%ldl" i
176 | Tpat_constant
(Const_int64 i
) -> fprintf ppf
"%LdL" i
177 | Tpat_constant
(Const_nativeint i
) -> fprintf ppf
"%ndn" i
179 fprintf ppf
"@[(%a)@]" (pretty_vals
",") vs
180 | Tpat_construct
({cstr_tag
=tag
},[]) ->
181 let name = get_constr_name tag v
.pat_type v
.pat_env
in
182 fprintf ppf
"%s" name
183 | Tpat_construct
({cstr_tag
=tag
},[w
]) ->
184 let name = get_constr_name tag v
.pat_type v
.pat_env
in
185 fprintf ppf
"@[<2>%s@ %a@]" name pretty_arg w
186 | Tpat_construct
({cstr_tag
=tag
},vs
) ->
187 let name = get_constr_name tag v
.pat_type v
.pat_env
in
188 begin match (name, vs
) with
190 fprintf ppf
"@[%a::@,%a@]" pretty_car v1 pretty_cdr v2
192 fprintf ppf
"@[<2>%s@ @[(%a)@]@]" name (pretty_vals
",") vs
194 | Tpat_variant
(l
, None
, _
) ->
196 | Tpat_variant
(l
, Some w
, _
) ->
197 fprintf ppf
"@[<2>`%s@ %a@]" l pretty_arg w
199 fprintf ppf
"@[{%a}@]"
200 (pretty_lvals
(get_record_labels v
.pat_type v
.pat_env
))
203 | (_
,{pat_desc
=Tpat_any
}) -> false (* do not show lbl=_ *)
206 fprintf ppf
"@[[| %a |]@]" (pretty_vals
" ;") vs
207 | Tpat_alias
(v
,x
) ->
208 fprintf ppf
"@[(%a@ as %a)@]" pretty_val v
Ident.print x
210 fprintf ppf
"@[(%a|@,%a)@]" pretty_or v pretty_or w
212 and pretty_car ppf v
= match v
.pat_desc
with
213 | Tpat_construct
({cstr_tag
=tag
}, [_
; _
])
214 when is_cons tag v
->
215 fprintf ppf
"(%a)" pretty_val v
216 | _
-> pretty_val ppf v
218 and pretty_cdr ppf v
= match v
.pat_desc
with
219 | Tpat_construct
({cstr_tag
=tag
}, [v1
; v2
])
220 when is_cons tag v
->
221 fprintf ppf
"%a::@,%a" pretty_car v1 pretty_cdr v2
222 | _
-> pretty_val ppf v
224 and pretty_arg ppf v
= match v
.pat_desc
with
225 | Tpat_construct
(_
,_
::_
) -> fprintf ppf
"(%a)" pretty_val v
226 | _
-> pretty_val ppf v
228 and pretty_or ppf v
= match v
.pat_desc
with
230 fprintf ppf
"%a|@,%a" pretty_or v pretty_or w
231 | _
-> pretty_val ppf v
233 and pretty_vals sep ppf
= function
235 | [v
] -> pretty_val ppf v
237 fprintf ppf
"%a%s@ %a" pretty_val v sep
(pretty_vals sep
) vs
239 and pretty_lvals lbls ppf
= function
242 let name = find_label lbl lbls
in
243 fprintf ppf
"%s=%a" name pretty_val v
245 let name = find_label lbl lbls
in
246 fprintf ppf
"%s=%a;@ %a" name pretty_val v
(pretty_lvals lbls
) rest
248 let top_pretty ppf v
=
249 fprintf ppf
"@[%a@]@?" pretty_val v
253 top_pretty str_formatter v
;
254 prerr_string
(flush_str_formatter
())
257 (****************************)
258 (* Utilities for matching *)
259 (****************************)
261 (* Check top matching *)
262 let simple_match p1 p2
=
263 match p1
.pat_desc
, p2
.pat_desc
with
264 | Tpat_construct
(c1
, _
), Tpat_construct
(c2
, _
) ->
265 c1
.cstr_tag
= c2
.cstr_tag
266 | Tpat_variant
(l1, _
, _
), Tpat_variant
(l2
, _
, _
) ->
268 | Tpat_constant
(Const_float s1
), Tpat_constant
(Const_float s2
) ->
269 float_of_string s1
= float_of_string s2
270 | Tpat_constant
(c1
), Tpat_constant
(c2
) -> c1
= c2
271 | Tpat_tuple _
, Tpat_tuple _
-> true
272 | Tpat_record _
, Tpat_record _
-> true
273 | Tpat_array p1s
, Tpat_array p2s
-> List.length p1s
= List.length p2s
274 | _
, (Tpat_any
| Tpat_var
(_
)) -> true
280 (* extract record fields as a whole *)
281 let record_arg p
= match p
.pat_desc
with
283 | Tpat_record args
-> args
284 | _
-> fatal_error
"Parmatch.as_record"
287 (* Raise Not_found when pos is not present in arg *)
290 let get_field pos arg
=
291 let _,p
= List.find
(fun (lbl
,_) -> pos
= lbl
.lbl_pos
) arg
in
295 let extract_fields omegas arg
=
299 get_field lbl
.lbl_pos arg
300 with Not_found
-> omega)
305 let sort_record p
= match p
.pat_desc
with
306 | Tpat_record args
->
308 (Tpat_record
(sort_fields args
))
312 let all_record_args lbls
= match lbls
with
313 | ({lbl_all
=lbl_all
},_)::_ ->
316 (fun lbl
-> lbl
,omega) lbl_all
in
318 (fun ((lbl
,_) as x
) -> t.(lbl
.lbl_pos
) <- x
)
321 | _ -> fatal_error
"Parmatch.all_record_args"
324 (* Build argument list when p2 >= p1, where p1 is a simple pattern *)
325 let rec simple_match_args p1 p2
= match p2
.pat_desc
with
326 | Tpat_alias
(p2
,_) -> simple_match_args p1 p2
327 | Tpat_construct
(cstr
, args
) -> args
328 | Tpat_variant
(lab
, Some arg
, _) -> [arg
]
329 | Tpat_tuple
(args
) -> args
330 | Tpat_record
(args
) -> extract_fields (record_arg p1
) args
331 | Tpat_array
(args
) -> args
332 | (Tpat_any
| Tpat_var
(_)) ->
333 begin match p1
.pat_desc
with
334 Tpat_construct
(_, args
) -> omega_list args
335 | Tpat_variant
(_, Some
_, _) -> [omega]
336 | Tpat_tuple
(args
) -> omega_list args
337 | Tpat_record
(args
) -> omega_list args
338 | Tpat_array
(args
) -> omega_list args
344 Normalize a pattern ->
345 all arguments are omega (simple pattern) and no more variables
348 let rec normalize_pat q
= match q
.pat_desc
with
349 | Tpat_any
| Tpat_constant
_ -> q
350 | Tpat_var
_ -> make_pat Tpat_any q
.pat_type q
.pat_env
351 | Tpat_alias
(p
,_) -> normalize_pat p
352 | Tpat_tuple
(args
) ->
353 make_pat (Tpat_tuple
(omega_list args
)) q
.pat_type q
.pat_env
354 | Tpat_construct
(c
,args
) ->
355 make_pat (Tpat_construct
(c
,omega_list args
)) q
.pat_type q
.pat_env
356 | Tpat_variant
(l
, arg
, row
) ->
357 make_pat (Tpat_variant
(l
, may_map
(fun _ -> omega) arg
, row
))
359 | Tpat_array
(args
) ->
360 make_pat (Tpat_array
(omega_list args
)) q
.pat_type q
.pat_env
361 | Tpat_record
(largs
) ->
362 make_pat (Tpat_record
(List.map
(fun (lbl
,_) -> lbl
,omega) largs
))
364 | Tpat_or
_ -> fatal_error
"Parmatch.normalize_pat"
368 Build normalized (cf. supra) discriminating pattern,
369 in the non-data type case
372 let discr_pat q pss
=
374 let rec acc_pat acc pss
= match pss
with
375 ({pat_desc
= Tpat_alias
(p
,_)}::ps)::pss
->
376 acc_pat acc
((p
::ps)::pss
)
377 | ({pat_desc
= Tpat_or
(p1
,p2
,_)}::ps)::pss
->
378 acc_pat acc
((p1
::ps)::(p2
::ps)::pss
)
379 | ({pat_desc
= (Tpat_any
| Tpat_var
_)}::_)::pss
->
381 | (({pat_desc
= Tpat_tuple
_} as p
)::_)::_ -> normalize_pat p
382 | (({pat_desc
= Tpat_record largs
} as p
)::_)::pss
->
387 let _ = get_field lbl
.lbl_pos r
in
394 (make_pat (Tpat_record
new_omegas) p
.pat_type p
.pat_env
)
398 match normalize_pat q
with
399 | {pat_desc
= (Tpat_any
| Tpat_record
_)} as q
->
400 sort_record (acc_pat q pss
)
404 In case a matching value is found, set actual arguments
405 of the matching pattern.
408 let rec read_args xs r
= match xs
,r
with
410 | _::xs
, arg
::rest
->
411 let args,rest
= read_args xs rest
in
414 fatal_error
"Parmatch.read_args"
416 let do_set_args erase_mutable q r
= match q
with
417 | {pat_desc
= Tpat_tuple
omegas} ->
418 let args,rest
= read_args omegas r
in
419 make_pat (Tpat_tuple
args) q
.pat_type q
.pat_env
::rest
420 | {pat_desc
= Tpat_record
omegas} ->
421 let args,rest
= read_args omegas r
in
424 (List.map2
(fun (lbl
,_) arg
->
427 (match lbl
.lbl_mut
with
428 | Mutable
-> true | Immutable
-> false)
434 q
.pat_type q
.pat_env
::
436 | {pat_desc
= Tpat_construct
(c
,omegas)} ->
437 let args,rest
= read_args omegas r
in
439 (Tpat_construct
(c
,args)) q
.pat_type q
.pat_env
::
441 | {pat_desc
= Tpat_variant
(l
, omega, row
)} ->
444 Some
_, a
::r
-> Some a
, r
449 (Tpat_variant
(l
, arg, row
)) q
.pat_type q
.pat_env
::
451 | {pat_desc
= Tpat_array
omegas} ->
452 let args,rest
= read_args omegas r
in
454 (Tpat_array
args) q
.pat_type q
.pat_env
::
456 | {pat_desc
=Tpat_constant
_|Tpat_any
} ->
457 q
::r
(* case any is used in matching.ml *)
458 | _ -> fatal_error
"Parmatch.set_args"
460 let set_args q r
= do_set_args false q r
461 and set_args_erase_mutable q r
= do_set_args true q r
463 (* filter pss acording to pattern q *)
464 let filter_one q pss
=
465 let rec filter_rec = function
466 ({pat_desc
= Tpat_alias
(p
,_)}::ps)::pss
->
467 filter_rec ((p
::ps)::pss
)
468 | ({pat_desc
= Tpat_or
(p1
,p2
,_)}::ps)::pss
->
469 filter_rec ((p1
::ps)::(p2
::ps)::pss
)
472 then (simple_match_args q p
@ ps) :: filter_rec pss
478 Filter pss in the ``extra case''. This applies :
479 - According to an extra constructor (datatype case, non-complete signature).
480 - Acordinng to anything (all-variables case).
482 let filter_extra pss
=
483 let rec filter_rec = function
484 ({pat_desc
= Tpat_alias
(p
,_)}::ps)::pss
->
485 filter_rec ((p
::ps)::pss
)
486 | ({pat_desc
= Tpat_or
(p1
,p2
,_)}::ps)::pss
->
487 filter_rec ((p1
::ps)::(p2
::ps)::pss
)
488 | ({pat_desc
= (Tpat_any
| Tpat_var
(_))} :: qs
) :: pss
->
490 | _::pss
-> filter_rec pss
495 Pattern p0 is the discriminating pattern,
496 returns [(q0,pss0) ; ... ; (qn,pssn)]
497 where the qi's are simple patterns and the pssi's are
501 * (qi,[]) is impossible.
502 * In the case when matching is useless (all-variable case),
506 let filter_all pat0 pss
=
508 let rec insert q qs env
=
511 let q0 = normalize_pat q
in
512 [q0, [simple_match_args q0 q
@ qs
]]
513 | ((q0,pss
) as c
)::env
->
515 then (q0, ((simple_match_args q0 q
@ qs
) :: pss
)) :: env
516 else c
:: insert q qs env
in
518 let rec filter_rec env
= function
519 ({pat_desc
= Tpat_alias
(p
,_)}::ps)::pss
->
520 filter_rec env
((p
::ps)::pss
)
521 | ({pat_desc
= Tpat_or
(p1
,p2
,_)}::ps)::pss
->
522 filter_rec env
((p1
::ps)::(p2
::ps)::pss
)
523 | ({pat_desc
= (Tpat_any
| Tpat_var
(_))}::_)::pss
->
526 filter_rec (insert p
ps env
) pss
529 and filter_omega env
= function
530 ({pat_desc
= Tpat_alias
(p
,_)}::ps)::pss
->
531 filter_omega env
((p
::ps)::pss
)
532 | ({pat_desc
= Tpat_or
(p1
,p2
,_)}::ps)::pss
->
533 filter_omega env
((p1
::ps)::(p2
::ps)::pss
)
534 | ({pat_desc
= (Tpat_any
| Tpat_var
(_))}::ps)::pss
->
536 (List.map
(fun (q
,qss
) -> (q
,(simple_match_args q
omega @ ps) :: qss
)) env
)
538 | _::pss
-> filter_omega env pss
543 (match pat0
.pat_desc
with
544 (Tpat_record
(_) | Tpat_tuple
(_)) -> [pat0
,[]]
549 (* Variant related functions *)
551 let rec set_last a
= function
554 | x
::l
-> x
:: set_last a l
556 (* mark constructor lines for failure when they are incomplete *)
557 let rec mark_partial = function
558 ({pat_desc
= Tpat_alias
(p
,_)}::ps)::pss
->
559 mark_partial ((p
::ps)::pss
)
560 | ({pat_desc
= Tpat_or
(p1
,p2
,_)}::ps)::pss
->
561 mark_partial ((p1
::ps)::(p2
::ps)::pss
)
562 | ({pat_desc
= (Tpat_any
| Tpat_var
(_))} :: _ as ps) :: pss
->
563 ps :: mark_partial pss
565 (set_last zero ps) :: mark_partial pss
568 let close_variant env row
=
569 let row = Btype.row_repr
row in
573 match Btype.row_field_repr f
with
574 | Reither
(_, _, false, e
) ->
575 (* m=false means that this tag is not explicitly matched *)
576 Btype.set_row_field e Rabsent
;
578 | Rabsent
| Reither
(_, _, true, _) | Rpresent
_ -> nm)
579 row.row_name
row.row_fields
in
580 if not
row.row_closed
|| nm != row.row_name
then begin
581 (* this unification cannot fail *)
582 Ctype.unify env
row.row_more
584 (Tvariant
{row with row_fields
= []; row_more
= Btype.newgenvar
();
585 row_closed
= true; row_name
= nm}))
589 match Ctype.expand_head pat
.pat_env pat
.pat_type
with
590 {desc
= Tvariant
row} -> Btype.row_repr
row
594 Check whether the first column of env makes up a complete signature or
598 let full_match closing env
= match env
with
599 | ({pat_desc
= Tpat_construct
({cstr_tag
=Cstr_exception
_},_)},_)::_ ->
601 | ({pat_desc
= Tpat_construct
(c
,_)},_) :: _ ->
602 List.length env
= c
.cstr_consts
+ c
.cstr_nonconsts
603 | ({pat_desc
= Tpat_variant
_} as p
,_) :: _ ->
606 (function ({pat_desc
= Tpat_variant
(tag
, _, _)}, _) -> tag
610 let row = row_of_pat p
in
611 if closing
&& not
row.row_fixed
then
612 (* closing=true, we are considering the variant as closed *)
615 match Btype.row_field_repr f
with
616 Rabsent
| Reither
(_, _, false, _) -> true
617 | Reither
(_, _, true, _)
618 (* m=true, do not discard matched tags, rather warn *)
619 | Rpresent
_ -> List.mem tag
fields)
625 Btype.row_field_repr f
= Rabsent
|| List.mem tag
fields)
627 | ({pat_desc
= Tpat_constant
(Const_char
_)},_) :: _ ->
628 List.length env
= 256
629 | ({pat_desc
= Tpat_constant
(_)},_) :: _ -> false
630 | ({pat_desc
= Tpat_tuple
(_)},_) :: _ -> true
631 | ({pat_desc
= Tpat_record
(_)},_) :: _ -> true
632 | ({pat_desc
= Tpat_array
(_)},_) :: _ -> false
633 | _ -> fatal_error
"Parmatch.full_match"
635 let extendable_match env
= match env
with
636 | ({pat_desc
= Tpat_construct
({cstr_tag
=(Cstr_constant
_|Cstr_block
_)},_)} as p
,_) :: _ ->
637 let path = get_type_path p
.pat_type p
.pat_env
in
639 (Path.same
path Predef.path_bool
||
640 Path.same
path Predef.path_list
||
641 Path.same
path Predef.path_option
)
645 let should_extend ext env
= match ext
with
647 | Some ext
-> match env
with
649 Tpat_construct
({cstr_tag
=(Cstr_constant
_|Cstr_block
_)},_)} as p
,_)
651 let path = get_type_path p
.pat_type p
.pat_env
in
655 (* complement constructor tags *)
656 let complete_tags nconsts nconstrs tags
=
657 let seen_const = Array.create nconsts
false
658 and seen_constr
= Array.create nconstrs
false in
661 | Cstr_constant i
-> seen_const.(i
) <- true
662 | Cstr_block i
-> seen_constr
.(i
) <- true
666 for i
= 0 to nconsts
-1 do
667 if not
seen_const.(i
) then
668 r := Cstr_constant i
:: !r
670 for i
= 0 to nconstrs
-1 do
671 if not seen_constr
.(i
) then
672 r := Cstr_block i
:: !r
676 (* build a pattern from a constructor list *)
677 let pat_of_constr ex_pat cstr
=
678 {ex_pat
with pat_desc
= Tpat_construct
(cstr
,omegas cstr
.cstr_arity
)}
680 let rec pat_of_constrs ex_pat
= function
682 | [cstr
] -> pat_of_constr ex_pat cstr
687 (pat_of_constr ex_pat cstr
,
688 pat_of_constrs ex_pat rem
, None
)}
690 (* Sends back a pattern that complements constructor tags all_tag *)
691 let complete_constrs p all_tags
= match p
.pat_desc
with
692 | Tpat_construct
(c
,_) ->
694 let not_tags = complete_tags c
.cstr_consts c
.cstr_nonconsts all_tags
in
697 let _,targs
= get_constr tag p
.pat_type p
.pat_env
in
701 cstr_arity
= List.length targs
})
704 | Datarepr.Constr_not_found
->
705 fatal_error
"Parmatch.complete_constr: constr_not_found"
707 | _ -> fatal_error
"Parmatch.complete_constr"
710 (* Auxiliary for build_other *)
712 let build_other_constant proj make first next p env
=
713 let all = List.map
(fun (p
, _) -> proj p
.pat_desc
) env
in
714 let rec try_const i
=
716 then try_const (next i
)
717 else make_pat (make i
) p
.pat_type p
.pat_env
721 Builds a pattern that is incompatible with all patterns in
722 in the first column of env
725 let build_other ext env
= match env
with
726 | ({pat_desc
= Tpat_construct
({cstr_tag
=Cstr_exception
_} as c
,_)},_)
731 cstr_tag
=(Cstr_exception
732 (Path.Pident
(Ident.create
"*exception*")))},
735 | ({pat_desc
= Tpat_construct
(_,_)} as p
,_) :: _ ->
737 | Some ext
when Path.same ext
(get_type_path p
.pat_type p
.pat_env
) ->
740 let get_tag = function
741 | {pat_desc
= Tpat_construct
(c
,_)} -> c
.cstr_tag
742 | _ -> fatal_error
"Parmatch.get_tag" in
743 let all_tags = List.map
(fun (p
,_) -> get_tag p
) env
in
744 pat_of_constrs p
(complete_constrs p
all_tags)
746 | ({pat_desc
= Tpat_variant
(_,_,r)} as p
,_) :: _ ->
749 (function ({pat_desc
= Tpat_variant
(tag
, _, _)}, _) -> tag
753 let row = row_of_pat p
in
754 let make_other_pat tag const
=
755 let arg = if const
then None
else Some
omega in
756 make_pat (Tpat_variant
(tag
, arg, r)) p
.pat_type p
.pat_env
in
759 (fun others
(tag
,f
) ->
760 if List.mem tag
tags then others
else
761 match Btype.row_field_repr f
with
762 Rabsent
(* | Reither _ *) -> others
763 (* This one is called after erasing pattern info *)
764 | Reither
(c
, _, _, _) -> make_other_pat tag c
:: others
765 | Rpresent
arg -> make_other_pat tag
(arg = None
) :: others
)
769 make_other_pat "AnyExtraTag" true
773 make_pat (Tpat_or
(pat
, p_res
, None
)) p
.pat_type p
.pat_env
)
776 | ({pat_desc
= Tpat_constant
(Const_char
_)} as p
,_) :: _ ->
779 (fun (p
,_) -> match p
.pat_desc
with
780 | Tpat_constant
(Const_char c
) -> c
784 let rec find_other i imax
=
785 if i
> imax
then raise Not_found
787 let ci = Char.chr i
in
788 if List.mem
ci all_chars then
789 find_other (i
+1) imax
791 make_pat (Tpat_constant
(Const_char
ci)) p
.pat_type p
.pat_env
in
792 let rec try_chars = function
796 find_other (Char.code c1
) (Char.code c2
)
798 | Not_found
-> try_chars rest
in
801 [ 'a'
, 'z'
; 'A'
, 'Z'
; '
0'
, '
9'
;
802 ' '
, '~'
; Char.chr
0 , Char.chr
255]
804 | ({pat_desc
=(Tpat_constant
(Const_int
_))} as p
,_) :: _ ->
806 (function Tpat_constant
(Const_int i
) -> i
| _ -> assert false)
807 (function i
-> Tpat_constant
(Const_int i
))
809 | ({pat_desc
=(Tpat_constant
(Const_int32
_))} as p
,_) :: _ ->
811 (function Tpat_constant
(Const_int32 i
) -> i
| _ -> assert false)
812 (function i
-> Tpat_constant
(Const_int32 i
))
814 | ({pat_desc
=(Tpat_constant
(Const_int64
_))} as p
,_) :: _ ->
816 (function Tpat_constant
(Const_int64 i
) -> i
| _ -> assert false)
817 (function i
-> Tpat_constant
(Const_int64 i
))
819 | ({pat_desc
=(Tpat_constant
(Const_nativeint
_))} as p
,_) :: _ ->
821 (function Tpat_constant
(Const_nativeint i
) -> i
| _ -> assert false)
822 (function i
-> Tpat_constant
(Const_nativeint i
))
823 0n
Nativeint.succ p env
824 | ({pat_desc
=(Tpat_constant
(Const_string
_))} as p
,_) :: _ ->
826 (function Tpat_constant
(Const_string s
) -> String.length s
828 (function i
-> Tpat_constant
(Const_string
(String.make i '
*'
)))
830 | ({pat_desc
=(Tpat_constant
(Const_float
_))} as p
,_) :: _ ->
832 (function Tpat_constant
(Const_float f
) -> float_of_string f
834 (function f
-> Tpat_constant
(Const_float
(string_of_float f
)))
835 0.0 (fun f
-> f
+. 1.0) p env
837 | ({pat_desc
= Tpat_array
args} as p
,_)::_ ->
840 (fun (p
,_) -> match p
.pat_desc
with
841 | Tpat_array
args -> List.length
args
844 let rec try_arrays l
=
845 if List.mem l
all_lengths then try_arrays (l
+1)
848 (Tpat_array
(omegas l
))
849 p
.pat_type p
.pat_env
in
856 Is the last row of pattern matrix pss + qs satisfiable ?
858 Does there exists at least one value vector, es such that :
859 1- for all ps in pss ps # es (ps and es are not compatible)
860 2- qs <= es (es matches qs)
863 let rec has_instance p
= match p
.pat_desc
with
864 | Tpat_variant
(l
,_,r) when is_absent l
r -> false
865 | Tpat_any
| Tpat_var
_ | Tpat_constant
_ | Tpat_variant
(_,None
,_) -> true
866 | Tpat_alias
(p
,_) | Tpat_variant
(_,Some p
,_) -> has_instance p
867 | Tpat_or
(p1
,p2
,_) -> has_instance p1
|| has_instance p2
868 | Tpat_construct
(_,ps) | Tpat_tuple
ps | Tpat_array
ps -> has_instances
ps
869 | Tpat_record lps
-> has_instances
(List.map snd lps
)
871 and has_instances
= function
873 | q
::rem
-> has_instance q
&& has_instances rem
875 let rec satisfiable pss qs
= match pss
with
876 | [] -> has_instances qs
880 | {pat_desc
= Tpat_or
(q1
,q2
,_)}::qs
->
881 satisfiable pss
(q1
::qs
) || satisfiable pss
(q2
::qs
)
882 | {pat_desc
= Tpat_alias
(q
,_)}::qs
->
883 satisfiable pss
(q
::qs
)
884 | {pat_desc
= (Tpat_any
| Tpat_var
(_))}::qs
->
885 let q0 = discr_pat omega pss
in
886 begin match filter_all q0 pss
with
887 (* first column of pss is made of variables only *)
888 | [] -> satisfiable (filter_extra pss
) qs
890 if full_match false constrs
then
893 not
(is_absent_pat p
) &&
894 satisfiable pss
(simple_match_args p
omega @ qs
))
897 satisfiable (filter_extra pss
) qs
899 | {pat_desc
=Tpat_variant
(l
,_,r)}::_ when is_absent l
r -> false
901 let q0 = discr_pat q pss
in
902 satisfiable (filter_one q0 pss
) (simple_match_args q0 q
@ qs
)
905 Now another satisfiable function that additionally
906 supplies an example of a matching value.
908 This function should be called for exhaustiveness check only.
912 | Rnone
(* No matching value *)
913 | Rsome
of 'a
(* This matching value *)
915 let rec try_many f
= function
919 | Rnone
-> try_many f rest
923 let rec exhaust ext pss n
= match pss
with
924 | [] -> Rsome
(omegas n
)
927 let q0 = discr_pat omega pss
in
928 begin match filter_all q0 pss
with
929 (* first column of pss is made of variables only *)
931 begin match exhaust ext
(filter_extra pss
) (n
-1) with
932 | Rsome
r -> Rsome
(q0::r)
936 let try_non_omega (p
,pss
) =
937 if is_absent_pat p
then
942 ext pss
(List.length
(simple_match_args p
omega) + n
- 1)
944 | Rsome
r -> Rsome
(set_args p
r)
947 full_match false constrs
&& not
(should_extend ext constrs
)
949 try_many try_non_omega constrs
952 D = filter_extra pss is the default matrix
953 as it is included in pss, one can avoid
954 recursive calls on specialized matrices,
956 * D exhaustive => pss exhaustive
957 * D non-exhaustive => we have a non-filtered value
959 let r = exhaust ext
(filter_extra pss
) (n
-1) in
964 Rsome
(build_other ext constrs
::r)
966 (* cannot occur, since constructors don't make a full signature *)
967 | Empty
-> fatal_error
"Parmatch.exhaust"
971 Another exhaustiveness check, enforcing variant typing.
972 Note that it does not check exact exhaustiveness, but whether a
973 matching could be made exhaustive by closing all variant types.
974 When this is true of all other columns, the current column is left
975 open (even if it means that the whole matching is not exhaustive as
977 When this is false for the matrix minus the current column, and the
978 current column is composed of variant tags, we close the variant
979 (even if it doesn't help in making the matching exhaustive).
982 let rec pressure_variants tdefs
= function
986 let q0 = discr_pat omega pss
in
987 begin match filter_all q0 pss
with
988 [] -> pressure_variants tdefs
(filter_extra pss
)
990 let rec try_non_omega = function
992 let ok = pressure_variants tdefs pss
in
993 try_non_omega rem
&& ok
996 if full_match (tdefs
=None
) constrs
then
997 try_non_omega constrs
998 else if tdefs
= None
then
999 pressure_variants None
(filter_extra pss
)
1001 let full = full_match true constrs
in
1003 if full then try_non_omega constrs
1004 else try_non_omega (filter_all q0 (mark_partial pss
))
1006 begin match constrs
, tdefs
with
1007 ({pat_desc
=Tpat_variant
_} as p
,_):: _, Some env
->
1008 let row = row_of_pat p
in
1010 || pressure_variants None
(filter_extra pss
) then ()
1011 else close_variant env
row
1018 (* Yet another satisfiable fonction *)
1021 This time every_satisfiable pss qs checks the
1022 utility of every expansion of qs.
1023 Expansion means expansion of or-patterns inside qs
1027 | Used
(* Useful pattern *)
1028 | Unused
(* Useless pattern *)
1029 | Upartial
of Typedtree.pattern list
(* Neither, with list of useless pattern *)
1033 top_pretty Format.str_formatter p
;
1034 prerr_string
(Format.flush_str_formatter
())
1036 type matrix
= pattern list list
1038 let pretty_line ps =
1041 top_pretty Format.str_formatter p
;
1043 prerr_string
(Format.flush_str_formatter
()) ;
1047 let pretty_matrix pss
=
1048 prerr_endline
"begin matrix" ;
1054 prerr_endline
"end matrix"
1056 (* this row type enable column processing inside the matrix
1057 - left -> elements not to be processed,
1058 - right -> elements to be processed
1060 type 'a
row = {no_ors
: 'a list
; ors
: 'a list
; active
: 'a list
}
1063 let pretty_row {ors
=ors
; no_ors
=no_ors
; active
=active
} =
1064 pretty_line ors
; prerr_string
" *" ;
1065 pretty_line no_ors
; prerr_string
" *" ;
1068 let pretty_rows rs
=
1069 prerr_endline
"begin matrix" ;
1075 prerr_endline
"end matrix"
1078 let make_row ps = {ors
=[] ; no_ors
=[]; active
=ps}
1080 let make_rows pss
= List.map
make_row pss
1083 (* Useful to detect and expand or pats inside as pats *)
1084 let rec unalias p
= match p
.pat_desc
with
1085 | Tpat_alias
(p
,_) -> unalias p
1089 let is_var p
= match (unalias p
).pat_desc
with
1090 | Tpat_any
|Tpat_var
_ -> true
1093 let is_var_column rs
=
1095 (fun r -> match r.active
with
1097 | [] -> assert false)
1100 (* Standard or-args for left-to-right matching *)
1101 let rec or_args p
= match p
.pat_desc
with
1102 | Tpat_or
(p1
,p2
,_) -> p1
,p2
1103 | Tpat_alias
(p
,_) -> or_args p
1106 (* Just remove current column *)
1107 let remove r = match r.active
with
1108 | _::rem
-> {r with active
=rem
}
1109 | [] -> assert false
1111 let remove_column rs
= List.map
remove rs
1113 (* Current column has been processed *)
1114 let push_no_or r = match r.active
with
1115 | p
::rem
-> { r with no_ors
= p
::r.no_ors
; active
=rem
}
1116 | [] -> assert false
1118 let push_or r = match r.active
with
1119 | p
::rem
-> { r with ors
= p
::r.ors
; active
=rem
}
1120 | [] -> assert false
1122 let push_or_column rs
= List.map
push_or rs
1123 and push_no_or_column rs
= List.map
push_no_or rs
1125 (* Those are adaptations of the previous homonymous functions that
1126 work on the current column, instead of the first column
1129 let discr_pat q rs
=
1130 discr_pat q
(List.map
(fun r -> r.active
) rs
)
1132 let filter_one q rs
=
1133 let rec filter_rec rs
= match rs
with
1137 | [] -> assert false
1138 | {pat_desc
= Tpat_alias
(p
,_)}::ps ->
1139 filter_rec ({r with active
= p
::ps}::rem
)
1140 | {pat_desc
= Tpat_or
(p1
,p2
,_)}::ps ->
1142 ({r with active
= p1
::ps}::
1143 {r with active
= p2
::ps}::
1146 if simple_match q p
then
1147 {r with active
=simple_match_args q p
@ ps} :: filter_rec rem
1153 (* Back to normal matrices *)
1154 let make_vector r = r.no_ors
1156 let make_matrix rs
= List.map
make_vector rs
1159 (* Standard union on answers *)
1160 let union_res r1 r2
= match r1
, r2
with
1162 | (_, Unused
) -> Unused
1165 | Upartial u1
, Upartial u2
-> Upartial
(u1
@u2
)
1167 (* propose or pats for expansion *)
1168 let extract_elements qs
=
1169 let rec do_rec seen
= function
1172 {no_ors
= List.rev_append seen rem
@ qs
.no_ors
;
1175 do_rec (q
::seen
) rem
in
1178 (* idem for matrices *)
1179 let transpose rs
= match rs
with
1180 | [] -> assert false
1182 let i = List.map
(fun x
-> [x
]) r in
1184 (List.map2
(fun r x
-> x
::r))
1187 let extract_columns pss qs
= match pss
with
1188 | [] -> List.map
(fun _ -> []) qs
.ors
1190 let rows = List.map
extract_elements pss
in
1194 The idea is to first look for or patterns (recursive case), then
1195 check or-patterns argument usefulness (terminal case)
1198 let rec every_satisfiables pss qs
= match qs
.active
with
1200 (* qs is now partitionned, check usefulness *)
1201 begin match qs
.ors
with
1202 | [] -> (* no or-patterns *)
1203 if satisfiable (make_matrix pss
) (make_vector qs
) then
1207 | _ -> (* n or-patterns -> 2n expansions *)
1209 (fun pss qs
r -> match r with
1212 match qs
.active
with
1214 let q1,q2
= or_args q
in
1215 let r_loc = every_both pss qs
q1 q2
in
1217 | _ -> assert false)
1218 (extract_columns pss qs
) (extract_elements qs
)
1222 let uq = unalias q
in
1223 begin match uq.pat_desc
with
1224 | Tpat_any
| Tpat_var
_ ->
1225 if is_var_column pss
then
1226 (* forget about ``all-variable'' columns now *)
1227 every_satisfiables (remove_column pss
) (remove qs
)
1229 (* otherwise this is direct food for satisfiable *)
1230 every_satisfiables (push_no_or_column pss
) (push_no_or qs
)
1231 | Tpat_or
(q1,q2
,_) ->
1233 q1.pat_loc
.Location.loc_ghost
&&
1234 q2
.pat_loc
.Location.loc_ghost
1236 (* syntactically generated or-pats should not be expanded *)
1237 every_satisfiables (push_no_or_column pss
) (push_no_or qs
)
1239 (* this is a real or-pattern *)
1240 every_satisfiables (push_or_column pss
) (push_or qs
)
1241 | Tpat_variant
(l
,_,r) when is_absent l
r -> (* Ah Jacques... *)
1244 (* standard case, filter matrix *)
1245 let q0 = discr_pat q pss
in
1248 {qs
with active
=simple_match_args q0 q
@ rem
}
1252 This function ``every_both'' performs the usefulness check
1254 The trick is to call every_satisfied twice with
1255 current active columns restricted to q1 and q2,
1257 - others orpats in qs.ors will not get expanded.
1258 - all matching work performed on qs.no_ors is not performed again.
1260 and every_both pss qs
q1 q2
=
1261 let qs1 = {qs
with active
=[q1]}
1262 and qs2
= {qs
with active
=[q2
]} in
1263 let r1 = every_satisfiables pss
qs1
1264 and r2
= every_satisfiables (if compat q1 q2
then qs1::pss
else pss
) qs2
in
1269 | Used
-> Upartial
[q1]
1270 | Upartial u2
-> Upartial
(q1::u2
)
1274 | Unused
-> Upartial
[q2
]
1279 | Unused
-> Upartial
(u1
@[q2
])
1281 | Upartial u2
-> Upartial
(u1
@ u2
)
1287 (* le_pat p q means, forall V, V matches q implies V matches p *)
1288 let rec le_pat p q
=
1289 match (p
.pat_desc
, q
.pat_desc
) with
1290 | (Tpat_var
_|Tpat_any
),_ -> true
1291 | Tpat_alias
(p
,_), _ -> le_pat p q
1292 | _, Tpat_alias
(q
,_) -> le_pat p q
1293 | Tpat_constant
(c1
), Tpat_constant
(c2
) -> c1
= c2
1294 | Tpat_construct
(c1
,ps), Tpat_construct
(c2
,qs
) ->
1295 c1
.cstr_tag
= c2
.cstr_tag
&& le_pats
ps qs
1296 | Tpat_variant
(l1,Some p1
,_), Tpat_variant
(l2
,Some p2
,_) ->
1297 (l1 = l2
&& le_pat p1 p2
)
1298 | Tpat_variant
(l1,None
,r1), Tpat_variant
(l2
,None
,_) ->
1300 | Tpat_variant
(_,_,_), Tpat_variant
(_,_,_) -> false
1301 | Tpat_tuple
(ps), Tpat_tuple
(qs
) -> le_pats
ps qs
1302 | Tpat_record
l1, Tpat_record l2
->
1303 let ps,qs
= records_args l1 l2
in
1305 | Tpat_array
(ps), Tpat_array
(qs
) ->
1306 List.length
ps = List.length qs
&& le_pats
ps qs
1307 (* In all other cases, enumeration is performed *)
1308 | _,_ -> not
(satisfiable [[p
]] [q
])
1312 p
::ps, q
::qs
-> le_pat p q
&& le_pats
ps qs
1315 let get_mins le
ps =
1316 let rec select_rec r = function
1319 if List.exists
(fun p0
-> le p0 p
) ps
1320 then select_rec r ps
1321 else select_rec (p
::r) ps in
1322 select_rec [] (select_rec [] ps)
1325 lub p q is a pattern that matches all values matched by p and q
1326 may raise Empty, when p and q and not compatible
1329 let rec lub p q
= match p
.pat_desc
,q
.pat_desc
with
1330 | Tpat_alias
(p
,_),_ -> lub p q
1331 | _,Tpat_alias
(q
,_) -> lub p q
1332 | (Tpat_any
|Tpat_var
_),_ -> q
1333 | _,(Tpat_any
|Tpat_var
_) -> p
1334 | Tpat_or
(p1
,p2
,_),_ -> orlub p1 p2 q
1335 | _,Tpat_or
(q1,q2
,_) -> orlub
q1 q2 p
(* Thanks god, lub is commutative *)
1336 | Tpat_constant c1
, Tpat_constant c2
when c1
=c2
-> p
1337 | Tpat_tuple
ps, Tpat_tuple qs
->
1338 let rs = lubs
ps qs
in
1339 make_pat (Tpat_tuple
rs) p
.pat_type p
.pat_env
1340 | Tpat_construct
(c1
,ps1
), Tpat_construct
(c2
,ps2
)
1341 when c1
.cstr_tag
= c2
.cstr_tag
->
1342 let rs = lubs ps1 ps2
in
1343 make_pat (Tpat_construct
(c1
,rs)) p
.pat_type p
.pat_env
1344 | Tpat_variant
(l1,Some p1
,row), Tpat_variant
(l2
,Some p2
,_)
1347 make_pat (Tpat_variant
(l1,Some
r,row)) p
.pat_type p
.pat_env
1348 | Tpat_variant
(l1,None
,row), Tpat_variant
(l2
,None
,_)
1350 | Tpat_record
l1,Tpat_record l2
->
1351 let rs = record_lubs
l1 l2
in
1352 make_pat (Tpat_record
rs) p
.pat_type p
.pat_env
1353 | Tpat_array
ps, Tpat_array qs
1354 when List.length
ps = List.length qs
->
1355 let rs = lubs
ps qs
in
1356 make_pat (Tpat_array
rs) p
.pat_type p
.pat_env
1362 let r1 = lub p1 q
in
1364 {q
with pat_desc
=(Tpat_or
(r1,lub p2 q
,None
))}
1370 and record_lubs
l1 l2
=
1371 let l1 = sort_fields l1 and l2
= sort_fields l2
in
1372 let rec lub_rec l1 l2
= match l1,l2
with
1375 | (lbl1
,p1
)::rem1
, (lbl2
,p2
)::rem2
->
1376 if lbl1
.lbl_pos
< lbl2
.lbl_pos
then
1377 (lbl1
,p1
)::lub_rec rem1 l2
1378 else if lbl2
.lbl_pos
< lbl1
.lbl_pos
then
1379 (lbl2
,p2
)::lub_rec l1 rem2
1381 (lbl1
,lub p1 p2
)::lub_rec rem1 rem2
in
1384 and lubs
ps qs
= match ps,qs
with
1385 | p
::ps, q
::qs
-> lub p q
:: lubs
ps qs
1389 (******************************)
1390 (* Exported variant closing *)
1391 (******************************)
1393 (* Apply pressure to variants *)
1395 let pressure_variants tdefs patl
=
1396 let pss = List.map
(fun p
-> [p
;omega]) patl
in
1397 ignore
(pressure_variants (Some tdefs
) pss)
1399 (*****************************)
1400 (* Utilities for diagnostics *)
1401 (*****************************)
1404 Build up a working pattern matrix by forgetting
1405 about guarded patterns
1408 let has_guard act
= match act
.exp_desc
with
1409 | Texp_when
(_, _) -> true
1413 let rec initial_matrix = function
1415 | (pat
, act
) :: rem
->
1420 [pat
] :: initial_matrix rem
1422 (******************************************)
1423 (* Look for a row that matches some value *)
1424 (******************************************)
1427 Useful for seeing if the example of
1428 non-matched value can indeed be matched
1429 (by a guarded clause)
1436 let rec initial_all no_guard
= function
1442 | (pat
, act
) :: rem
->
1443 ([pat
], pat
.pat_loc
) :: initial_all (no_guard
&& not
(has_guard act
)) rem
1446 let rec do_filter_var = function
1447 | (_::ps,loc
)::rem
-> (ps,loc
)::do_filter_var rem
1450 let do_filter_one q
pss =
1451 let rec filter_rec = function
1452 | ({pat_desc
= Tpat_alias
(p
,_)}::ps,loc
)::pss ->
1453 filter_rec ((p
::ps,loc
)::pss)
1454 | ({pat_desc
= Tpat_or
(p1
,p2
,_)}::ps,loc
)::pss ->
1455 filter_rec ((p1
::ps,loc
)::(p2
::ps,loc
)::pss)
1456 | (p
::ps,loc
)::pss ->
1458 then (simple_match_args q p
@ ps, loc
) :: filter_rec pss
1463 let rec do_match pss qs
= match qs
with
1465 begin match pss with
1466 | ([],loc
)::_ -> Some loc
1469 | q
::qs
-> match q
with
1470 | {pat_desc
= Tpat_or
(q1,q2
,_)} ->
1471 begin match do_match pss (q1::qs
) with
1472 | None
-> do_match pss (q2
::qs
)
1475 | {pat_desc
= Tpat_any
} ->
1476 do_match (do_filter_var pss) qs
1478 let q0 = normalize_pat q
in
1479 do_match (do_filter_one q0 pss) (simple_match_args q0 q
@ qs
)
1482 let check_partial_all v casel
=
1484 let pss = initial_all true casel
in
1489 (************************)
1490 (* Exhaustiveness check *)
1491 (************************)
1493 let do_check_partial loc casel
pss = match pss with
1497 - For empty matches generated by ocamlp4 (no warning)
1498 - when all patterns have guards (then, casel <> [])
1500 Then match MUST be considered non-exhaustive,
1501 otherwise compilation of PM is broken.
1503 begin match casel
with
1505 | _ -> Location.prerr_warning loc
Warnings.All_clauses_guarded
1509 begin match exhaust None
pss (List.length
ps) with
1514 let buf = Buffer.create
16 in
1515 let fmt = formatter_of_buffer
buf in
1517 begin match check_partial_all v casel
with
1520 (* This is 'Some loc', where loc is the location of
1521 a possibly matching clause.
1522 Forget about loc, because printing two locations
1523 is a pain in the top-level *)
1524 Buffer.add_string
buf
1525 "\n(However, some guarded clause may match this value.)"
1530 Location.prerr_warning loc
(Warnings.Partial_match
errmsg) ;
1533 fatal_error
"Parmatch.check_partial"
1541 (* Collect all data types in a pattern *)
1543 let rec add_path path = function
1545 | x
::rem
as paths
->
1546 if Path.same
path x
then paths
1547 else x
::add_path path rem
1549 let extendable_path path =
1551 (Path.same
path Predef.path_bool
||
1552 Path.same
path Predef.path_list
||
1553 Path.same
path Predef.path_option
)
1555 let rec collect_paths_from_pat r p
= match p
.pat_desc
with
1556 | Tpat_construct
({cstr_tag
=(Cstr_constant
_|Cstr_block
_)},ps) ->
1557 let path = get_type_path p
.pat_type p
.pat_env
in
1559 collect_paths_from_pat
1560 (if extendable_path path then add_path path r else r)
1562 | Tpat_any
|Tpat_var
_|Tpat_constant
_| Tpat_variant
(_,None
,_) -> r
1563 | Tpat_tuple
ps | Tpat_array
ps
1564 | Tpat_construct
({cstr_tag
=Cstr_exception
_}, ps)->
1565 List.fold_left
collect_paths_from_pat r ps
1566 | Tpat_record lps
->
1568 (fun r (_,p
) -> collect_paths_from_pat r p
)
1570 | Tpat_variant
(_, Some p
, _) | Tpat_alias
(p
,_) -> collect_paths_from_pat r p
1571 | Tpat_or
(p1
,p2
,_) ->
1572 collect_paths_from_pat (collect_paths_from_pat r p1
) p2
1576 Actual fragile check
1577 1. Collect data types in the patterns of the match.
1578 2. One exhautivity check per datatype, considering that
1579 the type is extended.
1582 let do_check_fragile loc casel
pss =
1585 (fun r (p
,_) -> collect_paths_from_pat r p
)
1589 | _ -> match pss with
1594 match exhaust (Some ext
) pss (List.length
ps) with
1596 Location.prerr_warning
1598 (Warnings.Fragile_match
(Path.name ext
))
1603 (********************************)
1604 (* Exported exhustiveness check *)
1605 (********************************)
1608 Fragile check is performed when required and
1609 on exhaustive matches only.
1612 let check_partial loc casel
=
1613 if Warnings.is_active
(Warnings.Partial_match
"") then begin
1614 let pss = initial_matrix casel
in
1615 let pss = get_mins le_pats
pss in
1616 let total = do_check_partial loc casel
pss in
1618 total = Total
&& Warnings.is_active
(Warnings.Fragile_match
"")
1620 do_check_fragile loc casel
pss
1627 (********************************)
1628 (* Exported unused clause check *)
1629 (********************************)
1631 let check_unused tdefs casel
=
1632 if Warnings.is_active
Warnings.Unused_match
then
1633 let rec do_rec pref
= function
1639 get_mins le_pats
(List.filter
(compats
qs) pref
) in
1640 let r = every_satisfiables (make_rows pss) (make_row qs) in
1643 Location.prerr_warning
1644 q
.pat_loc
Warnings.Unused_match
1648 Location.prerr_warning
1649 p
.pat_loc
Warnings.Unused_pat
)
1652 with e
-> assert false
1655 if has_guard act
then
1658 do_rec ([q
]::pref
) rem
in