Module Linexpr0

module Linexpr0: sig .. end

type t 

APRON Linear expressions of level 0

val make : int option -> t

Create a linear expression. Its representation is sparse if None is provided, dense of size size if Some size is provided.

val of_list : int option -> (Coeff.t * Dim.t) list -> Coeff.t option -> t

Combines Linexpr0.make and Linexpr0.set_list (see below)

val of_array : int option -> (Coeff.t * Dim.t) array -> Coeff.t option -> t

Combines Linexpr0.make and Linexpr0.set_array (see below)

val minimize : t -> unit

In case of sparse representation, remove zero coefficients

val copy : t -> t

Copy

val compare : t -> t -> int

Comparison with lexicographic ordering using Coeff.cmp, terminating by constant

val hash : t -> int

Hashing function

val get_size : t -> int

Get the size of the linear expression (which may be sparse or dense)

val get_cst : t -> Coeff.t

Get the constant

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

Get the coefficient corresponding to the dimension

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

Set simultaneously a number of coefficients.

set_list expr [(c1,1); (c2,2)] (Some cst) assigns coefficients c1 to dimension 1, coefficient c2 to dimension 2, 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 * Dim.t) array -> Coeff.t option -> unit

Set simultaneously a number of coefficients, as set_list.

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

Set the constant

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

Set the coefficient corresponding to the dimension

Iter the function on the pairs coefficient/dimension of the linear expression

val iter : (Coeff.t -> Dim.t -> unit) -> t -> unit
val print : (Dim.t -> string) -> Stdlib.Format.formatter -> t -> unit

Print a linear expression, using a function converting from dimensions to names