Module Mach

type integer_comparison =
| Isigned of Cmm.integer_comparison
| Iunsigned of Cmm.integer_comparison
type integer_operation =
| Iadd
| Isub
| Imul
| Imulh
| Idiv
| Imod
| Iand
| Ior
| Ixor
| Ilsl
| Ilsr
| Iasr
| Icomp of integer_comparison
| Icheckbound
type float_comparison = Cmm.float_comparison
type test =
| Itruetest
| Ifalsetest
| Iinttest of integer_comparison
| Iinttest_imm of integer_comparison * int
| Ifloattest of float_comparison
| Ioddtest
| Ieventest
type operation =
| Imove
| Ispill
| Ireload
| Iconst_int of nativeint
| Iconst_float of int64
| Iconst_symbol of string
| Icall_ind
| Icall_imm of {
func : string;
}
| Itailcall_ind
| Itailcall_imm of {
func : string;
}
| Iextcall of {
func : string;
ty_res : Cmm.machtype;
ty_args : Cmm.exttype list;
alloc : bool;
}
| Istackoffset of int
| Iload of Cmm.memory_chunk * Arch.addressing_mode
| Istore of Cmm.memory_chunk * Arch.addressing_mode * bool
| Ialloc of {
bytes : int;
dbginfo : Debuginfo.alloc_dbginfo;
}
| Iintop of integer_operation
| Iintop_imm of integer_operation * int
| Inegf
| Iabsf
| Iaddf
| Isubf
| Imulf
| Idivf
| Ifloatofint
| Iintoffloat
| Ispecific of Arch.specific_operation
| Iname_for_debugger of {
ident : Backend_var.t;
which_parameter : int option;
provenance : unit option;
is_assignment : bool;
}
(*

Iname_for_debugger has the following semantics: (a) The argument register(s) is/are deemed to contain the value of the given identifier. (b) If is_assignment is true, any information about other Reg.ts that have been previously deemed to hold the value of that identifier is forgotten.

*)
type instruction = {
desc : instruction_desc;
next : instruction;
arg : Reg.t array;
res : Reg.t array;
dbg : Debuginfo.t;
mutable live : Reg.Set.t;
mutable available_before : Reg_availability_set.t;
mutable available_across : Reg_availability_set.t option;
}
and instruction_desc =
| Iend
| Iop of operation
| Ireturn
| Iifthenelse of test * instruction * instruction
| Iswitch of int array * instruction array
| Icatch of Cmm.rec_flag * (int * instruction) list * instruction
| Iexit of int
| Itrywith of instruction * instruction
| Iraise of Lambda.raise_kind
type fundecl = {
fun_name : string;
fun_args : Reg.t array;
fun_body : instruction;
fun_codegen_options : Cmm.codegen_option list;
fun_dbg : Debuginfo.t;
fun_num_stack_slots : int array;
fun_contains_calls : bool;
}
val dummy_instr : instruction
val end_instr : unit -> instruction
val instr_cons : instruction_desc -> Reg.t array -> Reg.t array -> instruction -> instruction
val instr_cons_debug : instruction_desc -> Reg.t array -> Reg.t array -> Debuginfo.t -> instruction -> instruction
val instr_iter : (instruction -> unit) -> instruction -> unit
val operation_can_raise : operation -> bool