sig
type t = { mutable linexpr0 : Linexpr0.t; mutable env : Environment.t; }
val make : ?sparse:bool -> Environment.t -> Linexpr1.t
val minimize : Linexpr1.t -> unit
val copy : Linexpr1.t -> Linexpr1.t
val print : Stdlib.Format.formatter -> Linexpr1.t -> unit
val set_list :
Linexpr1.t -> (Coeff.t * Var.t) list -> Coeff.t option -> unit
val set_array :
Linexpr1.t -> (Coeff.t * Var.t) array -> Coeff.t option -> unit
val iter : (Coeff.t -> Var.t -> unit) -> Linexpr1.t -> unit
val get_cst : Linexpr1.t -> Coeff.t
val set_cst : Linexpr1.t -> Coeff.t -> unit
external get_coeff : Linexpr1.t -> Var.t -> Coeff.t
= "camlidl_linexpr1_ap_linexpr1_get_coeff"
external set_coeff : Linexpr1.t -> Var.t -> Coeff.t -> unit
= "camlidl_linexpr1_ap_linexpr1_set_coeff"
external extend_environment : Linexpr1.t -> Environment.t -> Linexpr1.t
= "camlidl_linexpr1_ap_linexpr1_extend_environment"
external extend_environment_with : Linexpr1.t -> Environment.t -> unit
= "camlidl_linexpr1_ap_linexpr1_extend_environment_with"
external is_integer : Linexpr1.t -> bool
= "camlidl_linexpr1_ap_linexpr1_is_integer"
external is_real : Linexpr1.t -> bool
= "camlidl_linexpr1_ap_linexpr1_is_real"
val get_linexpr0 : Linexpr1.t -> Linexpr0.t
val get_env : Linexpr1.t -> Environment.t
end