type machtype = machtype_component array
val typ_void : machtype
val typ_val : machtype
val typ_addr : machtype
val typ_int : machtype
val typ_float : machtype
val lub_component : machtype_component -> machtype_component -> machtype_component
Least upper bound of two machtype_component
s.
val ge_component : machtype_component -> machtype_component -> bool
Returns true
iff the first supplied machtype_component
is greater than or equal to the second under the relation used by lub_component
.
val negate_integer_comparison : integer_comparison -> integer_comparison
val swap_integer_comparison : integer_comparison -> integer_comparison
type float_comparison = Lambda.float_comparison =
| CFeq |
| CFneq |
| CFlt |
| CFnlt |
| CFgt |
| CFngt |
| CFle |
| CFnle |
| CFge |
| CFnge |
val negate_float_comparison : float_comparison -> float_comparison
val swap_float_comparison : float_comparison -> float_comparison
val new_label : unit -> label
type phantom_defining_expr =
| Cphantom_const_int of Targetint.t | The phantom-let-bound variable is a constant integer. The argument must be the tagged representation of an integer within the range of type | ||
| Cphantom_const_symbol of string | The phantom-let-bound variable is an alias for a symbol. | ||
| Cphantom_var of Backend_var.t | The phantom-let-bound variable is an alias for another variable. The aliased variable must not be a bound by a phantom let. | ||
| Cphantom_offset_var of {
} | The phantom-let-bound-variable's value is defined by adding the given number of words to the pointer contained in the given identifier. | ||
| Cphantom_read_field of {
} | The phantom-let-bound-variable's value is found by adding the given number of words to the pointer contained in the given identifier, then dereferencing. | ||
| Cphantom_read_symbol_field of {
} | As for | ||
| Cphantom_block of {
} | The phantom-let-bound variable points at a block with the given structure. |
type memory_chunk =
| Byte_unsigned |
| Byte_signed |
| Sixteen_unsigned |
| Sixteen_signed |
| Thirtytwo_unsigned |
| Thirtytwo_signed |
| Word_int |
| Word_val |
| Single |
| Double |
| Double_u |
and operation =
| Capply of machtype |
| Cextcall of string * machtype * bool * label option |
| Cload of memory_chunk * Asttypes.mutable_flag |
| Calloc |
| Cstore of memory_chunk * Lambda.initialization_or_assignment |
| Caddi |
| Csubi |
| Cmuli |
| Cmulhi |
| Cdivi |
| Cmodi |
| Cand |
| Cor |
| Cxor |
| Clsl |
| Clsr |
| Casr |
| Ccmpi of integer_comparison |
| Caddv |
| Cadda |
| Ccmpa of integer_comparison |
| Cnegf |
| Cabsf |
| Caddf |
| Csubf |
| Cmulf |
| Cdivf |
| Cfloatofint |
| Cintoffloat |
| Ccmpf of float_comparison |
| Craise of Lambda.raise_kind |
| Ccheckbound |
and expression =
Every basic block should have a corresponding Debuginfo.t
for its beginning.
type fundecl = {
fun_name : string; |
fun_args : (Backend_var.With_provenance.t * machtype) list; |
fun_body : expression; |
fun_codegen_options : codegen_option list; |
fun_dbg : Debuginfo.t; |
}
type data_item =
val ccatch : (int * (Backend_var.With_provenance.t * machtype) list * expression * expression * Debuginfo.t) -> expression
val iter_shallow_tail : (expression -> unit) -> expression -> bool
Either apply the callback to all immediate sub-expressions that can produce the final result for the expression and return true
, or do nothing and return false
. Note that the notion of "tail" sub-expression used here does not match the one used to trigger tail calls; in particular, try...with handlers are considered to be in tail position (because their result become the final result for the expression).
val map_tail : (expression -> expression) -> expression -> expression
Apply the transformation to an expression, trying to push it to all inner sub-expressions that can produce the final result. Same disclaimer as for iter_shallow_tail
about the notion of "tail" sub-expression.
val map_shallow : (expression -> expression) -> expression -> expression
Apply the transformation to each immediate sub-expression.