sig
type t
and unop = Neg | Cast | Sqrt
and binop = Add | Sub | Mul | Div | Mod | Pow
and typ = Real | Int | Single | Double | Extended | Quad
and round = Near | Zero | Up | Down | Rnd
type expr =
Cst of Coeff.t
| Dim of Dim.t
| Unop of Texpr0.unop * Texpr0.expr * Texpr0.typ * Texpr0.round
| Binop of Texpr0.binop * Texpr0.expr * Texpr0.expr * Texpr0.typ *
Texpr0.round
external of_expr : Texpr0.expr -> Texpr0.t
= "camlidl_texpr0_ap_texpr0_of_expr"
external copy : Texpr0.t -> Texpr0.t = "camlidl_texpr0_ap_texpr0_copy"
external of_linexpr : Linexpr0.t -> Texpr0.t
= "camlidl_texpr0_ap_texpr0_of_linexpr"
external to_expr : Texpr0.t -> Texpr0.expr
= "camlidl_texpr0_ap_texpr0_to_expr"
external cst : Coeff.t -> Texpr0.t = "camlidl_texpr0_ap_texpr0_cst"
external dim : Dim.t -> Texpr0.t = "camlidl_texpr0_ap_texpr0_dim"
external unop :
Texpr0.unop -> Texpr0.t -> Texpr0.typ -> Texpr0.round -> Texpr0.t
= "camlidl_texpr0_ap_texpr0_unop"
external binop :
Texpr0.binop ->
Texpr0.typ -> Texpr0.round -> Texpr0.t -> Texpr0.t -> Texpr0.t
= "camlidl_texpr0_ap_texpr0_binop"
external is_interval_cst : Texpr0.t -> bool
= "camlidl_texpr0_ap_texpr0_is_interval_cst"
external is_interval_linear : Texpr0.t -> bool
= "camlidl_texpr0_ap_texpr0_is_interval_linear"
external is_interval_polynomial : Texpr0.t -> bool
= "camlidl_texpr0_ap_texpr0_is_interval_polynomial"
external is_interval_polyfrac : Texpr0.t -> bool
= "camlidl_texpr0_ap_texpr0_is_interval_polyfrac"
external is_scalar : Texpr0.t -> bool
= "camlidl_texpr0_ap_texpr0_is_scalar"
val string_of_unop : Texpr0.unop -> string
val string_of_binop : Texpr0.binop -> string
val string_of_typ : Texpr0.typ -> string
val string_of_round : Texpr0.round -> string
val print_unop : Stdlib.Format.formatter -> Texpr0.unop -> unit
val print_binop : Stdlib.Format.formatter -> Texpr0.binop -> unit
val print_typ : Stdlib.Format.formatter -> Texpr0.typ -> unit
val print_round : Stdlib.Format.formatter -> Texpr0.round -> unit
val print_expr :
(Dim.t -> string) -> Stdlib.Format.formatter -> Texpr0.expr -> unit
val print :
(Dim.t -> string) -> Stdlib.Format.formatter -> Texpr0.t -> unit
val print_sprint_unop : Texpr0.unop -> Texpr0.typ -> Texpr0.round -> string
val print_sprint_binop :
Texpr0.binop -> Texpr0.typ -> Texpr0.round -> string
val print_precedence_of_unop : Texpr0.unop -> int
val print_precedence_of_binop : Texpr0.binop -> int
end