Parmatch
Detection of partial matches and unused match cases.
val const_compare : Asttypes.constant -> Asttypes.constant -> int
const_compare c1 c2
compares the actual values represented by c1
and c2
, while simply using Stdlib.compare
would compare the representations.
cf. MPR#5758
val le_pat : Typedtree.pattern -> Typedtree.pattern -> bool
le_pat p q
means: forall V, V matches q implies V matches p
val le_pats : Typedtree.pattern list -> Typedtree.pattern list -> bool
le_pats (p1 .. pm) (q1 .. qn)
means: forall i <= m, le_pat pi qi
Exported compatibility functor, abstracted over constructor equality
val lub : Typedtree.pattern -> Typedtree.pattern -> Typedtree.pattern
lub p q
is a pattern that matches all values matched by p
and q
. May raise Empty
, when p
and q
are not compatible.
val lubs : Typedtree.pattern list -> Typedtree.pattern list -> Typedtree.pattern list
lubs [p1; ...; pn] [q1; ...; qk]
, where n < k
, is [lub p1 q1; ...; lub pk qk]
.
val set_args : Typedtree.pattern -> Typedtree.pattern list -> Typedtree.pattern list
Those two functions recombine one pattern and its arguments: For instance: (_,_)::p1::p2::rem -> (p1, p2)::rem The second one will replace mutable arguments by '_'
val set_args_erase_mutable : Typedtree.pattern -> Typedtree.pattern list -> Typedtree.pattern list
val pat_of_constr : Typedtree.pattern -> Types.constructor_description -> Typedtree.pattern
val complete_constrs : Types.constructor_description Typedtree.pattern_data -> Types.constructor_tag list -> Types.constructor_description list
ppat_of_type
builds an untyped pattern from its expected type, for explosion of wildcard patterns in Typecore.type_pat.
There are four interesting cases:
PT_empty
)PT_any
)PE_single
)PE_gadt_cases
).type ppat_of_type =
| PT_empty |
| PT_any |
| PT_pattern of pat_explosion * Parsetree.pattern * (string, Types.constructor_description) Hashtbl.t * (string, Types.label_description) Hashtbl.t |
val ppat_of_type : Env.t -> Types.type_expr -> ppat_of_type
val pressure_variants : Env.t -> Typedtree.pattern list -> unit
val pressure_variants_in_computation_pattern : Env.t -> Typedtree.computation Typedtree.general_pattern list -> unit
val check_partial : ((string, Types.constructor_description) Hashtbl.t -> (string, Types.label_description) Hashtbl.t -> Parsetree.pattern -> Typedtree.pattern option) -> Location.t -> Typedtree.value Typedtree.case list -> Typedtree.partial
check_partial pred loc caselist
and check_unused refute pred caselist
are called with a function pred
which will be given counter-example candidates: they may be partially ill-typed, and have to be type-checked to extract a valid counter-example. pred
returns a valid counter-example or None
. refute
indicates that check_unused
was called on a refutation clause.
val check_unused : (bool -> (string, Types.constructor_description) Hashtbl.t -> (string, Types.label_description) Hashtbl.t -> Parsetree.pattern -> Typedtree.pattern option) -> Typedtree.value Typedtree.case list -> unit
val irrefutable : Typedtree.pattern -> bool
val inactive : partial:Typedtree.partial -> Typedtree.pattern -> bool
An inactive pattern is a pattern, matching against which can be duplicated, erased or delayed without change in observable behavior of the program. Patterns containing (lazy _) subpatterns or reads of mutable fields are active.
val check_ambiguous_bindings : Typedtree.value Typedtree.case list -> unit
val some_private_tag : Asttypes.label