Cmmtype machtype = machtype_component arrayval typ_void : machtypeval typ_val : machtypeval typ_addr : machtypeval typ_int : machtypeval typ_float : machtypeval lub_component : machtype_component -> machtype_component -> machtype_componentLeast upper bound of two machtype_components.
val ge_component : machtype_component -> machtype_component -> boolReturns true iff the first supplied machtype_component is greater than or equal to the second under the relation used by lub_component.
type exttype = | XInt | (* r OCaml value, word-sized integer *) |
| XInt32 | (* r 32-bit integer *) |
| XInt64 | (* r 64-bit integer *) |
| XFloat | (* r double-precision FP number *) |
A variant of machtype used to describe arguments to external C functions
val negate_integer_comparison : integer_comparison -> integer_comparisonval swap_integer_comparison : integer_comparison -> integer_comparisontype float_comparison = Lambda.float_comparison = | CFeq |
| CFneq |
| CFlt |
| CFnlt |
| CFgt |
| CFngt |
| CFle |
| CFnle |
| CFge |
| CFnge |
val negate_float_comparison : float_comparison -> float_comparisonval swap_float_comparison : float_comparison -> float_comparisonval new_label : unit -> labelval set_label : label -> unitval cur_label : unit -> labeltype 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. *) |
and operation = | Capply of machtype | |
| Cextcall of string * machtype * exttype list * bool | (* The |
| 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 = | Cconst_int of int * Debuginfo.t |
| Cconst_natint of nativeint * Debuginfo.t |
| Cconst_float of float * Debuginfo.t |
| Cconst_symbol of string * Debuginfo.t |
| Cvar of Backend_var.t |
| Clet of Backend_var.With_provenance.t * expression * expression |
| Clet_mut of Backend_var.With_provenance.t * machtype * expression * expression |
| Cphantom_let of Backend_var.With_provenance.t * phantom_defining_expr option * expression |
| Cassign of Backend_var.t * expression |
| Ctuple of expression list |
| Cop of operation * expression list * Debuginfo.t |
| Csequence of expression * expression |
| Cifthenelse of expression * Debuginfo.t * expression * Debuginfo.t * expression * Debuginfo.t |
| Cswitch of expression * int array * (expression * Debuginfo.t) array * Debuginfo.t |
| Ccatch of rec_flag * (int * (Backend_var.With_provenance.t * machtype) list * expression * Debuginfo.t) list * expression |
| Cexit of int * expression list |
| Ctrywith of expression * Backend_var.With_provenance.t * expression * Debuginfo.t |
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; |
}val ccatch : (int * (Backend_var.With_provenance.t * machtype) list * expression * expression * Debuginfo.t) -> expressionval iter_shallow_tail : (expression -> unit) -> expression -> boolEither 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 -> expressionApply 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 -> expressionApply the transformation to each immediate sub-expression.