ocaml/asmcomp/mach.mli

103 lines
3.7 KiB
OCaml

(**************************************************************************)
(* *)
(* OCaml *)
(* *)
(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
(* *)
(* Copyright 1996 Institut National de Recherche en Informatique et *)
(* en Automatique. *)
(* *)
(* All rights reserved. This file is distributed under the terms of *)
(* the GNU Lesser General Public License version 2.1, with the *)
(* special exception on linking described in the file LICENSE. *)
(* *)
(**************************************************************************)
(* Representation of machine code by sequences of pseudoinstructions *)
(** N.B. Backends vary in their treatment of call gc and checkbound
points. If the positioning of any labels associated with these is
important for some new feature in the compiler, the relevant backends'
behaviour should be checked. *)
type label = Cmm.label
type integer_comparison =
Isigned of Cmm.comparison
| Iunsigned of Cmm.comparison
type integer_operation =
Iadd | Isub | Imul | Imulh | Idiv | Imod
| Iand | Ior | Ixor | Ilsl | Ilsr | Iasr
| Icomp of integer_comparison
| Icheckbound of { label_after_error : label option; }
type test =
Itruetest
| Ifalsetest
| Iinttest of integer_comparison
| Iinttest_imm of integer_comparison * int
| Ifloattest of Cmm.comparison * bool
| Ioddtest
| Ieventest
type operation =
Imove
| Ispill
| Ireload
| Iconst_int of nativeint
| Iconst_float of int64
| Iconst_symbol of string
| Iconst_blockheader of nativeint
| Icall_ind of { label_after : label; }
| Icall_imm of { func : string; label_after : label; }
| Itailcall_ind of { label_after : label; }
| Itailcall_imm of { func : string; label_after : label; }
| Iextcall of { func : string; alloc : bool; label_after : label; }
| Istackoffset of int
| Iload of Cmm.memory_chunk * Arch.addressing_mode
| Istore of Cmm.memory_chunk * Arch.addressing_mode * bool
(* false = initialization, true = assignment *)
| Ialloc of { words : int; label_after_call_gc : label option; }
| Iintop of integer_operation
| Iintop_imm of integer_operation * int
| Inegf | Iabsf | Iaddf | Isubf | Imulf | Idivf
| Ifloatofint | Iintoffloat
| Ispecific of Arch.specific_operation
type instruction =
{ desc: instruction_desc;
next: instruction;
arg: Reg.t array;
res: Reg.t array;
dbg: Debuginfo.t;
mutable live: Reg.Set.t }
and instruction_desc =
Iend
| Iop of operation
| Ireturn
| Iifthenelse of test * instruction * instruction
| Iswitch of int array * instruction array
| Iloop of instruction
| Icatch of int * instruction * 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_fast: bool;
fun_dbg : Debuginfo.t }
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