ocaml/asmcomp/mach.ml

128 lines
3.5 KiB
OCaml
Raw Normal View History

(***********************************************************************)
(* *)
(* Caml Special Light *)
(* *)
(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
(* *)
(* Copyright 1995 Institut National de Recherche en Informatique et *)
(* Automatique. Distributed only by permission. *)
(* *)
(***********************************************************************)
(* $Id$ *)
(* Representation of machine code by sequences of pseudoinstructions *)
type integer_comparison =
Isigned of Cmm.comparison
| Iunsigned of Cmm.comparison
type integer_operation =
Iadd | Isub | Imul | Idiv | Imod
| Iand | Ior | Ixor | Ilsl | Ilsr | Iasr
| Icomp of integer_comparison
| Icheckbound
type test =
Itruetest
| Ifalsetest
| Iinttest of integer_comparison
| Iinttest_imm of integer_comparison * int
| Ifloattest of Cmm.comparison
| Ioddtest
| Ieventest
type operation =
Imove
| Ispill
| Ireload
| Iconst_int of int
| Iconst_float of string
| Iconst_symbol of string
| Icall_ind
| Icall_imm of string
| Itailcall_ind
| Itailcall_imm of string
| Iextcall of string * bool
| Istackoffset of int
| Iload of Cmm.memory_chunk * Arch.addressing_mode
| Istore of Cmm.memory_chunk * Arch.addressing_mode
| Ialloc of int
| Iintop of integer_operation
| Iintop_imm of integer_operation * int
| 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;
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 instruction * instruction
| Iexit
| Itrywith of instruction * instruction
| Iraise
type fundecl =
{ fun_name: string;
fun_args: Reg.t array;
fun_body: instruction;
fun_fast: bool }
let rec dummy_instr =
{ desc = Iend;
next = dummy_instr;
arg = [||];
res = [||];
live = Reg.Set.empty }
let end_instr () =
{ desc = Iend;
next = dummy_instr;
arg = [||];
res = [||];
live = Reg.Set.empty }
let instr_cons d a r n =
{ desc = d; next = n; arg = a; res = r; live = Reg.Set.empty }
let instr_cons_live d a r l n =
{ desc = d; next = n; arg = a; res = r; live = l }
let rec instr_iter f i =
match i.desc with
Iend -> ()
| _ ->
f i;
match i.desc with
Iend -> ()
| Ireturn | Iop(Itailcall_ind) | Iop(Itailcall_imm _) -> ()
| Iifthenelse(tst, ifso, ifnot) ->
instr_iter f ifso; instr_iter f ifnot; instr_iter f i.next
| Iswitch(index, cases) ->
for i = 0 to Array.length cases - 1 do
instr_iter f cases.(i)
done;
instr_iter f i.next
| Iloop(body) ->
instr_iter f body; instr_iter f i.next
| Icatch(body, handler) ->
instr_iter f body; instr_iter f handler; instr_iter f i.next
| Iexit -> ()
| Itrywith(body, handler) ->
instr_iter f body; instr_iter f handler; instr_iter f i.next
| Iraise -> ()
| _ ->
instr_iter f i.next