module Texpr0:sig..end
type t
type unop =
| |
Neg |
| |
Cast |
| |
Sqrt |
Unary operators
type binop =
| |
Add |
| |
Sub |
| |
Mul |
| |
Div |
| |
Mod |
| |
Pow |
Binary operators
type typ =
| |
Real |
| |
Int |
| |
Single |
| |
Double |
| |
Extended |
| |
Quad |
Destination type for rounding
type round =
| |
Near |
| |
Zero |
| |
Up |
| |
Down |
| |
Rnd |
Rounding direction
APRON tree expressions of level 0
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 equal instead.
type expr =
| |
Cst of |
| |
Dim of |
| |
Unop of |
| |
Binop of |
User type for tree expressions
val of_expr : expr -> tGeneral constructor (actually the most efficient
val copy : t -> tCopy
val of_linexpr : Linexpr0.t -> tConversion
val to_expr : t -> exprGeneral destructor
val cst : Coeff.t -> t
val dim : Dim.t -> t
val unop : unop -> t -> typ -> round -> t
val binop : binop ->
typ -> round -> t -> t -> 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 -> bool
val equal : t -> t -> boolEquality test
val hash : t -> intHashing function
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 : (Dim.t -> string) -> Stdlib.Format.formatter -> expr -> unitPrint a tree expression, using a function converting from dimensions to names
val print : (Dim.t -> string) -> Stdlib.Format.formatter -> t -> unitPrint an abstract tree expression, using a function converting from dimensions to names
val print_sprint_unop : unop -> typ -> round -> string
val print_sprint_binop : binop -> typ -> round -> string
val print_precedence_of_unop : unop -> int
val print_precedence_of_binop : binop -> int