module Linexpr1:sig..end
type t = {
|
mutable linexpr0 : |
|
mutable env : |
}
APRON Expressions of level 1
NOTE: Linear expressions are not totally ordered.
As of 0.9.15, they do not implement the polymorphic compare function to avoid confusion.
As a consequence, the polymorphic =, <=, etc. operators cannot be used.
Use Linexpr0.equal and Linexpr0.cmp on the linexpr0 field instead.
val make : ?sparse:bool -> Environment.t -> tBuild a linear expression defined on the given argument, which is sparse by default.
val minimize : t -> unitIn case of sparse representation, remove zero coefficients
val copy : t -> tCopy
val print : Stdlib.Format.formatter -> t -> unitPrint the linear expression
val set_list : t -> (Coeff.t * Var.t) list -> Coeff.t option -> unitSet simultaneously a number of coefficients.
set_list expr [(c1,"x"); (c2,"y")] (Some cst) assigns coefficients c1
to variable "x", coefficient c2 to variable "y", and coefficient cst
to the constant. If (Some cst) is replaced by None,
the constant coefficient is not assigned.
val set_array : t -> (Coeff.t * Var.t) array -> Coeff.t option -> unitSet simultaneously a number of coefficients, as set_list.
val iter : (Coeff.t -> Var.t -> unit) -> t -> unitIter the function on the pair coefficient/variable of the linear expression
val get_cst : t -> Coeff.tGet the constant
val set_cst : t -> Coeff.t -> unitSet the constant
val get_coeff : t -> Var.t -> Coeff.tGet the coefficient of the variable
val set_coeff : t -> Var.t -> Coeff.t -> unitSet the coefficient of the variable
val extend_environment : t -> Environment.t -> tChange the environment of the expression for a super-environment. Raise Failure if it is not the case
val extend_environment_with : t -> Environment.t -> unitSide-effet version of the previous function
val is_integer : t -> boolDoes the linear expression depend only on integer variables ?
val is_real : t -> boolDoes the linear expression depend only on real variables ?
val get_linexpr0 : t -> Linexpr0.tGet the underlying expression of level 0 (which is not a copy).
val get_env : t -> Environment.tGet the environment of the expression