Module Linexpr1

module Linexpr1: sig .. end

type t = {
   mutable linexpr0 : Linexpr0.t;
   mutable env : Environment.t;
}

APRON Expressions of level 1

val make : ?sparse:bool -> Environment.t -> t

Build a linear expression defined on the given argument, which is sparse by default.

val minimize : t -> unit

In case of sparse representation, remove zero coefficients

val copy : t -> t

Copy

val print : Stdlib.Format.formatter -> t -> unit

Print the linear expression

val set_list : t -> (Coeff.t * Var.t) list -> Coeff.t option -> unit

Set 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 -> unit

Set simultaneously a number of coefficients, as set_list.

val iter : (Coeff.t -> Var.t -> unit) -> t -> unit

Iter the function on the pair coefficient/variable of the linear expression

val get_cst : t -> Coeff.t

Get the constant

val set_cst : t -> Coeff.t -> unit

Set the constant

val get_coeff : t -> Var.t -> Coeff.t

Get the coefficient of the variable

val set_coeff : t -> Var.t -> Coeff.t -> unit

Set the coefficient of the variable

val extend_environment : t -> Environment.t -> t

Change the environment of the expression for a super-environment. Raise Failure if it is not the case

val extend_environment_with : t -> Environment.t -> unit

Side-effet version of the previous function

val is_integer : t -> bool

Does the linear expression depend only on integer variables ?

val is_real : t -> bool

Does the linear expression depend only on real variables ?

val get_linexpr0 : t -> Linexpr0.t

Get the underlying expression of level 0 (which is not a copy).

val get_env : t -> Environment.t

Get the environment of the expression