module Texpr1:sig..end
type t = {
|
mutable texpr0 : |
|
mutable env : |
}
APRON Expressions of level 1
NOTE: Expressions 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.
Use Texpr0.equal on the texpr0 field instead.
typeunop =Texpr0.unop=
| |
Neg |
| |
Cast |
| |
Sqrt |
Unary operators
typebinop =Texpr0.binop=
| |
Add |
| |
Sub |
| |
Mul |
| |
Div |
| |
Mod |
| |
Pow |
Binary operators
typetyp =Texpr0.typ=
| |
Real |
| |
Int |
| |
Single |
| |
Double |
| |
Extended |
| |
Quad |
Destination type for rounding
typeround =Texpr0.round=
| |
Near |
| |
Zero |
| |
Up |
| |
Down |
| |
Rnd |
Rounding direction
type expr =
| |
Cst of |
| |
Var of |
| |
Unop of |
| |
Binop of |
User type for tree expressions
val of_expr : Environment.t -> expr -> tGeneral constructor (actually the most efficient)
val copy : t -> tCopy
val of_linexpr : Linexpr1.t -> tConversion
val to_expr : t -> exprGeneral destructor
val cst : Environment.t -> Coeff.t -> t
val var : Environment.t -> Var.t -> t
val unop : Texpr0.unop -> t -> Texpr0.typ -> Texpr0.round -> t
val binop : Texpr0.binop ->
t -> t -> Texpr0.typ -> Texpr0.round -> tval is_interval_cst : t -> bool
val is_interval_linear : t -> bool
val is_interval_polynomial : t -> bool
val is_interval_polyfrac : t -> bool
val is_scalar : t -> boolval extend_environment : t -> Environment.t -> tChange the environment of the expression for a super-environment. Raise Failure if it is not the case
val extend_environment_with : t -> Environment.t -> unitSide-effet version of the previous function
val get_texpr0 : t -> Texpr0.tGet the underlying expression of level 0 (which is not a copy).
val get_env : t -> Environment.tGet the environment of the expression
val string_of_unop : unop -> string
val string_of_binop : binop -> string
val string_of_typ : typ -> string
val string_of_round : round -> string
val print_unop : Stdlib.Format.formatter -> unop -> unit
val print_binop : Stdlib.Format.formatter -> binop -> unit
val print_typ : Stdlib.Format.formatter -> typ -> unit
val print_round : Stdlib.Format.formatter -> round -> unit
val print_expr : Stdlib.Format.formatter -> expr -> unitPrint a tree expression
val print : Stdlib.Format.formatter -> t -> unitPrint an abstract tree expression