merge-more-functions
parent
93c087ae28
commit
afd03f2934
|
@ -1218,16 +1218,16 @@ and transl_apply ?(should_be_tailcall=false) ?(inlined = Default_inline)
|
|||
: Lambda.lambda)
|
||||
|
||||
and transl_function loc untuplify_fn repr partial param cases =
|
||||
match cases with
|
||||
match cases, partial with
|
||||
[{c_lhs=pat; c_guard=None;
|
||||
c_rhs={exp_desc = Texp_function { arg_label = _; param = param'; cases;
|
||||
partial = partial'; }} as exp}]
|
||||
when Parmatch.fluid pat ->
|
||||
partial = partial'; }} as exp}], Total
|
||||
when Parmatch.inactive pat ->
|
||||
let ((_, params), body) =
|
||||
transl_function exp.exp_loc false repr partial' param' cases in
|
||||
((Curried, param :: params),
|
||||
Matching.for_function loc None (Lvar param) [pat, body] partial)
|
||||
| {c_lhs={pat_desc = Tpat_tuple pl}} :: _ when untuplify_fn ->
|
||||
| {c_lhs={pat_desc = Tpat_tuple pl}} :: _, _ when untuplify_fn ->
|
||||
begin try
|
||||
let size = List.length pl in
|
||||
let pats_expr_list =
|
||||
|
|
|
@ -2004,23 +2004,20 @@ let irrefutable pat = le_pat pat omega
|
|||
trivial computations (tag/equality tests).
|
||||
Patterns containing (lazy _) subpatterns are active. *)
|
||||
|
||||
let rec inactive pat = match pat with
|
||||
| Tpat_lazy _ ->
|
||||
false
|
||||
| Tpat_any | Tpat_var _ | Tpat_constant _ | Tpat_variant (_, None, _) ->
|
||||
true
|
||||
| Tpat_tuple ps | Tpat_construct (_, _, ps) | Tpat_array ps ->
|
||||
List.for_all (fun p -> inactive p.pat_desc) ps
|
||||
| Tpat_alias (p,_,_) | Tpat_variant (_, Some p, _) ->
|
||||
inactive p.pat_desc
|
||||
| Tpat_record (ldps,_) ->
|
||||
List.exists (fun (_, _, p) -> inactive p.pat_desc) ldps
|
||||
| Tpat_or (p,q,_) ->
|
||||
inactive p.pat_desc && inactive q.pat_desc
|
||||
|
||||
(* A `fluid' pattern is both irrefutable and inactive *)
|
||||
|
||||
let fluid pat = irrefutable pat && inactive pat.pat_desc
|
||||
let rec inactive pat =
|
||||
match pat.pat_desc with
|
||||
| Tpat_lazy _ ->
|
||||
false
|
||||
| Tpat_any | Tpat_var _ | Tpat_constant _ | Tpat_variant (_, None, _) ->
|
||||
true
|
||||
| Tpat_tuple ps | Tpat_construct (_, _, ps) | Tpat_array ps ->
|
||||
List.for_all (fun p -> inactive p) ps
|
||||
| Tpat_alias (p,_,_) | Tpat_variant (_, Some p, _) ->
|
||||
inactive p
|
||||
| Tpat_record (ldps,_) ->
|
||||
List.exists (fun (_, _, p) -> inactive p) ldps
|
||||
| Tpat_or (p,q,_) ->
|
||||
inactive p && inactive q
|
||||
|
||||
|
||||
|
||||
|
|
|
@ -75,7 +75,7 @@ val check_unused:
|
|||
|
||||
(* Irrefutability tests *)
|
||||
val irrefutable : pattern -> bool
|
||||
val fluid : pattern -> bool
|
||||
val inactive : pattern -> bool
|
||||
|
||||
(* Ambiguous bindings *)
|
||||
val check_ambiguous_bindings : case list -> unit
|
||||
|
|
Loading…
Reference in New Issue