Module Texpr1

module Texpr1: sig .. end

type t = {
   mutable texpr0 : Texpr0.t;
   mutable env : Environment.t;
}

APRON Expressions of level 1

type unop = Texpr0.unop = 
| Neg
| Cast
| Sqrt

Unary operators

type binop = Texpr0.binop = 
| Add
| Sub
| Mul
| Div
| Mod
| Pow

Binary operators

type typ = Texpr0.typ = 
| Real
| Int
| Single
| Double
| Extended
| Quad

Destination type for rounding

type round = Texpr0.round = 
| Near
| Zero
| Up
| Down
| Rnd

Rounding direction

type expr = 
| Cst of Coeff.t
| Var of Var.t
| Unop of unop * expr * typ * round
| Binop of binop * expr * expr * typ * round

User type for tree expressions

Constructors and Destructor

val of_expr : Environment.t -> expr -> t

General constructor (actually the most efficient)

val copy : t -> t

Copy

val of_linexpr : Linexpr1.t -> t

Conversion

val to_expr : t -> expr

General destructor

Incremental constructors

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

Tests

val 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

Operations

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

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

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

Side-effet version of the previous function

val get_texpr0 : t -> Texpr0.t

Get the underlying expression of level 0 (which is not a copy).

val get_env : t -> Environment.t

Get the environment of the expression

Printing

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

Print a tree expression

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

Print an abstract tree expression