module Generator1:sig..end
type t = {
|
mutable generator0 : |
|
mutable env : |
}
type earray = {
|
mutable generator0_array : |
|
mutable array_env : |
}
APRON Generators and array of generators of level 1
NOTE: Generators 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.
typetyp =Generator0.typ=
| |
LINE |
| |
RAY |
| |
VERTEX |
| |
LINEMOD |
| |
RAYMOD |
val make : Linexpr1.t -> Generator0.typ -> tMake a generator. Modifying later the linear expression (not advisable) modifies correspondingly the generator and conversely, except for changes of environments
val copy : t -> tCopy (deep copy)
val print : Stdlib.Format.formatter -> t -> unitPrint the generator
val get_typ : t -> Generator0.typGet the generator type
val iter : (Coeff.t -> Var.t -> unit) -> t -> unitIter the function on the pair coefficient/variable of the underlying linear expression
val set_typ : t -> Generator0.typ -> unitSet the generator type
val set_list : t -> (Coeff.t * Var.t) list -> unitSet simultaneously a number of coefficients.
set_list expr [(c1,"x"); (c2,"y")] assigns coefficients c1
to variable "x" and coefficient c2 to variable "y".
val set_array : t -> (Coeff.t * Var.t) array -> unitSet simultaneously a number of coefficients, as set_list.
val get_coeff : t -> Var.t -> Coeff.tGet the coefficient of the variable in the underlying linear expression
val set_coeff : t -> Var.t -> Coeff.t -> unitSet the coefficient of the variable in the underlying linear expression
val extend_environment : t -> Environment.t -> tChange the environment of the generator for a super-environment. Raise Failure if it is not the case
val extend_environment_with : t -> Environment.t -> unitSide-effect version of the previous function
val array_make : Environment.t -> int -> earrayMake an array of generators with the given size and defined on the given environment. The elements are initialized with the line 0.
val array_print : ?first:(unit, Stdlib.Format.formatter, unit) Stdlib.format ->
?sep:(unit, Stdlib.Format.formatter, unit) Stdlib.format ->
?last:(unit, Stdlib.Format.formatter, unit) Stdlib.format ->
Stdlib.Format.formatter -> earray -> unitPrint an array of generators
val array_length : earray -> intGet the size of the array
val array_get : earray -> int -> tGet the element of the given index (which is not a copy)
val array_set : earray -> int -> t -> unitSet the element of the given index (without any copy). The array and the
generator should be defined on the same environment; otherwise a Failure
exception is raised.
val array_extend_environment : earray -> Environment.t -> earrayChange the environment of the array of generators for a super-environment. Raise Failure if it is not the case
val array_extend_environment_with : earray -> Environment.t -> unitSide-effect version of the previous function
val get_env : t -> Environment.tGet the environment of the generator
val get_linexpr1 : t -> Linexpr1.tGet the underlying linear expression. Modifying the linear expression (not advisable) modifies correspondingly the generator and conversely, except for changes of environments
val get_generator0 : t -> Generator0.tGet the underlying generator of level 0. Modifying the generator of level 0 (not advisable) modifies correspondingly the generator and conversely, except for changes of environments