Module Disjunction

module Disjunction: sig .. end

Disjunctions of APRON abstract values


type 'a t 
val manager_alloc : 'a Manager.t -> 'a t Manager.t
val manager_decompose : 'a t Manager.t -> 'a Manager.t
val to_lincons0_set : 'a t Manager.t ->
'a t Abstract0.t -> Lincons0.t array
val to_lincons1_set : 'a t Manager.t -> 'a t Abstract1.t -> Lincons1.earray
val _decompose : 'a t Manager.t ->
'a t Abstract0.t -> 'a Abstract0.t array * int

Decompose an abstract value

val decompose : 'a t Manager.t ->
'a t Abstract0.t -> 'a Abstract0.t array
val compose : 'a t Manager.t ->
'a Abstract0.t array -> 'a t Abstract0.t

Type conversions

val manager_is_disjunction : 'a Manager.t -> bool

Return true iff the argument manager is a disjunction manager

val manager_of_disjunction : 'a t Manager.t -> 'b Manager.t

Make a disjunction manager generic

val manager_to_disjunction : 'a Manager.t -> 'b t Manager.t

Instanciate the type of a disjunction manager. Raises Failure if the argument manager is not a disjunction manager

module Abstract0: sig .. end
module Abstract1: sig .. end