Module Generator1

module Generator1: sig .. end

type t = {
   mutable generator0 : Generator0.t;
   mutable env : Environment.t;
}
type earray = {
   mutable generator0_array : Generator0.t array;
   mutable array_env : Environment.t;
}

APRON Generators and array of generators of level 1

type typ = Generator0.typ = 
| LINE
| RAY
| VERTEX
| LINEMOD
| RAYMOD
val make : Linexpr1.t -> Generator0.typ -> t

Make a generator. Modifying later the linear expression (not advisable) modifies correspondingly the generator and conversely, except for changes of environments

val copy : t -> t

Copy (deep copy)

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

Print the generator

val get_typ : t -> Generator0.typ

Get the generator type

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

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

val set_typ : t -> Generator0.typ -> unit

Set the generator type

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

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

Set simultaneously a number of coefficients, as set_list.

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

Get the coefficient of the variable in the underlying linear expression

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

Set the coefficient of the variable in the underlying linear expression

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

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

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

Side-effect version of the previous function

Type earray

val array_make : Environment.t -> int -> earray

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

Print an array of generators

val array_length : earray -> int

Get the size of the array

val array_get : earray -> int -> t

Get the element of the given index (which is not a copy)

val array_set : earray -> int -> t -> unit

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

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

Side-effect version of the previous function

val get_env : t -> Environment.t

Get the environment of the generator

val get_linexpr1 : t -> Linexpr1.t

Get 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.t

Get 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